Skip to content
Draft
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 2 additions & 0 deletions test/main.f90
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,7 @@
!> Driver for unit testing
program tester
use, intrinsic :: iso_fortran_env, only : error_unit
use, intrinsic :: ieee_arithmetic, only: ieee_quiet_nan
use testdrive, only : run_testsuite, new_testsuite, testsuite_type, &
& select_suite, run_selected, get_argument, junit_output, junit_header, &
& init_color_output
Expand All @@ -29,6 +30,7 @@ program tester
stat = 0
call junit_header(junit, "testdrive")

allocate(testsuites(2))
testsuites = [ &
new_testsuite("check", collect_check), &
new_testsuite("select", collect_select) &
Expand Down
3 changes: 2 additions & 1 deletion test/test_check.F90
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@
#endif

module test_check
use, intrinsic :: ieee_arithmetic, only : ieee_value, ieee_quiet_nan
use, intrinsic :: ieee_arithmetic, only : ieee_value, ieee_quiet_nan
use testdrive, only : new_unittest, unittest_type, error_type, check, skip_test, to_string
implicit none
private
Expand Down Expand Up @@ -67,6 +67,7 @@ subroutine collect_check(testsuite)
!> Collection of tests
type(unittest_type), allocatable, intent(out) :: testsuite(:)

allocate(testsuite(95))
testsuite = [ &
new_unittest("success", test_success), &
new_unittest("failure", test_failure, should_fail=.true.), &
Expand Down
4 changes: 4 additions & 0 deletions test/test_select.F90
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,7 @@ subroutine collect_select(testsuite)

!> Collection of tests
type(unittest_type), allocatable, intent(out) :: testsuite(:)
allocate(testsuite(6))

testsuite = [ &
new_unittest("always-pass", always_pass), &
Expand Down Expand Up @@ -68,6 +69,8 @@ subroutine stub_collect(testsuite)
!> Collection of tests
type(unittest_type), allocatable, intent(out) :: testsuite(:)

allocate(testsuite(2))

testsuite = [ &
new_unittest("always-pass", always_pass), &
new_unittest("always-fail", always_fail, should_fail=.true.) &
Expand All @@ -81,6 +84,7 @@ subroutine stub_collect_bad(testsuite)

!> Collection of tests
type(unittest_type), allocatable, intent(out) :: testsuite(:)
allocate(testsuite(2))

testsuite = [ &
new_unittest("always-pass", always_pass, should_fail=.true.), &
Expand Down