system

System and sub-processing module

The stdlib_system module provides interface for interacting with external processes, enabling the execution and monitoring of system commands or applications directly from Fortran.

run - Execute an external process synchronously

Status

Experimental

Description

The run interface allows execution of external processes using a single command string or a list of arguments.
Processes run synchronously, meaning execution is blocked until the process finishes.
Optional arguments enable the collection of standard output and error streams, as well as sending input via standard input. Additionally, a callback function can be specified to execute upon process completion, optionally receiving a user-defined payload.

Syntax

process = stdlib_system (args [, stdin] [, want_stdout] [, want_stderr] [, callback] [, payload])

Arguments

args: Shall be a character(*) string (for command-line execution) or a character(*), dimension(:) array (for argument-based execution). It specifies the command and arguments to execute. This is an intent(in) argument.

stdin (optional): Shall be a character(*) value containing input to send to the process via standard input (pipe). This is an intent(in) argument.

want_stdout (optional): Shall be a logical flag. If .true., the standard output of the process will be captured; if .false. (default), it will be lost. This is an intent(in) argument.

want_stderr (optional): Shall be a logical flag. If .true., the standard error output of the process will be captured. If .false. (default), it will be lost. This is an intent(in) argument.

callback (optional): Shall be a procedure conforming to the process_callback interface. If present, this function will be called upon process completion with the process ID, exit state, and optionally collected standard input, output, and error streams. This is an intent(in) argument.

payload (optional): Shall be a generic (class(*)) scalar that will be passed to the callback function upon process completion. It allows users to associate custom data with the process execution. This is an intent(inout), target argument.

Return Value

Returns an object of type process_type that contains information about the state of the created process.

Example

! Example usage with command line or list of arguments
type(process_type) :: p

! Run a simple command line synchronously
p = run("echo 'Hello, world!'", want_stdout=.true.)

runasync - Execute an external process asynchronously

Status

Experimental

Description

The runasync interface allows execution of external processes using a single command string or a list of arguments.
Processes are run asynchronously (non-blocking), meaning execution does not wait for the process to finish.
Optional arguments enable the collection of standard output and error streams, as well as sending input via standard input. Additionally, a callback function can be specified to execute upon process completion, optionally receiving a user-defined payload.

Syntax

process = stdlib_system (args [, stdin] [, want_stdout] [, want_stderr] [, callback] [, payload])

Arguments

args: Shall be a character(*) string (for command-line execution) or a character(*), dimension(:) array (for argument-based execution). It specifies the command and arguments to execute. This is an intent(in) argument.

stdin (optional): Shall be a character(*) value containing input to send to the process via standard input (pipe). This is an intent(in) argument.

want_stdout (optional): Shall be a logical flag. If .true., the standard output of the process will be captured; if .false. (default), it will be lost. This is an intent(in) argument.

want_stderr (optional): Shall be a logical flag. If .true., the standard error output of the process will be captured. Default: .false.. This is an intent(in) argument.

callback (optional): Shall be a procedure conforming to the process_callback interface. If present, this function will be called upon process completion with the process ID, exit state, and optionally collected standard input, output, and error streams. This is an intent(in) argument.

payload (optional): Shall be a generic (class(*)) scalar that will be passed to the callback function upon process completion. It allows users to associate custom data with the process execution. This is an intent(inout), target argument.

Return Value

Returns an object of type process_type that contains information about the state of the created process.

Example

! Process example 1: Run a Command Synchronously and Capture Output
program run_sync
    use stdlib_system, only: run, is_completed, is_windows, process_type
    implicit none

    type(process_type) :: p
    logical :: completed

    ! Run a synchronous process to list directory contents
    if (is_windows()) then
        p = run("dir", want_stdout=.true.)
    else
        p = run("ls -l", want_stdout=.true.)
    end if

    ! Check if the process is completed (should be true since wait=.true.)
    if (is_completed(p)) then
        print *, "Process completed successfully. The current directory: "
        print *, p%stdout
    else
        print *, "Process is still running (unexpected)."
    end if

end program run_sync

is_running - Check if a process is still running

Status

Experimental

Description

The is_running interface provides a method to check if an external process is still running.
This is useful for monitoring the status of asynchronous processes created with the run interface.

Syntax

status = stdlib_system (process)

Arguments

process: Shall be a type(process_type) object representing the external process to check. This is an intent(inout) argument.

Return Value

Returns a logical value: .true. if the process is still running, or .false. if the process has terminated. After a call to is_running, the type(process_type) structure is also updated to the latest process state.

Example

! Process example 2: Run an Asynchronous Command and check its status
program run_async
    use stdlib_system, only: process_type, runasync, is_running, wait
    implicit none

    type(process_type) :: p

    ! Run an asynchronous process to sleep for 1 second
    p = runasync("sleep 1")

    ! Check if the process is running
    if (is_running(p)) then
        print *, "Process is running."
    else
        print *, "Process has already completed."
    end if

    ! Wait for the process to complete
    call wait(p, max_wait_time = 5.0)
    print *, "Process has now completed."
end program run_async

is_completed - Check if a process has completed execution

Status

Experimental

Description

The is_completed interface provides a method to check if an external process has finished execution.
This is useful for determining whether asynchronous processes created with the run interface have terminated.

Syntax

status = stdlib_system (process)

Arguments

process: Shall be a type(process_type) object representing the external process to check. This is an intent(inout) argument.

Return Value

Returns a logical value:
- .true. if the process has completed.
- .false. if the process is still running.

After a call to is_completed, the type(process_type) structure is updated to reflect the latest process state.

Example

! Process example 1: Run a Command Synchronously and Capture Output
program run_sync
    use stdlib_system, only: run, is_completed, is_windows, process_type
    implicit none

    type(process_type) :: p
    logical :: completed

    ! Run a synchronous process to list directory contents
    if (is_windows()) then
        p = run("dir", want_stdout=.true.)
    else
        p = run("ls -l", want_stdout=.true.)
    end if

    ! Check if the process is completed (should be true since wait=.true.)
    if (is_completed(p)) then
        print *, "Process completed successfully. The current directory: "
        print *, p%stdout
    else
        print *, "Process is still running (unexpected)."
    end if

end program run_sync

elapsed - Return process lifetime in seconds

Status

Experimental

Description

The elapsed interface provides a method to calculate the total time that has elapsed since a process was started.
This is useful for tracking the duration of an external process or for performance monitoring purposes.

The result is a real value representing the elapsed time in seconds, measured from the time the process was created.

Syntax

delta_t = stdlib_system (process)

Arguments

process: Shall be a type(process_type) object representing the external process. It is an intent(in) argument.

Return Value

Returns a real(real64) value that represents the elapsed time (in seconds) since the process was started.
If the process is still running, the value returned is the time elapsed until the call to this function. Otherwise, the total process duration from creation until completion is returned.

Example

! Process example 3: Run with many arguments, and check runtime
program run_with_args
    use stdlib_system, only: process_type, run, elapsed, wait
    implicit none

    type(process_type) :: p
    character(len=15), allocatable :: args(:)

    ! Define arguments for the `echo` command
    allocate(args(2))
    args(1) = "echo"
    args(2) = "Hello, Fortran!"

    ! Run the command with arguments (synchronous)
    p = run(args)

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

    ! Clean up
    deallocate(args)
end program run_with_args

wait - Wait until a running process is completed

Status

Experimental

Description

The wait interface provides a method to block the calling program until the specified process completes.
If the process is running asynchronously, this subroutine will pause the workflow until the given process finishes.
Additionally, an optional maximum wait time can be provided. If the process does not finish within the specified time, the subroutine will return without waiting further.

On return from this routine, the process state is accordingly updated. This is useful when you want to wait for a background task to complete, but want to avoid indefinite blocking in case of process hang or delay.

Syntax

call stdlib_system (process [, max_wait_time])

Arguments

process: Shall be a type(process_type) object representing the external process to monitor.
This is an intent(inout) argument, and its state is updated upon completion.

max_wait_time (optional): Shall be a real value specifying the maximum wait time in seconds.
If not provided, the subroutine will wait indefinitely until the process completes.

Example

! Process example 2: Run an Asynchronous Command and check its status
program run_async
    use stdlib_system, only: process_type, runasync, is_running, wait
    implicit none

    type(process_type) :: p

    ! Run an asynchronous process to sleep for 1 second
    p = runasync("sleep 1")

    ! Check if the process is running
    if (is_running(p)) then
        print *, "Process is running."
    else
        print *, "Process has already completed."
    end if

    ! Wait for the process to complete
    call wait(p, max_wait_time = 5.0)
    print *, "Process has now completed."
end program run_async

update - Update the internal state of a process

Status

Experimental

Description

The update interface allows the internal state of a process object to be updated by querying the system.
After the process completes, the standard output and standard error are retrieved, if they were requested, and loaded into the process%stdout and process%stderr string variables, respectively.

This is especially useful for monitoring asynchronous processes and retrieving their output after they have finished.

Syntax

call stdlib_system (process)

Arguments

process: Shall be a type(process_type) object representing the external process whose state needs to be updated.
This is an intent(inout) argument, and its internal state is updated on completion.

Example

! Process example 5: Object-oriented interface
program example_process_5
    use stdlib_system, only: process_type, runasync, is_windows, sleep, update
    implicit none
    type(process_type) :: process

    if (is_windows()) then
        process = runasync("ping -n 10 127.0.0.1")
    else
        process = runasync("ping -c 10 127.0.0.1")
    endif

    ! Verify the process is running
    do while (process%is_running())

        ! Update process state
        call update(process)

        ! Wait a bit before killing the process
        call sleep(millisec=1500)

        print *, "Process has been running for ",process%elapsed()," seconds..."

    end do

    print *, "Process ",process%pid()," completed in ",process%elapsed()," seconds."

end program example_process_5

kill - Terminate a running process

Status

Experimental

Description

The kill interface is used to terminate a running external process. It attempts to stop the process and returns a boolean flag indicating whether the operation was successful. This interface is useful when a process needs to be forcefully stopped, for example, if it becomes unresponsive or if its execution is no longer required.

Syntax

call stdlib_system (process, success)

Arguments

process: Shall be a type(process_type) object representing the external process to be terminated.
This is an intent(inout) argument, and on return is updated with the terminated process state.

success: Shall be a logical variable. It is set to .true. if the process was successfully killed, or .false. otherwise.

Example

! Process example 4: Kill a running process
program example_process_kill
    use stdlib_system, only: process_type, runasync, is_running, kill, elapsed, is_windows, sleep
    implicit none
    type(process_type) :: process
    logical :: running, success

    print *, "Starting a long-running process..."
    if (is_windows()) then
        process = runasync("ping -n 10 127.0.0.1")
    else
        process = runasync("ping -c 10 127.0.0.1")
    endif

    ! Verify the process is running
    running = is_running(process)
    print *, "Process running:", running

    ! Wait a bit before killing the process
    call sleep(millisec=250) 

    print *, "Killing the process..."
    call kill(process, success)

    if (success) then
        print *, "Process killed successfully."
    else
        print *, "Failed to kill the process."
    endif

    ! Verify the process is no longer running
    running = is_running(process)
    print *, "Process running after kill:", running

end program example_process_kill

sleep - Pause execution for a specified time in milliseconds

Status

Experimental

Description

The sleep interface pauses the execution of a program for a specified duration, given in milliseconds. This routine acts as a cross-platform wrapper, abstracting the underlying platform-specific sleep implementations. It ensures that the requested sleep duration is honored on both Windows and Unix-like systems.

Syntax

call stdlib_system (millisec)

Arguments

millisec: Shall be an integer representing the number of milliseconds to sleep. This is an intent(in) argument.

Example

! Usage of `sleep`
program example_sleep
    use stdlib_system, only: sleep
    implicit none

    print *, "Starting sleep..."

    ! Sleep for 500 milliseconds
    call sleep(500)

    print *, "Finished sleeping!"

end program example_sleep    

is_windows - Check if the system is running on Windows

Status

Experimental

Description

The is_windows interface provides a quick, compile-time check to determine if the current system is Windows. It leverages a C function that checks for the presence of the _WIN32 macro, which is defined in C compilers when targeting Windows. This function is highly efficient and works during the compilation phase, avoiding the need for runtime checks.

Syntax

result = stdlib_system ()

Return Value

Returns a logical flag: .true. if the system is Windows, or .false. otherwise.

Example

! Process example 1: Run a Command Synchronously and Capture Output
program run_sync
    use stdlib_system, only: run, is_completed, is_windows, process_type
    implicit none

    type(process_type) :: p
    logical :: completed

    ! Run a synchronous process to list directory contents
    if (is_windows()) then
        p = run("dir", want_stdout=.true.)
    else
        p = run("ls -l", want_stdout=.true.)
    end if

    ! Check if the process is completed (should be true since wait=.true.)
    if (is_completed(p)) then
        print *, "Process completed successfully. The current directory: "
        print *, p%stdout
    else
        print *, "Process is still running (unexpected)."
    end if

end program run_sync

get_runtime_os - Determine the OS type at runtime

Status

Experimental

Description

get_runtime_os inspects the runtime environment to identify the current OS type. It evaluates environment variables (OSTYPE, OS) and checks for specific files associated with known operating systems. The supported OS types are integer, parameter variables stored in the stdlib_system module:

  • Linux (OS_LINUX)
  • macOS (OS_MACOS)
  • Windows (OS_WINDOWS)
  • Cygwin (OS_CYGWIN)
  • Solaris (OS_SOLARIS)
  • FreeBSD (OS_FREEBSD)
  • OpenBSD (OS_OPENBSD)

If the OS cannot be identified, the function returns OS_UNKNOWN.

Syntax

os = [[stdlib_system(module):get_runtime_os(function)]]()

Class

Function

Arguments

None.

Return Value

Returns one of the integer OS_* parameters representing the OS type, from the stdlib_system module, or OS_UNKNOWN if undetermined.

Example

! Demonstrate usage of (non-cached) runtime OS query
program example_get_runtime_os
    use stdlib_system, only: OS_NAME, get_runtime_os
    implicit none

    ! Runtime OS detection (full inspection)
    print *, "Runtime OS Type: ", OS_NAME(get_runtime_os())

end program example_get_runtime_os

OS_TYPE - Cached OS type retrieval

Status

Experimental

Description

OS_TYPE provides a cached result of the get_runtime_os function. The OS type is determined during the first invocation and stored in a static variable. Subsequent calls reuse the cached value, making this function highly efficient.

This caching mechanism ensures negligible overhead for repeated calls, unlike get_runtime_os, which performs a full runtime inspection.

Syntax

os = [[stdlib_system(module):OS_TYPE(function)]]()

Class

Function

Arguments

None.

Return Value

Returns one of the integer OS_* parameters representing the OS type, from the stdlib_system module, or OS_UNKNOWN if undetermined.

Example

! Demonstrate OS detection
program example_os_type
    use stdlib_system, only: OS_TYPE, OS_NAME
    implicit none

    integer :: current_os

    ! Cached OS detection
    current_os = OS_TYPE() 
    print *, "Current OS Type: ", OS_NAME(current_os) 

end program example_os_type

is_directory - Test if a path is a directory

Status

Experimental

Description

This function checks if a specified file system path is a directory. It is designed to work across multiple platforms. On Windows, paths with both forward / and backward \ slashes are accepted.

Syntax

result = [[stdlib_system(module):is_directory(function)]] (path)

Class

Function

Arguments

path: Shall be a character string containing the file system path to evaluate. It is an intent(in) argument.

Return values

The function returns a logical value:

  • .true. if the path matches an existing directory.
  • .false. otherwise, or if the operating system is unsupported.

Example

! Demonstrate usage of `is_directory`
program example_is_directory
  use stdlib_system, only: is_directory
  implicit none
  ! Test a directory path
  if (is_directory("/path/to/check")) then 
    print *, "The specified path is a directory."
  else
    print *, "The specified path is not a directory."
  end if
end program example_is_directory

null_device - Return the null device file path

Status

Experimental

Description

This function returns the file path of the null device, which is a special file used to discard any data written to it. It reads as an empty file. The null device's path varies by operating system: - On Windows, the null device is represented as NUL. - On UNIX-like systems (Linux, macOS), the null device is represented as /dev/null.

Syntax

path = [[stdlib_system(module):null_device(function)]]()

Class

Function

Arguments

None.

Return Value

  • Type: character(:), allocatable
  • Returns the null device file path as a character string, appropriate for the operating system.

Example

! Showcase usage of the null device
program example_null_device
    use stdlib_system, only: null_device
    use iso_fortran_env, only: output_unit
    implicit none
    integer :: unit 
    logical :: screen_output = .false.

    if (screen_output) then 
       unit = output_unit
    else
       ! Write to the null device if no screen output is wanted
       open(newunit=unit,file=null_device())
    endif     

    write(unit,*) "Hello, world!" 

    if (.not.screen_output) close(unit) 

end program example_null_device

delete_file - Delete a file

Status

Experimental

Description

This subroutine deletes a specified file from the filesystem. It ensures that the file exists and is not a directory before attempting deletion. If the file cannot be deleted due to permissions, being a directory, or other issues, an error is raised. The function provides an optional error-handling mechanism via the state_type class. If the err argument is not provided, exceptions will trigger an error stop.

Syntax

call [[stdlib_system(module):delete_file(subroutine)]] (path [, err])

Class

Subroutine

Arguments

path: Shall be a character string containing the path to the file to be deleted. It is an intent(in) argument.

err (optional): Shall be a type(state_type) variable for error handling. If provided, errors are returned as a state object. If not provided, the program stops execution on error.

Behavior

  • Checks if the file exists. If not, an error is raised.
  • Ensures the path is not a directory before deletion.
  • Attempts to delete the file, raising an error if unsuccessful.

Return values

The file is removed from the filesystem if the operation is successful. If the operation fails, an error is raised.

Example

! Demonstrate usage of `delete_file`
program example_delete_file
  use stdlib_system, only: delete_file
  use stdlib_error, only: state_type
  implicit none

  type(state_type) :: err
  character(*), parameter :: filename = "example.txt"

  ! Delete a file with error handling
  call delete_file(filename, err)

  if (err%error()) then
    print *, err%print() 
  else
    print *, "File "//filename//" deleted successfully."
  end if
end program example_delete_file