@@ -4,9 +4,10 @@ module testsuite
4
4
implicit none
5
5
private
6
6
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
8
9
public :: check_string
9
- public :: unittest_t, error_t
10
+ public :: unittest_t, testsuite_t, error_t
10
11
11
12
12
13
abstract interface
@@ -48,6 +49,22 @@ end subroutine collect_interface
48
49
end interface
49
50
50
51
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
+
51
68
contains
52
69
53
70
@@ -61,42 +78,141 @@ subroutine run_testsuite(collect, unit, stat)
61
78
integer , intent (in ) :: unit
62
79
63
80
! > Number of failed tests
64
- integer , intent (out ) :: stat
81
+ integer , intent (inout ) :: stat
65
82
66
83
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
70
84
integer :: ii
71
85
72
- stat = 0
73
-
74
86
call collect(testsuite)
75
87
76
88
do ii = 1 , size (testsuite)
77
89
write (unit, ' ("#", 3(1x, a), 1x, "(", i0, "/", i0, ")")' ) &
78
90
& " 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]"
87
150
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]"
93
152
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
96
187
end if
97
188
end do
98
189
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
100
216
101
217
102
218
! > Register a new unit test
@@ -121,6 +237,24 @@ function new_unittest(name, test, should_fail) result(self)
121
237
end function new_unittest
122
238
123
239
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
+
124
258
! > Check a deferred length character variable against a reference value
125
259
subroutine check_string (error , actual , expected , name )
126
260
0 commit comments