https://gcc.gnu.org/bugzilla/show_bug.cgi?id=110725

kargl at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
            Summary|[13/14 Regression] internal |[13/14 Regression,openmp]
                   |compiler error: in          |internal compiler error: in
                   |expand_expr_real_1, at      |expand_expr_real_1, at
                   |expr.cc:10897               |expr.cc:10897
                 CC|                            |kargl at gcc dot gnu.org

--- Comment #2 from kargl at gcc dot gnu.org ---
Reduced testcase.  The '!$omp end teams' line in subroutine initial appears to
be out-of-place.


      module swim_mod

      INTEGER, PARAMETER :: N1=7702, N2=7702

      DOUBLE PRECISION, ALLOCATABLE, DIMENSION(:,:) :: U, V

      INTEGER :: M, N, MP1, NP1

!$omp declare target(U, V)
!$omp declare target(M,N,MP1,NP1)

      CONTAINS

      SUBROUTINE ALLOC
         IMPLICIT NONE
!$omp target update to(M,N,MP1,NP1)
!$omp&
         ALLOCATE(U(NP1,MP1), V(NP1,MP1))
      END SUBROUTINE

      SUBROUTINE INITAL
      INTEGER I
!$omp target
!$omp teams
!$omp distribute parallel do simd
      DO 75 I=1,M
         U(I+1,N+1) = U(I+1,1)
         V(I,1) = V(I,N+1)
   75 CONTINUE
!$omp end teams
      U(1,N+1) = U(M+1,1)
      V(M+1,1) = V(1,N+1)
!$omp end target
      END SUBROUTINE

      end module swim_mod

Reply via email to