Skip to content

Commit 48da380

Browse files
committed
add single-command run API
1 parent e8451b2 commit 48da380

File tree

2 files changed

+36
-10
lines changed

2 files changed

+36
-10
lines changed

src/stdlib_system.F90

Lines changed: 18 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,8 @@ module stdlib_system
1111
public :: process_type
1212
public :: is_completed
1313
public :: is_running
14+
public :: update
15+
public :: wait
1416

1517
! CPU clock ticks storage
1618
integer, parameter, private :: TICKS = int64
@@ -33,9 +35,6 @@ module stdlib_system
3335
logical :: completed = .false.
3436
integer(TICKS) :: start_time = 0
3537

36-
!> Process exit code
37-
integer :: exit_code = 0
38-
3938
!> Stdin file name
4039
character(:), allocatable :: stdin_file
4140

@@ -44,6 +43,7 @@ module stdlib_system
4443
character(:), allocatable :: stdout
4544

4645
!> Error output
46+
integer :: exit_code = 0
4747
character(:), allocatable :: stderr_file
4848
character(:), allocatable :: stderr
4949

@@ -53,8 +53,19 @@ module stdlib_system
5353
end type process_type
5454

5555
interface run
56-
!> Open a new, asynchronous process
57-
module type(process_type) function process_open(args,wait,stdin,want_stdout,want_stderr) result(process)
56+
!> Open a new process from a command line
57+
module type(process_type) function process_open_cmd(cmd,wait,stdin,want_stdout,want_stderr) result(process)
58+
!> The command and arguments
59+
character(*), intent(in) :: cmd
60+
!> Optional character input to be sent to the process via pipe
61+
character(*), optional, intent(in) :: stdin
62+
!> Define if the process should be synchronous (wait=.true.), or asynchronous(wait=.false.)
63+
logical, optional, intent(in) :: wait
64+
!> Require collecting output
65+
logical, optional, intent(in) :: want_stdout, want_stderr
66+
end function process_open_cmd
67+
!> Open a new, asynchronous process from a list of arguments
68+
module type(process_type) function process_open_args(args,wait,stdin,want_stdout,want_stderr) result(process)
5869
!> The command and arguments
5970
character(*), intent(in) :: args(:)
6071
!> Optional character input to be sent to the process via pipe
@@ -63,7 +74,7 @@ module type(process_type) function process_open(args,wait,stdin,want_stdout,want
6374
logical, optional, intent(in) :: wait
6475
!> Require collecting output
6576
logical, optional, intent(in) :: want_stdout, want_stderr
66-
end function process_open
77+
end function process_open_args
6778
end interface run
6879

6980
!> Live check if a process is still running
@@ -101,7 +112,7 @@ end subroutine wait_for_completion
101112
module subroutine update_process_state(process)
102113
type(process_type), intent(inout) :: process
103114
end subroutine update_process_state
104-
end interface
115+
end interface update
105116

106117
!! version: experimental
107118
!!

src/stdlib_system_subprocess.F90

Lines changed: 18 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -69,8 +69,23 @@ module subroutine sleep(millisec)
6969

7070
end subroutine sleep
7171

72-
!> Open a new, asynchronous process
73-
module type(process_type) function process_open(args,wait,stdin,want_stdout,want_stderr) result(process)
72+
!> Open a new process
73+
module type(process_type) function process_open_cmd(cmd,wait,stdin,want_stdout,want_stderr) result(process)
74+
!> The command and arguments
75+
character(*), intent(in) :: cmd
76+
!> Optional character input to be sent to the process via pipe
77+
character(*), optional, intent(in) :: stdin
78+
!> Define if the process should be synchronous (wait=.true.), or asynchronous(wait=.false.)
79+
logical, optional, intent(in) :: wait
80+
!> Require collecting output
81+
logical, optional, intent(in) :: want_stdout, want_stderr
82+
83+
process = process_open_args([cmd],wait,stdin,want_stdout,want_stderr)
84+
85+
end function process_open_cmd
86+
87+
!> Open a new process
88+
module type(process_type) function process_open_args(args,wait,stdin,want_stdout,want_stderr) result(process)
7489
!> The command and arguments
7590
character(*), intent(in) :: args(:)
7691
!> Optional character input to be sent to the process via pipe
@@ -138,7 +153,7 @@ module type(process_type) function process_open(args,wait,stdin,want_stdout,want
138153
! Run a first update
139154
call update_process_state(process)
140155

141-
end function process_open
156+
end function process_open_args
142157

143158
subroutine launch_asynchronous(process, args, stdin)
144159
class(process_type), intent(inout) :: process

0 commit comments

Comments
 (0)