diff options
author | upstream source tree <ports@midipix.org> | 2015-03-15 20:14:05 -0400 |
---|---|---|
committer | upstream source tree <ports@midipix.org> | 2015-03-15 20:14:05 -0400 |
commit | 554fd8c5195424bdbcabf5de30fdc183aba391bd (patch) | |
tree | 976dc5ab7fddf506dadce60ae936f43f58787092 /gcc/testsuite/gfortran.dg/gomp | |
download | cbb-gcc-4.6.4-554fd8c5195424bdbcabf5de30fdc183aba391bd.tar.bz2 cbb-gcc-4.6.4-554fd8c5195424bdbcabf5de30fdc183aba391bd.tar.xz |
obtained gcc-4.6.4.tar.bz2 from upstream website;upstream
verified gcc-4.6.4.tar.bz2.sig;
imported gcc-4.6.4 source tree from verified upstream tarball.
downloading a git-generated archive based on the 'upstream' tag
should provide you with a source tree that is binary identical
to the one extracted from the above tarball.
if you have obtained the source via the command 'git clone',
however, do note that line-endings of files in your working
directory might differ from line-endings of the respective
files in the upstream repository.
Diffstat (limited to 'gcc/testsuite/gfortran.dg/gomp')
109 files changed, 2613 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/gomp/allocatable_components_1.f90 b/gcc/testsuite/gfortran.dg/gomp/allocatable_components_1.f90 new file mode 100644 index 000000000..225d0a2b5 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/allocatable_components_1.f90 @@ -0,0 +1,59 @@ +! { dg-do compile } +! +! PR fortran/32467 +! Derived types with allocatable components +! + +MODULE test_allocatable_components + type :: t + integer, allocatable :: a(:) + end type + +CONTAINS + SUBROUTINE test_copyin() + TYPE(t), SAVE :: a + + !$omp threadprivate(a) + !$omp parallel copyin(a) ! { dg-error "has ALLOCATABLE components" } + ! do something + !$omp end parallel + END SUBROUTINE + + SUBROUTINE test_copyprivate() + TYPE(t) :: a + + !$omp single ! { dg-error "has ALLOCATABLE components" } + ! do something + !$omp end single copyprivate (a) + END SUBROUTINE + + SUBROUTINE test_firstprivate + TYPE(t) :: a + + !$omp parallel firstprivate(a) ! { dg-error "has ALLOCATABLE components" } + ! do something + !$omp end parallel + END SUBROUTINE + + SUBROUTINE test_lastprivate + TYPE(t) :: a + INTEGER :: i + + !$omp parallel do lastprivate(a) ! { dg-error "has ALLOCATABLE components" } + DO i = 1, 1 + END DO + !$omp end parallel do + END SUBROUTINE + + SUBROUTINE test_reduction + TYPE(t) :: a(10) + INTEGER :: i + + !$omp parallel do reduction(+: a) ! { dg-error "must be of numeric type" } + DO i = 1, SIZE(a) + END DO + !$omp end parallel do + END SUBROUTINE +END MODULE + +! { dg-final { cleanup-modules "test_allocatable_components" } } diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.1.1.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.1.1.f90 new file mode 100644 index 000000000..fd83131b5 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.1.1.f90 @@ -0,0 +1,10 @@ +! { dg-do compile } + SUBROUTINE A1(N, A, B) + INTEGER I, N + REAL B(N), A(N) +!$OMP PARALLEL DO !I is private by default + DO I=2,N + B(I) = (A(I) + A(I-1)) / 2.0 + ENDDO +!$OMP END PARALLEL DO + END SUBROUTINE A1 diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.11.1.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.11.1.f90 new file mode 100644 index 000000000..eb8455e19 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.11.1.f90 @@ -0,0 +1,12 @@ +! { dg-do compile } + SUBROUTINE A11_1(AA, BB, CC, DD, EE, FF, N) + INTEGER N + REAL AA(N,N), BB(N,N), CC(N,N), DD(N,N), EE(N,N), FF(N,N) +!$OMP PARALLEL +!$OMP WORKSHARE + AA = BB + CC = DD + EE = FF +!$OMP END WORKSHARE +!$OMP END PARALLEL + END SUBROUTINE A11_1 diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.11.2.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.11.2.f90 new file mode 100644 index 000000000..11fdc1caa --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.11.2.f90 @@ -0,0 +1,16 @@ +! { do-do compile } + + SUBROUTINE A11_2(AA, BB, CC, DD, EE, FF, N) + INTEGER N + REAL AA(N,N), BB(N,N), CC(N,N) + REAL DD(N,N), EE(N,N), FF(N,N) +!$OMP PARALLEL +!$OMP WORKSHARE + AA = BB + CC = DD +!$OMP END WORKSHARE NOWAIT +!$OMP WORKSHARE + EE = FF +!$OMP END WORKSHARE +!$OMP END PARALLEL + END SUBROUTINE A11_2 diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.11.3.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.11.3.f90 new file mode 100644 index 000000000..b87232f9c --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.11.3.f90 @@ -0,0 +1,15 @@ +! { dg-do compile } + SUBROUTINE A11_3(AA, BB, CC, DD, N) + INTEGER N + REAL AA(N,N), BB(N,N), CC(N,N), DD(N,N) + REAL R + R=0 +!$OMP PARALLEL +!$OMP WORKSHARE + AA = BB +!$OMP ATOMIC + R = R + SUM(AA) + CC = DD +!$OMP END WORKSHARE +!$OMP END PARALLEL + END SUBROUTINE A11_3 diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.11.4.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.11.4.f90 new file mode 100644 index 000000000..ae95c1f98 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.11.4.f90 @@ -0,0 +1,16 @@ +! { dg-do compile } + + SUBROUTINE A11_4(AA, BB, CC, DD, EE, FF, GG, HH, N) + INTEGER N + REAL AA(N,N), BB(N,N), CC(N,N) + REAL DD(N,N), EE(N,N), FF(N,N) + REAL GG(N,N), HH(N,N) +!$OMP PARALLEL +!$OMP WORKSHARE + AA = BB + CC = DD + WHERE (EE .ne. 0) FF = 1 / EE + GG = HH +!$OMP END WORKSHARE +!$OMP END PARALLEL + END SUBROUTINE A11_4 diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.11.5.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.11.5.f90 new file mode 100644 index 000000000..6b8e4fa3d --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.11.5.f90 @@ -0,0 +1,14 @@ +! { dg-do compile } + SUBROUTINE A11_5(AA, BB, CC, DD, N) + INTEGER N + REAL AA(N,N), BB(N,N), CC(N,N), DD(N,N) + INTEGER SHR +!$OMP PARALLEL SHARED(SHR) +!$OMP WORKSHARE + AA = BB + SHR = 1 + CC = DD * SHR +!$OMP END WORKSHARE +!$OMP END PARALLEL + END SUBROUTINE A11_5 + diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.11.6.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.11.6.f90 new file mode 100644 index 000000000..fa31bcffc --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.11.6.f90 @@ -0,0 +1,14 @@ +! { dg-do compile } + + SUBROUTINE A11_6_WRONG(AA, BB, CC, DD, N) + INTEGER N + REAL AA(N,N), BB(N,N), CC(N,N), DD(N,N) + INTEGER PRI +!$OMP PARALLEL PRIVATE(PRI) +!$OMP WORKSHARE + AA = BB + PRI = 1 + CC = DD * PRI +!$OMP END WORKSHARE +!$OMP END PARALLEL + END SUBROUTINE A11_6_WRONG diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.11.7.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.11.7.f90 new file mode 100644 index 000000000..86b8c7bc5 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.11.7.f90 @@ -0,0 +1,11 @@ +! { dg-do compile } + SUBROUTINE A11_7(AA, BB, CC, N) + INTEGER N + REAL AA(N), BB(N), CC(N) +!$OMP PARALLEL +!$OMP WORKSHARE + AA(1:50) = BB(11:60) + CC(11:20) = AA(1:10) +!$OMP END WORKSHARE +!$OMP END PARALLEL + END SUBROUTINE A11_7 diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.12.1.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.12.1.f90 new file mode 100644 index 000000000..38389e4f4 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.12.1.f90 @@ -0,0 +1,32 @@ +! { dg-do compile } + SUBROUTINE A12( X, XOLD, N, TOL ) + REAL X(*), XOLD(*), TOL + INTEGER N + INTEGER C, I, TOOBIG + REAL ERROR, Y, AVERAGE + EXTERNAL AVERAGE + C=0 + TOOBIG = 1 +!$OMP PARALLEL + DO WHILE( TOOBIG > 0 ) +!$OMP DO PRIVATE(I) + DO I = 2, N-1 + XOLD(I) = X(I) + ENDDO +!$OMP SINGLE + TOOBIG = 0 +!$OMP END SINGLE +!$OMP DO PRIVATE(I,Y,ERROR), REDUCTION(+:TOOBIG) + DO I = 2, N-1 + Y = X(I) + X(I) = AVERAGE( XOLD(I-1), X(I), XOLD(I+1) ) + ERROR = Y-X(I) + IF( ERROR > TOL .OR. ERROR < -TOL ) TOOBIG = TOOBIG+1 + ENDDO +!$OMP MASTER + C=C+1 + PRINT *, "Iteration ", C, " TOOBIG=", TOOBIG +!$OMP END MASTER + ENDDO +!$OMP END PARALLEL + END SUBROUTINE A12 diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.13.1.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.13.1.f90 new file mode 100644 index 000000000..57f5b8912 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.13.1.f90 @@ -0,0 +1,16 @@ +! { dg-do compile } + SUBROUTINE A13(X, Y) + REAL X(*), Y(*) + INTEGER IX_NEXT, IY_NEXT +!$OMP PARALLEL SHARED(X, Y) PRIVATE(IX_NEXT, IY_NEXT) +!$OMP CRITICAL(XAXIS) + CALL DEQUEUE(IX_NEXT, X) +!$OMP END CRITICAL(XAXIS) + CALL WORK(IX_NEXT, X) +!$OMP CRITICAL(YAXIS) + CALL DEQUEUE(IY_NEXT,Y) +!$OMP END CRITICAL(YAXIS) + CALL WORK(IY_NEXT, Y) +!$OMP END PARALLEL + END SUBROUTINE A13 + diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.14.1.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.14.1.f90 new file mode 100644 index 000000000..6db107afa --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.14.1.f90 @@ -0,0 +1,15 @@ +! { dg-do compile } + SUBROUTINE A14() + INTEGER I + I=1 +!$OMP PARALLEL SECTIONS +!$OMP SECTION +!$OMP CRITICAL (NAME) +!$OMP PARALLEL +!$OMP SINGLE + I=I+1 +!$OMP END SINGLE +!$OMP END PARALLEL +!$OMP END CRITICAL (NAME) +!$OMP END PARALLEL SECTIONS + END SUBROUTINE A14 diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.17.1.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.17.1.f90 new file mode 100644 index 000000000..8fd600176 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.17.1.f90 @@ -0,0 +1,14 @@ +! { dg-do compile } + SUBROUTINE A17_1_WRONG() + INTEGER:: I + REAL:: R + EQUIVALENCE(I,R) +!$OMP PARALLEL +!$OMP ATOMIC + I=I+1 +!$OMP ATOMIC + R = R + 1.0 +! incorrect because I and R reference the same location +! but have different types +!$OMP END PARALLEL + END SUBROUTINE A17_1_WRONG diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.17.2.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.17.2.f90 new file mode 100644 index 000000000..a19db8c0d --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.17.2.f90 @@ -0,0 +1,19 @@ +! { dg-do compile } + + SUBROUTINE SUB() + COMMON /BLK/ R + REAL R +!$OMP ATOMIC + R = R + 1.0 + END SUBROUTINE SUB + + SUBROUTINE A17_2_WRONG() + COMMON /BLK/ I + INTEGER I +!$OMP PARALLEL +!$OMP ATOMIC + I=I+1 + CALL SUB() +!$OMP END PARALLEL + END SUBROUTINE A17_2_WRONG + diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.17.3.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.17.3.f90 new file mode 100644 index 000000000..4f4f55c09 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.17.3.f90 @@ -0,0 +1,18 @@ +! { dg-do compile } + SUBROUTINE A17_3_WRONG + INTEGER:: I + REAL:: R + EQUIVALENCE(I,R) +!$OMP PARALLEL +!$OMP ATOMIC + I=I+1 +! incorrect because I and R reference the same location +! but have different types +!$OMP END PARALLEL +!$OMP PARALLEL +!$OMP ATOMIC + R = R + 1.0 +! incorrect because I and R reference the same location +! but have different types +!$OMP END PARALLEL + END SUBROUTINE A17_3_WRONG diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.21.2.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.21.2.f90 new file mode 100644 index 000000000..87359a152 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.21.2.f90 @@ -0,0 +1,20 @@ +! { dg-do compile } + + SUBROUTINE WORK(I) + INTEGER I + END SUBROUTINE WORK + SUBROUTINE A21_WRONG(N) + INTEGER N + INTEGER I +!$OMP DO ORDERED + DO I = 1, N +! incorrect because an iteration may not execute more than one +! ordered region +!$OMP ORDERED + CALL WORK(I) +!$OMP END ORDERED +!$OMP ORDERED + CALL WORK(I+1) +!$OMP END ORDERED + END DO + END SUBROUTINE A21_WRONG diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.21.3.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.21.3.f90 new file mode 100644 index 000000000..97ca8f458 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.21.3.f90 @@ -0,0 +1,18 @@ +! { dg-do compile } + + SUBROUTINE A21_GOOD(N) + INTEGER N +!$OMP DO ORDERED + DO I = 1,N + IF (I <= 10) THEN +!$OMP ORDERED + CALL WORK(I) +!$OMP END ORDERED + ENDIF + IF (I > 10) THEN +!$OMP ORDERED + CALL WORK(I+1) +!$OMP END ORDERED + ENDIF + ENDDO + END SUBROUTINE A21_GOOD diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.22.1.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.22.1.f90 new file mode 100644 index 000000000..cc94b1403 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.22.1.f90 @@ -0,0 +1,10 @@ +! { dg-do compile } +! { dg-require-effective-target tls } + + INTEGER FUNCTION INCREMENT_COUNTER() + COMMON/A22_COMMON/COUNTER +!$OMP THREADPRIVATE(/A22_COMMON/) + COUNTER = COUNTER +1 + INCREMENT_COUNTER = COUNTER + RETURN + END FUNCTION INCREMENT_COUNTER diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.22.4.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.22.4.f90 new file mode 100644 index 000000000..2a637580b --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.22.4.f90 @@ -0,0 +1,12 @@ +! { dg-do compile } +! { dg-require-effective-target tls } + + MODULE A22_MODULE + COMMON /T/ A + END MODULE A22_MODULE + SUBROUTINE A22_4_WRONG() + USE A22_MODULE +!$OMP THREADPRIVATE(/T/) ! { dg-error "COMMON block" } + !non-conforming because /T/ not declared in A22_4_WRONG + END SUBROUTINE A22_4_WRONG +! { dg-final { cleanup-modules "A22_MODULE" } } diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.22.5.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.22.5.f90 new file mode 100644 index 000000000..6531d826c --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.22.5.f90 @@ -0,0 +1,13 @@ +! { dg-do compile } +! { dg-require-effective-target tls } + + SUBROUTINE A22_5_WRONG() + COMMON /T/ A +!$OMP THREADPRIVATE(/T/) + CONTAINS + SUBROUTINE A22_5S_WRONG() +!$OMP PARALLEL COPYIN(/T/) ! { dg-error "COMMON block" } + !non-conforming because /T/ not declared in A22_5S_WRONG +!$OMP END PARALLEL ! { dg-error "Unexpected" } + END SUBROUTINE A22_5S_WRONG + END SUBROUTINE A22_5_WRONG diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.22.6.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.22.6.f90 new file mode 100644 index 000000000..0a2e6a683 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.22.6.f90 @@ -0,0 +1,14 @@ +! { dg-do compile } +! { dg-require-effective-target tls } + + SUBROUTINE A22_6_GOOD() + COMMON /T/ A +!$OMP THREADPRIVATE(/T/) + CONTAINS + SUBROUTINE A22_6S_GOOD() + COMMON /T/ A +!$OMP THREADPRIVATE(/T/) +!$OMP PARALLEL COPYIN(/T/) +!$OMP END PARALLEL + END SUBROUTINE A22_6S_GOOD + END SUBROUTINE A22_6_GOOD diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.23.1.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.23.1.f90 new file mode 100644 index 000000000..6eab68729 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.23.1.f90 @@ -0,0 +1,11 @@ +! { dg-do compile } + SUBROUTINE A23_1_GOOD() + COMMON /C/ X,Y + REAL X, Y +!$OMP PARALLEL PRIVATE (/C/) + ! do work here +!$OMP END PARALLEL +!$OMP PARALLEL SHARED (X,Y) + ! do work here +!$OMP END PARALLEL + END SUBROUTINE A23_1_GOOD diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.23.2.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.23.2.f90 new file mode 100644 index 000000000..ecfdbe5a2 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.23.2.f90 @@ -0,0 +1,19 @@ +! { dg-do compile } + SUBROUTINE A23_2_GOOD() + COMMON /C/ X,Y + REAL X, Y + INTEGER I +!$OMP PARALLEL +!$OMP DO PRIVATE(/C/) + DO I=1,1000 + ! do work here + ENDDO +!$OMP END DO +! +!$OMP DO PRIVATE(X) + DO I=1,1000 + ! do work here + ENDDO +!$OMP END DO +!$OMP END PARALLEL + END SUBROUTINE A23_2_GOOD diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.23.3.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.23.3.f90 new file mode 100644 index 000000000..abd804102 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.23.3.f90 @@ -0,0 +1,11 @@ +! { dg-do compile } + + SUBROUTINE A23_3_GOOD() + COMMON /C/ X,Y +!$OMP PARALLEL PRIVATE (/C/) + ! do work here +!$OMP END PARALLEL +!$OMP PARALLEL SHARED (/C/) + ! do work here +!$OMP END PARALLEL + END SUBROUTINE A23_3_GOOD diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.23.4.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.23.4.f90 new file mode 100644 index 000000000..8c6e2281d --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.23.4.f90 @@ -0,0 +1,9 @@ +! { dg-do compile } + + SUBROUTINE A23_4_WRONG() + COMMON /C/ X,Y +! Incorrect because X is a constituent element of C +!$OMP PARALLEL PRIVATE(/C/), SHARED(X) ! { dg-error "Symbol 'x' present" } + ! do work here +!$OMP END PARALLEL + END SUBROUTINE A23_4_WRONG diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.23.5.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.23.5.f90 new file mode 100644 index 000000000..732c15f23 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.23.5.f90 @@ -0,0 +1,12 @@ +! { dg-do compile } + + SUBROUTINE A23_5_WRONG() + COMMON /C/ X,Y +! Incorrect: common block C cannot be declared both +! shared and private +!$OMP PARALLEL PRIVATE (/C/), SHARED(/C/) + ! { dg-error "Symbol 'y' present" "" { target *-*-* } 7 } + ! { dg-error "Symbol 'x' present" "" { target *-*-* } 7 } + ! do work here +!$OMP END PARALLEL + END SUBROUTINE A23_5_WRONG diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.24.1.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.24.1.f90 new file mode 100644 index 000000000..e5b95450d --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.24.1.f90 @@ -0,0 +1,31 @@ +! { dg-do compile } +! { dg-require-effective-target tls } + + SUBROUTINE A24(A) + INTEGER A + INTEGER X, Y, Z(1000) + INTEGER OMP_GET_NUM_THREADS + COMMON/BLOCKX/X + COMMON/BLOCKY/Y + COMMON/BLOCKZ/Z +!$OMP THREADPRIVATE(/BLOCKX/) + INTEGER I, J + i=1 +!$OMP PARALLEL DEFAULT(NONE) PRIVATE(A) SHARED(Z) PRIVATE(J) + J = OMP_GET_NUM_THREADS(); + ! O.K. - J is listed in PRIVATE clause + A = Z(J) ! O.K. - A is listed in PRIVATE clause + ! - Z is listed in SHARED clause + X=1 ! O.K. - X is THREADPRIVATE + Z(I) = Y ! Error - cannot reference I or Y here +! { dg-error "'i' not specified" "" { target *-*-* } 20 } */ +! { dg-error "enclosing parallel" "" { target *-*-* } 14 } */ +! { dg-error "'y' not specified" "" { target *-*-* } 20 } */ +!$OMP DO firstprivate(y) + DO I = 1,10 + Z(I) = Y ! O.K. - I is the loop iteration variable + ! Y is listed in FIRSTPRIVATE clause + END DO + Z(I) = Y ! Error - cannot reference I or Y here +!$OMP END PARALLEL + END SUBROUTINE A24 diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.25.1.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.25.1.f90 new file mode 100644 index 000000000..66bfba80e --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.25.1.f90 @@ -0,0 +1,19 @@ +! { dg-do compile } + + SUBROUTINE A25 + INTEGER OMP_GET_THREAD_NUM + REAL A(20) + INTEGER MYTHREAD + !$OMP PARALLEL SHARED(A) PRIVATE(MYTHREAD) + MYTHREAD = OMP_GET_THREAD_NUM() + IF (MYTHREAD .EQ. 0) THEN + CALL SUB(A(1:10)) ! compiler may introduce writes to A(6:10) + ELSE + A(6:10) = 12 + ENDIF + !$OMP END PARALLEL + END SUBROUTINE A25 + SUBROUTINE SUB(X) + REAL X(*) + X(1:5) = 4 + END SUBROUTINE SUB diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.26.2.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.26.2.f90 new file mode 100644 index 000000000..3d43424b6 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.26.2.f90 @@ -0,0 +1,23 @@ +! { dg-do compile } + + MODULE A26_2 + REAL A + CONTAINS + SUBROUTINE G(K) + REAL K + A = K ! This is A in module A26_2, not the private + ! A in F + END SUBROUTINE G + SUBROUTINE F(N) + INTEGER N + REAL A + INTEGER I +!$OMP PARALLEL DO PRIVATE(A) + DO I = 1,N + A=I + CALL G(A*2) + ENDDO +!$OMP END PARALLEL DO + END SUBROUTINE F + END MODULE A26_2 +! { dg-final { cleanup-modules "A26_2" } } diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.27.1.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.27.1.f90 new file mode 100644 index 000000000..f564bd380 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.27.1.f90 @@ -0,0 +1,12 @@ +! { dg-do compile } + + SUBROUTINE A27() + INTEGER I, A +!$OMP PARALLEL PRIVATE(A) +!$OMP PARALLEL DO PRIVATE(A) + DO I = 1, 10 + ! do work here + END DO +!$OMP END PARALLEL DO +!$OMP END PARALLEL + END SUBROUTINE A27 diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.30.1.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.30.1.f90 new file mode 100644 index 000000000..e62cbf81b --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.30.1.f90 @@ -0,0 +1,14 @@ +! { dg-do compile } + + SUBROUTINE A30(N, A, B) + INTEGER N + REAL A(*), B(*) + INTEGER I +!$OMP PARALLEL +!$OMP DO LASTPRIVATE(I) + DO I=1,N-1 + A(I) = B(I) + B(I+1) + ENDDO +!$OMP END PARALLEL + A(I) = B(I) ! I has the value of N here + END SUBROUTINE A30 diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.31.1.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.31.1.f90 new file mode 100644 index 000000000..7459897eb --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.31.1.f90 @@ -0,0 +1,15 @@ +! { dg-do compile } + + SUBROUTINE A31_1(A, B, X, Y, N) + INTEGER N + REAL X(*), Y(*), A, B +!$OMP PARALLEL DO PRIVATE(I) SHARED(X, N) REDUCTION(+:A) & +!$OMP& REDUCTION(MIN:B) + DO I=1,N + A = A + X(I) + B = MIN(B, Y(I)) +! Note that some reductions can be expressed in +! other forms. For example, the MIN could be expressed as +! IF (B > Y(I)) B = Y(I) + END DO + END SUBROUTINE A31_1 diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.31.2.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.31.2.f90 new file mode 100644 index 000000000..f78188c7c --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.31.2.f90 @@ -0,0 +1,20 @@ +! { dg-do compile } + + SUBROUTINE A31_2 (A, B, X, Y, N) + INTEGER N + REAL X(*), Y(*), A, B, A_P, B_P +!$OMP PARALLEL SHARED(X, Y, N, A, B) PRIVATE(A_P, B_P) + A_P = 0.0 + B_P = HUGE(B_P) +!$OMP DO PRIVATE(I) + DO I=1,N + A_P = A_P + X(I) + B_P = MIN(B_P, Y(I)) + ENDDO +!$OMP END DO +!$OMP CRITICAL + A = A + A_P + B = MIN(B, B_P) +!$OMP END CRITICAL +!$OMP END PARALLEL + END SUBROUTINE A31_2 diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.31.3.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.31.3.f90 new file mode 100644 index 000000000..f67c91c21 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.31.3.f90 @@ -0,0 +1,15 @@ +! { dg-do compile } + PROGRAM A31_3_WRONG + MAX = HUGE(0) + M=0 + !$OMP PARALLEL DO REDUCTION(MAX: M) ! MAX is no longer the + ! intrinsic so this + ! is non-conforming +! { dg-error "is not INTRINSIC procedure name" "" { target *-*-* } 5 } */ + DO I = 1, 100 + CALL SUB(M,I) + END DO + END PROGRAM A31_3_WRONG + SUBROUTINE SUB(M,I) + M = MAX(M,I) + END SUBROUTINE SUB diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.32.1.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.32.1.f90 new file mode 100644 index 000000000..498a6d324 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.32.1.f90 @@ -0,0 +1,25 @@ +! { dg-do compile } +! { dg-require-effective-target tls } + + MODULE M + REAL, POINTER, SAVE :: WORK(:) + INTEGER :: SIZE + REAL :: TOL +!$OMP THREADPRIVATE(WORK,SIZE,TOL) + END MODULE M + SUBROUTINE A32( T, N ) + USE M + REAL :: T + INTEGER :: N + TOL = T + SIZE = N +!$OMP PARALLEL COPYIN(TOL,SIZE) + CALL BUILD +!$OMP END PARALLEL + END SUBROUTINE A32 + SUBROUTINE BUILD + USE M + ALLOCATE(WORK(SIZE)) + WORK = TOL + END SUBROUTINE BUILD +! { dg-final { cleanup-modules "M" } } diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.33.1.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.33.1.f90 new file mode 100644 index 000000000..05145b171 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.33.1.f90 @@ -0,0 +1,11 @@ +! { dg-do compile } +! { dg-require-effective-target tls } + + SUBROUTINE INIT(A,B) + REAL A, B + COMMON /XY/ X,Y +!$OMP THREADPRIVATE (/XY/) +!$OMP SINGLE + READ (11) A,B,X,Y +!$OMP END SINGLE COPYPRIVATE (A,B,/XY/) + END SUBROUTINE INIT diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.33.2.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.33.2.f90 new file mode 100644 index 000000000..ced23c856 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.33.2.f90 @@ -0,0 +1,17 @@ +! { dg-do compile } + + REAL FUNCTION READ_NEXT() + REAL, POINTER :: TMP +!$OMP SINGLE + ALLOCATE (TMP) +!$OMP END SINGLE COPYPRIVATE (TMP) ! copies the pointer only +!$OMP MASTER + READ (11) TMP +!$OMP END MASTER +!$OMP BARRIER + READ_NEXT = TMP +!$OMP BARRIER +!$OMP SINGLE + DEALLOCATE (TMP) +!$OMP END SINGLE NOWAIT + END FUNCTION READ_NEXT diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.33.4.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.33.4.f90 new file mode 100644 index 000000000..7a9e1840b --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.33.4.f90 @@ -0,0 +1,19 @@ +! { dg-do compile } + SUBROUTINE S(N) + INTEGER N + REAL, DIMENSION(:), ALLOCATABLE :: A + REAL, DIMENSION(:), POINTER :: B + ALLOCATE (A(N)) +!$OMP SINGLE + ALLOCATE (B(N)) + READ (11) A,B +!$OMP END SINGLE COPYPRIVATE(A,B) + ! Variable A designates a private object + ! which has the same value in each thread + ! Variable B designates a shared object +!$OMP BARRIER +!$OMP SINGLE + DEALLOCATE (B) +!$OMP END SINGLE NOWAIT + END SUBROUTINE S + diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.34.1.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.34.1.f90 new file mode 100644 index 000000000..29ea952cb --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.34.1.f90 @@ -0,0 +1,19 @@ +! { dg-do compile } + SUBROUTINE WORK(I, J) + INTEGER I, J + END SUBROUTINE WORK + SUBROUTINE GOOD_NESTING(N) + INTEGER N + INTEGER I +!$OMP PARALLEL DEFAULT(SHARED) +!$OMP DO + DO I = 1, N +!$OMP PARALLEL SHARED(I,N) +!$OMP DO + DO J = 1, N + CALL WORK(I,J) + END DO +!$OMP END PARALLEL + END DO +!$OMP END PARALLEL + END SUBROUTINE GOOD_NESTING diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.34.2.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.34.2.f90 new file mode 100644 index 000000000..980a62372 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.34.2.f90 @@ -0,0 +1,22 @@ +! { dg-do compile } + SUBROUTINE WORK(I, J) + INTEGER I, J + END SUBROUTINE WORK + SUBROUTINE WORK1(I, N) + INTEGER J +!$OMP PARALLEL DEFAULT(SHARED) +!$OMP DO + DO J = 1, N + CALL WORK(I,J) + END DO +!$OMP END PARALLEL + END SUBROUTINE WORK1 + SUBROUTINE GOOD_NESTING2(N) + INTEGER N +!$OMP PARALLEL DEFAULT(SHARED) +!$OMP DO + DO I = 1, N + CALL WORK1(I, N) + END DO +!$OMP END PARALLEL + END SUBROUTINE GOOD_NESTING2 diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.35.1.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.35.1.f90 new file mode 100644 index 000000000..7431a6579 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.35.1.f90 @@ -0,0 +1,19 @@ +! { dg-do compile } + + SUBROUTINE WORK(I, J) + INTEGER I, J + END SUBROUTINE WORK + SUBROUTINE WRONG1(N) + INTEGER N + INTEGER I,J +!$OMP PARALLEL DEFAULT(SHARED) +!$OMP DO + DO I = 1, N + ! incorrect nesting of loop regions +!$OMP DO ! { dg-warning "may not be closely nested" } + DO J = 1, N + CALL WORK(I,J) + END DO + END DO +!$OMP END PARALLEL + END SUBROUTINE WRONG1 diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.35.2.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.35.2.f90 new file mode 100644 index 000000000..5fad2c05f --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.35.2.f90 @@ -0,0 +1,20 @@ +! { dg-do compile } + + SUBROUTINE WORK1(I,N) + INTEGER I, N + INTEGER J +!$OMP DO ! incorrect nesting of loop regions + DO J = 1, N + CALL WORK(I,J) + END DO + END SUBROUTINE WORK1 + SUBROUTINE WRONG2(N) + INTEGER N + INTEGER I +!$OMP PARALLEL DEFAULT(SHARED) +!$OMP DO + DO I = 1, N + CALL WORK1(I,N) + END DO +!$OMP END PARALLEL + END SUBROUTINE WRONG2 diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.35.3.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.35.3.f90 new file mode 100644 index 000000000..bb3e02fef --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.35.3.f90 @@ -0,0 +1,15 @@ +! { dg-do compile } + + SUBROUTINE WRONG3(N) + INTEGER N + INTEGER I +!$OMP PARALLEL DEFAULT(SHARED) +!$OMP DO + DO I = 1, N + ! incorrect nesting of regions +!$OMP SINGLE ! { dg-warning "may not be closely nested" } + CALL WORK(I, 1) +!$OMP END SINGLE + END DO +!$OMP END PARALLEL + END SUBROUTINE WRONG3 diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.35.4.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.35.4.f90 new file mode 100644 index 000000000..f130dd5f4 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.35.4.f90 @@ -0,0 +1,15 @@ +! { dg-do compile } + + SUBROUTINE WRONG4(N) + INTEGER N + INTEGER I +!$OMP PARALLEL DEFAULT(SHARED) +!$OMP DO + DO I = 1, N + CALL WORK(I, 1) +! incorrect nesting of barrier region in a loop region +!$OMP BARRIER ! { dg-warning "may not be closely nested" } + CALL WORK(I, 2) + END DO +!$OMP END PARALLEL + END SUBROUTINE WRONG4 diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.35.5.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.35.5.f90 new file mode 100644 index 000000000..083c0b3b7 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.35.5.f90 @@ -0,0 +1,13 @@ +! { dg-do compile } + + SUBROUTINE WRONG5(N) + INTEGER N +!$OMP PARALLEL DEFAULT(SHARED) +!$OMP CRITICAL + CALL WORK(N,1) +! incorrect nesting of barrier region in a critical region +!$OMP BARRIER + CALL WORK(N,2) +!$OMP END CRITICAL +!$OMP END PARALLEL + END SUBROUTINE WRONG5 diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.35.6.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.35.6.f90 new file mode 100644 index 000000000..62ba24523 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.35.6.f90 @@ -0,0 +1,14 @@ +! { dg-do compile } + + SUBROUTINE WRONG6(N) + INTEGER N +!$OMP PARALLEL DEFAULT(SHARED) +!$OMP SINGLE + CALL WORK(N,1) +! incorrect nesting of barrier region in a single region +!$OMP BARRIER ! { dg-warning "may not be closely nested" } + CALL WORK(N,2) +!$OMP END SINGLE +!$OMP END PARALLEL + END SUBROUTINE WRONG6 + diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.36.1.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.36.1.f90 new file mode 100644 index 000000000..be68188ec --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.36.1.f90 @@ -0,0 +1,23 @@ +! { dg-do compile } + + SUBROUTINE DO_BY_16(X, IAM, IPOINTS) + REAL X(*) + INTEGER IAM, IPOINTS + END SUBROUTINE DO_BY_16 + SUBROUTINE SUBA36(X, NPOINTS) + INTEGER NPOINTS + REAL X(NPOINTS) + INTEGER IAM, IPOINTS + EXTERNAL OMP_SET_DYNAMIC, OMP_SET_NUM_THREADS + INTEGER OMP_GET_NUM_THREADS, OMP_GET_THREAD_NUM + CALL OMP_SET_DYNAMIC(.FALSE.) + CALL OMP_SET_NUM_THREADS(16) +!$OMP PARALLEL SHARED(X,NPOINTS) PRIVATE(IAM, IPOINTS) + IF (OMP_GET_NUM_THREADS() .NE. 16) THEN + STOP + ENDIF + IAM = OMP_GET_THREAD_NUM() + IPOINTS = NPOINTS/16 + CALL DO_BY_16(X,IAM,IPOINTS) +!$OMP END PARALLEL + END SUBROUTINE SUBA36 diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.37.1.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.37.1.f90 new file mode 100644 index 000000000..473c1fec8 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.37.1.f90 @@ -0,0 +1,15 @@ +! { dg-do compile } + SUBROUTINE WORK(I) + INTEGER I + I=I+1 + END SUBROUTINE WORK + SUBROUTINE INCORRECT() + INTEGER OMP_GET_NUM_THREADS + INTEGER I, NP + NP = OMP_GET_NUM_THREADS() !misplaced: will return 1 +!$OMP PARALLEL DO SCHEDULE(STATIC) + DO I = 0, NP-1 + CALL WORK(I) + ENDDO +!$OMP END PARALLEL DO + END SUBROUTINE INCORRECT diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.37.2.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.37.2.f90 new file mode 100644 index 000000000..c5fbcbbd0 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.37.2.f90 @@ -0,0 +1,13 @@ +! { dg-do compile } + SUBROUTINE WORK(I) + INTEGER I + I=I+1 + END SUBROUTINE WORK + SUBROUTINE CORRECT() + INTEGER OMP_GET_THREAD_NUM + INTEGER I +!$OMP PARALLEL PRIVATE(I) + I = OMP_GET_THREAD_NUM() + CALL WORK(I) +!$OMP END PARALLEL + END SUBROUTINE CORRECT diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.6.1.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.6.1.f90 new file mode 100644 index 000000000..f1c6c6596 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.6.1.f90 @@ -0,0 +1,24 @@ +! { dg-do compile } + + SUBROUTINE WORK(I, J) + INTEGER I,J + END SUBROUTINE WORK + SUBROUTINE A6_GOOD() + INTEGER I, J + REAL A(1000) + DO 100 I = 1,10 +!$OMP DO + DO 100 J = 1,10 + CALL WORK(I,J) + 100 CONTINUE ! !$OMP ENDDO implied here +!$OMP DO + DO 200 J = 1,10 +200 A(I) = I + 1 +!$OMP ENDDO +!$OMP DO + DO 300 I = 1,10 + DO 300 J = 1,10 + CALL WORK(I,J) +300 CONTINUE +!$OMP ENDDO + END SUBROUTINE A6_GOOD diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.6.2.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.6.2.f90 new file mode 100644 index 000000000..e13880899 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.6.2.f90 @@ -0,0 +1,15 @@ +! { dg-do compile } + + SUBROUTINE WORK(I, J) + INTEGER I,J + END SUBROUTINE WORK + + SUBROUTINE A6_WRONG + INTEGER I, J + DO 100 I = 1,10 +!$OMP DO + DO 100 J = 1,10 + CALL WORK(I,J) + 100 CONTINUE +!$OMP ENDDO ! { dg-error "Unexpected ..OMP END DO statement" } + END SUBROUTINE A6_WRONG diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.7.1.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.7.1.f90 new file mode 100644 index 000000000..9f3b08d2e --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.7.1.f90 @@ -0,0 +1,12 @@ +! { dg-do compile } +SUBROUTINE A7_1(A,N) +INTEGER OMP_GET_THREAD_NUM +REAL A(*) +INTEGER I, MYOFFSET, N +!$OMP PARALLEL PRIVATE(MYOFFSET) + MYOFFSET = OMP_GET_THREAD_NUM()*N + DO I = 1, N + A(MYOFFSET+I) = FLOAT(I) + ENDDO +!$OMP END PARALLEL +END SUBROUTINE A7_1 diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.7.2.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.7.2.f90 new file mode 100644 index 000000000..23f231876 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.7.2.f90 @@ -0,0 +1,22 @@ +! { dg-do compile } + +SUBROUTINE A7_2(A,B,N,I1,I2) +REAL A(*), B(*) +INTEGER I1, I2, N +!$OMP PARALLEL SHARED(A,B,I1,I2) +!$OMP SECTIONS +!$OMP SECTION + DO I1 = I1, N + IF (A(I1).NE.0.0) EXIT + ENDDO +!$OMP SECTION + DO I2 = I2, N + IF (B(I2).NE.0.0) EXIT + ENDDO +!$OMP END SECTIONS +!$OMP SINGLE + IF (I1.LE.N) PRINT *, "ITEMS IN A UP TO ", I1, " ARE ALL ZERO." + IF (I2.LE.N) PRINT *, "ITEMS IN B UP TO ", I2, " ARE ALL ZERO." +!$OMP END SINGLE +!$OMP END PARALLEL +END SUBROUTINE A7_2 diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.8.1.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.8.1.f90 new file mode 100644 index 000000000..f499e7f89 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.8.1.f90 @@ -0,0 +1,18 @@ +! { dg-do compile } + SUBROUTINE A8(N, M, A, B, Y, Z) + INTEGER N, M + REAL A(*), B(*), Y(*), Z(*) + INTEGER I +!$OMP PARALLEL +!$OMP DO + DO I=2,N + B(I) = (A(I) + A(I-1)) / 2.0 + ENDDO +!$OMP END DO NOWAIT +!$OMP DO + DO I=1,M + Y(I) = SQRT(Z(I)) + ENDDO +!$OMP END DO NOWAIT +!$OMP END PARALLEL + END SUBROUTINE A8 diff --git a/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.9.1.f90 b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.9.1.f90 new file mode 100644 index 000000000..fc7b67de5 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/appendix-a/a.9.1.f90 @@ -0,0 +1,11 @@ +! { dg-do compile } + SUBROUTINE A9() +!$OMP PARALLEL SECTIONS +!$OMP SECTION + CALL XAXIS() +!$OMP SECTION + CALL YAXIS() +!$OMP SECTION + CALL ZAXIS() +!$OMP END PARALLEL SECTIONS + END SUBROUTINE A9 diff --git a/gcc/testsuite/gfortran.dg/gomp/block-1.f90 b/gcc/testsuite/gfortran.dg/gomp/block-1.f90 new file mode 100644 index 000000000..04c39a40a --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/block-1.f90 @@ -0,0 +1,10 @@ +! { dg-do compile } + +!$omp parallel +!$omp critical + goto 10 ! { dg-error "invalid (exit|branch)" } +!$omp end critical + 10 x = 1 +!$omp end parallel + + end diff --git a/gcc/testsuite/gfortran.dg/gomp/collapse1.f90 b/gcc/testsuite/gfortran.dg/gomp/collapse1.f90 new file mode 100644 index 000000000..f16a780ad --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/collapse1.f90 @@ -0,0 +1,57 @@ +! { dg-do compile } +! { dg-options "-fopenmp" } + +subroutine collapse1 + integer :: i, j, k, a(1:3, 4:6, 5:7) + real :: r + logical :: l + integer, save :: thr + !$omp threadprivate (thr) + l = .false. + a(:, :, :) = 0 + !$omp parallel do collapse(4) schedule(static, 4) ! { dg-error "not enough DO loops for collapsed" } + do i = 1, 3 + do j = 4, 6 + do k = 5, 7 + a(i, j, k) = i + j + k + end do + end do + end do + !$omp parallel do collapse(2) + do i = 1, 5, 2 + do j = i + 1, 7, i ! { dg-error "collapsed loops don.t form rectangular iteration space" } + end do + end do + !$omp parallel do collapse(2) shared(j) + do i = 1, 3 + do j = 4, 6 ! { dg-error "iteration variable present on clause other than PRIVATE or LASTPRIVATE" } + end do + end do + !$omp parallel do collapse(2) + do i = 1, 3 + do j = 4, 6 + end do + k = 4 + end do + !$omp parallel do collapse(2) + do i = 1, 3 + do ! { dg-error "cannot be a DO WHILE or DO without loop control" } + end do + end do + !$omp parallel do collapse(2) + do i = 1, 3 + do r = 4, 6 ! { dg-warning "must be integer" } + end do + end do +end subroutine collapse1 + +subroutine collapse1_2 + integer :: i + !$omp parallel do collapse(2) + do i = -6, 6 ! { dg-error "cannot be redefined inside loop beginning" } + do i = 4, 6 ! { dg-error "collapsed loops don.t form rectangular iteration space|cannot be redefined" } + end do + end do +end subroutine collapse1_2 + +! { dg-error "iteration variable must be of type integer" "integer" { target *-*-* } 43 } diff --git a/gcc/testsuite/gfortran.dg/gomp/crayptr1.f90 b/gcc/testsuite/gfortran.dg/gomp/crayptr1.f90 new file mode 100644 index 000000000..fca5606e0 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/crayptr1.f90 @@ -0,0 +1,51 @@ +! { dg-do compile } +! { dg-options "-fopenmp -fcray-pointer" } + + integer :: a, b, c, d, i + pointer (ip1, a) + pointer (ip2, b) + pointer (ip3, c) + pointer (ip4, d) + +!$omp parallel shared (a) ! { dg-error "Cray pointee 'a' in SHARED clause" } +!$omp end parallel + +!$omp parallel private (b) ! { dg-error "Cray pointee 'b' in PRIVATE clause" } +!$omp end parallel + +!$omp parallel firstprivate (c) ! { dg-error "Cray pointee 'c' in FIRSTPRIVATE clause" } +!$omp end parallel + +!$omp parallel do lastprivate (d) ! { dg-error "Cray pointee 'd' in LASTPRIVATE clause" } + do i = 1, 10 + if (i .eq. 10) d = 1 + end do +!$omp end parallel do + +!$omp parallel reduction (+: a) ! { dg-error "Cray pointee 'a' in REDUCTION clause" } +!$omp end parallel + + ip1 = loc (i) +!$omp parallel shared (ip1) + a = 2 +!$omp end parallel + +!$omp parallel private (ip2, i) + ip2 = loc (i) + b = 1 +!$omp end parallel + + ip3 = loc (i) +!$omp parallel firstprivate (ip3) ! { dg-error "Cray pointer 'ip3' in FIRSTPRIVATE clause" } +!$omp end parallel + +!$omp parallel do lastprivate (ip4) ! { dg-error "Cray pointer 'ip4' in LASTPRIVATE clause" } + do i = 1, 10 + if (i .eq. 10) ip4 = loc (i) + end do +!$omp end parallel do + +!$omp parallel reduction (+: ip1) ! { dg-error "Cray pointer 'ip1' in REDUCTION clause" } +!$omp end parallel + +end diff --git a/gcc/testsuite/gfortran.dg/gomp/crayptr2.f90 b/gcc/testsuite/gfortran.dg/gomp/crayptr2.f90 new file mode 100644 index 000000000..476d7b9e7 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/crayptr2.f90 @@ -0,0 +1,17 @@ +! { dg-do compile } +! { dg-options "-fopenmp -fcray-pointer" } +! { dg-require-effective-target tls } + +module crayptr2 + integer :: e ! { dg-error "CRAY POINTEE attribute conflicts with THREADPRIVATE" } + pointer (ip5, e) + +! The standard is not very clear about this. +! Certainly, Cray pointees can't be SAVEd, nor they can be +! in COMMON, so the only way to make threadprivate Cray pointees would +! be if they are module variables. But threadprivate pointees don't +! make any sense anyway. + +!$omp threadprivate (e) + +end module crayptr2 diff --git a/gcc/testsuite/gfortran.dg/gomp/crayptr3.f90 b/gcc/testsuite/gfortran.dg/gomp/crayptr3.f90 new file mode 100644 index 000000000..be8f5a0f4 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/crayptr3.f90 @@ -0,0 +1,22 @@ +! { dg-do compile } +! { dg-options "-fopenmp -fcray-pointer" } + + integer :: a, b + pointer (ip, a) + + b = 2 + ip = loc (b) +!$omp parallel default (none) shared (ip) + a = 1 +!$omp end parallel + +!$omp parallel default (none) private (ip, b) + b = 3 + ip = loc (b) + a = 1 +!$omp end parallel + +!$omp parallel default (none) ! { dg-error "enclosing parallel" } + a = 1 ! { dg-error "'ip' not specified in enclosing parallel" } +!$omp end parallel +end diff --git a/gcc/testsuite/gfortran.dg/gomp/crayptr4.f90 b/gcc/testsuite/gfortran.dg/gomp/crayptr4.f90 new file mode 100644 index 000000000..d7da0bd8c --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/crayptr4.f90 @@ -0,0 +1,24 @@ +! { dg-do compile } +! { dg-options "-fopenmp -fcray-pointer" } + +subroutine foo (n) + integer :: a, b (38), n + pointer (ip, a (n + 1)) + + b = 2 + n = 36 + ip = loc (b) +!$omp parallel default (none) shared (ip) +!$omp parallel default (none) shared (ip) + a = 1 +!$omp end parallel +!$omp end parallel + +!$omp parallel default (none) +!$omp parallel default (none) private (ip, b) + b = 3 + ip = loc (b) + a = 1 +!$omp end parallel +!$omp end parallel +end diff --git a/gcc/testsuite/gfortran.dg/gomp/crayptr5.f90 b/gcc/testsuite/gfortran.dg/gomp/crayptr5.f90 new file mode 100644 index 000000000..5ade16c83 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/crayptr5.f90 @@ -0,0 +1,27 @@ +! { dg-do compile } +! { dg-options "-fopenmp -fcray-pointer" } +! +! PR fortran/43985 + +subroutine pete(A) + real(8) :: A + print *, 'pete got ',A + if (A /= 3.0) call abort() +end subroutine pete + + subroutine bob() + implicit none + real(8) peted + pointer (ipeted, peted(*)) + integer(4) sz + ipeted = malloc(5*8) + peted(1:5) = [ 1.,2.,3.,4.,5.] + sz = 3 +!$omp parallel default(shared) + call pete(peted(sz)) +!$omp end parallel + return + end subroutine bob + +call bob() +end diff --git a/gcc/testsuite/gfortran.dg/gomp/do-1.f90 b/gcc/testsuite/gfortran.dg/gomp/do-1.f90 new file mode 100644 index 000000000..a9c9cf11d --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/do-1.f90 @@ -0,0 +1,26 @@ +! { dg-do compile } +! { dg-options "-O -fopenmp -fdump-tree-omplower" } + +subroutine foo (i, j, k, s, a) + integer :: i, j, k, s, a(100), l +!$omp parallel do schedule (dynamic, s * 2) + do 100, l = j, k +100 a(l) = i +!$omp parallel do schedule (dynamic, s * 2) + do 101, l = j, k, 3 +101 a(l) = i + 1 +end subroutine foo + +subroutine bar (i, j, k, s, a) + integer :: i, j, k, s, a(100), l +!$omp parallel do schedule (guided, s * 2) + do 100, l = j, k +100 a(l) = i +!$omp parallel do schedule (guided, s * 2) + do 101, l = j, k, 3 +101 a(l) = i + 1 +end subroutine bar + +! { dg-final { scan-tree-dump-times "GOMP_parallel_loop_dynamic_start" 2 "omplower" { xfail *-*-* } } } +! { dg-final { scan-tree-dump-times "GOMP_parallel_loop_guided_start" 2 "omplower" { xfail *-*-* } } } +! { dg-final { cleanup-tree-dump "omplower" } } diff --git a/gcc/testsuite/gfortran.dg/gomp/fixed-1.f b/gcc/testsuite/gfortran.dg/gomp/fixed-1.f new file mode 100644 index 000000000..d61f2ba63 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/fixed-1.f @@ -0,0 +1,22 @@ +C PR fortran/24493 +C { dg-do compile } +C { dg-require-effective-target tls } + INTEGER I, J, K, L, M +C$OMP THREADPRIVATE(I) +C SOME COMMENT + SAVE I ! ANOTHER COMMENT +C$OMP THREADPRIVATE +C$OMP+(J) ! OMP DIRECTIVE COMMENT +* NORMAL COMMENT +c$OMP THREAD! COMMENT +C$OMP&PRIVATE! COMMENT +*$OMP+ (K) +C$OMP THREADPRIVATE (L ! COMMENT +*$OMP& , M) + SAVE J, K, L, M + I = 1 + J = 2 + K = 3 + L = 4 + M = 5 + END diff --git a/gcc/testsuite/gfortran.dg/gomp/free-1.f90 b/gcc/testsuite/gfortran.dg/gomp/free-1.f90 new file mode 100644 index 000000000..f6f9de444 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/free-1.f90 @@ -0,0 +1,8 @@ +! { dg-require-effective-target tls } + +subroutine foo +integer, save :: i ! Some comment +!$omp threadpri& + !$omp&vate (i) +i = 1 +end subroutine diff --git a/gcc/testsuite/gfortran.dg/gomp/free-2.f90 b/gcc/testsuite/gfortran.dg/gomp/free-2.f90 new file mode 100644 index 000000000..60bac66b8 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/free-2.f90 @@ -0,0 +1,14 @@ +! { dg-do compile } +! +! PR fortran/33445 +! +!$OMP&foo ! { dg-warning "starts a commented line" } +! +!$OMP parallel +!$OMP& default(shared) ! { dg-warning "starts a commented line" } +!$OMP end parallel +! +!$OMP parallel +!$OMP+ default(shared) ! { dg-warning "starts a commented line" } +!$OMP end parallel + end diff --git a/gcc/testsuite/gfortran.dg/gomp/gomp.exp b/gcc/testsuite/gfortran.dg/gomp/gomp.exp new file mode 100644 index 000000000..e12864b4f --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/gomp.exp @@ -0,0 +1,36 @@ +# Copyright (C) 2005, 2006, 2007, 2008 Free Software Foundation, Inc. +# +# This file is part of GCC. +# +# GCC is free software; you can redistribute it and/or modify +# it under the terms of the GNU General Public License as published by +# the Free Software Foundation; either version 3, or (at your option) +# any later version. +# +# GCC is distributed in the hope that it will be useful, +# but WITHOUT ANY WARRANTY; without even the implied warranty of +# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +# GNU General Public License for more details. +# +# You should have received a copy of the GNU General Public License +# along with GCC; see the file COPYING3. If not see +# <http://www.gnu.org/licenses/>. + +# GCC testsuite that uses the `dg.exp' driver. + +# Load support procs. +load_lib gfortran-dg.exp + +if ![check_effective_target_fopenmp] { + return +} + +# Initialize `dg'. +dg-init + +# Main loop. +gfortran-dg-runtest [lsort \ + [find $srcdir/$subdir *.\[fF\]{,90,95,03,08} ] ] " -fopenmp" + +# All done. +dg-finish diff --git a/gcc/testsuite/gfortran.dg/gomp/omp_atomic1.f90 b/gcc/testsuite/gfortran.dg/gomp/omp_atomic1.f90 new file mode 100644 index 000000000..247f8ae50 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/omp_atomic1.f90 @@ -0,0 +1,38 @@ +! { dg-do compile } +subroutine test_atomic + integer (kind = 4) :: a + integer :: b + real :: c, f + double precision :: d + integer, dimension (10) :: e + a = 1 + b = 2 + c = 3 + d = 4 + e = 5 + f = 6 +!$omp atomic + a = a + 4 +!$omp atomic + b = 4 - b +!$omp atomic + c = c * 2 +!$omp atomic + d = 2 / d +!$omp atomic + e = 1 ! { dg-error "must set a scalar variable" } +!$omp atomic + a = a ** 8 ! { dg-error "assignment operator must be" } +!$omp atomic + b = b + 3 + b ! { dg-error "cannot reference" } +!$omp atomic + c = c - f + 1 ! { dg-error "not mathematically equivalent to" } +!$omp atomic + a = ishft (a, 1) ! { dg-error "assignment intrinsic must be" } +!$omp atomic + c = min (c, 2.1, c) ! { dg-error "intrinsic arguments except one" } +!$omp atomic + a = max (b, e(1)) ! { dg-error "intrinsic argument must be 'a'" } +!$omp atomic + d = 12 ! { dg-error "assignment must have an operator" } +end subroutine test_atomic diff --git a/gcc/testsuite/gfortran.dg/gomp/omp_clauses1.f90 b/gcc/testsuite/gfortran.dg/gomp/omp_clauses1.f90 new file mode 100644 index 000000000..8851101b9 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/omp_clauses1.f90 @@ -0,0 +1,25 @@ +! { dg-do compile } + subroutine test1 + integer :: i, j, k, l + common /b/ j, k +!$omp parallel shared (i) private (/b/) +!$omp end parallel +!$omp parallel do shared (/b/), firstprivate (i), lastprivate (i) + do l = 1, 10 + end do +!$omp end parallel do +!$omp parallel shared (j) private (/b/) ! { dg-error "'j' present on multiple clauses" } +!$omp end parallel +!$omp parallel shared (j, j) private (i) ! { dg-error "'j' present on multiple clauses" } +!$omp end parallel +!$omp parallel firstprivate (i, j, i) ! { dg-error "'i' present on multiple clauses" } +!$omp end parallel +!$omp parallel shared (i) private (/b/, /b/) ! { dg-error "'\[jk\]' present on multiple clauses" } +!$omp end parallel +!$omp parallel shared (i) reduction (+ : i, j) ! { dg-error "'i' present on multiple clauses" } +!$omp end parallel +!$omp parallel do shared (/b/), firstprivate (/b/), lastprivate (i) ! { dg-error "'\[jk\]' present on multiple clauses" } + do l = 1, 10 + end do +!$omp end parallel do + end subroutine test1 diff --git a/gcc/testsuite/gfortran.dg/gomp/omp_do1.f90 b/gcc/testsuite/gfortran.dg/gomp/omp_do1.f90 new file mode 100644 index 000000000..c97af1ddb --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/omp_do1.f90 @@ -0,0 +1,57 @@ +! { dg-do compile } +! { dg-options "-fopenmp -std=gnu" } +subroutine foo + integer :: i, j + integer, dimension (30) :: a + double precision :: d + i = 0 +!$omp do private (i) + do 100 ! { dg-error "cannot be a DO WHILE or DO without loop control" } + if (i .gt. 0) exit ! { dg-error "EXIT statement" } +100 i = i + 1 + i = 0 +!$omp do private (i) + do ! { dg-error "cannot be a DO WHILE or DO without loop control" } + if (i .gt. 0) exit ! { dg-error "EXIT statement" } + i = i + 1 + end do + i = 0 +!$omp do private (i) + do 200 while (i .lt. 4) ! { dg-error "cannot be a DO WHILE or DO without loop control" } +200 i = i + 1 +!$omp do private (i) + do while (i .lt. 8) ! { dg-error "cannot be a DO WHILE or DO without loop control" } + i = i + 1 + end do +!$omp do + do 300 d = 1, 30, 6 ! { dg-warning "Deleted feature: Loop variable" } + i = d +300 a(i) = 1 +!$omp do + do d = 1, 30, 5 ! { dg-warning "Deleted feature: Loop variable" } + i = d + a(i) = 2 + end do +!$omp do + do i = 1, 30 + if (i .eq. 16) exit ! { dg-error "EXIT statement" } + end do +!$omp do +outer: do i = 1, 30 + do j = 5, 10 + if (i .eq. 6 .and. j .eq. 7) exit outer ! { dg-error "EXIT statement" } + end do + end do outer +last: do i = 1, 30 +!$omp parallel + if (i .eq. 21) exit last ! { dg-error "leaving OpenMP structured block" } +!$omp end parallel + end do last +!$omp parallel do shared (i) + do i = 1, 30, 2 ! { dg-error "iteration variable present on clause" } + a(i) = 5 + end do +!$omp end parallel do +end subroutine +! { dg-error "iteration variable must be of type integer" "" { target *-*-* } 27 } +! { dg-error "iteration variable must be of type integer" "" { target *-*-* } 31 } diff --git a/gcc/testsuite/gfortran.dg/gomp/omp_parse1.f90 b/gcc/testsuite/gfortran.dg/gomp/omp_parse1.f90 new file mode 100644 index 000000000..3ab436707 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/omp_parse1.f90 @@ -0,0 +1,20 @@ +! { dg-do compile } +! { dg-options "-fopenmp -fdump-tree-omplower" } + !$omp parallel +call bar + !$omp end parallel + !$omp p& +!$omp&arallel +call bar +!$omp e& +!$omp&ndparallel +!$omp & +!$omp & & +!$omp pa& +!$omp rallel +call bar +!$omp end parallel +end + +! { dg-final { scan-tree-dump-times "pragma omp parallel" 3 "omplower" } } +! { dg-final { cleanup-tree-dump "omplower" } } diff --git a/gcc/testsuite/gfortran.dg/gomp/omp_parse2.f b/gcc/testsuite/gfortran.dg/gomp/omp_parse2.f new file mode 100644 index 000000000..510d33795 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/omp_parse2.f @@ -0,0 +1,14 @@ +c { dg-do compile } +c { dg-options "-fopenmp -fdump-tree-omplower" } +!$omp parallel + call bar +c$omp end parallel +C$omp p +*$omp+arallel + call bar +!$omp e +!$omp+ndparallel + end + +! { dg-final { scan-tree-dump-times "pragma omp parallel" 2 "omplower" } } +! { dg-final { cleanup-tree-dump "omplower" } } diff --git a/gcc/testsuite/gfortran.dg/gomp/omp_threadprivate1.f90 b/gcc/testsuite/gfortran.dg/gomp/omp_threadprivate1.f90 new file mode 100644 index 000000000..2ccf93cac --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/omp_threadprivate1.f90 @@ -0,0 +1,18 @@ +! { dg-require-effective-target tls } + module omp_threadprivate1 + common /T/ a + end module omp_threadprivate1 + subroutine bad1 + use omp_threadprivate1 +!$omp threadprivate (/T/) ! { dg-error "not found" } + end subroutine bad1 + subroutine bad2 + common /S/ b +!$omp threadprivate (/S/) + contains + subroutine bad3 +!$omp parallel copyin (/T/) ! { dg-error "not found" } +!$omp end parallel ! { dg-error "" } + end subroutine bad3 + end subroutine bad2 +! { dg-final { cleanup-modules "omp_threadprivate1" } } diff --git a/gcc/testsuite/gfortran.dg/gomp/omp_threadprivate2.f90 b/gcc/testsuite/gfortran.dg/gomp/omp_threadprivate2.f90 new file mode 100644 index 000000000..cd1ab5cd6 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/omp_threadprivate2.f90 @@ -0,0 +1,6 @@ +! { dg-do compile } +! { dg-require-effective-target tls } + subroutine bad1 + double precision :: d ! { dg-error "isn't SAVEd" } +!$omp threadprivate (d) + end subroutine bad1 diff --git a/gcc/testsuite/gfortran.dg/gomp/pr26224.f b/gcc/testsuite/gfortran.dg/gomp/pr26224.f new file mode 100644 index 000000000..0446d5254 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr26224.f @@ -0,0 +1,8 @@ +C PR fortran/26224 +C { dg-do compile } + + PROGRAM PR26224 + INTEGER FOO +C$OMP SINGLE +C$OMP END SINGLE COPYPRIVATE (FOO, BAR) + END diff --git a/gcc/testsuite/gfortran.dg/gomp/pr27573.f90 b/gcc/testsuite/gfortran.dg/gomp/pr27573.f90 new file mode 100644 index 000000000..1d3d3b751 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr27573.f90 @@ -0,0 +1,13 @@ +! PR middle-end/27573 +! { dg-do compile } +! { dg-options "-O2 -fopenmp -fprofile-generate" } + +program pr27573 + integer i,j + j = 8 + !$omp parallel + print *, "foo" + do i = 1, j - 1 + end do + !$omp end parallel +end diff --git a/gcc/testsuite/gfortran.dg/gomp/pr29759.f90 b/gcc/testsuite/gfortran.dg/gomp/pr29759.f90 new file mode 100644 index 000000000..b723eeb3c --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr29759.f90 @@ -0,0 +1,42 @@ +! PR fortran/29759 +! { dg-do compile } + +PROGRAM test_omp +!$OMP PARALLEL & +!$OMP NUM_THREADS(2) +!$OMP END PARALLEL + +!$OMP PARALLEL & +!$OMP & NUM_THREADS(2) +!$OMP END PARALLEL + +!$OMP PARALLEL & +! +!$OMP NUM_THREADS(2) +!$OMP END PARALLEL + +!$OMP PARALLEL & +! +!$OMP & NUM_THREADS(2) +!$OMP END PARALLEL + + +!$OMP PARALLEL & ! { dg-error "Unclassifiable OpenMP" } +!$ NUM_THREADS(2) ! { dg-error "Unclassifiable|Invalid character" } +!$OMP END PARALLEL ! { dg-error "Unexpected" } + +!$OMP PARALLEL & ! { dg-error "Unclassifiable OpenMP" } +!$ & NUM_THREADS(2) ! { dg-error "Unclassifiable|Invalid character" } +!$OMP END PARALLEL ! { dg-error "Unexpected" } + +!$OMP PARALLEL & ! { dg-error "Unclassifiable OpenMP" } +! +!$ NUM_THREADS(2) ! { dg-error "Unclassifiable|Invalid character" } +!$OMP END PARALLEL ! { dg-error "Unexpected" } + +!$OMP PARALLEL & ! { dg-error "Unclassifiable OpenMP" } +! +!$ & NUM_THREADS(2) ! { dg-error "Unclassifiable|Invalid character" } +!$OMP END PARALLEL ! { dg-error "Unexpected" } + +END PROGRAM diff --git a/gcc/testsuite/gfortran.dg/gomp/pr33439.f90 b/gcc/testsuite/gfortran.dg/gomp/pr33439.f90 new file mode 100644 index 000000000..f7db7593d --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr33439.f90 @@ -0,0 +1,38 @@ +! PR fortran/33439 +! { dg-do compile } +! { dg-options "-fopenmp" } + +subroutine pr33439_1 + integer :: s, i + s = 4 +!$omp parallel default(none) ! { dg-error "enclosing parallel" } + call somethingelse +!$omp do schedule(static, s) ! { dg-error "not specified in enclosing parallel" } + do i = 1, 8 + call something + end do +!$omp end do +!$omp end parallel +end subroutine pr33439_1 + +subroutine pr33439_2 + integer :: s, i + s = 4 +!$omp parallel default(none) ! { dg-error "enclosing parallel" } +!$omp do schedule(static, s) ! { dg-error "not specified in enclosing parallel" } + do i = 1, 8 + call something + end do +!$omp end do +!$omp end parallel +end subroutine pr33439_2 + +subroutine pr33439_3 + integer :: s, i + s = 4 +!$omp parallel do default(none) schedule(static, s) ! { dg-error "enclosing parallel" } + do i = 1, 8 + call something + end do +!$omp end parallel do +end subroutine pr33439_3 diff --git a/gcc/testsuite/gfortran.dg/gomp/pr35786-1.f90 b/gcc/testsuite/gfortran.dg/gomp/pr35786-1.f90 new file mode 100644 index 000000000..c8639abdb --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr35786-1.f90 @@ -0,0 +1,74 @@ +! PR fortran/35786 +! { dg-do compile } +! { dg-options "-fopenmp" } + +module pr35768 + real, parameter :: one = 1.0 +contains + subroutine fn1 + !$omp parallel firstprivate (one) ! { dg-error "is not a variable" } + !$omp end parallel + end subroutine fn1 + subroutine fn2 (doit) + external doit + !$omp parallel firstprivate (doit) ! { dg-error "is not a variable" } + call doit () + !$omp end parallel + end subroutine fn2 + subroutine fn3 + interface fn4 + subroutine fn4 () + end subroutine fn4 + end interface + !$omp parallel private (fn4) ! { dg-error "is not a variable" } + call fn4 () + !$omp end parallel + end subroutine fn3 + subroutine fn5 + interface fn6 + function fn6 () + integer :: fn6 + end function fn6 + end interface + integer :: x + !$omp parallel private (fn6, x) ! { dg-error "is not a variable" } + x = fn6 () + !$omp end parallel + end subroutine fn5 + function fn7 () result (re7) + integer :: re7 + !$omp parallel private (fn7) ! { dg-error "is not a variable" } + !$omp end parallel + end function fn7 + function fn8 () result (re8) + integer :: re8 + call fn9 + contains + subroutine fn9 + !$omp parallel private (fn8) ! { dg-error "is not a variable" } + !$omp end parallel + end subroutine fn9 + end function fn8 + function fn10 () result (re10) + integer :: re10, re11 + entry fn11 () result (re11) + !$omp parallel private (fn10) ! { dg-error "is not a variable" } + !$omp end parallel + !$omp parallel private (fn11) ! { dg-error "is not a variable" } + !$omp end parallel + end function fn10 + function fn12 () result (re12) + integer :: re12, re13 + entry fn13 () result (re13) + call fn14 + contains + subroutine fn14 + !$omp parallel private (fn12) ! { dg-error "is not a variable" } + !$omp end parallel + !$omp parallel private (fn13) ! { dg-error "is not a variable" } + !$omp end parallel + end subroutine fn14 + end function fn12 +end module + +! { dg-final { cleanup-modules "pr35768" } } diff --git a/gcc/testsuite/gfortran.dg/gomp/pr35786-2.f90 b/gcc/testsuite/gfortran.dg/gomp/pr35786-2.f90 new file mode 100644 index 000000000..beb1a828d --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr35786-2.f90 @@ -0,0 +1,48 @@ +! PR fortran/35786 +! { dg-do compile } +! { dg-options "-fopenmp" } + +function fn7 () + integer :: fn7 + !$omp parallel private (fn7) + fn7 = 6 + !$omp end parallel + fn7 = 7 +end function fn7 +function fn8 () + integer :: fn8 + call fn9 +contains + subroutine fn9 + !$omp parallel private (fn8) + fn8 = 6 + !$omp end parallel + fn8 = 7 + end subroutine fn9 +end function fn8 +function fn10 () + integer :: fn10, fn11 + entry fn11 () + !$omp parallel private (fn10) + fn10 = 6 + !$omp end parallel + !$omp parallel private (fn11) + fn11 = 6 + !$omp end parallel + fn10 = 7 +end function fn10 +function fn12 () + integer :: fn12, fn13 + entry fn13 () + call fn14 +contains + subroutine fn14 + !$omp parallel private (fn12) + fn12 = 6 + !$omp end parallel + !$omp parallel private (fn13) + fn13 = 6 + !$omp end parallel + fn12 = 7 + end subroutine fn14 +end function fn12 diff --git a/gcc/testsuite/gfortran.dg/gomp/pr36726.f90 b/gcc/testsuite/gfortran.dg/gomp/pr36726.f90 new file mode 100644 index 000000000..99e170ad7 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr36726.f90 @@ -0,0 +1,20 @@ +! PR middle-end/36726 +! { dg-do compile } +! { dg-options "-fopenmp" } + +subroutine foo + integer, allocatable :: vs(:) + !$omp parallel private (vs) + allocate (vs(10)) + vs = 2 + deallocate (vs) + !$omp end parallel +end subroutine foo +subroutine bar + integer, allocatable :: vs(:) + !$omp parallel private (vs) + allocate (vs(10)) + vs = 2 + deallocate (vs) + !$omp end parallel +end subroutine bar diff --git a/gcc/testsuite/gfortran.dg/gomp/pr39152.f90 b/gcc/testsuite/gfortran.dg/gomp/pr39152.f90 new file mode 100644 index 000000000..ff088b5ef --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr39152.f90 @@ -0,0 +1,32 @@ +! { dg-do compile { target { { i?86-*-* x86_64-*-* } && ilp32 } } } +! { dg-options "-march=i486 -fopenmp -mavx -O3 -funroll-all-loops" } + + call test_workshare + +contains + subroutine test_workshare + integer :: i, j, k, l, m + double precision, dimension (64) :: d, e + integer, dimension (10) :: f, g + integer, dimension (16, 16) :: a, b, c + integer, dimension (16) :: n +!$omp parallel num_threads (4) private (j, k) +!$omp barrier +!$omp workshare + where (g .lt. 0) + f = 100 + elsewhere + where (g .gt. 6) f = f + sum (g) + f = 300 + f + end where +!$omp end workshare nowait +!$omp workshare + forall (j = 1:16, k = 1:16) b (k, j) = a (j, k) + forall (j = 2:16, n (17 - j) / 4 * 4 .ne. n (17 - j)) + n (j) = n (j - 1) * n (j) + end forall +!$omp endworkshare +!$omp end parallel + + end subroutine test_workshare +end diff --git a/gcc/testsuite/gfortran.dg/gomp/pr39354.f90 b/gcc/testsuite/gfortran.dg/gomp/pr39354.f90 new file mode 100644 index 000000000..3b9c32784 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr39354.f90 @@ -0,0 +1,37 @@ +! PR fortran/39354 +! { dg-do compile } +! { dg-options "-fopenmp" } + SUBROUTINE ltest(l1, l2, l3, l4, r1, r2, r3, r4) + LOGICAL l1, l2, l3, l4, r1, r2, r3, r4 +!$OMP ATOMIC + l1 = l1 .and. r1 +!$OMP ATOMIC + l2 = l2 .or. r2 +!$OMP ATOMIC + l3 = l3 .eqv. r3 +!$OMP ATOMIC + l4 = l4 .neqv. r4 + END + SUBROUTINE itest(l1, l2, l3, l4, l5, l6, l7, l8, l9, & +& r1, r2, r3, r4, r5, r6, r7, r8, r9) + INTEGER l1, l2, l3, l4, l5, l6, l7, l8, l9, & +& r1, r2, r3, r4, r5, r6, r7, r8, r9 +!$OMP ATOMIC + l1 = l1 + r1 +!$OMP ATOMIC + l2 = l2 - r2 +!$OMP ATOMIC + l3 = l3 * r3 +!$OMP ATOMIC + l4 = l4 / r4 +!$OMP ATOMIC + l5 = max (l5, r1, r5) +!$OMP ATOMIC + l6 = min (r1, r6, l6) +!$OMP ATOMIC + l7 = iand (l7, r7) +!$OMP ATOMIC + l8 = ior (r8, l8) +!$OMP ATOMIC + l9 = ieor (l9, r9) + END diff --git a/gcc/testsuite/gfortran.dg/gomp/pr40878-1.f90 b/gcc/testsuite/gfortran.dg/gomp/pr40878-1.f90 new file mode 100644 index 000000000..86202ab5d --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr40878-1.f90 @@ -0,0 +1,63 @@ +! PR fortran/40878 +! { dg-do compile } +! { dg-options "-fopenmp" } + +subroutine test1 + integer :: j, k + integer :: m = 2 +!$omp parallel do collapse(m) schedule (static,1) ! { dg-error "Constant expression required" } + do k = 1, 2 + do j = 1, 6 + enddo + enddo +!$omp end parallel do +end +subroutine test2 + integer :: j, k + integer :: m + m = 2 +!$omp parallel do collapse(m) schedule (static,1) ! { dg-error "Constant expression required" } + do k = 1, 2 + do j = 1, 6 + enddo + enddo +!$omp end parallel do +end +subroutine test3 + integer :: j, k + integer, parameter :: m = 0 +!$omp parallel do collapse(m) schedule (static,1) ! { dg-error "not constant positive integer" } + do k = 1, 2 + do j = 1, 6 + enddo + enddo +!$omp end parallel do +end +subroutine test4 + integer :: j, k + integer, parameter :: m = -2 +!$omp parallel do collapse(m) schedule (static,1) ! { dg-error "not constant positive integer" } + do k = 1, 2 + do j = 1, 6 + enddo + enddo +!$omp end parallel do +end +subroutine test5 + integer :: j, k +!$omp parallel do collapse(0) schedule (static,1) ! { dg-error "not constant positive integer" } + do k = 1, 2 + do j = 1, 6 + enddo + enddo +!$omp end parallel do +end +subroutine test6 + integer :: j, k +!$omp parallel do collapse(-1) schedule (static,1) ! { dg-error "not constant positive integer" } + do k = 1, 2 + do j = 1, 6 + enddo + enddo +!$omp end parallel do +end diff --git a/gcc/testsuite/gfortran.dg/gomp/pr40878-2.f90 b/gcc/testsuite/gfortran.dg/gomp/pr40878-2.f90 new file mode 100644 index 000000000..a118aa860 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr40878-2.f90 @@ -0,0 +1,23 @@ +! PR fortran/40878 +! { dg-do compile } +! { dg-options "-fopenmp" } + +subroutine test1 + integer :: j, k + integer, parameter :: m = 2 +!$omp parallel do collapse(m) schedule (static,1) + do k = 1, 2 + do j = 1, 6 + enddo + enddo +!$omp end parallel do +end +subroutine test2 + integer :: j, k +!$omp parallel do collapse(2) schedule (static,1) + do k = 1, 2 + do j = 1, 6 + enddo + enddo +!$omp end parallel do +end diff --git a/gcc/testsuite/gfortran.dg/gomp/pr41344.f b/gcc/testsuite/gfortran.dg/gomp/pr41344.f new file mode 100644 index 000000000..66ae8b35d --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr41344.f @@ -0,0 +1,16 @@ + subroutine xrotate(nerr) + + common /dfm/ndfl + +*$omp parallel private(ix) + ix = 0 +*$omp do + do i=1,ndfl + ix = ix + 1 + if (ix.gt.5) go to 9000 ! { dg-error "invalid (exit|branch)" } + enddo +*$omp end do +*$omp end parallel + +9000 continue + end diff --git a/gcc/testsuite/gfortran.dg/gomp/pr43337.f90 b/gcc/testsuite/gfortran.dg/gomp/pr43337.f90 new file mode 100644 index 000000000..f07ccb441 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr43337.f90 @@ -0,0 +1,30 @@ +! PR middle-end/43337 +! { dg-do compile } +! { dg-options "-fopenmp -O2 -g" } + +subroutine pr43337 + integer :: a, b(10) + call foo (b) + call bar (b) +contains + subroutine foo (b) + integer :: b(10) +!$omp parallel if (.false.) +!$omp task if (.false.) shared(b) + do a = 1, 10 + b(a) = 1 + end do +!$omp end task +!$omp end parallel + end subroutine foo + subroutine bar (b) + integer :: b(10) +!$omp parallel if (.false.) +!$omp parallel if (.false.) + do a = 1, 10 + b(a) = 1 + end do +!$omp end parallel +!$omp end parallel + end subroutine bar +end subroutine pr43337 diff --git a/gcc/testsuite/gfortran.dg/gomp/pr43711.f90 b/gcc/testsuite/gfortran.dg/gomp/pr43711.f90 new file mode 100644 index 000000000..e47e586ea --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr43711.f90 @@ -0,0 +1,18 @@ +! { dg-do compile } +! { dg-options "-fopenmp" } +! +! PR fortran/43711 uninformative error message for two 'nowait' in omp statement +! Contributed by Bill Long <longb AT cray DOT com> + +program NF03_2_5_2_1a + !$omp parallel + !$omp sections + !$omp section + print *, 'FAIL' + !$omp section + print *, 'FAIL' + !$omp end sections nowait nowait ! { dg-error "Unexpected junk" } + !$omp end parallel +end program NF03_2_5_2_1a + +! { dg-excess-errors "Unexpected" } diff --git a/gcc/testsuite/gfortran.dg/gomp/pr43836.f90 b/gcc/testsuite/gfortran.dg/gomp/pr43836.f90 new file mode 100644 index 000000000..cf86523f5 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr43836.f90 @@ -0,0 +1,10 @@ +! PR fortran/43836 +! { dg-do compile } +! { dg-options "-fopenmp -fexceptions -O2" } +subroutine foo +!$omp single +!$omp parallel + call bar +!$omp end parallel +!$omp end single +end subroutine foo diff --git a/gcc/testsuite/gfortran.dg/gomp/pr44036-1.f90 b/gcc/testsuite/gfortran.dg/gomp/pr44036-1.f90 new file mode 100644 index 000000000..a4633a3e9 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr44036-1.f90 @@ -0,0 +1,24 @@ +! PR fortran/44036 +! { dg-do compile } +! { dg-options "-fopenmp" } +subroutine foo(a, b) + integer, external :: a + integer, external, pointer :: b + integer, external :: c + integer, external, pointer :: d + integer :: x + x = 6 +!$omp parallel default(none) private (x) + x = a(4) +!$omp end parallel +!$omp parallel default(none) private (x) ! { dg-error "enclosing parallel" } + x = b(5) ! { dg-error "not specified in" } +!$omp end parallel +!$omp parallel default(none) private (x) + x = c(6) +!$omp end parallel + d => a +!$omp parallel default(none) private (x) ! { dg-error "enclosing parallel" } + x = d(7) ! { dg-error "not specified in" } +!$omp end parallel +end diff --git a/gcc/testsuite/gfortran.dg/gomp/pr44036-2.f90 b/gcc/testsuite/gfortran.dg/gomp/pr44036-2.f90 new file mode 100644 index 000000000..c9320f139 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr44036-2.f90 @@ -0,0 +1,17 @@ +! PR fortran/44036 +! { dg-do compile } +! { dg-options "-fopenmp" } +subroutine foo(a, b) + integer, external :: a + integer, external, pointer :: b + integer, external :: c + integer, external, pointer :: d + integer :: x + d => a +!$omp parallel default(none) private (x) firstprivate (b, d) + x = a(4) + x = b(5) + x = c(6) + x = d(7) +!$omp end parallel +end diff --git a/gcc/testsuite/gfortran.dg/gomp/pr44036-3.f90 b/gcc/testsuite/gfortran.dg/gomp/pr44036-3.f90 new file mode 100644 index 000000000..449cb9572 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr44036-3.f90 @@ -0,0 +1,13 @@ +! PR fortran/44036 +! { dg-do compile } +! { dg-options "-fopenmp" } +subroutine foo(a) + integer, external :: a, c + integer :: x +!$omp parallel default(none) private (x) shared (a) ! { dg-error "is not a variable" } + x = a(6) +!$omp end parallel +!$omp parallel default(none) private (x) shared (c) ! { dg-error "is not a variable" } + x = c(6) +!$omp end parallel +end diff --git a/gcc/testsuite/gfortran.dg/gomp/pr44085.f90 b/gcc/testsuite/gfortran.dg/gomp/pr44085.f90 new file mode 100644 index 000000000..db8fbbc95 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr44085.f90 @@ -0,0 +1,25 @@ +! PR middle-end/44085 +! { dg-do compile } +! { dg-require-effective-target tls_native } +! { dg-options "-fopenmp" } + + integer, save :: thr1, thr2 + integer :: thr3, thr4 + common /thrs/ thr3, thr4 +!$omp threadprivate (thr1, thr2, /thrs/) + +!$omp task untied ! { dg-error "enclosing task" } + thr1 = thr1 + 1 ! { dg-error "used in untied task" } + thr2 = thr2 + 2 ! { dg-error "used in untied task" } + thr3 = thr3 + 3 ! { dg-error "used in untied task" } + thr4 = thr4 + 4 ! { dg-error "used in untied task" } +!$omp end task + +!$omp task + thr1 = thr1 + 1 + thr2 = thr2 + 2 + thr3 = thr3 + 3 + thr4 = thr4 + 4 +!$omp end task + + end diff --git a/gcc/testsuite/gfortran.dg/gomp/pr44536.f90 b/gcc/testsuite/gfortran.dg/gomp/pr44536.f90 new file mode 100644 index 000000000..0dc896dcc --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr44536.f90 @@ -0,0 +1,10 @@ +! PR fortran/44536 +! { dg-do compile } +! { dg-options "-fopenmp" } + subroutine foo (a, i, j) + integer, dimension(:) :: a + integer :: i, j +!$omp parallel default(none) shared(i, j) ! { dg-error "enclosing parallel" } + j=a(i) ! { dg-error "not specified in" } +!$omp end parallel + end subroutine diff --git a/gcc/testsuite/gfortran.dg/gomp/pr44847.f90 b/gcc/testsuite/gfortran.dg/gomp/pr44847.f90 new file mode 100644 index 000000000..3da431149 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr44847.f90 @@ -0,0 +1,86 @@ +! PR fortran/44847 +! { dg-do compile } +! { dg-options "-fopenmp" } + +subroutine pr44847_1 + integer :: i, j +!$omp parallel do collapse(2) +l:do i = 1, 2 + do j = 1, 2 + cycle l ! { dg-error "CYCLE statement" } + end do + end do l +end subroutine +subroutine pr44847_2 + integer :: i, j, k +!$omp parallel do collapse(3) + do i = 1, 2 + l:do j = 1, 2 + do k = 1, 2 + cycle l ! { dg-error "CYCLE statement" } + end do + end do l + end do +end subroutine +subroutine pr44847_3 + integer :: i, j +!$omp parallel do +l:do i = 1, 2 + do j = 1, 2 + cycle l + end do + end do l +end subroutine +subroutine pr44847_4 + integer :: i, j, k +!$omp parallel do collapse(2) + do i = 1, 2 + l:do j = 1, 2 + do k = 1, 2 + cycle l + end do + end do l + end do +end subroutine +subroutine pr44847_5 + integer :: i, j +!$omp parallel do collapse(2) +l:do i = 1, 2 + do j = 1, 2 + exit l ! { dg-error "EXIT statement" } + end do + end do l +end subroutine +subroutine pr44847_6 + integer :: i, j, k +!$omp parallel do collapse(3) + do i = 1, 2 + l:do j = 1, 2 + do k = 1, 2 + exit l ! { dg-error "EXIT statement" } + end do + end do l + end do +end subroutine +subroutine pr44847_7 + integer :: i, j, k +!$omp parallel do collapse(2) + do i = 1, 2 + l:do j = 1, 2 + do k = 1, 2 + exit l ! { dg-error "EXIT statement" } + end do + end do l + end do +end subroutine +subroutine pr44847_8 + integer :: i, j, k +!$omp parallel do + do i = 1, 2 + l:do j = 1, 2 + do k = 1, 2 + exit l + end do + end do l + end do +end subroutine diff --git a/gcc/testsuite/gfortran.dg/gomp/pr45172.f90 b/gcc/testsuite/gfortran.dg/gomp/pr45172.f90 new file mode 100644 index 000000000..dbb242bb1 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr45172.f90 @@ -0,0 +1,21 @@ +! { dg-do compile } +! { dg-options "-O -fopenmp -fexceptions" } + + SUBROUTINE dbcsr_mult_m_e_e ( ) + LOGICAL, PARAMETER :: use_combined_types = .FALSE. + INTEGER, ALLOCATABLE, DIMENSION(:, :) :: right_index_sr + INTEGER, ALLOCATABLE, DIMENSION(:, :, :) :: my_sizes + INTEGER, ALLOCATABLE, DIMENSION(:, :, :, :) :: all_sizes + ALLOCATE (all_sizes(4, LBOUND(my_sizes,2):UBOUND(my_sizes,2), & + LBOUND(my_sizes,3):UBOUND(my_sizes,3), 0:numnodes-1)) + IF (use_combined_types) THEN + CALL mp_waitall (right_index_sr) + ENDIF + DO ki = 0, min_nimages-1 +!$omp parallel default (none) & +!$omp reduction (+: flop_single, t_all, t_dgemm) +!$omp end parallel + ENDDO + checksum = dbcsr_checksum (product_matrix, error) + END SUBROUTINE dbcsr_mult_m_e_e + diff --git a/gcc/testsuite/gfortran.dg/gomp/pr45595.f90 b/gcc/testsuite/gfortran.dg/gomp/pr45595.f90 new file mode 100644 index 000000000..ab10c3f95 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr45595.f90 @@ -0,0 +1,10 @@ +! PR fortran/45595 +! { dg-do compile } +! { dg-options "-fopenmp" } + +subroutine foo(l,u) + integer :: k,l,u + !$omp parallel do shared(l,u) collapse(3) ! { dg-error "not enough DO loops" } + do k = l,u + end do +end subroutine diff --git a/gcc/testsuite/gfortran.dg/gomp/pr45597.f90 b/gcc/testsuite/gfortran.dg/gomp/pr45597.f90 new file mode 100644 index 000000000..6d6a65d44 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr45597.f90 @@ -0,0 +1,22 @@ +! PR fortran/45597 +! { dg-do compile } +! { dg-options "-fopenmp" } + +subroutine foo(n) + integer :: i, n(6) + !$omp parallel do default(none) shared(n) + do i = 1, 6 + if (n(i).gt.0) cycle + end do +end subroutine +subroutine bar(n) + integer :: i, j, k, n(6, 6, 6) + !$omp parallel do default(none) shared(n) collapse(3) + do i = 1, 6 + do j = 1, 6 + do k = 1, 6 + if (n(i, j, k).gt.0) cycle + end do + end do + end do +end subroutine diff --git a/gcc/testsuite/gfortran.dg/gomp/pr47331.f90 b/gcc/testsuite/gfortran.dg/gomp/pr47331.f90 new file mode 100644 index 000000000..71713e022 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr47331.f90 @@ -0,0 +1,24 @@ +! PR fortran/47331 +! { dg-do compile } +! { dg-options "-fopenmp -fwhole-file" } + +subroutine foo + !$omp parallel + call bar () + !$omp end parallel +end subroutine foo + +subroutine bar + integer :: k + do k=1,5 + call baz (k) + end do +end subroutine bar + +subroutine baz (k) + integer :: k +end subroutine + +program pr47331 + call foo +end program pr47331 diff --git a/gcc/testsuite/gfortran.dg/gomp/pr48117.f90 b/gcc/testsuite/gfortran.dg/gomp/pr48117.f90 new file mode 100644 index 000000000..bc8ad9bc3 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr48117.f90 @@ -0,0 +1,11 @@ +! PR fortran/48117 +! { dg-do compile } +! { dg-options "-O2 -fopenmp" } + +subroutine foo(x) + character(len=*), optional :: x + character(len=80) :: v + !$omp master + if (present(x)) v = adjustl(x) + !$omp end master +end subroutine foo diff --git a/gcc/testsuite/gfortran.dg/gomp/pr48611.f90 b/gcc/testsuite/gfortran.dg/gomp/pr48611.f90 new file mode 100644 index 000000000..643cc5c3e --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr48611.f90 @@ -0,0 +1,12 @@ +! PR tree-optimization/48611 +! { dg-do compile } +! { dg-options "-Os -fopenmp -fexceptions -fno-tree-ccp -fno-tree-copy-prop" } + + integer, allocatable :: a(:) + logical :: l +!$omp parallel private (a) reduction (.or.:l) + do i = 1, 7 + a(:) = i + end do +!$omp end parallel +end diff --git a/gcc/testsuite/gfortran.dg/gomp/pr48794.f90 b/gcc/testsuite/gfortran.dg/gomp/pr48794.f90 new file mode 100644 index 000000000..11edb0bb4 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/pr48794.f90 @@ -0,0 +1,12 @@ +! PR tree-optimization/48794 +! { dg-do compile } +! { dg-options "-Os -fopenmp -fexceptions -fno-tree-ccp -fno-tree-copy-prop" } + + integer, allocatable :: a(:) + logical :: l + if (allocated (a)) call abort +!$omp parallel private (a) reduction (.or.:l) + do i = 1, 7 + end do +!$omp end parallel +end diff --git a/gcc/testsuite/gfortran.dg/gomp/reduction1.f90 b/gcc/testsuite/gfortran.dg/gomp/reduction1.f90 new file mode 100644 index 000000000..4912f7178 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/reduction1.f90 @@ -0,0 +1,132 @@ +! { dg-do compile } +! { dg-options "-fopenmp -fmax-errors=100" } +! { dg-require-effective-target tls } + +subroutine foo (ia1) +integer :: i1, i2, i3 +integer, dimension (*) :: ia1 +integer, dimension (10) :: ia2 +real :: r1 +real, dimension (5) :: ra1 +double precision :: d1 +double precision, dimension (4) :: da1 +complex :: c1 +complex, dimension (7) :: ca1 +logical :: l1 +logical, dimension (3) :: la1 +character (5) :: a1 +type t + integer :: i +end type +type(t) :: t1 +type(t), dimension (2) :: ta1 +real, pointer :: p1 => NULL() +integer, allocatable :: aa1 (:,:) +save i2 +!$omp threadprivate (i2) +common /blk/ i1 + +!$omp parallel reduction (+:i3, ia2, r1, ra1, d1, da1, c1, ca1) +!$omp end parallel +!$omp parallel reduction (*:i3, ia2, r1, ra1, d1, da1, c1, ca1) +!$omp end parallel +!$omp parallel reduction (-:i3, ia2, r1, ra1, d1, da1, c1, ca1) +!$omp end parallel +!$omp parallel reduction (.and.:l1, la1) +!$omp end parallel +!$omp parallel reduction (.or.:l1, la1) +!$omp end parallel +!$omp parallel reduction (.eqv.:l1, la1) +!$omp end parallel +!$omp parallel reduction (.neqv.:l1, la1) +!$omp end parallel +!$omp parallel reduction (min:i3, ia2, r1, ra1, d1, da1) +!$omp end parallel +!$omp parallel reduction (max:i3, ia2, r1, ra1, d1, da1) +!$omp end parallel +!$omp parallel reduction (iand:i3, ia2) +!$omp end parallel +!$omp parallel reduction (ior:i3, ia2) +!$omp end parallel +!$omp parallel reduction (ieor:i3, ia2) +!$omp end parallel +!$omp parallel reduction (+:/blk/) ! { dg-error "Syntax error" } +!$omp end parallel ! { dg-error "Unexpected" } +!$omp parallel reduction (+:i2) ! { dg-error "THREADPRIVATE object" } +!$omp end parallel +!$omp parallel reduction (*:p1) ! { dg-error "POINTER object" } +!$omp end parallel +!$omp parallel reduction (-:aa1) +!$omp end parallel +!$omp parallel reduction (*:ia1) ! { dg-error "Assumed size" } +!$omp end parallel +!$omp parallel reduction (+:l1) ! { dg-error "must be of numeric type, got LOGICAL" } +!$omp end parallel +!$omp parallel reduction (*:la1) ! { dg-error "must be of numeric type, got LOGICAL" } +!$omp end parallel +!$omp parallel reduction (-:a1) ! { dg-error "must be of numeric type, got CHARACTER" } +!$omp end parallel +!$omp parallel reduction (+:t1) ! { dg-error "must be of numeric type, got TYPE" } +!$omp end parallel +!$omp parallel reduction (*:ta1) ! { dg-error "must be of numeric type, got TYPE" } +!$omp end parallel +!$omp parallel reduction (.and.:i3) ! { dg-error "must be LOGICAL" } +!$omp end parallel +!$omp parallel reduction (.or.:ia2) ! { dg-error "must be LOGICAL" } +!$omp end parallel +!$omp parallel reduction (.eqv.:r1) ! { dg-error "must be LOGICAL" } +!$omp end parallel +!$omp parallel reduction (.neqv.:ra1) ! { dg-error "must be LOGICAL" } +!$omp end parallel +!$omp parallel reduction (.and.:d1) ! { dg-error "must be LOGICAL" } +!$omp end parallel +!$omp parallel reduction (.or.:da1) ! { dg-error "must be LOGICAL" } +!$omp end parallel +!$omp parallel reduction (.eqv.:c1) ! { dg-error "must be LOGICAL" } +!$omp end parallel +!$omp parallel reduction (.neqv.:ca1) ! { dg-error "must be LOGICAL" } +!$omp end parallel +!$omp parallel reduction (.and.:a1) ! { dg-error "must be LOGICAL" } +!$omp end parallel +!$omp parallel reduction (.or.:t1) ! { dg-error "must be LOGICAL" } +!$omp end parallel +!$omp parallel reduction (.eqv.:ta1) ! { dg-error "must be LOGICAL" } +!$omp end parallel +!$omp parallel reduction (min:c1) ! { dg-error "must be INTEGER or REAL" } +!$omp end parallel +!$omp parallel reduction (max:ca1) ! { dg-error "must be INTEGER or REAL" } +!$omp end parallel +!$omp parallel reduction (max:l1) ! { dg-error "must be INTEGER or REAL" } +!$omp end parallel +!$omp parallel reduction (min:la1) ! { dg-error "must be INTEGER or REAL" } +!$omp end parallel +!$omp parallel reduction (max:a1) ! { dg-error "must be INTEGER or REAL" } +!$omp end parallel +!$omp parallel reduction (min:t1) ! { dg-error "must be INTEGER or REAL" } +!$omp end parallel +!$omp parallel reduction (max:ta1) ! { dg-error "must be INTEGER or REAL" } +!$omp end parallel +!$omp parallel reduction (iand:r1) ! { dg-error "must be INTEGER" } +!$omp end parallel +!$omp parallel reduction (ior:ra1) ! { dg-error "must be INTEGER" } +!$omp end parallel +!$omp parallel reduction (ieor:d1) ! { dg-error "must be INTEGER" } +!$omp end parallel +!$omp parallel reduction (ior:da1) ! { dg-error "must be INTEGER" } +!$omp end parallel +!$omp parallel reduction (iand:c1) ! { dg-error "must be INTEGER" } +!$omp end parallel +!$omp parallel reduction (ior:ca1) ! { dg-error "must be INTEGER" } +!$omp end parallel +!$omp parallel reduction (ieor:l1) ! { dg-error "must be INTEGER" } +!$omp end parallel +!$omp parallel reduction (iand:la1) ! { dg-error "must be INTEGER" } +!$omp end parallel +!$omp parallel reduction (ior:a1) ! { dg-error "must be INTEGER" } +!$omp end parallel +!$omp parallel reduction (ieor:t1) ! { dg-error "must be INTEGER" } +!$omp end parallel +!$omp parallel reduction (iand:ta1) ! { dg-error "must be INTEGER" } +!$omp end parallel + +end subroutine diff --git a/gcc/testsuite/gfortran.dg/gomp/reduction2.f90 b/gcc/testsuite/gfortran.dg/gomp/reduction2.f90 new file mode 100644 index 000000000..f855d0e7f --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/reduction2.f90 @@ -0,0 +1,33 @@ +! { dg-do compile } + +subroutine f1 + integer :: i + i = 0 +!$omp parallel reduction (ior:i) + i = ior (i, 3) +!$omp end parallel +!$omp parallel reduction (ior:i) + i = ior (i, 16) +!$omp end parallel +end subroutine f1 +subroutine f2 + integer :: i + i = ior (2, 4) +!$omp parallel reduction (ior:i) + i = ior (i, 3) +!$omp end parallel +end subroutine f2 +subroutine f3 + integer :: i + i = 6 +!$omp parallel reduction (ior:i) + i = ior (i, 3) +!$omp end parallel +end subroutine f3 +subroutine f4 + integer :: i, ior + i = 6 +!$omp parallel reduction (ior:i) + i = ior (i, 3) +!$omp end parallel +end subroutine f4 diff --git a/gcc/testsuite/gfortran.dg/gomp/reduction3.f90 b/gcc/testsuite/gfortran.dg/gomp/reduction3.f90 new file mode 100644 index 000000000..0272a7415 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/reduction3.f90 @@ -0,0 +1,65 @@ +! { dg-do compile } + +module mreduction3 + interface + function ior (a, b) + integer :: ior, a, b + end function + end interface +contains + function iand (a, b) + integer :: iand, a, b + iand = a + b + end function +end module mreduction3 +subroutine f1 + integer :: i, ior + ior = 6 + i = 6 +!$omp parallel reduction (ior:i) ! { dg-error "is not INTRINSIC procedure name" } +!$omp end parallel +end subroutine f1 +subroutine f2 + integer :: i + interface + function ior (a, b) + integer :: ior, a, b + end function + end interface + i = 6 +!$omp parallel reduction (ior:i) ! { dg-error "is not INTRINSIC procedure name" } + i = ior (i, 3) +!$omp end parallel +end subroutine f2 +subroutine f3 + integer :: i + intrinsic ior + i = 6 +!$omp parallel reduction (ior:i) + i = ior (i, 3) +!$omp end parallel +end subroutine f3 +subroutine f4 + integer :: i, ior + i = 6 +!$omp parallel reduction (ior:i) + ior = 4 ! { dg-error "is not a variable" } +!$omp end parallel +end subroutine f4 +subroutine f5 + use mreduction3 + integer :: i + i = 6 +!$omp parallel reduction (ior:i) ! { dg-error "is not INTRINSIC procedure name" } + i = ior (i, 7) +!$omp end parallel +end subroutine f5 +subroutine f6 + use mreduction3 + integer :: i + i = 6 +!$omp parallel reduction (iand:i) ! { dg-error "is not INTRINSIC procedure name" } + i = iand (i, 18) +!$omp end parallel +end subroutine f6 +! { dg-final { cleanup-modules "mreduction3" } } diff --git a/gcc/testsuite/gfortran.dg/gomp/sharing-1.f90 b/gcc/testsuite/gfortran.dg/gomp/sharing-1.f90 new file mode 100644 index 000000000..7a107ffe7 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/sharing-1.f90 @@ -0,0 +1,28 @@ +! { dg-do compile } +! { dg-require-effective-target tls } + + integer :: thrpriv, thr, i, j, s, g1, g2, m + integer, dimension (6) :: p + common /thrblk/ thr + common /gblk/ g1 + save thrpriv, g2 +!$omp threadprivate (/thrblk/, thrpriv) + s = 1 +!$omp parallel do default (none) & +!$omp & private (p) shared (s) ! { dg-error "enclosing parallel" } + do i = 1, 64 + call foo (thrpriv) ! Predetermined - threadprivate + call foo (thr) ! Predetermined - threadprivate + call foo (i) ! Predetermined - omp do iteration var + do j = 1, 64 ! Predetermined - sequential loop + call foo (j) ! iteration variable + end do + call bar ((/ (k * 4, k = 1, 8) /)) ! Predetermined - implied do + forall (l = 1 : i) &! Predetermined - forall indice + p(l) = 6 ! Explicitly determined - private + call foo (s) ! Explicitly determined - shared + call foo (g1) ! { dg-error "not specified in" } + call foo (g2) ! { dg-error "not specified in" } + call foo (m) ! { dg-error "not specified in" } + end do +end diff --git a/gcc/testsuite/gfortran.dg/gomp/sharing-2.f90 b/gcc/testsuite/gfortran.dg/gomp/sharing-2.f90 new file mode 100644 index 000000000..b7d7e0729 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/sharing-2.f90 @@ -0,0 +1,84 @@ + integer :: i, j, k, l + integer, dimension (10, 10) :: a +!$omp parallel do default (none) shared (a) + do i = 1, 10 + j = 4 + do j = 1, 10 + a(i, j) = i + j + end do + j = 8 + end do +!$omp end parallel do +!$omp parallel default (none) shared (a) ! { dg-error "enclosing parallel" } + i = 1 + j = 1 + k = 1 + l = 1 ! { dg-error "not specified in" } + do i = 1, 10 + a(i, 1) = 1 + end do +!$omp critical + do j = 1, 10 + a(1, j) = j + end do +!$omp end critical +!$omp single + do k = 1, 10 + a(k, k) = k + end do +!$omp end single +!$omp end parallel +!$omp parallel default (none) shared (a) ! { dg-error "enclosing parallel" } + i = 1 ! { dg-error "not specified in" } + j = 1 ! { dg-error "not specified in" } + k = 1 ! { dg-error "not specified in" } +!$omp parallel default (none) shared (a) + i = 1 + j = 1 + k = 1 + do i = 1, 10 + a(i, 1) = 1 + end do +!$omp critical + do j = 1, 10 + a(1, j) = j + end do +!$omp end critical +!$omp single + do k = 1, 10 + a(k, k) = k + end do +!$omp end single +!$omp end parallel + i = 1 + j = 1 + k = 1 +!$omp end parallel +!$omp parallel default (none) shared (a) ! { dg-error "enclosing parallel" } + i = 1 ! { dg-error "not specified in" } +!$omp do + do i = 1, 10 + a(i, 1) = i + 1 + end do +!$omp end parallel +!$omp parallel default (none) shared (a) ! { dg-error "enclosing parallel" } + i = 1 ! { dg-error "not specified in" } +!$omp parallel do default (none) shared (a) + do i = 1, 10 + a(i, 1) = i + 1 + end do +!$omp end parallel +!$omp parallel default (none) shared (a) ! { dg-error "enclosing parallel" } + i = 1 ! { dg-error "not specified in" } +!$omp parallel default (none) shared (a, i) + i = 2 +!$omp parallel default (none) shared (a) + do i = 1, 10 + a(i, 1) = i + end do +!$omp end parallel + i = 3 +!$omp end parallel + i = 4 +!$omp end parallel +end diff --git a/gcc/testsuite/gfortran.dg/gomp/sharing-3.f90 b/gcc/testsuite/gfortran.dg/gomp/sharing-3.f90 new file mode 100644 index 000000000..05be38283 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/sharing-3.f90 @@ -0,0 +1,37 @@ +! { dg-do compile } +! { dg-options "-fopenmp" } + +subroutine foo (vara, varb, varc, vard, n) + integer :: n, vara(n), varb(*), varc(:), vard(6), vare(6) + vare(:) = 0 + !$omp parallel default(none) shared(vara, varb, varc, vard, vare) + !$omp master + vara(1) = 1 + varb(1) = 1 + varc(1) = 1 + vard(1) = 1 + vare(1) = 1 + !$omp end master + !$omp end parallel + !$omp parallel default(none) private(vara, varc, vard, vare) + vara(1) = 1 + varc(1) = 1 + vard(1) = 1 + vare(1) = 1 + !$omp end parallel + !$omp parallel default(none) firstprivate(vara, varc, vard, vare) + vara(1) = 1 + varc(1) = 1 + vard(1) = 1 + vare(1) = 1 + !$omp end parallel + !$omp parallel default(none) ! { dg-error "enclosing parallel" } + !$omp master + vara(1) = 1 ! { dg-error "not specified" } + varb(1) = 1 ! Assumed-size is predetermined + varc(1) = 1 ! { dg-error "not specified" } + vard(1) = 1 ! { dg-error "not specified" } + vare(1) = 1 ! { dg-error "not specified" } + !$omp end master + !$omp end parallel +end subroutine foo diff --git a/gcc/testsuite/gfortran.dg/gomp/workshare1.f90 b/gcc/testsuite/gfortran.dg/gomp/workshare1.f90 new file mode 100644 index 000000000..ffbb1db82 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/gomp/workshare1.f90 @@ -0,0 +1,42 @@ +! { dg-do compile } + +interface + subroutine foo + end subroutine + function bar () + integer :: bar + end function bar + elemental function baz () + integer :: baz + end function baz +end interface + + integer :: i, j + real :: a, b (10), c + a = 0.5 + b = 0.25 +!$omp parallel workshare + a = sin (a) + b = sin (b) + forall (i = 1:10) b(i) = cos (b(i)) - 0.5 + j = baz () +!$omp parallel if (bar () .gt. 2) & +!$omp & num_threads (bar () + 1) + i = bar () +!$omp end parallel +!$omp parallel do schedule (static, bar () + 4) + do j = 1, 10 + i = bar () + end do +!$omp end parallel do +!$omp end parallel workshare +!$omp parallel workshare + call foo ! { dg-error "CALL statement" } + i = bar () ! { dg-error "non-ELEMENTAL" } +!$omp critical + i = bar () ! { dg-error "non-ELEMENTAL" } +!$omp end critical +!$omp atomic + j = j + bar () ! { dg-error "non-ELEMENTAL" } +!$omp end parallel workshare +end |