CONTINUE ENDDO END SUBROUTINE DO_GOOD The following example is non-conforming because the matching do directive for the end do does not precede the outermost loop: Example fort_do.2f SUBROUTINE WORK(I,J) INTEGER I,J END SUBROUTINE WORK SUBROUTINE DO_WRONG INTEGER I,了 c D0100=1,10 - !SOMP DO S-10 D0100J=1,10 s-11 CALL WORK (I,J) 818 100 CONTINUE SOMP ENDDO S-14 END SUBROUTINE DO_WRONG Fortran 30 OpenMP Examples Version 4.0.2-March 2015
S-24 300 CONTINUE S-25 !$OMP ENDDO S-26 END SUBROUTINE DO_GOOD 1 The following example is non-conforming because the matching do directive for the end do does 2 not precede the outermost loop: 3 Example fort_do.2f S-1 SUBROUTINE WORK(I, J) S-2 INTEGER I,J S-3 END SUBROUTINE WORK S-4 S-5 SUBROUTINE DO_WRONG S-6 INTEGER I, J S-7 S-8 DO 100 I = 1,10 S-9 !$OMP DO S-10 DO 100 J = 1,10 S-11 CALL WORK(I,J) S-12 100 CONTINUE S-13 !$OMP ENDDO S-14 END SUBROUTINE DO_WRONG Fortran 30 OpenMP Examples Version 4.0.2 - March 2015
1 CHAPTER 10 2 Fortran Private Loop Iteration Variables Fortran 34 In general loop iteration variables will be private,when used in the do-loop of a do and parallel do construct or in sequential loops in a parallel construct(see Section 2.7.1 and Section 2.14.1 of the OpenMP 4.0 specification).In the following example of a sequential loop in a 6 parallel construct the loop iteration variable I will be private. Example fort_loopvar.If SUBROUTINE PLOOP_1(A,N) INCLUDE”omp1ib.h !or USE OMP_LIB s-5 INTEGER I,MYOFFSET,N 9 !SOMP PARALLEL PRIVATE(MYOFFSET) s-8 MYOFFSET OMP GET_THREAD_NUM()*N s.o DO I 1,N s-10 A(MYOFFSET+I)=FLOAT (I) 9.11 ENDDO S-12 SOMP END PARALLEL s-13 S-14 END SUBROUTINE PLOOP 1 8 In exceptional cases.loop iteration variables can be made shared,as in the following example 9 Example fort_loopvar.2f S-1 SUBROUTINE PLOOP_2(A,B,N,I1,I2) REAL A黄】,B(*】 INTEGER I1,I2,N ISOMP PARALLEL SHARED(A,B,I1,I2) SOMP SECTIONS
1 CHAPTER 10 2 Fortran Private Loop Iteration Variables Fortran 3 In general loop iteration variables will be private, when used in the do-loop of a do and 4 parallel do construct or in sequential loops in a parallel construct (see Section 2.7.1 and 5 Section 2.14.1 of the OpenMP 4.0 specification). In the following example of a sequential loop in a 6 parallel construct the loop iteration variable I will be private. 7 Example fort_loopvar.1f S-1 SUBROUTINE PLOOP_1(A,N) S-2 INCLUDE "omp_lib.h" ! or USE OMP_LIB S-3 S-4 REAL A(*) S-5 INTEGER I, MYOFFSET, N S-6 S-7 !$OMP PARALLEL PRIVATE(MYOFFSET) S-8 MYOFFSET = OMP_GET_THREAD_NUM()*N S-9 DO I = 1, N S-10 A(MYOFFSET+I) = FLOAT(I) S-11 ENDDO S-12 !$OMP END PARALLEL S-13 S-14 END SUBROUTINE PLOOP_1 8 In exceptional cases, loop iteration variables can be made shared, as in the following example: 9 Example fort_loopvar.2f S-1 SUBROUTINE PLOOP_2(A,B,N,I1,I2) S-2 REAL A(*), B(*) S-3 INTEGER I1, I2, N S-4 S-5 !$OMP PARALLEL SHARED(A,B,I1,I2) S-6 !$OMP SECTIONS 31
ISOMP SECTION ENDDO !SOMP I2,N (B(E2).NE.0.0)Ex ND !SOMP SECTIONS LE.N)PRINT END SUBROUTINE PLOOP_2 Note however that the use of shared loop iteration variables can easily lead to race conditions. Fortran 32 OpenMP Examples Version 4.0.2-March 2015
S-7 !$OMP SECTION S-8 DO I1 = I1, N S-9 IF (A(I1).NE.0.0) EXIT S-10 ENDDO S-11 !$OMP SECTION S-12 DO I2 = I2, N S-13 IF (B(I2).NE.0.0) EXIT S-14 ENDDO S-15 !$OMP END SECTIONS S-16 !$OMP SINGLE S-17 IF (I1.LE.N) PRINT *, ’ITEMS IN A UP TO ’, I1, ’ARE ALL ZERO.’ S-18 IF (I2.LE.N) PRINT *, ’ITEMS IN B UP TO ’, I2, ’ARE ALL ZERO.’ S-19 !$OMP END SINGLE S-20 !$OMP END PARALLEL S-21 S-22 END SUBROUTINE PLOOP_2 1 Note however that the use of shared loop iteration variables can easily lead to race conditions. Fortran 32 OpenMP Examples Version 4.0.2 - March 2015
1 CHAPTER 11 2 The nowait Clause 34 If there are multiple independent loops within a parallel region,you can use the nowait C/C++ Example nowait.Ic S-1 #include <math.h> 83 void nowait_example(int n,int m,float wa,float tb,float ty,float *z) int i; S-7 S-8 pragma omp for nowait S-9 for (i=1;i<n;i++) S-10 b[i]=(a[i]+a【i-1])/2.0; S-11 S-12 #pragma omp for nowait S-13 for (i=0;i<m;i++) S-14 y[i】=sqrt(z【i]): S-15 S-16 C/C++
1 CHAPTER 11 2 The nowait Clause 3 If there are multiple independent loops within a parallel region, you can use the nowait 4 clause to avoid the implied barrier at the end of the loop construct, as follows: C / C++ 5 Example nowait.1c S-1 #include <math.h> S-2 S-3 void nowait_example(int n, int m, float *a, float *b, float *y, float *z) S-4 { S-5 int i; S-6 #pragma omp parallel S-7 { S-8 #pragma omp for nowait S-9 for (i=1; i<n; i++) S-10 b[i] = (a[i] + a[i-1]) / 2.0; S-11 S-12 #pragma omp for nowait S-13 for (i=0; i<m; i++) S-14 y[i] = sqrt(z[i]); S-15 } S-16 } C / C++ 33
Fortran Example nowait.If SUBROUTINE NOWAIT_EXAMPLE(N,M,A,B,¥,Z) INTEGER I !SOMP PARALLEL !SOMP DO DO I=2,N S-12 B()=(a()+a(-1)/2.0 S-13 ENDDO S-14 ISOMP END DO NOWAIT S-15 S-16 !SOMP DO s-17 DO I=1.M S-18 x (I)SORT(Z (I)) s-19 ENDDO S-20 SOMP END DO NOWAIT S-21 S-22 SOMP END PARALLEL 5-23 S-24 END SUBROUTINE NOWAIT EXAMPLE Fortran 23 In the following example,static scheduling distributes the same logical iteration numbers to the threads that execute the three loop regions.This allows the nowait clause to be used,even though 45 there is a data dependence between the loops.The dependence is satisfied as long the same thread executes the same logical iteration numbers in each loop. 678 Note that the iteration count of the loops must be the same.The example satisfies this requirement the iteration space o first two loops is fromto(the Fortran version) hle the iteration space of the last loop is from to(2to N+in the Fortran version). 34 OpenMP Examples Version 4.0.2-March 2015
Fortran 1 Example nowait.1f S-1 SUBROUTINE NOWAIT_EXAMPLE(N, M, A, B, Y, Z) S-2 S-3 INTEGER N, M S-4 REAL A(*), B(*), Y(*), Z(*) S-5 S-6 INTEGER I S-7 S-8 !$OMP PARALLEL S-9 S-10 !$OMP DO S-11 DO I=2,N S-12 B(I) = (A(I) + A(I-1)) / 2.0 S-13 ENDDO S-14 !$OMP END DO NOWAIT S-15 S-16 !$OMP DO S-17 DO I=1,M S-18 Y(I) = SQRT(Z(I)) S-19 ENDDO S-20 !$OMP END DO NOWAIT S-21 S-22 !$OMP END PARALLEL S-23 S-24 END SUBROUTINE NOWAIT_EXAMPLE Fortran 2 In the following example, static scheduling distributes the same logical iteration numbers to the 3 threads that execute the three loop regions. This allows the nowait clause to be used, even though 4 there is a data dependence between the loops. The dependence is satisfied as long the same thread 5 executes the same logical iteration numbers in each loop. 6 Note that the iteration count of the loops must be the same. The example satisfies this requirement, 7 since the iteration space of the first two loops is from 0 to n-1 (from 1 to N in the Fortran version), 8 while the iteration space of the last loop is from 1 to n (2 to N+1 in the Fortran version). 34 OpenMP Examples Version 4.0.2 - March 2015