gcc/libgomp/testsuite/libgomp.oacc-fortran/deep-copy-3.f90
Julian Brown 278c3214b3 Don't allow mixed component and non-component accesses for OpenACC/Fortran
gcc/fortran/
	* gfortran.h (gfc_symbol): Add comp_mark bitfield.
	* openmp.c (resolve_omp_clauses): Disallow mixed component and
	full-derived-type accesses to the same variable within a single
	directive.

	libgomp/
	* testsuite/libgomp.oacc-fortran/deep-copy-2.f90: Remove test from here.
	* testsuite/libgomp.oacc-fortran/deep-copy-3.f90: Don't use mixed
	component/non-component variable refs in a single directive.
	* testsuite/libgomp.oacc-fortran/classtypes-1.f95: Likewise.

	gcc/testsuite/
	* gfortran.dg/goacc/deep-copy-2.f90: Move test here (from libgomp
	testsuite). Make a compilation test, and expect rejection of mixed
	component/non-component accesses.
	* gfortran.dg/goacc/mapping-tests-1.f90: New test.
2020-01-28 06:00:29 -08:00

36 lines
623 B
Fortran

! { dg-do run }
! Test of attach/detach with "acc parallel".
program dtype
implicit none
integer, parameter :: n = 512
type mytype
integer, allocatable :: a(:)
integer, allocatable :: b(:)
end type mytype
integer i
type(mytype) :: var
allocate(var%a(1:n))
allocate(var%b(1:n))
!$acc data copy(var)
!$acc parallel loop copy(var%a(1:n)) copy(var%b(1:n))
do i = 1,n
var%a(i) = i
var%b(i) = i
end do
!$acc end parallel loop
!$acc end data
do i = 1,n
if (i .ne. var%a(i)) stop 1
if (i .ne. var%b(i)) stop 2
end do
deallocate(var%a)
deallocate(var%b)
end program dtype