9be3ac5d63
gcc/fortran/ * openmp.c (resolve_oacc_data_clauses): Don't disallow allocatable polymorphic types for OpenACC. * trans-openmp.c (gfc_trans_omp_clauses): Support polymorphic class types. libgomp/ * testsuite/libgomp.oacc-fortran/class-ptr-param.f95: New test. * testsuite/libgomp.oacc-fortran/classtypes-1.f95: New test. * testsuite/libgomp.oacc-fortran/classtypes-2.f95: New test. From-SVN: r279631
35 lines
445 B
Fortran
35 lines
445 B
Fortran
! { dg-do run }
|
|
|
|
module typemod
|
|
|
|
type mytype
|
|
integer :: a
|
|
end type mytype
|
|
|
|
contains
|
|
|
|
subroutine mysub(c)
|
|
implicit none
|
|
|
|
class(mytype), allocatable :: c
|
|
|
|
!$acc parallel copy(c)
|
|
c%a = 5
|
|
!$acc end parallel
|
|
end subroutine mysub
|
|
|
|
end module typemod
|
|
|
|
program main
|
|
use typemod
|
|
implicit none
|
|
|
|
class(mytype), allocatable :: myvar
|
|
allocate(mytype :: myvar)
|
|
|
|
myvar%a = 0
|
|
call mysub(myvar)
|
|
|
|
if (myvar%a .ne. 5) stop 1
|
|
end program main
|