Is there a way to capture output generated by execute_command_line?

Hi ,

I would like to be able to capture output from running another binary with execute_command_line()
Except I don’t know how .
I want to capture the output from the multicore main to the variable greetings
Here are the programs (one uses coarray Fortran)
main :

program main
  implicit none

  character(len=*),parameter :: filename="multi_core",&
       compile_multi_core_backend="caf -O3 multi_core.f90 -o multi_core"
  integer,parameter :: max_cores=12
  character,allocatable :: greetings(:,:)
  character(len=1000) :: run_multi_core_backend
  character(len=1) :: recompile_answer
  integer :: number_of_cores
  logical :: ex

  inquire(file=filename,exist=ex)
  select case (ex)
     case (.false.)
        print "(a)", "Doesn't exist"
        print "(a)", "Compiling.."
        call execute_command_line (compile_multi_core_backend)
        call select_cores_and_run()
     case (.true.)
        print "(a)", "It exists!"
        write(unit=*,fmt="(a,1x)",advance="no") "Do you want to recompile it?"
        read *, recompile_answer
        select case (recompile_answer)
           case ("y")
              print "(a)", "Compiling.."
              call execute_command_line(compile_multi_core_backend)
              call select_cores_and_run()
           case ("Y")
              print "(a)", "Compiling.."
              call execute_command_line(compile_multi_core_backend)
              call select_cores_and_run()
           case("n")
              call select_cores_and_run()
           case("N")
              call select_cores_and_run()
           end select
     end select

contains

  subroutine select_cores_and_run()

    write(unit=*,fmt="(a,1x)",advance="no")&
         "How many cores do you want?"
    read *, number_of_cores
    if (number_of_cores .gt. max_cores) STOP "Error: Too many cores !"
    allocate (greetings(number_of_cores,100))
    write(unit=run_multi_core_backend,fmt="(a,1x,a,1x,i0,1x,a)")&
         "cafrun","-n",number_of_cores,"./multi_core"
    call execute_command_line(run_multi_core_backend)

  end subroutine select_cores_and_run

end program main

multi core main :

program multi_main
  implicit none

  print "(a,1x,i0)", "Hello from",this_image()

end program multi_main

AFAIK there’s no way to get the output using the routine arguments. One way is to redirect the output of your command to a text file, and then open and read this file. Below each output line is eventually stored in a string array element:

character(len=256), string
character(len=256), allocatable :: output(:)
integer :: stat

output = [character(len=256)::]
call execute_command_line (compile_multi_core_backend // " > /path/to/file.txt")
open(unit=50,file="/path/to/file.txt",form='formatted')
do 
    read(50,"(A)",iostat=stat) string
    if (stat /= 0) exit
    output = [output string]
end do
close(unit=50)
...
2 Likes

.You might use pipes or (popen-like function). Unfortunately they are not standardized in Fortran.

1 Like

This was the solution I thought of. I was hoping for a more elegant solution. :frowning:

Also if anyone has a better way to do this, please let me know.

At least on Linux and FreeBSD, you have access to the POSIX function popen(3) through my fortran-unix interface bindings (other Unix-like operating systems probably require more pre-processor macros):

! pipe.f90
program main
    use, intrinsic :: iso_c_binding
    use, intrinsic :: iso_fortran_env, only: i8 => int64
    use :: unix
    implicit none (type, external)

    character(len=1024) :: bytes
    integer(kind=i8)    :: n
    type(c_ptr)         :: pipe

    call pipe_open(pipe, 'echo "Hi, there!"', 'r')
    if (.not. c_associated(pipe)) stop 'Error: failed to open pipe'

    call pipe_read(pipe, bytes, n)
    call pipe_close(pipe)

    if (n == 0) stop 'Error: failed to read from pipe'

    print '(a)', bytes(1:n)
contains
    subroutine pipe_close(pipe)
        type(c_ptr), intent(inout) :: pipe
        integer                    :: rc

        if (.not. c_associated(pipe)) return
        rc = c_pclose(pipe)
    end subroutine pipe_close

    subroutine pipe_open(pipe, command, access)
        type(c_ptr),      intent(out) :: pipe
        character(len=*), intent(in)  :: command
        character(len=1), intent(in)  :: access

        pipe = c_null_ptr
        if (access /= 'r' .and. access /= 'w') return
        pipe = c_popen(trim(command) // c_null_char, access // c_null_char)
    end subroutine pipe_open

    subroutine pipe_read(pipe, bytes, n)
        type(c_ptr),              intent(inout) :: pipe
        character(len=*), target, intent(inout) :: bytes
        integer(kind=i8),         intent(out)   :: n

        bytes = ' '
        n = c_fread(c_loc(bytes), int(1, kind=c_size_t), len(bytes, kind=c_size_t), pipe)
    end subroutine pipe_read
end program main

To compile, link, and run the example:

$ gfortran -o pipe pipe.f90 libfortran-unix.a
$ ./pipe
Hi, there!
2 Likes

With standard Fortran, what is shown to you by @PierU is the common approach. About the only improvement you can consider from a coding style aspect is a variable or a named constant for the name of the text file you want to use for the data exchange and the NEWUNIT facility for the logical unit number.

..
character(len=*), parameter :: txtfile = "/path/xxx.txt"
..
call .. ( .. command="ccc" // ">> "// txtfile )
..
open(newunit=lun, file=txtfile,..)
..
read( unit=lun,..)
..
1 Like

Thank you two for the input :+1:

See also my post from 2014 on how to do this sort of thing. And it doesn’t require to you assume a maximum length of the resulting string.

4 Likes

This is what I was looking for ! Thank you and everyone else :slight_smile:

Well, elegancy can take several paths :wink: . This one has a compact code and is Fortran only… not too bad. Managing arbitrary line lengths is also possible with a few more code lines if needed.

1 Like

Don’t get me wrong. I am not saying your solution isn’t elegant. I just think writing to file is a considerable speed bump. Am I wrong in this regard ?

Don’t worry, there was no offense anyway :wink:

Unless a huge volume is written to the standard output, the text file will be entirely in the RAM cache, that is fast to write and fast to read. If you absolutely want to avoid using the disk, the file can be placed on a ramdisk (many Linux distributions have one by default)

1 Like

I didn’t know this. Thank you once again for helping out :slight_smile:

On unix, it is often said that “everything” is a file. A named pipe looks like a file, but the underlying OS operations are just moving bits from the output of one process into the input of another process. Redirection of stdin, stdout, and stderr are like that too. They look like files to the program, but the OS is really just moving bits from one process to another.

Regarding the original question, it is straightforward in fortran to read and write to standard input and standard output, and the OS+shell can string together fortran programs in the usual way to exploit that capability. But it is more difficult that it seems like it should be to simply capture the output from, for example, a child process. The difficulty I think is that not all operating systems have this concept, so to build it into the language might make fortran less portable to these other operating systems. The POSIX fortran interface addressed some of this functionality, but that IEEE standard has been unsupported since the mid 1990s. So that leaves just the POSIX standard itself, along with c interoperability, as has been used above by @interkosmos.

1 Like

I did a bit of digging and micro$oft seems to have pipelines in their power shell, i dunno though if this is similar.

I think there atre also popen-like functions in the Windows API, zhat are similat, but not odentical to the POSIX ones. (So far, i have not used them)

1 Like