aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSebastian Ehlert <28669218+awvwgk@users.noreply.github.com>2020-09-16 07:44:42 +0200
committerSebastian Ehlert <28669218+awvwgk@users.noreply.github.com>2020-09-16 07:44:42 +0200
commite969f5e675c832e3abbb9fb3db142c52ef0eb9d6 (patch)
tree9228387b2547ab4f4a32a56884497950a2279f76
parent4a5ecae744b63010b510dfda230278286253ffe6 (diff)
downloadfpm-e969f5e675c832e3abbb9fb3db142c52ef0eb9d6.tar.gz
fpm-e969f5e675c832e3abbb9fb3db142c52ef0eb9d6.zip
Don't exit after failing in a test suite
-rw-r--r--fpm/test/main.f9019
-rw-r--r--fpm/test/testsuite.f9010
2 files changed, 11 insertions, 18 deletions
diff --git a/fpm/test/main.f90 b/fpm/test/main.f90
index 0e4f156..bc8ad29 100644
--- a/fpm/test/main.f90
+++ b/fpm/test/main.f90
@@ -12,6 +12,8 @@ program fpm_testing
type(testsuite_t), allocatable :: testsuite(:)
character(len=*), parameter :: fmt = '("#", *(1x, a))'
+ stat = 0
+
testsuite = [ &
& new_testsuite("fpm_toml", collect_toml), &
& new_testsuite("fpm_manifest", collect_manifest), &
@@ -27,18 +29,13 @@ program fpm_testing
if (allocated(test_name)) then
write(error_unit, fmt) "Suite:", testsuite(is)%name
call run_selected(testsuite(is)%collect, test_name, error_unit, stat)
- if (stat == -1) then
+ if (stat < 0) then
error stop 1
end if
else
write(error_unit, fmt) "Testing:", testsuite(is)%name
call run_testsuite(testsuite(is)%collect, error_unit, stat)
end if
-
- if (stat > 0) then
- write(error_unit, '(i0, 1x, a)') stat, "test(s) failed!"
- error stop 1
- end if
else
write(error_unit, fmt) "Available testsuites"
do is = 1, size(testsuite)
@@ -50,14 +47,14 @@ program fpm_testing
do is = 1, size(testsuite)
write(error_unit, fmt) "Testing:", testsuite(is)%name
call run_testsuite(testsuite(is)%collect, error_unit, stat)
-
- if (stat > 0) then
- write(error_unit, '(i0, 1x, a)') stat, "test(s) failed!"
- error stop 1
- end if
end do
end if
+ if (stat > 0) then
+ write(error_unit, '(i0, 1x, a)') stat, "test(s) failed!"
+ error stop 1
+ end if
+
contains
diff --git a/fpm/test/testsuite.f90 b/fpm/test/testsuite.f90
index 4e46217..124d19a 100644
--- a/fpm/test/testsuite.f90
+++ b/fpm/test/testsuite.f90
@@ -78,13 +78,11 @@ contains
integer, intent(in) :: unit
!> Number of failed tests
- integer, intent(out) :: stat
+ integer, intent(inout) :: stat
type(unittest_t), allocatable :: testsuite(:)
integer :: ii
- stat = 0
-
call collect(testsuite)
do ii = 1, size(testsuite)
@@ -109,13 +107,11 @@ contains
integer, intent(in) :: unit
!> Number of failed tests
- integer, intent(out) :: stat
+ integer, intent(inout) :: stat
type(unittest_t), allocatable :: testsuite(:)
integer :: ii
- stat = 0
-
call collect(testsuite)
ii = select_test(testsuite, name)
@@ -127,7 +123,7 @@ contains
do ii = 1, size(testsuite)
write(unit, fmt) "-", testsuite(ii)%name
end do
- stat = -1
+ stat = -huge(ii)
end if
end subroutine run_selected