Skip to content

Commit e79b47e

Browse files
authored
Merge pull request #177 from awvwgk/selective-testing
Allow selective testing of single suites and tests
2 parents 898a4ef + e969f5e commit e79b47e

File tree

2 files changed

+234
-42
lines changed

2 files changed

+234
-42
lines changed

fpm/test/main.f90

Lines changed: 76 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -1,36 +1,94 @@
11
!> Driver for unit testing
22
program fpm_testing
33
use, intrinsic :: iso_fortran_env, only : error_unit
4-
use testsuite, only : run_testsuite
4+
use testsuite, only : run_testsuite, new_testsuite, testsuite_t, &
5+
& select_suite, run_selected
56
use test_toml, only : collect_toml
67
use test_manifest, only : collect_manifest
78
use test_source_parsing, only : collect_source_parsing
89
implicit none
9-
integer :: stat
10+
integer :: stat, is
11+
character(len=:), allocatable :: suite_name, test_name
12+
type(testsuite_t), allocatable :: testsuite(:)
1013
character(len=*), parameter :: fmt = '("#", *(1x, a))'
1114

12-
write(error_unit, fmt) "Testing:", "fpm_toml"
13-
call run_testsuite(collect_toml, error_unit, stat)
15+
stat = 0
1416

15-
if (stat > 0) then
16-
write(error_unit, '(i0, 1x, a)') stat, "tests failed!"
17-
error stop 1
18-
end if
17+
testsuite = [ &
18+
& new_testsuite("fpm_toml", collect_toml), &
19+
& new_testsuite("fpm_manifest", collect_manifest), &
20+
& new_testsuite("fpm_source_parsing", collect_source_parsing) &
21+
& ]
1922

20-
write(error_unit, fmt) "Testing:", "fpm_manifest"
21-
call run_testsuite(collect_manifest, error_unit, stat)
23+
call get_argument(1, suite_name)
24+
call get_argument(2, test_name)
2225

23-
if (stat > 0) then
24-
write(error_unit, '(i0, 1x, a)') stat, "tests failed!"
25-
error stop 1
26+
if (allocated(suite_name)) then
27+
is = select_suite(testsuite, suite_name)
28+
if (is > 0 .and. is <= size(testsuite)) then
29+
if (allocated(test_name)) then
30+
write(error_unit, fmt) "Suite:", testsuite(is)%name
31+
call run_selected(testsuite(is)%collect, test_name, error_unit, stat)
32+
if (stat < 0) then
33+
error stop 1
34+
end if
35+
else
36+
write(error_unit, fmt) "Testing:", testsuite(is)%name
37+
call run_testsuite(testsuite(is)%collect, error_unit, stat)
38+
end if
39+
else
40+
write(error_unit, fmt) "Available testsuites"
41+
do is = 1, size(testsuite)
42+
write(error_unit, fmt) "-", testsuite(is)%name
43+
end do
44+
error stop 1
45+
end if
46+
else
47+
do is = 1, size(testsuite)
48+
write(error_unit, fmt) "Testing:", testsuite(is)%name
49+
call run_testsuite(testsuite(is)%collect, error_unit, stat)
50+
end do
2651
end if
2752

28-
write(error_unit, fmt) "Testing:", "fpm_sources (parsing)"
29-
call run_testsuite(collect_source_parsing, error_unit, stat)
30-
3153
if (stat > 0) then
32-
write(error_unit, '(i0, 1x, a)') stat, "tests failed!"
33-
error stop 1
54+
write(error_unit, '(i0, 1x, a)') stat, "test(s) failed!"
55+
error stop 1
3456
end if
3557

58+
59+
contains
60+
61+
62+
!> Obtain the command line argument at a given index
63+
subroutine get_argument(idx, arg)
64+
65+
!> Index of command line argument, range [0:command_argument_count()]
66+
integer, intent(in) :: idx
67+
68+
!> Command line argument
69+
character(len=:), allocatable, intent(out) :: arg
70+
71+
integer :: length, stat
72+
73+
call get_command_argument(idx, length=length, status=stat)
74+
if (stat /= 0) then
75+
return
76+
endif
77+
78+
allocate(character(len=length) :: arg, stat=stat)
79+
if (stat /= 0) then
80+
return
81+
endif
82+
83+
if (length > 0) then
84+
call get_command_argument(idx, arg, status=stat)
85+
if (stat /= 0) then
86+
deallocate(arg)
87+
return
88+
end if
89+
end if
90+
91+
end subroutine get_argument
92+
93+
3694
end program fpm_testing

fpm/test/testsuite.f90

Lines changed: 158 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -4,9 +4,10 @@ module testsuite
44
implicit none
55
private
66

7-
public :: run_testsuite, new_unittest, test_failed
7+
public :: run_testsuite, run_selected, new_unittest, new_testsuite, test_failed
8+
public :: select_test, select_suite
89
public :: check_string
9-
public :: unittest_t, error_t
10+
public :: unittest_t, testsuite_t, error_t
1011

1112

1213
abstract interface
@@ -48,6 +49,22 @@ end subroutine collect_interface
4849
end interface
4950

5051

52+
!> Collection of unit tests
53+
type :: testsuite_t
54+
55+
!> Name of the testsuite
56+
character(len=:), allocatable :: name
57+
58+
!> Entry point of the test
59+
procedure(collect_interface), pointer, nopass :: collect => null()
60+
61+
end type testsuite_t
62+
63+
64+
character(len=*), parameter :: fmt = '("#", *(1x, a))'
65+
character(len=*), parameter :: indent = repeat(" ", 5) // repeat(".", 3)
66+
67+
5168
contains
5269

5370

@@ -61,42 +78,141 @@ subroutine run_testsuite(collect, unit, stat)
6178
integer, intent(in) :: unit
6279

6380
!> Number of failed tests
64-
integer, intent(out) :: stat
81+
integer, intent(inout) :: stat
6582

6683
type(unittest_t), allocatable :: testsuite(:)
67-
character(len=*), parameter :: fmt = '("#", *(1x, a))'
68-
character(len=*), parameter :: indent = repeat(" ", 5) // repeat(".", 3)
69-
type(error_t), allocatable :: error
7084
integer :: ii
7185

72-
stat = 0
73-
7486
call collect(testsuite)
7587

7688
do ii = 1, size(testsuite)
7789
write(unit, '("#", 3(1x, a), 1x, "(", i0, "/", i0, ")")') &
7890
& "Starting", testsuite(ii)%name, "...", ii, size(testsuite)
79-
call testsuite(ii)%test(error)
80-
if (allocated(error) .neqv. testsuite(ii)%should_fail) then
81-
if (testsuite(ii)%should_fail) then
82-
write(unit, fmt) indent, testsuite(ii)%name, "[UNEXPECTED PASS]"
83-
else
84-
write(unit, fmt) indent, testsuite(ii)%name, "[FAILED]"
85-
end if
86-
stat = stat + 1
91+
call run_unittest(testsuite(ii), unit, stat)
92+
end do
93+
94+
end subroutine run_testsuite
95+
96+
97+
!> Driver for selective testing
98+
subroutine run_selected(collect, name, unit, stat)
99+
100+
!> Collect tests
101+
procedure(collect_interface) :: collect
102+
103+
!> Name of the selected test
104+
character(len=*), intent(in) :: name
105+
106+
!> Unit for IO
107+
integer, intent(in) :: unit
108+
109+
!> Number of failed tests
110+
integer, intent(inout) :: stat
111+
112+
type(unittest_t), allocatable :: testsuite(:)
113+
integer :: ii
114+
115+
call collect(testsuite)
116+
117+
ii = select_test(testsuite, name)
118+
119+
if (ii > 0 .and. ii <= size(testsuite)) then
120+
call run_unittest(testsuite(ii), unit, stat)
121+
else
122+
write(unit, fmt) "Available tests:"
123+
do ii = 1, size(testsuite)
124+
write(unit, fmt) "-", testsuite(ii)%name
125+
end do
126+
stat = -huge(ii)
127+
end if
128+
129+
end subroutine run_selected
130+
131+
132+
!> Run a selected unit test
133+
subroutine run_unittest(test, unit, stat)
134+
135+
!> Unit test
136+
type(unittest_t), intent(in) :: test
137+
138+
!> Unit for IO
139+
integer, intent(in) :: unit
140+
141+
!> Number of failed tests
142+
integer, intent(inout) :: stat
143+
144+
type(error_t), allocatable :: error
145+
146+
call test%test(error)
147+
if (allocated(error) .neqv. test%should_fail) then
148+
if (test%should_fail) then
149+
write(unit, fmt) indent, test%name, "[UNEXPECTED PASS]"
87150
else
88-
if (testsuite(ii)%should_fail) then
89-
write(unit, fmt) indent, testsuite(ii)%name, "[EXPECTED FAIL]"
90-
else
91-
write(unit, fmt) indent, testsuite(ii)%name, "[PASSED]"
92-
end if
151+
write(unit, fmt) indent, test%name, "[FAILED]"
93152
end if
94-
if (allocated(error)) then
95-
write(unit, fmt) "Message:", error%message
153+
stat = stat + 1
154+
else
155+
if (test%should_fail) then
156+
write(unit, fmt) indent, test%name, "[EXPECTED FAIL]"
157+
else
158+
write(unit, fmt) indent, test%name, "[PASSED]"
159+
end if
160+
end if
161+
if (allocated(error)) then
162+
write(unit, fmt) "Message:", error%message
163+
end if
164+
165+
end subroutine run_unittest
166+
167+
168+
!> Select a unit test from all available tests
169+
function select_test(tests, name) result(pos)
170+
171+
!> Name identifying the test suite
172+
character(len=*), intent(in) :: name
173+
174+
!> Available unit tests
175+
type(unittest_t) :: tests(:)
176+
177+
!> Selected test suite
178+
integer :: pos
179+
180+
integer :: it
181+
182+
pos = 0
183+
do it = 1, size(tests)
184+
if (name == tests(it)%name) then
185+
pos = it
186+
exit
96187
end if
97188
end do
98189

99-
end subroutine run_testsuite
190+
end function select_test
191+
192+
193+
!> Select a test suite from all available suites
194+
function select_suite(suites, name) result(pos)
195+
196+
!> Name identifying the test suite
197+
character(len=*), intent(in) :: name
198+
199+
!> Available test suites
200+
type(testsuite_t) :: suites(:)
201+
202+
!> Selected test suite
203+
integer :: pos
204+
205+
integer :: it
206+
207+
pos = 0
208+
do it = 1, size(suites)
209+
if (name == suites(it)%name) then
210+
pos = it
211+
exit
212+
end if
213+
end do
214+
215+
end function select_suite
100216

101217

102218
!> Register a new unit test
@@ -121,6 +237,24 @@ function new_unittest(name, test, should_fail) result(self)
121237
end function new_unittest
122238

123239

240+
!> Register a new testsuite
241+
function new_testsuite(name, collect) result(self)
242+
243+
!> Name of the testsuite
244+
character(len=*), intent(in) :: name
245+
246+
!> Entry point to collect tests
247+
procedure(collect_interface) :: collect
248+
249+
!> Newly registered testsuite
250+
type(testsuite_t) :: self
251+
252+
self%name = name
253+
self%collect => collect
254+
255+
end function new_testsuite
256+
257+
124258
!> Check a deferred length character variable against a reference value
125259
subroutine check_string(error, actual, expected, name)
126260

0 commit comments

Comments
 (0)