Stdlib system interaction API: call for feedback

Dear Fortran enthusiasts, I have been proposing cross-platform system interaction APIs for stdlib: mainly subprocessing and filesystem operations.

I would like to gather community feedback on the proposed API, for example:

  • should we prefer a functional style, oo style, both?
  • what names should be using? (i.e. is_directory, is_dir, isdir, etc.)?
  • What functionality should be encapsulated? I.e., for delete, should we have separate functions delete and delete_directory, or both with the same name, etc.?

For sub-processing functionality, stdlib_system now provides an interface for managing external processes which has a similar design as the Python subprocess module. It allows running processes synchronously or asynchronously, checking their status, retrieving outputs, and handling process termination.

Current API proposal

The current design uses Fortran interfaces for consistency with stdlib. Error handling uses integer exit codes but could be integrated with state_type if/when standardized for the whole stdlib.

  • type(process_type): Represents an external process, storing process state, stdin, stdout, and stderr.

  • Run a process (synchronous or asynchronous):

    process = run(cmd     [, wait=.true.,] [, stdin=string] [, want_stdout=.false.] [, want_stderr=.false.])
    process = run(args(:) [, wait=.true.,] [, stdin=string] [, want_stdout=.false.] [, want_stderr=.false.])
    
  • Run a synchronous command:

    call run(cmd [, exit_state] [, command_state] [, stdout] [, stderr])  
    
  • Update process state:

    call update(process)
    
  • Check if a process is running:

    status = is_running(process)
    
  • Check if a process has completed:

    status = is_completed(process)
    
  • Wait for process completion (optional timeout):

    call wait(process [, max_wait_time=10.0])
    
  • Get elapsed time since process start or total duration:

    duration = elapsed(process)
    
  • Kill a running process:

    call kill(process, success)
    
  • Retrieve process output:

    print *, process%stdout
    print *, process%stderr
    print *, 'success = ',process%exit_code == 0
    
  • Check if a path is a directory:

    is_directory(path) → logical
    
  • Delete a file:

    call delete_file(path [, err])  
    
  • Retrieve OS type:

    function os_type() → cached OS flag  
    
    • cached to static storage
  • Get OS name:

    function OS_NAME() → string  
    
  • Get null device path:

    function null_device() → string  
    
  • Load a whole ASCII file into a string_type variable:

    type(string_type) function getfile(fileName [, err] [, delete])
    
    • Optionally delete the file after reading (delete=.true.).
  • Library-wide error handling:

    • extend state_type error handling, that was well accepted for linear algebra, to the whole library (without API changes: just via a polymorphic state_type->linalg_state_type inheritance)

Let’s use this thread to collect the best ideas for implementation.
Looking forward to your feedback!

16 Likes

My approach to most things I code these days is to write all the parts of the code that do the heavy lifting (computations etc) in a functional style and then if justified wrap the functional code in OO code that does what I like to call “command and control” (ie managing memory, setting up IO etc). That way if I manage to program my way into an OOP mousetrap (which can easily happen with a poor OOP design), I have the functional code that actually does the bulk of the work to fall back on. So I vote both.

3 Likes

I agree with you: TBPs come basically for free and I also like the object-oriented coding style. This is one of the applications where object oriented programming fits best (you will never work with arrays of thousands of processes, and the overhead of calling a virtual procedure is nothing compared to the actual external process runtime)

@FedericoPerini, that sounds like a very good idea.
I implemented something similar for a project (that I cannot open source unfortunately) but I would gladly contribute if you need help.
For the file system, I found it convenient to wrap calls to dirent. It does not exists on windows but you can use this project.

For the subprocess, I use popen. But you are limited to read OR write operation. Having both requires some C++ on Windows to wrap the API call. I also would love to get the PID of the process as a return value.

As for the style, I completely agree with @rwmsu, with low level functional style and a oo wrapper.

1 Like

Didn’t know of this tool, looks very interesting, thank you!

Exactly. I’ve been using fork on unix and CreateProcess on Windows so when we have pipes, we can both read/write to the process.

Yes, this is what I’ve been using as a Fortran process handle. The non-cross platform structs are only gathered on the C side using the process ID, so the Fortran side remains cleaner… at least I hope so.

I might be able to share some code using CreateProcess if you are interested.

Concerning the file system, it may be interesting to add fileinfo and directoryinfo types that would wrap calls to the inquire intrinsic and check for existence and size for instance.
Whenever I need to design a new API I usually have a look at what is available in .NET. It’s usually a good source of inspiration.

What is the difference between functional and object-oriented interface?

Well, if you look at the present case, in order to run a subprocess you could do it in a functional style:

call run(process, [args])

Or in a oo style:

call process%run([args])

Those are two different styles deriving from two different paradigms. There are also a matter of preference.

1 Like

My take on this is that with an OO interface you can encapsulate some of the data you would normally pass to the routine as arguments as class (aka derived type) data and therefore reduce the number of arguments you have pass which simplifies the interface somewhat. Keeping the low level routines that usually do the bulk of the work functional (or procedural as I would call it) allows you to use existing routines that might have a large number of arguments but hide the more complex (and sometime error prone) functional interface behind a potentially simpler OO interface.

It’s a matter of personal preference but I am usually not a big fan of optional arguments. In the present case, maybe the asynchronous calls could be separated using a runasync function?

I also notice that stdin and stdout are treated quite differently (string vs Boolean). Maybe there is an elegant way to make it similar.

1 Like

Yeah, I’m definitely open to feedback on this one. I did that because Fortran has the optional wait=.true. in execute_command_line, so it seemed like a good similarity to have. But I also like the idea of different function names.

We should also find a good naming (rather than the current: put stuff in two different modules) for the function version process = run(...) vs. the simple synchronous call (call run(cmd, ...))

You might be able to mimic fork on Windows. I recall that Winnie-AFL has a forklib for doing just that.
I also put together some of the experiments I did and created the subprocess.f. At the moment, only the synchronous version is implemented but that may give some ideas and provide a simple sandbox for testing purposes.

While thinking a bit more about the async version, it could be interesting to have the possibility to provide a callback function that would be called when the process ends

call runasync(..., callback)
...
subroutine callback(exit_state)
    integer, intent(in) :: exit_state
    if (exit_state /= 0) print*, "Oops, something went wrong"
end subroutine

As for the stdin and stdout/stderr, one could also use procedures as arguments. This may provide an easy way for piping and facilitate the use of a logger to redirect to output to something else than the console. If you are familiar with C#, you can have a look at CliWrap. There API is written in an expressive object oriented style that is easy to follow.

2 Likes

Nice, elegant idea! let’s try to discuss this a bit deeper cause I’m not super expert in this event-driven coding. If I want to do something similar, with the current logic I’d just do:

if (is_completed(process)) call callback(process%exit_state)

However, we could add it part of the process type as a pointer:

procedure(process_oncomplete), pointer :: callback => null()

And then when the process is completed:

! check completion
[...]
process%complete = .true.

! [...] load stdout, stderr

if (associated(process%callback)) &
call process%callback(process%exit_state,process%stdin,process%stdout,process%stderr)

So I think a good callback interface would be

abstract interface
    procedure process_oncomplete(exit_state,stdin,stdout,stderr)
        integer, intent(in) :: exit_state
        ! presence depends on allocation status in process type (<- user request)
        character(len=*), optional, intent(in) :: stdin,stdout,stderr
    end procedure process_oncomplete
end interface

Another slightly related thing is that we may want to ensure the system is not clogged with dangling processes. Should we have a finalizer?

! Process variable goes out of scope: ensure no dangling process
subroutine process_final(process)
    type(process_type), intent(inout) :: process
    logical :: success

    if (is_running(process)) call kill(process, success)
end subroutine

Well you may also need the pid of the process and later info on the elapsed time, etc…, so one could also return the entire object process_type :smile:. Otherwise, the logic looks good. I used the exact same approach to register an exit event that is triggered when exiting the main program.

The finalizer is a good idea and since the callback is a pointer you may also want to nullify it. One should just be careful if using a constructor-like interface since the rhs of the assignment gets finalized. But the condition is_running should prevent any undesired process kill

1 Like

Style question: if we’re including an optional callback creating the process, we will have something like:

process = run(cmd [, others..] [, callback])

If the point of knowing pid is to be able to reference to the process variable, should we just make the callback interface self-aware instead? I.e., something like:

abstract interface
    procedure process_oncomplete(process)
        ! Access any process data
        class(process_type), intent(in) :: process  
    end procedure process_oncomplete
end interface

The way Python does it is with polymorphism (a CompletedProcess class) but I don’t think we want to go down the same route here.

Also, what other usage were you thinking about that requires a pid after such pid has been deleted?

That sounds a lot like Node.js’s callbacks —with the associated callback hell that eventually got resolved through async/await.

These days, I tend to look at Go’s standard library, rather than Python’s, for inspiration on how to implement certain things in Fortran.

Go’s approach, when things may fail, is to always return an error object —which, in Fortran terms, means using subroutines rather than functions.

And there’s also the factory-function-and-then-methods approach, something like:

module mod1
    type :: process
        ...
    contains
        procedure :: process_id
        procedure :: run     ! synchronous
        procedure :: start   ! asynchronous
        procedure :: wait    ! wait for asynchronous
        ...
        generic :: write(formatted) => write_formatted_process
        ...
    end type

    interface process
        module procedure process_new
    end interface

contains
    function process_new(...) result(new)
        type(process) :: new
        ...
    end function

    pure function process_id(this) result(pid)
        ...
    end function

    subroutine start(this, ...)
        ...
    end subroutine

    subroutine run(this, ..., output, error)
        ...
        character(:), allocatable, optional, intent(out) :: output
        ...
    end subroutine

    subroutine wait(this, output, error)
        ...
    end subroutine

    ...
end module

See, for example, the exec package.

Cooperative locking comes to mind —e.g., if two applications use the same locking mechanism provided by stdlib.

1 Like

Events are a necessary evil when the backend needs to communicate with a UI sitting in a different thread. This is usually the case in MVC or MVVM kind of architectures. So I would agree with you that Fortran being primarily a backend language, it does not needs to be cluttered with events. That being said I often find an exit event quite useful. Here is a real case example:
I have a piece of code running some kind of optimization. Each value of the fitness function is obtained by calling an external program. The fitness function is then evaluated when the external program returns. So I ended up creating a stack of processes (one per cpu) and running those concurrently. Whenever one process terminates, I start a new one (or restart the same depending on the error code). But of course all the scheduling logic can be implemented externally with some kind of watcher instead of using events.

1 Like

I’d suggest only to add callback functionality only, if it really adds a considerable benefit to realize scenarios being to complicated or impossible otherwise. They are always quite fishy according to my experience.

But if added, I’d suggest to ensure, that the callback function can access arbitrary data in the called program if required.

I see two possible solutions:

  • The callback argument of run() accepts an instance of a class derived from a generic interface, like:

    type, abstract :: callback_interface
    contains
     procedure, deferred :: callback => callback_interface_callback
    end type callback_interface
    
    abstract interface
      subroutine callback_interface_callback(this, <any other args the run function wants to pass to the callback function>)
        class(callback_interface), intent(inout) :: this
        ...
      end subroutine callback_interface_callback
    end interface
    

    This way, the caller can pack any data into the derived class which must be present at the time of the callback.

  • Alternatively, one could pass a class(*) pointer to run() as an extra agrument, which run() passes unaltered to the callback function, so that it can cast it to something useful.

Otherwise, the callback function can only do very trivial things as it has no access to any data apart of those passed by run(). For example, if the program calling run() uses its own logger, how could the callback function log to it? (Unless, one uses global module variables, which we definitely should not promote IMO…)

1 Like

Totally agree with you @aradi. Generally, when dealing with these anonymous interfaces, I use temporary wrappers see

subroutine solve_ode(problem)
   class(ode_problem), intent(inout) :: problem
   ...
   ! Call ODE integrator
   call VODE(fun, ...)

   contains
 
   ! wrap to VODE interface
   subroutine ode_fun(n,t,y,rpar,ipar)
     integer, intent(in) :: n
     real(wp), intent(inout) :: t,y(n),rpar(*)
     integer, intent(inout) :: ipar(*)
     ! Access everything from the parent scope
   end subroutine ode_fun  
end subroutine solve_ode

So yes, it is possible to have a callback interface with no pointers. But as you say, it’s clunky: in the case of a process, one must ensure that the temporary function does not go out of scope before the process exits, otherwise when called, the program would segfault. I also do not like the idea of a special derived type just for callback handling.

So maybe we should do like you’re suggesting: something like

abstract interface
    procedure process_oncomplete(exit_state,stdin,stdout,stderr,data)
        integer, intent(in) :: exit_state
        ! presence depends on allocation status in process type (<- user request)
        character(len=*), optional, intent(in) :: stdin,stdout,stderr
        ! optional pointer to a user-defined class
        class(*), optional, intent(in) :: data
    end procedure process_oncomplete
end interface

So in the actual implementation, one can cast the pointer to their known class and use the data

subroutine my_process_exit(exit_state,stdin,stdout,stderr,data)
    integer, intent(in) :: exit_state
    character(len=*), optional, intent(in) :: stdin,stdout,stderr
    class(*), optional, intent(inout) :: data
        
    if (present(data)) then 
       select type (typed_data => data)
            type is (...)
               ! do stuff
       end select
    endif
end subroutine my_process_exit

Then in the process creation interface, we add

p = runasync(cmd [,...] [, callback] [,data])

which is declared as

class(*), optional, intent(inout), target :: data

then storing both inside the process variable

procedure(process_oncomplete), pointer :: callback => null()
class(*), pointer :: callback_data => null()

So that the classes the user has attached to that process gets passed as an argument to the callback function.

This is the best approach I can think about, was this what you were envisioning? (example here)

@FedericoPerini Oh indeed, passing an internal routine and using the variables of the enclosing routine is also a valid option, I completely overlooked that.

Still, I think, I prefer either the OO-approach (which you seem not being a big fan of :laughing:) , or the passing of a data object which is forwarded to the callback routine when called. Pretty much along the lines of your demonstration, but I’d recommend to avoid the target attribute when declaring data and use pointer instead:

class(*), optional, intent(in), pointer :: data

The problem with target is, that if the caller forgets to declare the target attribute for the actual argument, the pointer stored to the dummy argument is not warranted to be valid when the call (create_process() in your example) returns. And you won’t get any compiler warning on that.

If one uses pointer instead, the caller must declare either target or pointer for the actual argument, otherwise the code won’t compile. So it is much more robust in my opinion.

3 Likes