M_process Module

NAME

M_process(3fm) - [M_process::INTRO] Fortran Module for calling
                 process-related C functions from Fortran
(LICENSE:PD)

SYNOPSIS

 use M_process, only : process_open_read, process_open_write, process_close

 use M_process, only : process_readline, process_readall, process_writeline

 use M_process, only : streampointer, process_debug

DESCRIPTION

Module M_process(3f) lets Fortran code read/write lines from/to processes.

These Fortran procedures use the ISO_C_BINDING interface to define Fortran-callable versions of the C procedures popen(3c)/pclose(3c) and fgets(3c)/fputs(3c). A set of record-oriented wrapper routines are then used to create a simple Fortran-callable interface.

A POSIX C interface is generally available but may require using a Linux subwindow or an application such as CygWin on MSWindows platforms.

Basically, you

o Open a process for either reading from or writing to using formatted sequential text records (eg. “lines”); much like with a regular file. o pass a CHARACTER variable to/from the process that represents a record. o Use internal READs and internal WRITEs or parsing routines to create or interpret the lines. o when done close the process much like closing a file.

The procedures defined are:

 ! open process to read from
 subroutine process_open_read(cmd,fp,ierr)

 ! open process to write to
 subroutine process_open_write(cmd,fp,ierr)

 ! read line from process
 subroutine process_readline(string,fp,ierr)
 ! read all of process output into a string string
 function process_readall(cmd,ierr) result (string)

 ! write lines to process
 subroutine process_writeline &
 & (string|string_array,fp,ierr[,trm=.t.|.f.])

 ! close process
 subroutine process_close(fp,ierr)

where the variable types are

   character(len=*)    :: cmd
   type(streampointer) :: fp
   character(len=*)    :: string
   integer             :: ierr

OPTIONS

cmd      command passed to system to start process
fp       C file pointer returned by process_open_*()
string   data line to send or receive from process
ierr     error flag returned.

          o process_writeline(3f) : negative indicates an error
          o process_readline(3f)  : Non-zero indicates an error

maximum character value length is currently 4096

EXAMPLES

An example that places all the output of a command into a single string variable (see process_readall(3) for an even simpler way to do this) …

program read_ex
use M_process ,only: process_open_read, process_readline
use M_process ,only: streampointer, process_close
implicit none
! C file pointer returned by process_open()
type(streampointer) :: fp
! check status of calls to process module routines
integer :: ierr
! hold results, assuming sufficient memory is available
character(len=:),allocatable :: string
! long enough to hold any expected line
character(len=4096) :: line
   string=''
   !###! open process to read from
   call process_open_read('ls',fp,ierr)
   !###! read output of process till end
   do
      call process_readline(line,fp,ierr)
      if(ierr.ne.0)exit
      !###! append output lines together
      string=string//trim(line)//' '
      write(*,*)'['//string//']'
   enddo
   write(*,*)trim(string)
   !###! Wrap up
   call process_close(fp,ierr)
end program read_ex

When calling a line-mode program from another program the most natural way is to open a process and write to it.

Following is an example program that calls the M_process module to start a plotting program called gnuplot(1) and give it enough commands to generate a plot. It then lets you interactively interact with the gnuplot(1) program or continue on in the program.

program gnuplotExample use M_process ,only: process_open_write, process_writeline use M_process ,only: streampointer, process_close implicit none ! ! Example of Fortran writing GNUPLOT command and data file. ! !! line of data to write !! (assumed long enough to hold any command line) character(len=4096) :: line !! C file pointer returned by process_open() type(streampointer) :: fp !! check status of calls to process module routines integer :: ierr !! DO loop counter integer :: i !! number of points to put into curve to be plotted integer,parameter :: n=50 !! arrays to fill with curve data to be plotted real :: x(n),y(n) integer :: ios !! Define sample X,Y array. do i=1,n !! set X() values as whole numbers 1 to N x(i)=i !! y(i)=(x(i)+0.5)2 enddo !! Write the GnuPlot commands !! open process to write to (ie. start gnuplot(1) program) call process_open_write(‘gnuplot’,fp,ierr) !! create in-line dataset $SET1 call process_writeline(‘$SET1 <<EOD’,fp,ierr) do i=1,n !! Write the X,Y array as coordinates to be plotted. write(line,’(2(f10.3,1x))’)x(i),y(i) call process_writeline(line,fp,ierr) enddo

call process_writeline([character(len=128) :: & &’EOD ‘, & &’set title ” Example of GNUPlot data and command file generation”’, & &’set nokey’ , & &’plot $SET1 with lines’ , & &’‘],fp,ierr)

!! Additional gnuplot commands; in this case interactively entered write(,’(a)’)’enter gnuplot commands or “.” to exit’ do write(,’(a)’,advance=’no’)’gnu>>’ read(,’(a)’,iostat=ios)line if(line.eq.’.’)exit call process_writeline(trim(line),fp,ierr) enddo !! Wrap up call process_close(fp,ierr) write(,*)’CLOSED THE PROCESS. RETURNING TO PROGRAM’ end program gnuplotExample

This program starts a bash shell that, among other things, calls sqlite3 and gnuplot. In this case the text is fixed to keep the example simple. More typically the text would be conditionally selected or generated by the program.

program demo_M_process
 use M_process ,only : process_open_write, process_writeline
 use M_process ,only : streampointer, process_close
 implicit none
 ! C file pointer returned by process_open()
 type(streampointer) :: fp
 ! check status of calls to process module routines
 integer :: ierr
 character(len=:),allocatable :: text(:)

 ! open process to write to (ie. start gnuplot(1) program)
 !!call process_open_write('cat',fp,ierr)
 ! open process to write to (ie. start gnuplot(1) program)
 call process_open_write('bash',fp,ierr)

 text=[character(len=128) :: &
 "rm -f sqlite1.db", &
 "sqlite3 sqlite1.db <<\EOF", &
 "-- ***********************************************",&
 "CREATE TABLE IF NOT EXISTS animals(               ",&
 "   name        TEXT   NOT NULL   PRIMARY KEY ,    ",&
 "   hair        INT    NOT NULL   ,                ",&
 "   mobility    INT    NOT NULL   ,                ",&
 "   vision      INT    NOT NULL   );               ",&
 "-- ***********************************************",&
 "INSERT INTO animals(&
 &name,hair,mobility,vision) VALUES('kittens',4,5,1);",&
 "INSERT INTO animals(&
 &name,hair,mobility,vision) VALUES('mice'   ,6,7,2);",&
 "INSERT INTO animals(&
 &name,hair,mobility,vision) VALUES('rats'   ,2,3,3);",&
 "-- ***********************************************",&
 ".quit", &
 "EOF", &
 "##################################################",&
 "sqlite3 -header -column sqlite1.db  'select * from animals'",&
 "sqlite3 sqlite1.db  &
 &'select name, hair, mobility, vision from animals'",&
 "##################################################",&
 "gnuplot --persist <<\EOF                          ",&
 "########################################          ",&
 "#set terminal gif                                 ",&
 "#set output 'M_process.3.gif'                     ",&
 "########################################          ",&
 "#set terminal png                                 ",&
 "#set output 'bar.png'                             ",&
 "########################################          ",&
 "#set terminal pdf enhanced                        ",&
 "#set output 'bar.pdf'                             ",&
 "########################################          ",&
 "#set style data lines                             ",&
 "########################################          ",&
 "set datafile separator ""|""                      ",&
 "set style data histogram                          ",&
 "set style histogram cluster gap 1                 ",&
 "set style fill solid border rgb ""black""         ",&
 "set auto x                                        ",&
 "set yrange [0:*]                                  ",&
 "plot ""< sqlite3 sqlite1.db  &
 &'select name, hair, mobility, vision  from animals'"" \  ", &
 "      using 2:xtic(1) title ""hair"",  \          ",&
 "   '' using 4:xtic(1) title ""vision"", \         ",&
 "   '' using 3:xtic(1) title ""mobility""          ",&
 "quit                                              ",&
 "EOF                                               ",&
 " "]

    !!write(*,'(a)')text
    call process_writeline(text,fp,ierr)
    call process_close(fp,ierr)
    write(*,'(a)')'CLOSED THE PROCESS. RETURNING TO PROGRAM'

 end program demo_M_process

This example shows a routine to read the output of one command and then call another command to write that output to.

  program test
  implicit none
    call readit('ls -l')
    call writeit('cat -n')
  contains

  subroutine readit(cmd)
  use M_process ,ONLY: process_open_read, process_readline
  use M_process ,ONLY: streampointer, process_close
  ! C file pointer returned by process_open()
  type(streampointer) :: fp
  ! command line executed to start process
  character(len=*)    :: cmd
  ! line of data to read (assumed long enough to hold any input line)
  character(len=4096) :: line
  integer ierr
    ! open process to read from
    call process_open_read(cmd,fp,ierr)
    write(*,*)'READTEST: process is opened with status ',ierr
    ierr=0
    do while(ierr .eq. 0)
      ! read a line from the process
      call process_readline(line,fp,ierr)
      if(ierr.ne.0)then
        write(*,*)'READTEST: ierr is ',ierr
        exit
      endif
      write(*,*)'READTEST: line:'//trim(line)
    enddo
    call process_close(fp,ierr)
    write(*,*)'READTEST: process closed with status ',ierr
  end subroutine readit
  !---------------------------------------------------------------------
  subroutine writeit(cmd)
  use M_process, only: process_open_write, process_writeline
  use M_process, only: streampointer, process_close
  ! C file pointer returned by process_open()
  type(streampointer) :: fp
  ! command line executed to start process
  character(len=*)    :: cmd
  ! line of data to write (assumed long enough to hold any output line)
  character(len=4096) :: line
  integer             :: ierr
  integer             :: i
    ! open process to write to
    call process_open_write(cmd,fp,ierr)
    write(*,*)'WRITETEST: process is opened'
    ierr=0
    do i=1,10
      write(line,'("WRITETEST: line ",i0)')i
      call process_writeline(line,fp,ierr)
      if(ierr.lt.0)then
        write(*,*)'WRITETEST: process write error ',ierr
        exit
      endif
    enddo
    call process_close(fp,ierr)
    write(*,*)'WRITETEST: process closed with status ',ierr
  end subroutine writeit
  end program test

SEE ALSO

o PIPES: pipe(3c), popen(3c), pclose(3c), fflush(3c)
o NAMED PIPES: mkfifo(3c), mknod(3c)
o SUBPROCESSES: fork(3c)
o OTHER: fflush(3c)

AUTHOR

John S. Urban

LICENSE

Public Domain

DESCRIPTION: record-oriented Fortran I/O interface to C popen,pclose,fgets,fputs

VERSION: 2.0.0, 20161105

AUTHOR: John S. Urban



Contents


Variables

Type Visibility Attributes Name Initial
logical, public :: process_debug = .false.

Interfaces

public interface process_writeline

  • private subroutine process_writeline_scalar(writefrom, fp, ierr, trm)

    NAME

    process_writeline(3fm) - [M_process] write to a process using a
                             POSIX interface
    (LICENSE:PD)
    

    SYNOPSIS

     subroutine process_writeline(string,fp,ierr)
    
       character(len=*)    :: string
       type(streampointer) :: fp
       integer             :: ierr
    

    DESCRIPTION

    The M_process Fortran procedures use the ISO_C_BINDING interface to define Fortran-callable versions of the C procedures popen(3c)/pclose(3c) and fgets(3c)/fputs(3c). A set of record-oriented wrapper routines are then used to create a simple Fortran-callable interface.

    A POSIX C interface is generally available but may require using a Linux subwindow or an application such as CygWin on MSWindows platforms.

    See “M_process” for an extended description.

    OPTIONS

    string   data line to to process
    fp       C file pointer returned by process_open_*()
    ierr     error flag returned.
    
              o process_writeline(3f) : negative indicates an error
              o process_readline(3f)  : Non-zero indicates an error
    
    maximum character value length is currently 4096
    

    EXAMPLES

    This example shows a routine to write lines to the stdin of a system process

    program demo_process_writeline use, intrinsic :: iso_fortran_env, only : & & stdin=>input_unit, & & stdout=>output_unit, & & stderr=>error_unit use m_process ,only: process_open_write, process_writeline use m_process ,only: streampointer, process_close implicit none type(streampointer) :: fp ! line of data to write character(len=4096) :: line integer :: ierr integer :: i ! open process to write to call process_open_write(‘cat -n’,fp,ierr) write(,)’WRITETEST: process is opened with status ‘,ierr ! remember C and Fortran I/O are often independent of each other flush(stdout) ierr=0 line=’xxxxxxxxxxxxxxxxxxxxxxxxxxx’ do i=1,10 ! write a line to the process call process_writeline(trim(line),fp,ierr) if(ierr.lt.0)then write(,)’WRITETEST: ierr is ‘,ierr exit endif enddo call process_close(fp,ierr) write(,)’WRITETEST: process closed with status ‘,ierr end program demo_process_writeline

    Sample output:

    WRITETEST: process is opened with status 0 1 xxxxxxxxxxxxxxxxxxxxxxxxxxx 2 xxxxxxxxxxxxxxxxxxxxxxxxxxx 3 xxxxxxxxxxxxxxxxxxxxxxxxxxx 4 xxxxxxxxxxxxxxxxxxxxxxxxxxx 5 xxxxxxxxxxxxxxxxxxxxxxxxxxx 6 xxxxxxxxxxxxxxxxxxxxxxxxxxx 7 xxxxxxxxxxxxxxxxxxxxxxxxxxx 8 xxxxxxxxxxxxxxxxxxxxxxxxxxx 9 xxxxxxxxxxxxxxxxxxxxxxxxxxx 10 xxxxxxxxxxxxxxxxxxxxxxxxxxx WRITETEST: process closed with status 0

    SEE ALSO

    o PIPES: pipe(3c), popen(3c), pclose(3c), fflush(3c)
    o NAMED PIPES: mkfifo(3c), mknod(3c)
    o SUBPROCESSES: fork(3c)
    o OTHER: fflush(3c)
    

    AUTHOR

    John S. Urban
    

    LICENSE

    Public Domain
    

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: writefrom
    type(streampointer), intent(in) :: fp
    integer, intent(out) :: ierr
    logical, intent(in), optional :: trm
  • private subroutine process_writeline_array(writefrom, fp, ierr)

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: writefrom(:)
    type(streampointer), intent(in) :: fp
    integer, intent(out) :: ierr

Derived Types

type, public ::  streampointer

Components

Type Visibility Attributes Name Initial
type(c_ptr), public :: handle = c_null_ptr

Functions

public function process_readall(cmd, delim, ierr) result(string)

syntax:

Read more…

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: cmd
character(len=*), intent(in), optional :: delim
integer, intent(out), optional :: ierr

Return Value character(len=:), allocatable

assume will not run out of memory


Subroutines

public subroutine process_close(fp, ierr)

The M_process Fortran procedures use the ISO_C_BINDING interface to define Fortran-callable versions of the C procedures popen(3c)/pclose(3c) and fgets(3c)/fputs(3c). A set of record-oriented wrapper routines are then used to create a simple Fortran-callable interface.

Read more…

Arguments

Type IntentOptional Attributes Name
type(streampointer) :: fp
integer, intent(out) :: ierr

public subroutine process_open_read(cmd, fp, ierr)

The M_process Fortran procedures use the ISO_C_BINDING interface to define Fortran-callable versions of the C procedures popen(3c)/pclose(3c) and fgets(3c)/fputs(3c). A set of record-oriented wrapper routines are then used to create a simple Fortran-callable interface.

Read more…

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: cmd
type(streampointer), intent(out) :: fp
integer, intent(out) :: ierr

public subroutine process_open_write(cmd, fp, ierr)

The M_process Fortran procedures use the ISO_C_BINDING interface to define Fortran-callable versions of the C procedures popen(3c)/pclose(3c) and fgets(3c)/fputs(3c). A set of record-oriented wrapper routines are then used to create a simple Fortran-callable interface.

Read more…

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: cmd
type(streampointer), intent(out) :: fp
integer, intent(out) :: ierr

public subroutine process_readline(readfrom, fp, ierr)

The M_process Fortran procedures use the ISO_C_BINDING interface to define Fortran-callable versions of the C procedures popen(3c)/pclose(3c) and fgets(3c)/fputs(3c). A set of record-oriented wrapper routines are then used to create a simple Fortran-callable interface.

Read more…

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(out) :: readfrom
type(streampointer), intent(in) :: fp
integer, intent(out) :: ierr