Skip to content

Commit a1aaf2f

Browse files
committed
split run vs runasync
1 parent bdb2840 commit a1aaf2f

File tree

7 files changed

+138
-37
lines changed

7 files changed

+138
-37
lines changed

example/system/example_process_1.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@ program run_sync
77
logical :: completed
88

99
! Run a synchronous process to list directory contents
10-
p = run("ls -l", wait=.true., want_stdout=.true.)
10+
p = run("ls -l", want_stdout=.true.)
1111

1212
! Check if the process is completed (should be true since wait=.true.)
1313
if (is_completed(p)) then

example/system/example_process_2.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,12 @@
11
! Process example 2: Run an Asynchronous Command and check its status
22
program run_async
3-
use stdlib_system, only: process_type, run, is_running, wait
3+
use stdlib_system, only: process_type, runasync, is_running, wait
44
implicit none
55

66
type(process_type) :: p
77

88
! Run an asynchronous process to sleep for 1 second
9-
p = run("sleep 1", wait=.false.)
9+
p = runasync("sleep 1")
1010

1111
! Check if the process is running
1212
if (is_running(p)) then

example/system/example_process_3.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -11,8 +11,8 @@ program run_with_args
1111
args(1) = "echo"
1212
args(2) = "Hello, Fortran!"
1313

14-
! Run the command with arguments
15-
p = run(args, wait=.true.)
14+
! Run the command with arguments (synchronous)
15+
p = run(args)
1616

1717
! Print the runtime of the process
1818
print *, "Process runtime:", elapsed(p), "seconds."

example/system/example_process_4.f90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,15 +1,15 @@
11
! Process example 4: Kill a running process
22
program example_process_kill
3-
use stdlib_system, only: process_type, run, is_running, kill, elapsed, has_win32, sleep
3+
use stdlib_system, only: process_type, runasync, is_running, kill, elapsed, has_win32, sleep
44
implicit none
55
type(process_type) :: process
66
logical :: running, success
77

88
print *, "Starting a long-running process..."
99
if (has_win32()) then
10-
process = run("ping -n 10 127.0.0.1", wait=.false.)
10+
process = runasync("ping -n 10 127.0.0.1")
1111
else
12-
process = run("ping -c 10 127.0.0.1", wait=.false.)
12+
process = runasync("ping -c 10 127.0.0.1")
1313
endif
1414

1515
! Verify the process is running

src/stdlib_system.F90

Lines changed: 50 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@ module stdlib_system
77

88
!> Public sub-processing interface
99
public :: run
10+
public :: runasync
1011
public :: process_type
1112
public :: is_completed
1213
public :: is_running
@@ -53,7 +54,7 @@ module stdlib_system
5354

5455
end type process_type
5556

56-
interface run
57+
interface runasync
5758
!! version: experimental
5859
!!
5960
!! Executes an external process, either synchronously or asynchronously.
@@ -72,40 +73,77 @@ module stdlib_system
7273
!!
7374
!! @note The implementation depends on system-level process management capabilities.
7475
!!
75-
!! #### Methods
76+
module function run_async_cmd(cmd, stdin, want_stdout, want_stderr) result(process)
77+
!> The command line string to execute.
78+
character(*), intent(in) :: cmd
79+
!> Optional input sent to the process via standard input (stdin).
80+
character(*), optional, intent(in) :: stdin
81+
!> Whether to collect standard output.
82+
logical, optional, intent(in) :: want_stdout
83+
!> Whether to collect standard error output.
84+
logical, optional, intent(in) :: want_stderr
85+
!> The output process handler.
86+
type(process_type) :: process
87+
end function run_async_cmd
88+
89+
module function run_async_args(args, stdin, want_stdout, want_stderr) result(process)
90+
!> List of arguments for the process to execute.
91+
character(*), intent(in) :: args(:)
92+
!> Optional input sent to the process via standard input (stdin).
93+
character(*), optional, intent(in) :: stdin
94+
!> Whether to collect standard output.
95+
logical, optional, intent(in) :: want_stdout
96+
!> Whether to collect standard error output.
97+
logical, optional, intent(in) :: want_stderr
98+
!> The output process handler.
99+
type(process_type) :: process
100+
end function run_async_args
101+
end interface runasync
102+
103+
interface run
104+
!! version: experimental
105+
!!
106+
!! Executes an external process, either synchronously or asynchronously.
107+
!! ([Specification](../page/specs/stdlib_system.html#run-execute-an-external-process))
108+
!!
109+
!! ### Summary
110+
!! Provides methods for executing external processes via a single command string or an argument list,
111+
!! with options for synchronous or asynchronous execution and output collection.
76112
!!
77-
!! - `process_open_cmd`: Opens a process using a command string.
78-
!! - `process_open_args`: Opens a process using an array of arguments.
113+
!! ### Description
79114
!!
80-
module function process_open_cmd(cmd, wait, stdin, want_stdout, want_stderr) result(process)
115+
!! This interface allows the user to spawn external processes using either a single command string
116+
!! or a list of arguments. Processes can be executed synchronously (blocking) or asynchronously
117+
!! (non-blocking), with optional request to collect standard output and error streams, or to provide
118+
!! a standard input stream via a `character` string.
119+
!!
120+
!! @note The implementation depends on system-level process management capabilities.
121+
!!
122+
module function run_sync_cmd(cmd, stdin, want_stdout, want_stderr) result(process)
81123
!> The command line string to execute.
82124
character(*), intent(in) :: cmd
83125
!> Optional input sent to the process via standard input (stdin).
84126
character(*), optional, intent(in) :: stdin
85-
!> Whether to wait for process completion (synchronous).
86-
logical, optional, intent(in) :: wait
87127
!> Whether to collect standard output.
88128
logical, optional, intent(in) :: want_stdout
89129
!> Whether to collect standard error output.
90130
logical, optional, intent(in) :: want_stderr
91131
!> The output process handler.
92132
type(process_type) :: process
93-
end function process_open_cmd
133+
end function run_sync_cmd
94134

95-
module function process_open_args(args, wait, stdin, want_stdout, want_stderr) result(process)
135+
module function run_sync_args(args, stdin, want_stdout, want_stderr) result(process)
96136
!> List of arguments for the process to execute.
97137
character(*), intent(in) :: args(:)
98138
!> Optional input sent to the process via standard input (stdin).
99139
character(*), optional, intent(in) :: stdin
100-
!> Whether to wait for process completion (synchronous).
101-
logical, optional, intent(in) :: wait
102140
!> Whether to collect standard output.
103141
logical, optional, intent(in) :: want_stdout
104142
!> Whether to collect standard error output.
105143
logical, optional, intent(in) :: want_stderr
106144
!> The output process handler.
107145
type(process_type) :: process
108-
end function process_open_args
146+
end function run_sync_args
109147
end interface run
110148

111149
interface is_running

src/stdlib_system_subprocess.F90

Lines changed: 73 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -85,31 +85,95 @@ module subroutine sleep(millisec)
8585

8686
end subroutine sleep
8787

88-
!> Open a new process
89-
module function process_open_cmd(cmd,wait,stdin,want_stdout,want_stderr) result(process)
88+
module function run_async_cmd(cmd, stdin, want_stdout, want_stderr) result(process)
89+
!> The command line string to execute.
90+
character(*), intent(in) :: cmd
91+
!> Optional input sent to the process via standard input (stdin).
92+
character(*), optional, intent(in) :: stdin
93+
!> Whether to collect standard output.
94+
logical, optional, intent(in) :: want_stdout
95+
!> Whether to collect standard error output.
96+
logical, optional, intent(in) :: want_stderr
97+
!> The output process handler.
98+
type(process_type) :: process
99+
100+
process = process_open([cmd],.false.,stdin,want_stdout,want_stderr)
101+
102+
end function run_async_cmd
103+
104+
module function run_async_args(args, stdin, want_stdout, want_stderr) result(process)
105+
!> List of arguments for the process to execute.
106+
character(*), intent(in) :: args(:)
107+
!> Optional input sent to the process via standard input (stdin).
108+
character(*), optional, intent(in) :: stdin
109+
!> Whether to collect standard output.
110+
logical, optional, intent(in) :: want_stdout
111+
!> Whether to collect standard error output.
112+
logical, optional, intent(in) :: want_stderr
113+
!> The output process handler.
114+
type(process_type) :: process
115+
116+
process = process_open(args,.false.,stdin,want_stdout,want_stderr)
117+
118+
end function run_async_args
119+
120+
module function run_sync_cmd(cmd, stdin, want_stdout, want_stderr) result(process)
121+
!> The command line string to execute.
122+
character(*), intent(in) :: cmd
123+
!> Optional input sent to the process via standard input (stdin).
124+
character(*), optional, intent(in) :: stdin
125+
!> Whether to collect standard output.
126+
logical, optional, intent(in) :: want_stdout
127+
!> Whether to collect standard error output.
128+
logical, optional, intent(in) :: want_stderr
129+
!> The output process handler.
130+
type(process_type) :: process
131+
132+
process = process_open([cmd],.true.,stdin,want_stdout,want_stderr)
133+
134+
end function run_sync_cmd
135+
136+
module function run_sync_args(args, stdin, want_stdout, want_stderr) result(process)
137+
!> List of arguments for the process to execute.
138+
character(*), intent(in) :: args(:)
139+
!> Optional input sent to the process via standard input (stdin).
140+
character(*), optional, intent(in) :: stdin
141+
!> Whether to collect standard output.
142+
logical, optional, intent(in) :: want_stdout
143+
!> Whether to collect standard error output.
144+
logical, optional, intent(in) :: want_stderr
145+
!> The output process handler.
146+
type(process_type) :: process
147+
148+
process = process_open(args,.true.,stdin,want_stdout,want_stderr)
149+
150+
end function run_sync_args
151+
152+
!> Internal function: open a new process from a command line
153+
function process_open_cmd(cmd,wait,stdin,want_stdout,want_stderr) result(process)
90154
!> The command and arguments
91155
character(*), intent(in) :: cmd
92156
!> Optional character input to be sent to the process via pipe
93157
character(*), optional, intent(in) :: stdin
94158
!> Define if the process should be synchronous (wait=.true.), or asynchronous(wait=.false.)
95-
logical, optional, intent(in) :: wait
159+
logical, intent(in) :: wait
96160
!> Require collecting output
97161
logical, optional, intent(in) :: want_stdout, want_stderr
98162
!> The output process handler
99163
type(process_type) :: process
100164

101-
process = process_open_args([cmd],wait,stdin,want_stdout,want_stderr)
165+
process = process_open([cmd],wait,stdin,want_stdout,want_stderr)
102166

103167
end function process_open_cmd
104168

105-
!> Open a new process
106-
module function process_open_args(args,wait,stdin,want_stdout,want_stderr) result(process)
169+
!> Internal function: open a new process from arguments
170+
function process_open(args,wait,stdin,want_stdout,want_stderr) result(process)
107171
!> The command and arguments
108172
character(*), intent(in) :: args(:)
109173
!> Optional character input to be sent to the process via pipe
110174
character(*), optional, intent(in) :: stdin
111175
!> Define if the process should be synchronous (wait=.true.), or asynchronous(wait=.false.)
112-
logical, optional, intent(in) :: wait
176+
logical, intent(in) :: wait
113177
!> Require collecting output
114178
logical, optional, intent(in) :: want_stdout, want_stderr
115179
!> The output process handler
@@ -121,11 +185,10 @@ module function process_open_args(args,wait,stdin,want_stdout,want_stderr) resul
121185
integer(TICKS) :: count_max
122186

123187
! Process user requests
124-
asynchronous = .false.
188+
asynchronous = .not.wait
125189
collect_stdout = .false.
126190
collect_stderr = .false.
127191
has_stdin = present(stdin)
128-
if (present(wait)) asynchronous = .not.wait
129192
if (present(want_stdout)) collect_stdout = want_stdout
130193
if (present(want_stderr)) collect_stderr = want_stderr
131194

@@ -173,7 +236,7 @@ module function process_open_args(args,wait,stdin,want_stdout,want_stderr) resul
173236
! Run a first update
174237
call update_process_state(process)
175238

176-
end function process_open_args
239+
end function process_open
177240

178241
subroutine launch_asynchronous(process, args, stdin)
179242
class(process_type), intent(inout) :: process

test/system/test_subprocess.f90

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
module test_subprocess
22
use testdrive, only : new_unittest, unittest_type, error_type, check, skip_test
3-
use stdlib_system, only: process_type, run, is_running, wait, update, elapsed, has_win32, kill
3+
use stdlib_system, only: process_type, run, runasync, is_running, wait, update, elapsed, has_win32, kill
44

55
implicit none
66

@@ -25,7 +25,7 @@ subroutine test_run_synchronous(error)
2525
type(process_type) :: process
2626
character(len=*), parameter :: command = "echo Hello"
2727

28-
process = run(command, wait=.true., want_stdout=.true.)
28+
process = run(command, want_stdout=.true.)
2929
call check(error, process%completed)
3030
if (allocated(error)) return
3131

@@ -40,9 +40,9 @@ subroutine test_run_asynchronous(error)
4040

4141
! The closest possible to a cross-platform command that waits
4242
if (has_win32()) then
43-
process = run("ping -n 2 127.0.0.1", wait=.false.)
43+
process = runasync("ping -n 2 127.0.0.1")
4444
else
45-
process = run("ping -c 2 127.0.0.1", wait=.false.)
45+
process = runasync("ping -c 2 127.0.0.1")
4646
endif
4747
! Should not be immediately completed
4848
call check(error, .not. process%completed, "ping process should not complete immediately")
@@ -68,9 +68,9 @@ subroutine test_process_kill(error)
6868

6969
! Start a long-running process asynchronously
7070
if (has_win32()) then
71-
process = run("ping -n 10 127.0.0.1", wait=.false.)
71+
process = runasync("ping -n 10 127.0.0.1")
7272
else
73-
process = run("ping -c 10 127.0.0.1", wait=.false.)
73+
process = runasync("ping -c 10 127.0.0.1")
7474
endif
7575

7676
! Ensure the process starts running
@@ -100,7 +100,7 @@ subroutine test_process_state(error)
100100
type(process_type) :: process
101101
character(len=*), parameter :: command = "echo Testing"
102102

103-
process = run(command, wait=.true., want_stdout=.true., want_stderr=.true.)
103+
process = run(command, want_stdout=.true., want_stderr=.true.)
104104

105105
call update(process)
106106
call check(error, process%completed)

0 commit comments

Comments
 (0)