Skip to content

Commit cc59dd7

Browse files
authored
Add OpenMP condition to serialize runtests on requests (#11)
1 parent 9c3401e commit cc59dd7

File tree

1 file changed

+10
-2
lines changed

1 file changed

+10
-2
lines changed

src/testdrive.F90

Lines changed: 10 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -311,7 +311,7 @@ end subroutine collect_interface
311311

312312

313313
!> Driver for testsuite
314-
recursive subroutine run_testsuite(collect, unit, stat)
314+
recursive subroutine run_testsuite(collect, unit, stat, parallel)
315315

316316
!> Collect tests
317317
procedure(collect_interface) :: collect
@@ -322,12 +322,20 @@ recursive subroutine run_testsuite(collect, unit, stat)
322322
!> Number of failed tests
323323
integer, intent(inout) :: stat
324324

325+
!> Run the tests in parallel
326+
logical, intent(in), optional :: parallel
327+
325328
type(unittest_type), allocatable :: testsuite(:)
326329
integer :: it
330+
logical :: parallel_
331+
332+
parallel_ = .true.
333+
if(present(parallel)) parallel_ = parallel
327334

328335
call collect(testsuite)
329336

330-
!$omp parallel do schedule(dynamic) shared(testsuite, unit) reduction(+:stat)
337+
!$omp parallel do schedule(dynamic) shared(testsuite, unit) reduction(+:stat) &
338+
!$ if (parallel_)
331339
do it = 1, size(testsuite)
332340
!$omp critical(testdrive_testsuite)
333341
write(unit, '(1x, 3(1x, a), 1x, "(", i0, "/", i0, ")")') &

0 commit comments

Comments
 (0)