Skip to content

Commit 6e994c6

Browse files
authored
Consistently call execute_command_line(3f) from the run(3f) wrapper (#832)
Tracebacks from system commands are generally not useful to the user. And the tracebacks generally go to stderr. In one recent issue the user was not capturing stderr, which resulted in just a message compiling was begun and nothing else (the compiler command was not in the user path). Changing all the calls in fpm_filesystem.f90 to use the run(3f) procedure and capturing and printing cmdmsg from execute_command_line(3f) creates a cleaner and more understandable message. System command issues such as missing commands, file system permission problems, full filesystems, ... generate a cleaner and more useful user message. Using run(3f) for all the calls also gives a single point of command execution for future consistent behavior and for easier debugging. Custom options such as echo mode, colorizing messages, verbose mode, ... do not require duplicate code and can be consistently applied using the run(3f) wrapper. So this lays the groundwork for some future enhancements as well. Flushing stdout and stderr in fpm_stop(3f) helps the messages appear synchronously, so the error message appears at the expected point in the output as well. See [#830](#830) for an example of an issue where this would have helped. The following example illustrates the difference when the compiler (ifort(1) in this case) is not in the path. This would apply to any system command failure, but it captures the idea and duplicates the actual case in #830 ... ```text fpm728 test --compiler ifort fpm: Entering directory '/home/urbanjs/venus/V600/REMOVE/fpm' 2K1Gfilesystem_utilities.c 93mcompiling...0m 2K1G[ 0%] Compiling...Fortran runtime error: EXECUTE_COMMAND_LINE: Invalid command line Error termination. Backtrace: at ./src/fpm_filesystem.F90:907 at ./src/fpm_compiler.f90:866 at ./src/fpm_backend.F90:324 at ./src/fpm_backend.F90:125 at ./src/fpm.f90:439 at app/main.f90:72 at app/main.f90:11 ``` ```text fpm test --compiler ifort fpm: Entering directory '/home/urbanjs/venus/V600/REMOVE/fpm' 2K1Gfilesystem_utilities.c 93mcompiling...0m 2K1G[ 0%] Compiling...<ERROR> failed command: icc -c ./src/filesystem_utilities.c -o build/ifort_00000000811C9DC5/fpm/src_filesystem_utilities.c.o>build/ifort_00000000811C9DC5/fpm/src_filesystem_utilities.c.o.log 2>&1 <ERROR>*run*:Invalid command line STOP 1 ```
1 parent 9cb38b2 commit 6e994c6

File tree

2 files changed

+44
-57
lines changed

2 files changed

+44
-57
lines changed

src/fpm/error.f90

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -166,12 +166,16 @@ subroutine fpm_stop(value,message)
166166
integer, intent(in) :: value
167167
!> Error message
168168
character(len=*), intent(in) :: message
169+
integer :: iostat
169170
if(message/='')then
171+
flush(unit=stderr,iostat=iostat)
172+
flush(unit=stdout,iostat=iostat)
170173
if(value>0)then
171174
write(stderr,'("<ERROR>",a)')trim(message)
172175
else
173176
write(stderr,'("<INFO> ",a)')trim(message)
174177
endif
178+
flush(unit=stderr,iostat=iostat)
175179
endif
176180
stop value
177181
end subroutine fpm_stop

src/fpm_filesystem.F90

Lines changed: 40 additions & 57 deletions
Original file line numberDiff line numberDiff line change
@@ -240,10 +240,12 @@ logical function is_dir(dir)
240240
select case (get_os_type())
241241

242242
case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD)
243-
call execute_command_line("test -d " // dir , exitstat=stat)
243+
call run( "test -d " // dir , &
244+
& exitstat=stat,echo=.false.,verbose=.false.)
244245

245246
case (OS_WINDOWS)
246-
call execute_command_line('cmd /c "if not exist ' // windows_path(dir) // '\ exit /B 1"', exitstat=stat)
247+
call run('cmd /c "if not exist ' // windows_path(dir) // '\ exit /B 1"', &
248+
& exitstat=stat,echo=.false.,verbose=.false.)
247249

248250
end select
249251

@@ -367,30 +369,16 @@ subroutine mkdir(dir, echo)
367369
logical, intent(in), optional :: echo
368370

369371
integer :: stat
370-
logical :: echo_local
371-
372-
if(present(echo))then
373-
echo_local=echo
374-
else
375-
echo_local=.true.
376-
end if
377372

378373
if (is_dir(dir)) return
379374

380375
select case (get_os_type())
381376
case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD)
382-
call execute_command_line('mkdir -p ' // dir, exitstat=stat)
383-
384-
if (echo_local) then
385-
write (*, *) '+ mkdir -p ' // dir
386-
end if
377+
call run('mkdir -p ' // dir, exitstat=stat,echo=echo,verbose=.false.)
387378

388379
case (OS_WINDOWS)
389-
call execute_command_line("mkdir " // windows_path(dir), exitstat=stat)
390-
391-
if (echo_local) then
392-
write (*, *) '+ mkdir ' // windows_path(dir)
393-
end if
380+
call run("mkdir " // windows_path(dir), &
381+
& echo=echo, exitstat=stat,verbose=.false.)
394382

395383
end select
396384

@@ -511,11 +499,11 @@ recursive subroutine list_files(dir, files, recurse)
511499

512500
select case (get_os_type())
513501
case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD)
514-
call execute_command_line('ls -A ' // dir // ' > ' // temp_file, &
515-
exitstat=stat)
502+
call run('ls -A ' // dir , &
503+
& redirect=temp_file, exitstat=stat,echo=.false.,verbose=.false.)
516504
case (OS_WINDOWS)
517-
call execute_command_line('dir /b ' // windows_path(dir) // ' > ' // temp_file, &
518-
exitstat=stat)
505+
call run('dir /b ' // windows_path(dir), &
506+
& redirect=temp_file, exitstat=stat,echo=.false.,verbose=.false.)
519507
end select
520508

521509
if (stat /= 0) then
@@ -864,18 +852,20 @@ function which(command) result(pathname)
864852
end function which
865853

866854
!> echo command string and pass it to the system for execution
855+
!call run(cmd,echo=.false.,exitstat=exitstat,verbose=.false.,redirect='')
867856
subroutine run(cmd,echo,exitstat,verbose,redirect)
868857
character(len=*), intent(in) :: cmd
869858
logical,intent(in),optional :: echo
870-
integer, intent(out),optional :: exitstat
859+
integer, intent(out),optional :: exitstat
871860
logical, intent(in), optional :: verbose
872861
character(*), intent(in), optional :: redirect
873862

863+
integer :: cmdstat
864+
character(len=256) :: cmdmsg, iomsg
874865
logical :: echo_local, verbose_local
875866
character(:), allocatable :: redirect_str
876867
character(:), allocatable :: line
877-
integer :: stat, fh, ios
878-
868+
integer :: stat, fh, iostat
879869

880870
if(present(echo))then
881871
echo_local=echo
@@ -890,33 +880,44 @@ subroutine run(cmd,echo,exitstat,verbose,redirect)
890880
end if
891881

892882
if (present(redirect)) then
893-
redirect_str = ">"//redirect//" 2>&1"
883+
if(redirect /= '')then
884+
redirect_str = ">"//redirect//" 2>&1"
885+
endif
894886
else
895887
if(verbose_local)then
896888
! No redirection but verbose output
897889
redirect_str = ""
898890
else
899891
! No redirection and non-verbose output
900892
if (os_is_unix()) then
901-
redirect_str = ">/dev/null 2>&1"
893+
redirect_str = " >/dev/null 2>&1"
902894
else
903-
redirect_str = ">NUL 2>&1"
895+
redirect_str = " >NUL 2>&1"
904896
end if
905897
end if
906898
end if
907899

908-
if(echo_local) print *, '+ ', cmd
900+
if(echo_local) print *, '+ ', cmd !//redirect_str
909901

910-
call execute_command_line(cmd//redirect_str, exitstat=stat)
902+
call execute_command_line(cmd//redirect_str, exitstat=stat,cmdstat=cmdstat,cmdmsg=cmdmsg)
903+
if(cmdstat /= 0)then
904+
write(*,'(a)')'<ERROR>:failed command '//cmd//redirect_str
905+
call fpm_stop(1,'*run*:'//trim(cmdmsg))
906+
endif
911907

912908
if (verbose_local.and.present(redirect)) then
913909

914-
open(newunit=fh,file=redirect,status='old')
915-
do
916-
call getline(fh, line, ios)
917-
if (ios /= 0) exit
918-
write(*,'(A)') trim(line)
919-
end do
910+
open(newunit=fh,file=redirect,status='old',iostat=iostat,iomsg=iomsg)
911+
if(iostat == 0)then
912+
do
913+
call getline(fh, line, iostat)
914+
if (iostat /= 0) exit
915+
write(*,'(A)') trim(line)
916+
end do
917+
else
918+
write(*,'(A)') trim(iomsg)
919+
endif
920+
920921
close(fh)
921922

922923
end if
@@ -937,28 +938,10 @@ subroutine os_delete_dir(unix, dir, echo)
937938
character(len=*), intent(in) :: dir
938939
logical, intent(in), optional :: echo
939940

940-
logical :: echo_local
941-
942-
if(present(echo))then
943-
echo_local=echo
944-
else
945-
echo_local=.true.
946-
end if
947-
948941
if (unix) then
949-
call run('rm -rf ' // dir, .false.)
950-
951-
if (echo_local) then
952-
write (*, *) '+ rm -rf ' // dir
953-
end if
954-
942+
call run('rm -rf ' // dir, echo=echo,verbose=.false.)
955943
else
956-
call run('rmdir /s/q ' // dir, .false.)
957-
958-
if (echo_local) then
959-
write (*, *) '+ rmdir /s/q ' // dir
960-
end if
961-
944+
call run('rmdir /s/q ' // dir, echo=echo,verbose=.false.)
962945
end if
963946

964947
end subroutine os_delete_dir

0 commit comments

Comments
 (0)