mirror of
https://gcc.gnu.org/git/gcc.git
synced 2024-12-14 22:43:39 +08:00
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
50 lines
874 B
Fortran
50 lines
874 B
Fortran
! { dg-do run }
|
|
|
|
! Test of attach/detach with "acc enter/exit data".
|
|
|
|
program dtype
|
|
implicit none
|
|
integer, parameter :: n = 512
|
|
type mytype
|
|
integer, allocatable :: a(:)
|
|
integer, allocatable :: b(:)
|
|
end type mytype
|
|
integer, allocatable :: r(:)
|
|
integer i
|
|
|
|
type(mytype) :: var
|
|
|
|
allocate(var%a(1:n))
|
|
allocate(var%b(1:n))
|
|
allocate(r(1:n))
|
|
|
|
!$acc enter data copyin(var)
|
|
|
|
!$acc enter data copyin(var%a, var%b, r)
|
|
|
|
!$acc parallel loop
|
|
do i = 1,n
|
|
var%a(i) = i
|
|
var%b(i) = i * 2
|
|
r(i) = i * 3
|
|
end do
|
|
!$acc end parallel loop
|
|
|
|
!$acc exit data copyout(var%a)
|
|
!$acc exit data copyout(var%b)
|
|
!$acc exit data copyout(r)
|
|
|
|
do i = 1,n
|
|
if (i .ne. var%a(i)) stop 1
|
|
if (i * 2 .ne. var%b(i)) stop 2
|
|
if (i * 3 .ne. r(i)) stop 3
|
|
end do
|
|
|
|
!$acc exit data delete(var)
|
|
|
|
deallocate(var%a)
|
|
deallocate(var%b)
|
|
deallocate(r)
|
|
|
|
end program dtype
|