aboutsummaryrefslogtreecommitdiff
path: root/libgomp
diff options
context:
space:
mode:
authorJulian Brown <julian@codesourcery.com>2019-02-20 05:21:15 -0800
committerThomas Schwinge <thomas@codesourcery.com>2020-03-03 12:49:59 +0100
commit5031a0790d1c95001eac4e487101e08c4af3382b (patch)
tree462216f2be99ec9c764b8cad3a59661c84ed0609 /libgomp
parentc68bbcbc64200458e9992cfc64edb31c834ecf70 (diff)
downloadgcc-5031a0790d1c95001eac4e487101e08c4af3382b.zip
gcc-5031a0790d1c95001eac4e487101e08c4af3382b.tar.gz
gcc-5031a0790d1c95001eac4e487101e08c4af3382b.tar.bz2
Support Fortran 2003 class pointers in OpenACC
gcc/ * gimplify.c (insert_struct_comp_map): Handle GOMP_MAP_ATTACH_DETACH. (gimplify_scan_omp_clauses): Separate out handling of OACC_ENTER_DATA and OACC_EXIT_DATA. Remove GOMP_MAP_POINTER and GOMP_MAP_TO_PSET mappings, apart from those following GOMP_MAP_DECLARE_{,DE}ALLOCATE. Handle GOMP_MAP_ATTACH_DETACH. * tree-pretty-print.c (dump_omp_clause): Support GOMP_MAP_ATTACH_DETACH. Print "bias" not "len" for attach/detach clause types. include/ * gomp-constants.h (gomp_map_kind): Add GOMP_MAP_ATTACH_DETACH. gcc/c/ * c-typeck.c (handle_omp_array_sections): Use GOMP_MAP_ATTACH_DETACH for OpenACC attach/detach operations. gcc/cp/ * semantics.c (handle_omp_array_sections): Likewise. (finish_omp_clauses): Handle GOMP_MAP_ATTACH_DETACH. gcc/fortran/ * openmp.c (resolve_oacc_data_clauses): Allow polymorphic allocatable variables. * trans-expr.c (gfc_conv_component_ref, conv_parent_component_reference): Make global. (gfc_auto_dereference_var): New function, broken out of... (gfc_conv_variable): ...here. Call outlined function instead. * trans-openmp.c (gfc_trans_omp_array_section): New function, broken out of... (gfc_trans_omp_clauses): ...here. Separate out OpenACC derived type/polymorphic class pointer handling. Call above outlined function. * trans.h (gfc_conv_component_ref, conv_parent_component_references, gfc_auto_dereference_var): Add prototypes. gcc/testsuite/ * c-c++-common/goacc/mdc-1.c: Update clause matching patterns. libgomp/ * oacc-parallel.c (GOACC_enter_exit_data): Fix optional arguments for changes to clause stripping in enter data/exit data directives. * 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. * 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. (cherry picked from openacc-gcc-9-branch commit 3c260613f2e74d6639c4dbd43b018b6640ae8454)
Diffstat (limited to 'libgomp')
-rw-r--r--libgomp/ChangeLog.omp11
-rw-r--r--libgomp/oacc-parallel.c3
-rw-r--r--libgomp/testsuite/libgomp.oacc-fortran/class-ptr-param.f9534
-rw-r--r--libgomp/testsuite/libgomp.oacc-fortran/classtypes-1.f9548
-rw-r--r--libgomp/testsuite/libgomp.oacc-fortran/classtypes-2.f95106
-rw-r--r--libgomp/testsuite/libgomp.oacc-fortran/derivedtype-1.f9530
-rw-r--r--libgomp/testsuite/libgomp.oacc-fortran/derivedtype-2.f9541
-rw-r--r--libgomp/testsuite/libgomp.oacc-fortran/multidim-slice.f9550
8 files changed, 322 insertions, 1 deletions
diff --git a/libgomp/ChangeLog.omp b/libgomp/ChangeLog.omp
index b3bcb31..1d88bd5 100644
--- a/libgomp/ChangeLog.omp
+++ b/libgomp/ChangeLog.omp
@@ -1,3 +1,14 @@
+2019-07-10 Julian Brown <julian@codesourcery.com>
+
+ * oacc-parallel.c (GOACC_enter_exit_data): Fix optional arguments for
+ changes to clause stripping in enter data/exit data directives.
+ * 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.
+ * 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.
+
2019-05-28 Julian Brown <julian@codesourcery.com>
* testsuite/libgomp.oacc-fortran/gangprivate-attrib-2.f90: New test.
diff --git a/libgomp/oacc-parallel.c b/libgomp/oacc-parallel.c
index b949599..8606341 100644
--- a/libgomp/oacc-parallel.c
+++ b/libgomp/oacc-parallel.c
@@ -550,7 +550,8 @@ GOACC_enter_exit_data (int flags_m, size_t mapnum,
break;
case GOMP_MAP_TO:
case GOMP_MAP_FORCE_TO:
- acc_copyin_async (hostaddrs[i], sizes[i], async);
+ if (hostaddrs[i])
+ acc_copyin_async (hostaddrs[i], sizes[i], async);
break;
case GOMP_MAP_STRUCT:
{
diff --git a/libgomp/testsuite/libgomp.oacc-fortran/class-ptr-param.f95 b/libgomp/testsuite/libgomp.oacc-fortran/class-ptr-param.f95
new file mode 100644
index 0000000..8014733
--- /dev/null
+++ b/libgomp/testsuite/libgomp.oacc-fortran/class-ptr-param.f95
@@ -0,0 +1,34 @@
+! { 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
diff --git a/libgomp/testsuite/libgomp.oacc-fortran/classtypes-1.f95 b/libgomp/testsuite/libgomp.oacc-fortran/classtypes-1.f95
new file mode 100644
index 0000000..f16f42f
--- /dev/null
+++ b/libgomp/testsuite/libgomp.oacc-fortran/classtypes-1.f95
@@ -0,0 +1,48 @@
+! { dg-do run }
+
+module typemod
+
+type :: typeimpl
+ real, pointer :: p(:) => null()
+end type typeimpl
+
+type :: basictype
+ class(typeimpl), pointer :: p => null()
+end type basictype
+
+type, extends(basictype) :: regulartype
+ character :: void
+end type regulartype
+
+end module typemod
+
+program main
+ use typemod
+ implicit none
+ type(regulartype), pointer :: myvar
+ integer :: i
+ real :: j, k
+
+ allocate(myvar)
+ allocate(myvar%p)
+ allocate(myvar%p%p(1:100))
+
+ do i=1,100
+ myvar%p%p(i) = -1.0
+ end do
+
+!$acc enter data copyin(myvar, myvar%p) create(myvar%p%p)
+
+!$acc parallel loop present(myvar%p%p)
+ do i=1,100
+ myvar%p%p(i) = i * 2
+ end do
+!$acc end parallel loop
+
+!$acc exit data copyout(myvar%p%p) delete(myvar, myvar%p)
+
+ do i=1,100
+ if (myvar%p%p(i) .ne. i * 2) stop 1
+ end do
+
+end program main
diff --git a/libgomp/testsuite/libgomp.oacc-fortran/classtypes-2.f95 b/libgomp/testsuite/libgomp.oacc-fortran/classtypes-2.f95
new file mode 100644
index 0000000..ad80ec2
--- /dev/null
+++ b/libgomp/testsuite/libgomp.oacc-fortran/classtypes-2.f95
@@ -0,0 +1,106 @@
+! { dg-do run }
+
+module wrapper_mod
+
+type compute
+ integer, allocatable :: block(:,:)
+contains
+ procedure :: initialize
+end type compute
+
+type, extends(compute) :: cpu_compute
+ integer :: blocksize
+contains
+ procedure :: setblocksize
+end type cpu_compute
+
+type, extends(compute) :: gpu_compute
+ integer :: numgangs
+ integer :: numworkers
+ integer :: vectorsize
+ integer, allocatable :: gpu_block(:,:)
+contains
+ procedure :: setdims
+end type gpu_compute
+
+contains
+
+subroutine initialize(c, length, width)
+ implicit none
+ class(compute) :: c
+ integer :: length
+ integer :: width
+ integer :: i
+ integer :: j
+
+ allocate (c%block(length, width))
+
+ do i=1,length
+ do j=1, width
+ c%block(i,j) = i + j
+ end do
+ end do
+end subroutine initialize
+
+subroutine setdims(c, g, w, v)
+ implicit none
+ class(gpu_compute) :: c
+ integer :: g
+ integer :: w
+ integer :: v
+ c%numgangs = g
+ c%numworkers = w
+ c%vectorsize = v
+end subroutine setdims
+
+subroutine setblocksize(c, bs)
+ implicit none
+ class(cpu_compute) :: c
+ integer :: bs
+ c%blocksize = bs
+end subroutine setblocksize
+
+end module wrapper_mod
+
+program main
+ use wrapper_mod
+ implicit none
+ class(compute), allocatable, target :: mycomp
+ integer :: i, j
+
+ allocate(gpu_compute::mycomp)
+
+ call mycomp%initialize(1024,1024)
+
+ !$acc enter data copyin(mycomp)
+
+ select type (mycomp)
+ type is (cpu_compute)
+ call mycomp%setblocksize(32)
+ type is (gpu_compute)
+ call mycomp%setdims(32,32,32)
+ allocate(mycomp%gpu_block(1024,1024))
+ !$acc update device(mycomp)
+ !$acc parallel copyin(mycomp%block) copyout(mycomp%gpu_block)
+ !$acc loop gang worker vector collapse(2)
+ do i=1,1024
+ do j=1,1024
+ mycomp%gpu_block(i,j) = mycomp%block(i,j) + 1
+ end do
+ end do
+ !$acc end parallel
+ end select
+
+ !$acc exit data copyout(mycomp)
+
+ select type (g => mycomp)
+ type is (gpu_compute)
+ do i = 1, 1024
+ do j = 1, 1024
+ if (g%gpu_block(i,j) .ne. i + j + 1) stop 1
+ end do
+ end do
+ end select
+
+ deallocate(mycomp)
+end program main
diff --git a/libgomp/testsuite/libgomp.oacc-fortran/derivedtype-1.f95 b/libgomp/testsuite/libgomp.oacc-fortran/derivedtype-1.f95
new file mode 100644
index 0000000..75ce48d
--- /dev/null
+++ b/libgomp/testsuite/libgomp.oacc-fortran/derivedtype-1.f95
@@ -0,0 +1,30 @@
+! { dg-do run }
+
+program main
+ implicit none
+
+ type mytype
+ integer :: a, b, c
+ end type mytype
+
+ type(mytype) :: myvar
+ integer :: i
+
+ myvar%a = 0
+ myvar%b = 0
+ myvar%c = 0
+
+!$acc enter data copyin(myvar)
+
+!$acc parallel present(myvar)
+ myvar%a = 1
+ myvar%b = 2
+ myvar%c = 3
+!$acc end parallel
+
+!$acc exit data copyout(myvar)
+
+ if (myvar%a .ne. 1) stop 1
+ if (myvar%b .ne. 2) stop 2
+ if (myvar%c .ne. 3) stop 3
+end program main
diff --git a/libgomp/testsuite/libgomp.oacc-fortran/derivedtype-2.f95 b/libgomp/testsuite/libgomp.oacc-fortran/derivedtype-2.f95
new file mode 100644
index 0000000..3088b83
--- /dev/null
+++ b/libgomp/testsuite/libgomp.oacc-fortran/derivedtype-2.f95
@@ -0,0 +1,41 @@
+! { dg-do run }
+
+program main
+ implicit none
+
+ type tnest
+ integer :: ia, ib, ic
+ end type tnest
+
+ type mytype
+ type(tnest) :: nest
+ integer :: a, b, c
+ end type mytype
+
+ type(mytype) :: myvar
+ integer :: i
+
+ myvar%a = 0
+ myvar%b = 0
+ myvar%c = 0
+ myvar%nest%ia = 0
+ myvar%nest%ib = 0
+ myvar%nest%ic = 0
+
+!$acc enter data copyin(myvar%nest)
+
+!$acc parallel present(myvar%nest)
+ myvar%nest%ia = 4
+ myvar%nest%ib = 5
+ myvar%nest%ic = 6
+!$acc end parallel
+
+!$acc exit data copyout(myvar%nest)
+
+ if (myvar%a .ne. 0) stop 1
+ if (myvar%b .ne. 0) stop 2
+ if (myvar%c .ne. 0) stop 3
+ if (myvar%nest%ia .ne. 4) stop 4
+ if (myvar%nest%ib .ne. 5) stop 5
+ if (myvar%nest%ic .ne. 6) stop 6
+end program main
diff --git a/libgomp/testsuite/libgomp.oacc-fortran/multidim-slice.f95 b/libgomp/testsuite/libgomp.oacc-fortran/multidim-slice.f95
new file mode 100644
index 0000000..a9b40ee
--- /dev/null
+++ b/libgomp/testsuite/libgomp.oacc-fortran/multidim-slice.f95
@@ -0,0 +1,50 @@
+! { dg-do run }
+
+program main
+ implicit none
+ real, allocatable :: myarr(:,:,:,:,:)
+ integer i, j, k, l, m
+
+ allocate(myarr(1:10,1:10,1:10,1:10,1:10))
+
+ do i=1,10
+ do j=1,10
+ do k=1,10
+ do l=1,10
+ do m=1,10
+ myarr(m,l,k,j,i) = i+j+k+l+m
+ end do
+ end do
+ end do
+ end do
+ end do
+
+ do i=1,10
+ !$acc data copy(myarr(:,:,:,:,i))
+ !$acc parallel loop collapse(4) present(myarr(:,:,:,:,i))
+ do j=1,10
+ do k=1,10
+ do l=1,10
+ do m=1,10
+ myarr(m,l,k,j,i) = myarr(m,l,k,j,i) + 1
+ end do
+ end do
+ end do
+ end do
+ !$acc end parallel loop
+ !$acc end data
+ end do
+
+ do i=1,10
+ do j=1,10
+ do k=1,10
+ do l=1,10
+ do m=1,10
+ if (myarr(m,l,k,j,i) .ne. i+j+k+l+m+1) stop 1
+ end do
+ end do
+ end do
+ end do
+ end do
+
+end program main