@@ -6,7 +6,7 @@ module numerical_testing_type
66implicit none  ; private 
77
88public  testing
9- public  testing_type_unit_test 
9+ public  numerical_testing_type_unit_tests 
1010
1111! > Class to assist in unit tests, not to be used outside of Recon1d types
1212type ::  testing
@@ -272,100 +272,136 @@ subroutine int_arr(this, n, i_test, i_true, label, ignore)
272272end  subroutine  int_arr 
273273
274274! > Tests the testing type itself
275- logical  function  testing_type_unit_test (verbose )
275+ logical  function  numerical_testing_type_unit_tests (verbose )
276276  logical , intent (in ) ::  verbose ! < If true, write results to stdout
277277  !  Local variables
278-   type (testing) ::  test !  The instance to be tested
278+   type (testing) ::  tester !  An instance to record tests
279+   type (testing) ::  test !  The instance used for testing (is mutable)
279280  logical  ::  tmpflag !  Temporary for return flags
280281
281-   testing_type_unit_test =  .false.  !  Assume all is well at the outset
282-   if  (verbose) write (test% stdout,* ) "   ===== testing_type: testing_type_unit_test ============" 
282+   numerical_testing_type_unit_tests =  .false.  !  Assume all is well at the outset
283+   if  (verbose) write (test% stdout,* ) "   ===== testing_type: numerical_testing_type_unit_tests =====" 
284+   call  tester% set( verbose= verbose ) !  Sets the verbosity flag in tester
283285
284286  call  test% set( verbose= verbose ) !  Sets the verbosity flag in test
285-   call  test% set( stderr= 0  ) !  Sets stderr
287+   call  test% set( stderr= 6  ) !  Sets stderr (redirect errors for "test" since they are not real) 
286288  call  test% set( stdout= 6  ) !  Sets stdout
287289  call  test% set( stop_instantly= .false.  ) !  Sets stop_instantly
288290  call  test% set( ignore_fail= .false.  ) !  Sets ignore_fail
289291
290-   call  test% test( .false. , " This should pass"   )
291-   if  (verbose .and.  .not.  test% state) then 
292-     write (test% stdout,* ) "    => test(F) passed" 
293-   else ; testing_type_unit_test =  testing_type_unit_test .or.  .true.  ; endif 
294- 
295-   call  test% test( .true. , " This should fail but be ignored"  , ignore= .true.  )
296-   if  (verbose .and.  .not.  test% state) then 
297-     write (test% stdout,* ) "    => test(T,ignore) passed" 
298-   else ; testing_type_unit_test =  testing_type_unit_test .or.  .true.  ; endif 
299- 
300-   call  test% real_scalar(1 ., 1 ., " s == s should pass"  , robits= 0 , tol= 0 .)
301-   if  (verbose .and.  .not.  test% state) then 
302-     write (test% stdout,* ) "    => real(s,s) passed" 
303-   else ; testing_type_unit_test =  testing_type_unit_test .or.  .true.  ; endif 
304- 
305-   call  test% real_scalar(1 ., 2 ., " s != t but ignored"  , ignore= .true. )
306-   if  (verbose .and.  .not.  test% state) then 
307-     write (test% stdout,* ) "    => real(s,t,ignore) passed" 
308-   else ; testing_type_unit_test =  testing_type_unit_test .or.  .true.  ; endif 
309- 
310-   call  test% real_arr(2 , (/ 1 .,2 ./ ), (/ 1 .,2 ./ ), " a == a should pass"  , robits= 0 , tol= 0 .)
311-   if  (verbose .and.  .not.  test% state) then 
312-     write (test% stdout,* ) "    => real(a,a) passed" 
313-   else ; testing_type_unit_test =  testing_type_unit_test .or.  .true.  ; endif 
314- 
315-   call  test% real_arr(2 , (/ 1 .,2 ./ ), (/ 3 .,4 ./ ), " a != b but ignored"  , ignore= .true. )
316-   if  (verbose .and.  .not.  test% state) then 
317-     write (test% stdout,* ) "    => real(a,b,ignore) passed" 
318-   else ; testing_type_unit_test =  testing_type_unit_test .or.  .true.  ; endif 
319- 
320-   call  test% int_arr(2 , (/ 1 ,2 / ), (/ 1 ,2 / ), " i == i should pass"  )
321-   if  (verbose .and.  .not.  test% state) then 
322-     write (test% stdout,* ) "    => int(a,a) passed" 
323-   else ; testing_type_unit_test =  testing_type_unit_test .or.  .true.  ; endif 
324- 
325-   call  test% int_arr(2 , (/ 1 ,2 / ), (/ 3 ,4 / ), " i != j but ignored"  , ignore= .true. )
326-   if  (verbose .and.  .not.  test% state) then 
327-     write (test% stdout,* ) "    => int(a,b,ignore) passed" 
328-   else ; testing_type_unit_test =  testing_type_unit_test .or.  .true.  ; endif 
329- 
330-   tmpflag =  test% summarize(" This summary is for a passing state"  )
331-   if  (verbose .and.  .not.  tmpflag) then 
332-     write (test% stdout,* ) "    => summarize(F) passed" 
333-   else ; testing_type_unit_test =  testing_type_unit_test .or.  .true.  ; endif 
334- 
335-   !  This following all fail
336-   test% state =  .false.  !  reset
337-   call  test% test( .true. , " This should fail"   )
338-   if  (verbose .and.  test% state) then 
339-     write (test% stdout,* ) "    => test(T) passed" 
340-   else ; testing_type_unit_test =  testing_type_unit_test .or.  .true.  ; endif 
292+   !  Check that %summary() reports nothing when %state is unset
293+   !  (note this has to be confirmed visually since everything is in stdout)
294+   tmpflag =  test% summarize(" Summary is for a passing state"  )
295+   call  tester% test(tmpflag, " test%summarize() with no fails"  )
296+ 
297+   !  Check that %test(.false.,...) leaves %state unchanged
298+   call  test% test( .false. , " test(F) should pass"   )
299+   call  tester% test(test% state, " test%test(F)"  )
300+ 
301+   !  Check that %test(.true.,...,ignore=.true.) leaves %state unchanged
302+   call  test% test( .true. , " test(T) should fail but be ignored"  , ignore= .true.  )
303+   call  tester% test(test% state, " test%test(T,ignore)"  )
341304
305+   !  Check that %test(.true.,...) sets %state
306+   call  test% test( .true. , " test(T) should fail"   )
307+   call  tester% test(.not.  test% state, " test%test(T,ignore)"  )
342308  test% state =  .false.  !  reset
309+ 
310+   !  Check that %real_scalar(a,a,...) leaves %state unchanged
311+   call  test% real_scalar(1 ., 1 ., " real_scalar(s,s) should pass"  , robits= 0 , tol= 0 .)
312+   call  tester% test(test% state, " test%real_scalar(s,s)"  )
313+ 
314+   !  Check that %real_scalar(a,b,...,ignore=.true.) leaves %state unchanged
315+   call  test% real_scalar(1 ., 2 ., " real_scalar(s,t) should fail but be ignored"  , ignore= .true. )
316+   call  tester% test(test% state, " test%real_scalar(s,t,ignore)"  )
317+ 
318+   !  Check that %real_scalar(a,a,...) sets %state
343319  call  test% real_scalar(1 ., 2 ., " s != t should fail"  )
344-   if  (verbose .and.  test% state) then 
345-     write (test% stdout,* ) "    => real(s,t) passed" 
346-   else ; testing_type_unit_test =  testing_type_unit_test .or.  .true.  ; endif 
320+   call  tester% test(.not.  test% state, " test%real_scalar(s,t)"  )
321+   test% state =  .false.  !  reset
322+ 
323+   !  Check that %real_arr(a,a,...) leaves %state unchanged
324+   call  test% real_arr(2 , (/ 1 .,2 ./ ), (/ 1 .,2 ./ ), " real_arr(a,a) should pass"  , robits= 0 , tol= 0 .)
325+   call  tester% test(test% state, " test%real_arr(a,a)"  )
347326
327+   !  Check that %real_arr(a,b,...,ignore=.true.) leaves %state unchanged
328+   call  test% real_arr(2 , (/ 1 .,2 ./ ), (/ 3 .,4 ./ ), " real_arr(a,b) should fail but be ignored"  , ignore= .true. )
329+   call  tester% test(test% state, " test%real_arr(a,b,ignore)"  )
330+ 
331+   !  Check that %real_arr(a,b,...) sets %state
332+   call  test% real_arr(2 , (/ 1 .,2 ./ ), (/ 3 .,4 ./ ), " real(a,b) should fail"  )
333+   call  tester% test(.not.  test% state, " test%real_arr(a,b)"  )
348334  test% state =  .false.  !  reset
349-   call  test% real_arr(2 , (/ 1 .,2 ./ ), (/ 3 .,4 ./ ), " a != b and should fail"  )
350-   if  (verbose .and.  test% state) then 
351-     write (test% stdout,* ) "    => real(a,b) passed" 
352-   else ; testing_type_unit_test =  testing_type_unit_test .or.  .true.  ; endif 
353335
336+   !  Check that %int_arr(a,a,...) leaves %state unchanged
337+   call  test% int_arr(2 , (/ 1 ,2 / ), (/ 1 ,2 / ), " int_arr(i,i) should pass"  )
338+   call  tester% test(test% state, " test%int_arr(i,i)"  )
339+ 
340+   !  Check that %int_arr(a,b,...,ignore=.true.) leaves %state unchanged
341+   call  test% int_arr(2 , (/ 1 ,2 / ), (/ 3 ,4 / ), " int_arr(i,j) should fail but be ignored"  , ignore= .true. )
342+   call  tester% test(test% state, " test%int_arr(i,j,ignore)"  )
343+ 
344+   !  Check that %int_arr(a,b,...) sets %state
345+   call  test% int_arr(2 , (/ 1 ,2 / ), (/ 3 ,4 / ), " int(arr(i,j) should fail"  )
346+   call  tester% test(.not.  test% state, " test%int_arr(i,j)"  )
354347  test% state =  .false.  !  reset
355-   call  test% int_arr(2 , (/ 1 ,2 / ), (/ 3 ,4 / ), " i != j and should fail"  )
356-   if  (verbose .and.  test% state) then 
357-     write (test% stdout,* ) "    => int(a,b) passed" 
358-   else ; testing_type_unit_test =  testing_type_unit_test .or.  .true.  ; endif 
359348
360-   tmpflag =  test% summarize(" This summary should have 3 fails"  )
361-   if  (verbose .and.  tmpflag) then 
362-     write (test% stdout,* ) "    => summarize(T) passed" 
363-   else ; testing_type_unit_test =  testing_type_unit_test .or.  .true.  ; endif 
349+   !  Check that %summary() reports nothing when %state is set
350+   !  (note this has to be confirmed visually since everything is in stdout)
351+   test% state =  .true.  !  reset to fail for testing %summary()
352+   tmpflag =  test% summarize(" This summary should report 4 fails"  )
353+   call  tester% test(.not.  tmpflag, " test%summarize() with fails"  )
364354
365-   if  (verbose  .and.   .not.  testing_type_unit_test)  write (test % stdout, * )  " testing_type_unit_test passed " 
355+   numerical_testing_type_unit_tests  =  tester % summarize( " numerical_testing_type_unit_tests " ) 
366356
367- end  function  testing_type_unit_test  
357+ end  function  numerical_testing_type_unit_tests  
368358
369359! > \namespace numerical_testing_type
370360! !
361+ ! ! numerical_testing_type is a helper class to facilitate implementing
362+ ! ! tests of a numerical nature.
363+ ! ! The class helps hide the logic and code associated with handling the
364+ ! ! results of a test, essentially reducing the multiple lines of `if
365+ ! ! ... then ... print ... else ... error_mesg ...` into one line.
366+ ! !
367+ ! ! The class is light weight, meaning is does not depend on anything else,
368+ ! ! allowing to be particularly useful in unit tests and small drivers.
369+ ! ! However, this means it is up to the user to do something with the results,
370+ ! ! e.g. `call MOM_error()` appropriately.
371+ ! !
372+ ! ! Each test, e.g. real_scalar(), is expected to pass.
373+ ! ! If a fail is encountered, it is immediately reported to stderr and stdour,
374+ ! ! recorded internally, but does not terminate execuation unless
375+ ! ! `set(stop_instantly=.true.)` was called previously.
376+ ! ! Most tests take the form of `f(a,b)` where `a` should equal `b`.
377+ ! ! Only test() takes a single input (boolean) which is expected to
378+ ! ! be false for the test to pass.
379+ ! !
380+ ! ! summarize() is used to "finalize" the tests.
381+ ! ! It prints a summary of how many and which tests faield, and returns a logical
382+ ! ! that is set to .true. if any test failed.
383+ ! !
384+ ! ! Usage by example:
385+ ! ! \verbatim
386+ ! ! use numerical_testing_type, only : testing
387+ ! ! ...
388+ ! !
389+ ! ! !> Runs my unit_tests. Returns .true. if a test fails, .false. otherwise
390+ ! ! logical function my_unit_tests(verbose)
391+ ! !   logical, intent(in) :: verbose !< If true, write results to stdout
392+ ! !   ...
393+ ! !   type(testing) :: test ! An instance of the numerical_testing_type
394+ ! !   ...
395+ ! !   call test%set( verbose=.true. ) ! Show intermediate results rather than just the fails
396+ ! !   ...
397+ ! !
398+ ! !   call test%test(flag, 'Flag is not set')               ! Check flag=.false.
399+ ! !   call test%real_scalar(a, 1., 'u = 1')                 ! Check a=1
400+ ! !   call test%real_arr(3, u, (/1.,2.,3./), 'u = [1,2,3]') ! Check u(:)=[1,2,3]
401+ ! !   call test%int_arr(2, iv, (/1,2/), 'iv = [1,2]')       ! Check that iv(:)=[1,2]
402+ ! !
403+ ! !   my_unit_tests = test%summarize('my_unit_tests') ! Return true if a fail occurs
404+ ! ! end function my_unit_tests(verbose)
405+ ! ! \endverbatim
406+ 
371407end module  numerical_testing_type
0 commit comments