xref: /openbsd-src/gnu/gcc/libgomp/testsuite/libgomp.fortran/appendix-a/a.28.5.f90 (revision 404b540a9034ac75a6199ad1a32d1bbc7a0d4210)
1*404b540aSrobert! { dg-do compile }
2*404b540aSrobert
3*404b540aSrobert      SUBROUTINE SUB1(X)
4*404b540aSrobert        DIMENSION X(10)
5*404b540aSrobert        ! This use of X does not conform to the
6*404b540aSrobert        ! specification. It would be legal Fortran 90,
7*404b540aSrobert        ! but the OpenMP private directive allows the
8*404b540aSrobert        ! compiler to break the sequence association that
9*404b540aSrobert        ! A had with the rest of the common block.
10*404b540aSrobert        FORALL (I = 1:10) X(I) = I
11*404b540aSrobert      END SUBROUTINE SUB1
12*404b540aSrobert      PROGRAM A28_5
13*404b540aSrobert        COMMON /BLOCK5/ A
14*404b540aSrobert        DIMENSION B(10)
15*404b540aSrobert        EQUIVALENCE (A,B(1))
16*404b540aSrobert        ! the common block has to be at least 10 words
17*404b540aSrobert        A=0
18*404b540aSrobert!$OMP PARALLEL PRIVATE(/BLOCK5/)
19*404b540aSrobert          ! Without the private clause,
20*404b540aSrobert          ! we would be passing a member of a sequence
21*404b540aSrobert          ! that is at least ten elements long.
22*404b540aSrobert          ! With the private clause, A may no longer be
23*404b540aSrobert          ! sequence-associated.
24*404b540aSrobert          CALL SUB1(A)
25*404b540aSrobert!$OMP MASTER
26*404b540aSrobert            PRINT *, A
27*404b540aSrobert!$OMP END MASTER
28*404b540aSrobert!$OMP END PARALLEL
29*404b540aSrobert      END PROGRAM A28_5
30