gcc/libgomp/testsuite/libgomp.oacc-fortran/update-dt-array.f90
Julian Brown d28f3da11d openacc: Fix lowering for derived-type mappings through array elements
This patch fixes lowering of derived-type mappings which select elements
of arrays of derived types, and similar. These would previously lead
to ICEs.

With this change, OpenACC directives can pass through constructs that
are no longer recognized by the gimplifier, hence alterations are needed
there also.

gcc/fortran/
	* trans-openmp.c (gfc_trans_omp_clauses): Handle element selection
	for arrays of derived types.

gcc/
	* gimplify.c (gimplify_scan_omp_clauses): Handle ATTACH_DETACH
	for non-decls.

gcc/testsuite/
	* gfortran.dg/goacc/array-with-dt-1.f90: New test.
	* gfortran.dg/goacc/array-with-dt-3.f90: Likewise.
	* gfortran.dg/goacc/array-with-dt-4.f90: Likewise.
	* gfortran.dg/goacc/array-with-dt-5.f90: Likewise.
	* gfortran.dg/goacc/derived-chartypes-1.f90: Re-enable test.
	* gfortran.dg/goacc/derived-chartypes-2.f90: Likewise.
	* gfortran.dg/goacc/derived-classtypes-1.f95: Uncomment
	previously-broken directives.

libgomp/
	* testsuite/libgomp.oacc-fortran/derivedtypes-arrays-1.f90: New test.
	* testsuite/libgomp.oacc-fortran/update-dt-array.f90: Likewise.
2021-02-17 06:13:55 -08:00

53 lines
857 B
Fortran

! { dg-do run }
program myprog
type mytype
integer, allocatable :: myarr(:,:)
end type mytype
integer :: i
type(mytype), allocatable :: typearr(:)
allocate(typearr(1:100))
do i=1,100
allocate(typearr(i)%myarr(1:100,1:100))
end do
do i=1,100
typearr(i)%myarr(:,:) = 0
end do
!$acc enter data copyin(typearr)
do i=1,100
!$acc enter data copyin(typearr(i)%myarr)
end do
i=33
typearr(i)%myarr(:,:) = 50
!$acc update device(typearr(i)%myarr(:,:))
do i=1,100
!$acc exit data copyout(typearr(i)%myarr)
end do
!$acc exit data delete(typearr)
do i=1,100
if (i.eq.33) then
if (any(typearr(i)%myarr.ne.50)) stop 1
else
if (any(typearr(i)%myarr.ne.0)) stop 2
end if
end do
do i=1,100
deallocate(typearr(i)%myarr)
end do
deallocate(typearr)
end program myprog