@@ -114,6 +114,7 @@ module testdrive
114
114
public :: check, test_failed, skip_test
115
115
public :: test_interface, collect_interface
116
116
public :: get_argument, get_variable, to_string
117
+ public :: junit_output, junit_header
117
118
118
119
119
120
! > Single precision real numbers
@@ -304,14 +305,46 @@ end subroutine collect_interface
304
305
end type testsuite_type
305
306
306
307
308
+ ! > Output JUnit.xml for discovering unit tests by other tools
309
+ type :: junit_output
310
+ ! > XML output string (initial block)
311
+ character (len= :), allocatable :: xml_start
312
+ ! > XML output string (current block)
313
+ character (len= :), allocatable :: xml_block
314
+ ! > XML output string (final block)
315
+ character (len= :), allocatable :: xml_final
316
+ ! > Unique identifier
317
+ integer :: uid = 0
318
+ ! > Timestamp
319
+ character (len= 19 ) :: timestamp = ' 1970-01-01T00:00:00'
320
+ ! > Hostname
321
+ character (len= :), allocatable :: hostname
322
+ ! > Package name
323
+ character (len= :), allocatable :: package
324
+ ! > Testsuite name
325
+ character (len= :), allocatable :: testsuite
326
+ ! > Number of tests
327
+ integer :: tests = 0
328
+ ! > Number of failures
329
+ integer :: failures = 0
330
+ ! > Number of errors
331
+ integer :: errors = 0
332
+ ! > Number of skipped tests
333
+ integer :: skipped = 0
334
+ ! > Running time
335
+ real (sp) :: time = 0.0_sp
336
+ end type junit_output
337
+
338
+
307
339
character (len=* ), parameter :: fmt = ' (1x, *(1x, a))'
340
+ character (len=* ), parameter :: newline = new_line(" a" )
308
341
309
342
310
343
contains
311
344
312
345
313
346
! > Driver for testsuite
314
- recursive subroutine run_testsuite (collect , unit , stat , parallel )
347
+ recursive subroutine run_testsuite (collect , unit , stat , parallel , junit )
315
348
316
349
! > Collect tests
317
350
procedure (collect_interface) :: collect
@@ -325,6 +358,9 @@ recursive subroutine run_testsuite(collect, unit, stat, parallel)
325
358
! > Run the tests in parallel
326
359
logical , intent (in ), optional :: parallel
327
360
361
+ ! > Produce junit output
362
+ type (junit_output), intent (inout ), optional :: junit
363
+
328
364
type (unittest_type), allocatable :: testsuite(:)
329
365
integer :: it
330
366
logical :: parallel_
@@ -334,21 +370,25 @@ recursive subroutine run_testsuite(collect, unit, stat, parallel)
334
370
335
371
call collect(testsuite)
336
372
373
+ call junit_push_suite(junit, " testdrive" )
374
+
337
375
! $omp parallel do schedule(dynamic) shared(testsuite, unit) reduction(+:stat) &
338
376
! $omp if (parallel_)
339
377
do it = 1 , size (testsuite)
340
378
! $omp critical(testdrive_testsuite)
341
379
write (unit, ' (1x, 3(1x, a), 1x, "(", i0, "/", i0, ")")' ) &
342
380
& " Starting" , testsuite(it)% name, " ..." , it, size (testsuite)
343
381
! $omp end critical(testdrive_testsuite)
344
- call run_unittest(testsuite(it), unit, stat)
382
+ call run_unittest(testsuite(it), unit, stat, junit )
345
383
end do
346
384
385
+ call junit_pop_suite(junit)
386
+
347
387
end subroutine run_testsuite
348
388
349
389
350
390
! > Driver for selective testing
351
- recursive subroutine run_selected (collect , name , unit , stat )
391
+ recursive subroutine run_selected (collect , name , unit , stat , junit )
352
392
353
393
! > Collect tests
354
394
procedure (collect_interface) :: collect
@@ -362,15 +402,20 @@ recursive subroutine run_selected(collect, name, unit, stat)
362
402
! > Number of failed tests
363
403
integer , intent (inout ) :: stat
364
404
405
+ ! > Produce junit output
406
+ type (junit_output), intent (inout ), optional :: junit
407
+
365
408
type (unittest_type), allocatable :: testsuite(:)
366
409
integer :: it
367
410
368
411
call collect(testsuite)
369
412
413
+ call junit_push_suite(junit, " testdrive" )
414
+
370
415
it = select_test(testsuite, name)
371
416
372
417
if (it > 0 .and. it <= size (testsuite)) then
373
- call run_unittest(testsuite(it), unit, stat)
418
+ call run_unittest(testsuite(it), unit, stat, junit )
374
419
else
375
420
write (unit, fmt) " Available tests:"
376
421
do it = 1 , size (testsuite)
@@ -379,11 +424,13 @@ recursive subroutine run_selected(collect, name, unit, stat)
379
424
stat = - huge (it)
380
425
end if
381
426
427
+ call junit_pop_suite(junit)
428
+
382
429
end subroutine run_selected
383
430
384
431
385
432
! > Run a selected unit test
386
- recursive subroutine run_unittest (test , unit , stat )
433
+ recursive subroutine run_unittest (test , unit , stat , junit )
387
434
388
435
! > Unit test
389
436
type (unittest_type), intent (in ) :: test
@@ -394,13 +441,17 @@ recursive subroutine run_unittest(test, unit, stat)
394
441
! > Number of failed tests
395
442
integer , intent (inout ) :: stat
396
443
444
+ ! > Produce junit output
445
+ type (junit_output), intent (inout ), optional :: junit
446
+
397
447
type (error_type), allocatable :: error
398
448
character (len= :), allocatable :: message
399
449
400
450
call test% test(error)
401
451
if (.not. test_skipped(error)) then
402
452
if (allocated (error) .neqv. test% should_fail) stat = stat + 1
403
453
end if
454
+ call junit_push_test(junit, test, error, 0.0_sp )
404
455
call make_output(message, test, error)
405
456
! $omp critical(testdrive_testsuite)
406
457
write (unit, ' (a)' ) message
@@ -445,7 +496,7 @@ pure subroutine make_output(output, test, error)
445
496
446
497
if (test_skipped(error)) then
447
498
output = indent // test% name // " [SKIPPED]" &
448
- & // new_line( " a " ) // " Message: " // error% message
499
+ & // newline // " Message: " // error% message
449
500
return
450
501
end if
451
502
@@ -464,11 +515,205 @@ pure subroutine make_output(output, test, error)
464
515
end if
465
516
output = indent // test% name // label
466
517
if (present (error)) then
467
- output = output // new_line( " a " ) // " Message: " // error% message
518
+ output = output // newline // " Message: " // error% message
468
519
end if
469
520
end subroutine make_output
470
521
471
522
523
+ ! > Initialize output for JUnit.xml
524
+ pure subroutine junit_header (junit , package )
525
+
526
+ ! > JUnit output
527
+ type (junit_output), intent (inout ), optional :: junit
528
+
529
+ ! > Package name
530
+ character (len=* ), intent (in ) :: package
531
+
532
+ if (.not. present (junit)) return
533
+
534
+ junit% xml_start = &
535
+ & ' <?xml version="1.0" encoding="UTF-8"?>' // newline // &
536
+ & ' <testsuites' // newline // &
537
+ & ' xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance"' // newline // &
538
+ & ' xsi:noNamespaceSchemaLocation="JUnit.xsd"' // newline // &
539
+ & ' >' // newline
540
+ junit% xml_block = ' '
541
+ junit% xml_final = &
542
+ & ' </testsuites>'
543
+
544
+ junit% hostname = ' localhost'
545
+ junit% package = package
546
+
547
+ end subroutine junit_header
548
+
549
+ ! > Register a test suite in JUnit.xml
550
+ subroutine junit_push_suite (junit , name )
551
+
552
+ ! > JUnit output
553
+ type (junit_output), intent (inout ), optional :: junit
554
+
555
+ ! > Name of the test suite
556
+ character (len=* ), intent (in ) :: name
557
+
558
+ if (.not. present (junit)) return
559
+
560
+ junit% timestamp = get_timestamp()
561
+ junit% testsuite = name
562
+ junit% uid = junit% uid + 1
563
+
564
+ end subroutine junit_push_suite
565
+
566
+ ! > Finalize a test suite in JUnit.xml
567
+ subroutine junit_pop_suite (junit )
568
+
569
+ ! > JUnit output
570
+ type (junit_output), intent (inout ), optional :: junit
571
+
572
+ if (.not. present (junit)) return
573
+
574
+ junit% xml_start = &
575
+ & junit% xml_start // &
576
+ & ' <testsuite' // newline // &
577
+ & ' name="' // junit% testsuite// ' "' // newline // &
578
+ & ' package="' // junit% package// ' "' // newline // &
579
+ & ' id="' // to_string(junit% uid)// ' "' // newline // &
580
+ & ' timestamp="' // junit% timestamp// ' "' // newline // &
581
+ & ' hostname="' // junit% hostname// ' "' // newline // &
582
+ & ' tests="' // to_string(junit% tests)// ' "' // newline // &
583
+ & ' failures="' // to_string(junit% failures)// ' "' // newline // &
584
+ & ' errors="' // to_string(junit% errors)// ' "' // newline // &
585
+ & ' skipped="' // to_string(junit% skipped)// ' "' // newline // &
586
+ & ' time="' // to_string(junit% time)// ' "' // newline // &
587
+ & ' >' // newline // &
588
+ & ' <properties>' // newline // &
589
+ & ' </properties>' // newline // &
590
+ & junit% xml_block // newline // &
591
+ & ' </testsuite>' // newline
592
+
593
+ junit% xml_block = ' '
594
+ junit% tests = 0
595
+ junit% failures = 0
596
+ junit% errors = 0
597
+ junit% skipped = 0
598
+ junit% time = 0.0_sp
599
+
600
+ call junit_write(junit)
601
+
602
+ end subroutine junit_pop_suite
603
+
604
+ ! > Register a new unit test
605
+ pure subroutine junit_push_test (junit , test , error , time )
606
+
607
+ ! > JUnit output
608
+ type (junit_output), intent (inout ), optional :: junit
609
+
610
+ ! > Unit test
611
+ type (unittest_type), intent (in ) :: test
612
+
613
+ ! > Error handling
614
+ type (error_type), intent (in ), optional :: error
615
+
616
+ ! > Running time
617
+ real (sp), intent (in ) :: time
618
+
619
+ if (.not. present (junit)) return
620
+
621
+ ! $omp critical(testdrive_junit)
622
+ junit% tests = junit% tests + 1
623
+ junit% time = junit% time + time
624
+
625
+ junit% xml_block = &
626
+ & junit% xml_block // &
627
+ & ' <testcase' // newline // &
628
+ & ' name="' // test% name// ' "' // newline // &
629
+ & ' classname="' // junit% testsuite// ' "' // newline // &
630
+ & ' time="' // to_string(time)// ' "' // newline // &
631
+ & ' >' // newline
632
+
633
+ if (test_skipped(error)) then
634
+ junit% xml_block = &
635
+ & junit% xml_block // &
636
+ & ' <skipped/>' // newline
637
+ junit% skipped = junit% skipped + 1
638
+ elseif (present (error)) then
639
+ if (test% should_fail) then
640
+ junit% xml_block = &
641
+ & junit% xml_block // &
642
+ & ' <system-out>' // newline // &
643
+ & ' "' // error% message// ' "' // newline // &
644
+ & ' </system-out>' // newline
645
+ else
646
+ junit% xml_block = &
647
+ & junit% xml_block // &
648
+ & ' <failure' // newline // &
649
+ & ' message="' // error% message// ' "' // newline // &
650
+ & ' type="AssertionError"' // newline // &
651
+ & ' />' // newline
652
+ junit% failures = junit% failures + 1
653
+ end if
654
+ else
655
+ if (test% should_fail) then
656
+ junit% xml_block = &
657
+ & junit% xml_block // &
658
+ & ' <failure' // newline // &
659
+ & ' message="Unexpected pass"' // newline // &
660
+ & ' type="AssertionError"' // newline // &
661
+ & ' />' // newline
662
+ junit% failures = junit% failures + 1
663
+ else
664
+ junit% xml_block = &
665
+ & junit% xml_block // &
666
+ & ' <system-out>' // newline // &
667
+ & ' "Test passed successfully"' // newline // &
668
+ & ' </system-out>' // newline
669
+ end if
670
+ end if
671
+
672
+ junit% xml_block = &
673
+ & junit% xml_block // &
674
+ & ' </testcase>' // newline
675
+ ! $omp end critical(testdrive_junit)
676
+
677
+ end subroutine junit_push_test
678
+
679
+
680
+ ! > Write results to JUnit.xml
681
+ subroutine junit_write (junit )
682
+
683
+ ! > JUnit output
684
+ type (junit_output), intent (inout ), optional :: junit
685
+
686
+ integer :: io
687
+
688
+ if (.not. present (junit)) return
689
+ open ( &
690
+ & newunit= io, &
691
+ & file= ' JUnit' // junit% package// ' .xml' , &
692
+ & status= ' replace' , &
693
+ & action= ' write' )
694
+ write (io, ' (a)' ) junit% xml_start // junit% xml_final
695
+ close (io)
696
+
697
+ end subroutine junit_write
698
+
699
+
700
+ ! > Create ISO 8601 formatted timestamp
701
+ function get_timestamp () result(timestamp)
702
+
703
+ ! > ISO 8601 formatted timestamp
704
+ character (len= 19 ) :: timestamp
705
+
706
+ character (len= 8 ) :: date
707
+ character (len= 10 ) :: time
708
+
709
+ call date_and_time (date= date, time= time)
710
+
711
+ timestamp = date(1 :4 ) // " -" // date(5 :6 ) // " -" // date(7 :8 ) // " T" // &
712
+ & time(1 :2 ) // " :" // time(3 :4 ) // " :" // time(5 :6 )
713
+
714
+ end function get_timestamp
715
+
716
+
472
717
! > Select a unit test from all available tests
473
718
function select_test (tests , name ) result(pos)
474
719
@@ -1577,7 +1822,7 @@ subroutine test_failed(error, message, more, and_more)
1577
1822
! > Another line of error message
1578
1823
character (len=* ), intent (in ), optional :: and_more
1579
1824
1580
- character (len=* ), parameter :: skip = new_line( " a " ) // repeat (" " , 11 )
1825
+ character (len=* ), parameter :: skip = newline // repeat (" " , 11 )
1581
1826
1582
1827
allocate (error)
1583
1828
error% stat = fatal
0 commit comments