gcc/libgomp/testsuite/libgomp.oacc-fortran/array-stride-dt-1.f90
Julian Brown 366cf1127a openacc: Strided array sections and components of derived-type arrays
This patch disallows selecting components of array sections in update
directives for OpenACC, as specified in OpenACC 3.0, "2.14.4. Update
Directive":

  In Fortran, members of variables of derived type may appear, including
  a subarray of a member. Members of subarrays of derived type may
  not appear.

The diagnostic for attempting to use the same construct on other
directives has also been improved.

gcc/fortran/
	* openmp.c (resolve_omp_clauses): Disallow selecting components
	of arrays of derived type.

gcc/testsuite/
	* gfortran.dg/goacc/array-with-dt-2.f90: Remove expected errors.
	* gfortran.dg/goacc/array-with-dt-6.f90: New test.
	* gfortran.dg/goacc/mapping-tests-2.f90: Update expected error.
	* gfortran.dg/goacc/ref_inquiry.f90: Update expected errors.
	* gfortran.dg/gomp/ref_inquiry.f90: Likewise.

libgomp/
	* testsuite/libgomp.oacc-fortran/array-stride-dt-1.f90: Remove
	expected errors.
2021-02-17 06:13:55 -08:00

44 lines
776 B
Fortran

! { dg-do run }
type t
integer, allocatable :: A(:,:)
end type t
type(t), allocatable :: b(:)
integer :: i
allocate(b(1:20))
do i=1,20
allocate(b(i)%A(1:20,1:20))
end do
do i=1,20
b(i)%A(:,:) = 0
end do
!$acc enter data copyin(b)
do i=1,20
!$acc enter data copyin(b(i)%A)
end do
b(1)%A(:,:) = 5
!$acc update device(b(::2))
!$acc update device(b(1)%A(::3,::4))
do i=1,20
!$acc exit data copyout(b(i)%A)
end do
!$acc exit data copyout(b)
! This is necessarily conservative because the "update" is allowed to copy
! e.g. the whole of the containing block for a discontinuous update.
! Try to ensure that the update covers a sufficient portion of the array.
if (any(b(1)%A(::3,::4) .ne. 5)) stop 1
do i=2,20
if (any(b(i)%A(:,:) .ne. 0)) stop 2
end do
end