aboutsummaryrefslogtreecommitdiff
path: root/src/fpm_filesystem.F90
diff options
context:
space:
mode:
authorLaurence Kedward <laurence.kedward@bristol.ac.uk>2021-11-28 11:55:50 +0000
committerLaurence Kedward <laurence.kedward@bristol.ac.uk>2021-11-29 11:56:10 +0000
commit0c561b0f76bc6fa7777dec884a16b76694913adf (patch)
tree76d60af0501dc66ee8c81881ef2a01f0ad6039e5 /src/fpm_filesystem.F90
parentb0115d1a000ee15d3ca773c3da3300595d805454 (diff)
downloadfpm-0c561b0f76bc6fa7777dec884a16b76694913adf.tar.gz
fpm-0c561b0f76bc6fa7777dec884a16b76694913adf.zip
Apply suggestion: move run to filesystem and use getline
fpm_environment::run is moved to fpm_filesystem so that it can use the getline function to retrieve redirected output from file
Diffstat (limited to 'src/fpm_filesystem.F90')
-rw-r--r--src/fpm_filesystem.F9073
1 files changed, 71 insertions, 2 deletions
diff --git a/src/fpm_filesystem.F90 b/src/fpm_filesystem.F90
index 6127844..7510ba7 100644
--- a/src/fpm_filesystem.F90
+++ b/src/fpm_filesystem.F90
@@ -5,7 +5,7 @@ module fpm_filesystem
use fpm_environment, only: get_os_type, &
OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, &
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD
- use fpm_environment, only: separator, get_env
+ use fpm_environment, only: separator, get_env, os_is_unix
use fpm_strings, only: f_string, replace, string_t, split, notabs
use iso_c_binding, only: c_char, c_ptr, c_int, c_null_char, c_associated, c_f_pointer
use fpm_error, only : fpm_stop
@@ -15,7 +15,7 @@ module fpm_filesystem
mkdir, exists, get_temp_filename, windows_path, unix_path, getline, delete_file
public :: fileopen, fileclose, filewrite, warnwrite, parent_dir
public :: read_lines, read_lines_expanded
- public :: which, LINE_BUFFER_LEN
+ public :: which, run, LINE_BUFFER_LEN
integer, parameter :: LINE_BUFFER_LEN = 1000
@@ -850,4 +850,73 @@ integer :: i, j
enddo SEARCH
end function which
+!> echo command string and pass it to the system for execution
+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
+
+ logical :: echo_local, verbose_local
+ character(:), allocatable :: redirect_str
+ character(:), allocatable :: line
+ integer :: stat, fh, ios
+
+
+ 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
+ redirect_str = ">"//redirect//" 2>&1"
+ 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
+
+ call execute_command_line(cmd//redirect_str, exitstat=stat)
+
+ if (verbose_local.and.present(redirect)) then
+
+ open(newunit=fh,file=redirect,status='old')
+ do
+ call getline(fh, line, ios)
+ if (ios /= 0) exit
+ write(*,'(A)') trim(line)
+ end do
+ close(fh)
+
+ end if
+
+ if (present(exitstat)) then
+ exitstat = stat
+ else
+ if (stat /= 0) then
+ call fpm_stop(1,'*run*:Command failed')
+ end if
+ end if
+
+end subroutine run
+
+
end module fpm_filesystem