10.6. Fortran Restrictions on Storage Association with the private Clause#

The following non-conforming examples illustrate the implications of the private clause rules with regard to storage association.

!!%compiler: gfortran
!!%cflags: -fopenmp

! name: fort_sa_private.1
! type: F-fixed
       SUBROUTINE SUB()
       COMMON /BLOCK/ X
       PRINT *,X             ! X is undefined
       END SUBROUTINE SUB

       PROGRAM PRIV_RESTRICT
         COMMON /BLOCK/ X
         X = 1.0
!$OMP    PARALLEL PRIVATE (X)
         X = 2.0
         CALL SUB()
!$OMP    END PARALLEL
      END PROGRAM PRIV_RESTRICT
!!%compiler: gfortran
!!%cflags: -fopenmp

! name: fort_sa_private.2
! type: F-fixed
      PROGRAM PRIV_RESTRICT2
        COMMON /BLOCK2/ X
        X = 1.0

!$OMP   PARALLEL PRIVATE (X)
          X = 2.0
          CALL SUB()
!$OMP   END PARALLEL

       CONTAINS

          SUBROUTINE SUB()
          COMMON /BLOCK2/ Y

          PRINT *,X               ! X is undefined
          PRINT *,Y               ! Y is undefined
          END SUBROUTINE SUB

       END PROGRAM PRIV_RESTRICT2
!!%compiler: gfortran
!!%cflags: -fopenmp

! name: fort_sa_private.3
! type: F-fixed
      PROGRAM PRIV_RESTRICT3
        EQUIVALENCE (X,Y)
        X = 1.0

!$OMP   PARALLEL PRIVATE(X)
          PRINT *,Y                  ! Y is undefined
          Y = 10
          PRINT *,X                  ! X is undefined
!$OMP   END PARALLEL
      END PROGRAM PRIV_RESTRICT3
!!%compiler: gfortran
!!%cflags: -fopenmp

! name: fort_sa_private.4
! type: F-fixed
      PROGRAM PRIV_RESTRICT4
        INTEGER I, J
        INTEGER A(100), B(100)
        EQUIVALENCE (A(51), B(1))

!$OMP PARALLEL DO DEFAULT(PRIVATE) PRIVATE(I,J) LASTPRIVATE(A)
          DO I=1,100
             DO J=1,100
               B(J) = J - 1
             ENDDO

             DO J=1,100
               A(J) = J   ! B becomes undefined at this point
             ENDDO

             DO J=1,50
               B(J) = B(J) + 1  ! B is undefined
                         ! A becomes undefined at this point
             ENDDO
          ENDDO
!$OMP END PARALLEL DO       ! The LASTPRIVATE write for A has
                            ! undefined results

         PRINT *, B    ! B is undefined since the LASTPRIVATE
                       ! write of A was not defined
       END PROGRAM PRIV_RESTRICT4
!!%compiler: gfortran
!!%cflags: -fopenmp

! name: fort_sa_private.5
! type: F-fixed
! version:    omp_5.1
      SUBROUTINE SUB1(X)
        DIMENSION X(10)

        ! This use of X does not conform to the
        ! specification. It would be legal Fortran 90,
        ! but the OpenMP private directive allows the
        ! compiler to break the sequence association that
        ! A had with the rest of the common block.

        FORALL (I = 1:10) X(I) = I
      END SUBROUTINE SUB1

      PROGRAM PRIV_RESTRICT5
        COMMON /BLOCK5/ A

        DIMENSION B(10)
        EQUIVALENCE (A,B(1))

        ! the common block has to be at least 10 words
        A = 0

!$OMP   PARALLEL PRIVATE(/BLOCK5/)

          ! Without the private clause,
          ! we would be passing a member of a sequence
          ! that is at least ten elements long.
          ! With the private clause, A may no longer be
          ! sequence-associated.

          CALL SUB1(A)
!$OMP     MASKED
            PRINT *, A
!$OMP     END MASKED

!$OMP   END PARALLEL