aboutsummaryrefslogtreecommitdiff
path: root/src/fpm.f90
diff options
context:
space:
mode:
authorLKedward <laurence.kedward@bristol.ac.uk>2021-06-05 14:46:31 +0100
committerLKedward <laurence.kedward@bristol.ac.uk>2021-06-05 14:49:14 +0100
commitbb95f17cc2fc99603e0cd2f17ae4f9cda16faf3c (patch)
tree9129e2027fc669b459bb6d486ffa5de39b99d481 /src/fpm.f90
parent7e9c3390b04a0fc746812abd65a574a9dd219c81 (diff)
downloadfpm-bb95f17cc2fc99603e0cd2f17ae4f9cda16faf3c.tar.gz
fpm-bb95f17cc2fc99603e0cd2f17ae4f9cda16faf3c.zip
Add: graceful failure for running apps & tests
Fixes #485
Diffstat (limited to 'src/fpm.f90')
-rw-r--r--src/fpm.f9018
1 files changed, 16 insertions, 2 deletions
diff --git a/src/fpm.f90 b/src/fpm.f90
index 5854cfb..401136b 100644
--- a/src/fpm.f90
+++ b/src/fpm.f90
@@ -297,6 +297,7 @@ subroutine cmd_run(settings,test)
type(build_target_t), pointer :: exe_target
type(srcfile_t), pointer :: exe_source
integer :: run_scope
+ integer, allocatable :: stat(:)
character(len=:),allocatable :: line
logical :: toomany
@@ -417,18 +418,31 @@ subroutine cmd_run(settings,test)
call compact_list()
else
+ allocate(stat(size(executables)))
do i=1,size(executables)
if (exists(executables(i)%s)) then
if(settings%runner .ne. ' ')then
- call run(settings%runner//' '//executables(i)%s//" "//settings%args,echo=settings%verbose)
+ call run(settings%runner//' '//executables(i)%s//" "//settings%args, &
+ echo=settings%verbose, exitstat=stat(i))
else
- call run(executables(i)%s//" "//settings%args,echo=settings%verbose)
+ call run(executables(i)%s//" "//settings%args,echo=settings%verbose, &
+ exitstat=stat(i))
endif
else
write(stderr,*)'fpm::run<ERROR>',executables(i)%s,' not found'
stop 1
end if
end do
+
+ if (any(stat /= 0)) then
+ do i=1,size(stat)
+ if (stat(i) /= 0) then
+ write(*,*) '<ERROR> Execution failed for "',basename(executables(i)%s),'"'
+ end if
+ end do
+ stop 1
+ end if
+
endif
contains
subroutine compact_list_all()