diff libgomp/testsuite/libgomp.fortran/appendix-a/a.28.5.f90 @ 0:a06113de4d67

first commit
author kent <kent@cr.ie.u-ryukyu.ac.jp>
date Fri, 17 Jul 2009 14:47:48 +0900
parents
children f6334be47118
line wrap: on
line diff
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/libgomp/testsuite/libgomp.fortran/appendix-a/a.28.5.f90	Fri Jul 17 14:47:48 2009 +0900
@@ -0,0 +1,29 @@
+! { dg-do compile }
+
+      SUBROUTINE SUB1(X)
+        DIMENSION X(10)
+        ! This use of X does not conform to the
+        ! specification. It would be legal Fortran 90,
+        ! but the OpenMP private directive allows the
+        ! compiler to break the sequence association that
+        ! A had with the rest of the common block.
+        FORALL (I = 1:10) X(I) = I
+      END SUBROUTINE SUB1
+      PROGRAM A28_5
+        COMMON /BLOCK5/ A
+        DIMENSION B(10)
+        EQUIVALENCE (A,B(1))
+        ! the common block has to be at least 10 words
+        A=0
+!$OMP PARALLEL PRIVATE(/BLOCK5/)
+          ! Without the private clause,
+          ! we would be passing a member of a sequence
+          ! that is at least ten elements long.
+          ! With the private clause, A may no longer be
+          ! sequence-associated.
+          CALL SUB1(A)
+!$OMP MASTER
+            PRINT *, A
+!$OMP END MASTER
+!$OMP END PARALLEL
+      END PROGRAM A28_5