I am working on implementing a module similar to std::process in Rust. This module would contain tools to spawn and interact with child processes.
Here is what I have so far:
module process_module
use iso_varying_string ! See https://gitlab.com/everythingfunctional/iso_varying_string
use, intrinsic :: iso_fortran_env, only: output_unit, input_unit, error_unit
implicit none
type :: command
type(varying_string) :: program
type(varying_string), allocatable :: args(:)
integer :: stderr_ = error_unit
integer :: stdin_ = input_unit
integer :: stdout_ = output_unit
contains
procedure :: new
procedure :: arg => set_arg
procedure :: stdin
procedure :: stderr
procedure :: stdout
procedure :: get_program
procedure :: get_args
procedure :: status
end type
contains
subroutine new(self,prog)
class(command), intent(out) :: self
character(len=*), intent(in) :: prog
if (allocated(self%args)) deallocate(self%args)
self%program = trim(prog)
end subroutine
function get_program(self) result(p)
class(command), intent(in) :: self
type(varying_string) :: p
p = self%program
end function
function get_args(self) result(args)
class(command), intent(in) :: self
type(varying_string), allocatable :: args(:)
allocate(args,source=self%args)
end function
subroutine set_arg(self,arg)
class(command), intent(inout) :: self
character(len=*), intent(in) :: arg
type(varying_string) :: vs
vs = arg
if (allocated(self%args)) then
self%args = [self%args, vs]
else
allocate(self%args(1))
self%args(1) = arg
end if
end subroutine
subroutine stdin(self,unit)
class(command), intent(inout) :: self
integer, intent(in) :: unit
self%stdin_ = unit
end subroutine
subroutine stderr(self,unit)
class(command), intent(inout) :: self
integer, intent(in) :: unit
self%stderr_ = unit
end subroutine
subroutine stdout(self,unit)
class(command), intent(inout) :: self
integer, intent(in) :: unit
self%stdout_ = unit
end subroutine
subroutine status(self,success,code)
class(command), intent(inout) :: self
logical, intent(out), optional :: success
integer, intent(out), optional :: code
integer :: exitstat, cmdstat
character(len=1000) :: cmdmsg
character(len=1000) :: command
integer :: i
cmdmsg = ""
command = self%program
if (allocated(self%args)) then
do i = 1, size(self%args)
command = trim(command)//" "//trim(self%args(i))
end do
end if
call execute_command_line(command,wait=.true., &
exitstat=exitstat, &
cmdstat=cmdstat, &
cmdmsg=cmdmsg)
print *, trim(cmdmsg)
if (present(success)) then
if (cmdstat == 0) then
success = .true.
else
success = .false.
end if
end if
if (present(code)) code = exitstat
end subroutine
end module
program main
use iso_varying_string
use process_module
implicit none
type(command) :: cmd
logical :: succ
integer :: code
call cmd%new("gfortran")
call cmd%arg("hello_world.f90") ! contains "print *, "Hello from child!"; end
call cmd%arg("-o")
call cmd%arg("hello_world")
call cmd%status(success=succ,code=code)
print *, succ, code
call cmd%new("./hello_world")
call cmd%status(success=s,code=code)
print *, succ, code
print *, "Hello from caller."
end program
The Rust API provides three ways to run a command with slightly different roles:
-
status
will run the command as a child process, wait for it to finish and collect it’s exit status; -
output
will run the command as a child process, wait for it to finish and collect it’s exit status and output (stderr, and, stdout); -
spawn
will run the command and return a handle to the process (the PID presumably).
Is it possible to replicate this functionality purely in Fortran?
If possible, can it be used in a parallel setting? For example if one image spawns a child process, and communicate the child id, can the second image check the status.
I would also appreciate learning any other ideas related to the functionality of such a process module.