run(3f) -  execute specified system command and selectively echo
command and output to a file and/or stdout.
(LICENSE:MIT)
subroutine run(cmd,echo,exitstat,verbose,redirect)
 character(len=*), intent(in)       :: cmd
 logical,intent(in),optional        :: echo
 integer, intent(out),optional      :: exitstat
 logical, intent(in), optional      :: verbose
 character(*), intent(in), optional :: redirect
Execute the specified system command. Optionally
Calling run(3f) is preferred to direct calls to execute_command_line(3f) in the fpm(1) source to provide a standard interface where output modes can be specified.
CMD       System command to execute
ECHO      Whether to echo the command being executed or not
          Defaults to .TRUE. .
VERBOSE   Whether to redirect the command output to a null device or not
          Defaults to .TRUE. .
REDIRECT  Filename to redirect stdout and stderr of the command into.
          If generated it is closed before run(3f) returns.
EXITSTAT  The system exit status of the command when supported by
          the system. If not present and a non-zero status is
          generated program termination occurs.
Sample program:
Checking the error message and counting lines:
 program demo_run
 use fpm_filesystem, only : run
 implicit none
 logical,parameter :: T=.true., F=.false.
 integer :: exitstat
 character(len=:),allocatable :: cmd
    cmd='ls -ltrasd *.md'
    call run(cmd)
    call run(cmd,exitstat=exitstat)
    call run(cmd,echo=F)
    call run(cmd,verbose=F)
 end program demo_run
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| character(len=*), | intent(in) | :: | cmd | |||
| logical, | intent(in), | optional | :: | echo | ||
| integer, | intent(out), | optional | :: | exitstat | ||
| logical, | intent(in), | optional | :: | verbose | ||
| character(len=*), | intent(in), | optional | :: | redirect | 
subroutine run(cmd,echo,exitstat,verbose,redirect) character(len=*), intent(in) :: cmd logical,intent(in),optional :: echo integer, intent(out),optional :: exitstat logical, intent(in), optional :: verbose character(*), intent(in), optional :: redirect integer :: cmdstat character(len=256) :: cmdmsg, iomsg logical :: echo_local, verbose_local character(:), allocatable :: redirect_str character(:), allocatable :: line integer :: stat, fh, iostat if(present(echo))then echo_local=echo else echo_local=.true. end if if(present(verbose))then verbose_local=verbose else verbose_local=.true. end if if (present(redirect)) then if(redirect /= '')then redirect_str = ">"//redirect//" 2>&1" else redirect_str = "" endif else if(verbose_local)then ! No redirection but verbose output redirect_str = "" else ! No redirection and non-verbose output if (os_is_unix()) then redirect_str = " >/dev/null 2>&1" else redirect_str = " >NUL 2>&1" end if end if end if if(echo_local) print *, '+ ', cmd !//redirect_str call execute_command_line(cmd//redirect_str, exitstat=stat,cmdstat=cmdstat,cmdmsg=cmdmsg) if(cmdstat /= 0)then write(*,'(a)')'<ERROR>:failed command '//cmd//redirect_str call fpm_stop(1,'*run*:'//trim(cmdmsg)) endif if (verbose_local.and.present(redirect)) then open(newunit=fh,file=redirect,status='old',iostat=iostat,iomsg=iomsg) if(iostat == 0)then do call getline(fh, line, iostat) if (iostat /= 0) exit write(*,'(A)') trim(line) end do else write(*,'(A)') trim(iomsg) endif close(fh) end if if (present(exitstat)) then exitstat = stat elseif (stat /= 0) then call fpm_stop(stat,'*run*: Command '//cmd//redirect_str//' returned a non-zero status code') end if end subroutine run