02817027ca
libgomp/ * testsuite/libgomp.oacc-fortran/deep-copy-1.f90: New test. * testsuite/libgomp.oacc-fortran/deep-copy-2.f90: New test. * testsuite/libgomp.oacc-fortran/deep-copy-3.f90: New test. * testsuite/libgomp.oacc-fortran/deep-copy-4.f90: New test. * testsuite/libgomp.oacc-fortran/deep-copy-5.f90: New test. * testsuite/libgomp.oacc-fortran/deep-copy-6.f90: New test. * testsuite/libgomp.oacc-fortran/deep-copy-7.f90: New test. * testsuite/libgomp.oacc-fortran/deep-copy-8.f90: New test. * testsuite/libgomp.oacc-fortran/derived-type-1.f90: New test. * testsuite/libgomp.oacc-fortran/derivedtype-1.f95: New test. * testsuite/libgomp.oacc-fortran/derivedtype-2.f95: New test. * testsuite/libgomp.oacc-fortran/multidim-slice.f95: New test. * testsuite/libgomp.oacc-fortran/update-2.f90: New test. Co-Authored-By: Cesar Philippidis <cesar@codesourcery.com> From-SVN: r279630
36 lines
500 B
Fortran
36 lines
500 B
Fortran
! { dg-do run }
|
|
|
|
! Test of attach/detach with "acc data".
|
|
|
|
program dtype
|
|
implicit none
|
|
integer, parameter :: n = 512
|
|
type mytype
|
|
integer, allocatable :: a(:)
|
|
end type mytype
|
|
integer i
|
|
|
|
type(mytype) :: var
|
|
|
|
allocate(var%a(1:n))
|
|
|
|
!$acc data copy(var)
|
|
!$acc data copy(var%a)
|
|
|
|
!$acc parallel loop
|
|
do i = 1,n
|
|
var%a(i) = i
|
|
end do
|
|
!$acc end parallel loop
|
|
|
|
!$acc end data
|
|
!$acc end data
|
|
|
|
do i = 1,n
|
|
if (i .ne. var%a(i)) stop 1
|
|
end do
|
|
|
|
deallocate(var%a)
|
|
|
|
end program dtype
|