OpenCores
URL https://opencores.org/ocsvn/openrisc/openrisc/trunk

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [libgomp/] [testsuite/] [libgomp.fortran/] [appendix-a/] [a.22.7.f90] - Rev 735

Compare with Previous | Blame | View Log

! { dg-do run }
! { dg-require-effective-target tls_runtime }

      PROGRAM A22_7_GOOD
        INTEGER, ALLOCATABLE, SAVE :: A(:)
        INTEGER, POINTER, SAVE :: PTR
        INTEGER, SAVE :: I
        INTEGER, TARGET :: TARG
        LOGICAL :: FIRSTIN = .TRUE.
!$OMP THREADPRIVATE(A, I, PTR)
        ALLOCATE (A(3))
        A = (/1,2,3/)
        PTR => TARG
        I=5
!$OMP PARALLEL COPYIN(I, PTR)
!$OMP CRITICAL
            IF (FIRSTIN) THEN
              TARG = 4           ! Update target of ptr
              I = I + 10
              IF (ALLOCATED(A)) A = A + 10
              FIRSTIN = .FALSE.
            END IF
            IF (ALLOCATED(A)) THEN
              PRINT *, "a = ", A
            ELSE
              PRINT *, "A is not allocated"
            END IF
            PRINT *, "ptr = ", PTR
            PRINT *, "i = ", I
            PRINT *
!$OMP END CRITICAL
!$OMP END PARALLEL
      END PROGRAM A22_7_GOOD

Compare with Previous | Blame | View Log

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.