use omp_lib
call test_master
call test_critical
call test_barrier
call test_atomic
contains
subroutine test_master
logical :: i, j
i = .false.
j = .false.
i = .true.
j = omp_get_thread_num () .eq. 0
if (.not. (i .or. j)) call abort
end subroutine test_master
subroutine test_critical_1 (i, j)
integer :: i, j
i = i + 1
j = j + 1
end subroutine test_critical_1
subroutine test_critical
integer :: i, j, n
n = -1
i = 0
j = 0
if (omp_get_thread_num () .eq. 0) n = omp_get_num_threads ()
call test_critical_1 (i, j)
call test_critical_1 (i, j)
j = j + 1
i = i + 1
if (n .lt. 1 .or. i .ne. n * 3 .or. j .ne. n * 3) call abort
end subroutine test_critical
subroutine test_barrier
integer :: i
logical :: j
i = 23
j = .false.
if (omp_get_thread_num () .eq. 0) i = 5
if (i .ne. 5) then
j = j .or. .true.
end if
if (i .ne. 5 .or. j) call abort
end subroutine test_barrier
subroutine test_atomic
integer :: a, b, c, d, e, f, g
a = 0
b = 1
c = 0
d = 1024
e = 1024
f = -1
g = -1
a = a + 2 + 4
b = 3 * b
c = 8 - c
d = d / 2
e = min (e, omp_get_thread_num ())
f = max (omp_get_thread_num (), f)
if (omp_get_thread_num () .eq. 0) g = omp_get_num_threads ()
if (g .le. 0 .or. g .gt. 8) call abort
if (a .ne. 6 * g .or. b .ne. 3 ** g) call abort
if (iand (g, 1) .eq. 1) then
if (c .ne. 8) call abort
else if (c .ne. 0) then
call abort
end if
if (d .ne. 1024 / (2 ** g)) call abort
if (e .ne. 0 .or. f .ne. g - 1) call abort
end subroutine test_atomic
end