xref: /openbsd-src/gnu/gcc/libgomp/testsuite/libgomp.fortran/nestedfn1.f90 (revision 404b540a9034ac75a6199ad1a32d1bbc7a0d4210)
1*404b540aSrobert! { dg-do run }
2*404b540aSrobert
3*404b540aSrobert  integer :: a, b, c
4*404b540aSrobert  a = 1
5*404b540aSrobert  b = 2
6*404b540aSrobert  c = 3
7*404b540aSrobert  call foo
8*404b540aSrobert  if (a .ne. 7) call abort
9*404b540aSrobertcontains
10*404b540aSrobert  subroutine foo
11*404b540aSrobert    use omp_lib
12*404b540aSrobert    logical :: l
13*404b540aSrobert    l = .false.
14*404b540aSrobert!$omp parallel shared (a) private (b) firstprivate (c) &
15*404b540aSrobert!$omp num_threads (2) reduction (.or.:l)
16*404b540aSrobert    if (a .ne. 1 .or. c .ne. 3) l = .true.
17*404b540aSrobert!$omp barrier
18*404b540aSrobert    if (omp_get_thread_num () .eq. 0) then
19*404b540aSrobert      a = 4
20*404b540aSrobert      b = 5
21*404b540aSrobert      c = 6
22*404b540aSrobert    end if
23*404b540aSrobert!$omp barrier
24*404b540aSrobert    if (omp_get_thread_num () .eq. 1) then
25*404b540aSrobert      if (a .ne. 4 .or. c .ne. 3) l = .true.
26*404b540aSrobert      a = 7
27*404b540aSrobert      b = 8
28*404b540aSrobert      c = 9
29*404b540aSrobert    else if (omp_get_num_threads () .eq. 1) then
30*404b540aSrobert      a = 7
31*404b540aSrobert    end if
32*404b540aSrobert!$omp barrier
33*404b540aSrobert    if (omp_get_thread_num () .eq. 0) then
34*404b540aSrobert      if (a .ne. 7 .or. b .ne. 5 .or. c .ne. 6) l = .true.
35*404b540aSrobert    end if
36*404b540aSrobert!$omp barrier
37*404b540aSrobert    if (omp_get_thread_num () .eq. 1) then
38*404b540aSrobert      if (a .ne. 7 .or. b .ne. 8 .or. c .ne. 9) l = .true.
39*404b540aSrobert    end if
40*404b540aSrobert!$omp end parallel
41*404b540aSrobert    if (l) call abort
42*404b540aSrobert  end subroutine foo
43*404b540aSrobertend
44