view libgomp/testsuite/libgomp.fortran/pr49792-2.f90 @ 152:2b5abeee2509

update gcc11
author anatofuz
date Mon, 25 May 2020 07:50:57 +0900
parents 1830386684a0
children
line wrap: on
line source

! PR fortran/49792
! { dg-do run }
! { dg-options "-std=f2003 -fall-intrinsics" }

subroutine reverse(n, a)
  integer :: n
  real(kind=8) :: a(n)
!$omp parallel workshare
  a(:) = a(n:1:-1)
!$omp end parallel workshare
end subroutine reverse

program pr49792
  integer :: b(16)
  integer, allocatable :: a(:)
  b = 1
!$omp parallel workshare
  a = b
!$omp end parallel workshare
  if (size(a).ne.size(b)) stop 1
  if (any (a.ne.b)) stop 2
end program pr49792