aboutsummaryrefslogtreecommitdiff
path: root/libgomp/testsuite/libgomp.fortran
diff options
context:
space:
mode:
Diffstat (limited to 'libgomp/testsuite/libgomp.fortran')
-rw-r--r--libgomp/testsuite/libgomp.fortran/alloc-comp-4.f9075
-rw-r--r--libgomp/testsuite/libgomp.fortran/allocate-8a.f9045
-rw-r--r--libgomp/testsuite/libgomp.fortran/interop-hip-amd-full.F903
-rw-r--r--libgomp/testsuite/libgomp.fortran/interop-hip-amd-no-module.F903
-rw-r--r--libgomp/testsuite/libgomp.fortran/interop-hip-nvidia-full.F903
-rw-r--r--libgomp/testsuite/libgomp.fortran/interop-hip-nvidia-no-module.F903
-rw-r--r--libgomp/testsuite/libgomp.fortran/map-alloc-comp-9-usm.f9011
-rw-r--r--libgomp/testsuite/libgomp.fortran/map-alloc-comp-9.f9019
-rw-r--r--libgomp/testsuite/libgomp.fortran/metadirective-1.f909
-rw-r--r--libgomp/testsuite/libgomp.fortran/omp_target_memset-2.f9067
-rw-r--r--libgomp/testsuite/libgomp.fortran/omp_target_memset.f9039
11 files changed, 276 insertions, 1 deletions
diff --git a/libgomp/testsuite/libgomp.fortran/alloc-comp-4.f90 b/libgomp/testsuite/libgomp.fortran/alloc-comp-4.f90
new file mode 100644
index 0000000..d5e982b
--- /dev/null
+++ b/libgomp/testsuite/libgomp.fortran/alloc-comp-4.f90
@@ -0,0 +1,75 @@
+!
+! Check that mapping with map(var%tiles(1)) works.
+!
+! This uses deep mapping to handle the allocatable
+! derived-type components
+!
+! The tricky part is that GCC generates intermittently
+! an SSA_NAME that needs to be resolved.
+!
+module m
+type t
+ integer, allocatable :: den1(:,:), den2(:,:)
+end type t
+
+type t2
+ type(t), allocatable :: tiles(:)
+end type t2
+end
+
+use m
+use iso_c_binding
+implicit none (type, external)
+type(t2), target :: var
+logical :: is_self_map
+type(C_ptr) :: pden1, pden2, ptiles, ptiles1
+
+allocate(var%tiles(1))
+var%tiles(1)%den1 = reshape([1,2,3,4],[2,2])
+var%tiles(1)%den2 = reshape([11,22,33,44],[2,2])
+
+ptiles = c_loc(var%tiles)
+ptiles1 = c_loc(var%tiles(1))
+pden1 = c_loc(var%tiles(1)%den1)
+pden2 = c_loc(var%tiles(1)%den2)
+
+
+is_self_map = .false.
+!$omp target map(to: is_self_map)
+ is_self_map = .true.
+!$omp end target
+
+!$omp target enter data map(var%tiles(1))
+
+!$omp target firstprivate(ptiles, ptiles1, pden1, pden2)
+ if (any (var%tiles(1)%den1 /= reshape([1,2,3,4],[2,2]))) stop 1
+ if (any (var%tiles(1)%den2 /= reshape([11,22,33,44],[2,2]))) stop 2
+ var%tiles(1)%den1 = var%tiles(1)%den1 + 5
+ var%tiles(1)%den2 = var%tiles(1)%den2 + 7
+
+ if (is_self_map) then
+ if (.not. c_associated (ptiles, c_loc(var%tiles))) stop 3
+ if (.not. c_associated (ptiles1, c_loc(var%tiles(1)))) stop 4
+ if (.not. c_associated (pden1, c_loc(var%tiles(1)%den1))) stop 5
+ if (.not. c_associated (pden2, c_loc(var%tiles(1)%den2))) stop 6
+ else
+ if (c_associated (ptiles, c_loc(var%tiles))) stop 3
+ if (c_associated (ptiles1, c_loc(var%tiles(1)))) stop 4
+ if (c_associated (pden1, c_loc(var%tiles(1)%den1))) stop 5
+ if (c_associated (pden2, c_loc(var%tiles(1)%den2))) stop 6
+ endif
+!$omp end target
+
+if (is_self_map) then
+ if (any (var%tiles(1)%den1 /= 5 + reshape([1,2,3,4],[2,2]))) stop 7
+ if (any (var%tiles(1)%den2 /= 7 + reshape([11,22,33,44],[2,2]))) stop 8
+else
+ if (any (var%tiles(1)%den1 /= reshape([1,2,3,4],[2,2]))) stop 7
+ if (any (var%tiles(1)%den2 /= reshape([11,22,33,44],[2,2]))) stop 8
+endif
+
+!$omp target exit data map(var%tiles(1))
+
+if (any (var%tiles(1)%den1 /= 5 + reshape([1,2,3,4],[2,2]))) stop 7
+if (any (var%tiles(1)%den2 /= 7 + reshape([11,22,33,44],[2,2]))) stop 8
+end
diff --git a/libgomp/testsuite/libgomp.fortran/allocate-8a.f90 b/libgomp/testsuite/libgomp.fortran/allocate-8a.f90
new file mode 100644
index 0000000..5f6c8c1
--- /dev/null
+++ b/libgomp/testsuite/libgomp.fortran/allocate-8a.f90
@@ -0,0 +1,45 @@
+! { dg-additional-options "-fopenmp-allocators" }
+! { dg-additional-options "-fdump-tree-omplower" }
+program main
+ use iso_c_binding
+ use omp_lib
+ implicit none (type, external)
+ integer(omp_allocator_handle_kind):: alloc_h
+ integer :: i, N
+ integer(c_intptr_t) :: intptr
+ integer, allocatable :: A(:)
+ type(omp_alloctrait):: traits(1) = [omp_alloctrait(omp_atk_alignment, 128)]
+
+ N = 10
+ alloc_h = omp_init_allocator(omp_default_mem_space, 1, traits)
+
+ !$omp allocate(A) allocator(alloc_h)
+ allocate(A(N))
+ a(:) = [(i, i=1,N)]
+ if (mod (transfer (loc(a), intptr),128) /= 0) &
+ stop 1
+ if (any (a /= [(i, i=1,N)])) &
+ stop 2
+ deallocate(A)
+ !$omp allocate(A) allocator(alloc_h) align(512)
+ allocate(A(N))
+ block
+ integer, allocatable :: B(:)
+ !$omp allocators allocate(allocator(alloc_h), align(256) : B)
+ allocate(B(N))
+ B(:) = [(2*i, i=1,N)]
+ A(:) = B
+ if (mod (transfer (loc(B), intptr), 256) /= 0) &
+ stop 1
+ ! end of scope deallocation
+ end block
+ if (mod (transfer (loc(a), intptr),512) /= 0) &
+ stop 1
+ if (any (a /= [(2*i, i=1,N)])) &
+ stop 2
+ deallocate(A) ! Must deallocate here - before deallocator is destroyed
+ call omp_destroy_allocator(alloc_h)
+ ! No auto dealloc of A because it is SAVE
+end
+! { dg-final { scan-tree-dump-times "__builtin_GOMP_alloc \\(" 3 "omplower" } }
+! { dg-final { scan-tree-dump-times "__builtin_GOMP_free \\(" 3 "omplower" } }
diff --git a/libgomp/testsuite/libgomp.fortran/interop-hip-amd-full.F90 b/libgomp/testsuite/libgomp.fortran/interop-hip-amd-full.F90
index bbd49dd..eb2f437 100644
--- a/libgomp/testsuite/libgomp.fortran/interop-hip-amd-full.F90
+++ b/libgomp/testsuite/libgomp.fortran/interop-hip-amd-full.F90
@@ -1,3 +1,6 @@
+! { dg-do run { target { offload_device_gcn } } }
+! { dg-do link { target { ! offload_device_gcn } } }
+
! { dg-require-effective-target gomp_hipfort_module }
! { dg-require-effective-target gomp_libamdhip64 }
! { dg-additional-options "-lamdhip64" }
diff --git a/libgomp/testsuite/libgomp.fortran/interop-hip-amd-no-module.F90 b/libgomp/testsuite/libgomp.fortran/interop-hip-amd-no-module.F90
index 0afec83..0ebbe80 100644
--- a/libgomp/testsuite/libgomp.fortran/interop-hip-amd-no-module.F90
+++ b/libgomp/testsuite/libgomp.fortran/interop-hip-amd-no-module.F90
@@ -1,3 +1,6 @@
+! { dg-do run { target { offload_device_gcn } } }
+! { dg-do link { target { ! offload_device_gcn } } }
+
! { dg-require-effective-target gomp_libamdhip64 }
! { dg-additional-options "-lamdhip64" }
diff --git a/libgomp/testsuite/libgomp.fortran/interop-hip-nvidia-full.F90 b/libgomp/testsuite/libgomp.fortran/interop-hip-nvidia-full.F90
index cef592f..d29a689 100644
--- a/libgomp/testsuite/libgomp.fortran/interop-hip-nvidia-full.F90
+++ b/libgomp/testsuite/libgomp.fortran/interop-hip-nvidia-full.F90
@@ -1,3 +1,6 @@
+! { dg-do run { target { offload_device_nvptx } } }
+! { dg-do link { target { ! offload_device_nvptx } } }
+
! { dg-require-effective-target gomp_hipfort_module }
! { dg-require-effective-target openacc_cudart }
! { dg-require-effective-target openacc_cuda }
diff --git a/libgomp/testsuite/libgomp.fortran/interop-hip-nvidia-no-module.F90 b/libgomp/testsuite/libgomp.fortran/interop-hip-nvidia-no-module.F90
index c1ef29d..2063610 100644
--- a/libgomp/testsuite/libgomp.fortran/interop-hip-nvidia-no-module.F90
+++ b/libgomp/testsuite/libgomp.fortran/interop-hip-nvidia-no-module.F90
@@ -1,3 +1,6 @@
+! { dg-do run { target { offload_device_nvptx } } }
+! { dg-do link { target { ! offload_device_nvptx } } }
+
! { dg-require-effective-target openacc_libcudart }
! { dg-require-effective-target openacc_libcuda }
! { dg-additional-options "-lcuda -lcudart" }
diff --git a/libgomp/testsuite/libgomp.fortran/map-alloc-comp-9-usm.f90 b/libgomp/testsuite/libgomp.fortran/map-alloc-comp-9-usm.f90
new file mode 100644
index 0000000..90378c0
--- /dev/null
+++ b/libgomp/testsuite/libgomp.fortran/map-alloc-comp-9-usm.f90
@@ -0,0 +1,11 @@
+! { dg-additional-options "-cpp -DUSE_USM_REQUIREMENT=1 -Wno-openmp" }
+!
+! We silence the warning:
+! Mapping of polymorphic list item '...' is unspecified behavior [-Wopenmp]
+!
+! Ensure that polymorphic mapping is diagnosed as undefined behavior
+! Ensure that static access to polymorphic variables works
+
+! Run map-alloc-comp-9.f90 in unified-shared-memory mode
+
+#include "map-alloc-comp-9.f90"
diff --git a/libgomp/testsuite/libgomp.fortran/map-alloc-comp-9.f90 b/libgomp/testsuite/libgomp.fortran/map-alloc-comp-9.f90
index 3cec392..26c73d7 100644
--- a/libgomp/testsuite/libgomp.fortran/map-alloc-comp-9.f90
+++ b/libgomp/testsuite/libgomp.fortran/map-alloc-comp-9.f90
@@ -1,8 +1,19 @@
+! { dg-additional-options "-cpp" }
+!
! Ensure that polymorphic mapping is diagnosed as undefined behavior
! Ensure that static access to polymorphic variables works
+! Some extended tests are only run with shared memory
+! To enforce this (where possible) on the device side:
+! #define USE_USM_REQUIREMENT
+! which is done in map-alloc-comp-9-usm.f90
+
subroutine test(case)
implicit none(type, external)
+#ifdef USE_USM_REQUIREMENT
+ !$omp requires unified_shared_memory
+#endif
+
type t
integer :: x(4)
end type t
@@ -73,10 +84,14 @@ var4%y2(2)%y%x%x = -7 * [1111,2222,3333,4444]
var4%y2(2)%y%x2(1)%x = -8 * [1111,2222,3333,4444]
var4%y2(2)%y%x2(2)%x = -9 * [1111,2222,3333,4444]
+#ifdef USE_USM_REQUIREMENT
+is_shared_mem = .true.
+#else
is_shared_mem = .false.
!$omp target map(to: is_shared_mem)
is_shared_mem = .true.
!$omp end target
+#endif
if (case == 1) then
! implicit mapping
@@ -532,6 +547,10 @@ end subroutine test
program main
use omp_lib
implicit none(type, external)
+#ifdef USE_USM_REQUIREMENT
+ !$omp requires unified_shared_memory
+#endif
+
interface
subroutine test(case)
integer, value :: case
diff --git a/libgomp/testsuite/libgomp.fortran/metadirective-1.f90 b/libgomp/testsuite/libgomp.fortran/metadirective-1.f90
index 7b3e09f..d6f4d5b 100644
--- a/libgomp/testsuite/libgomp.fortran/metadirective-1.f90
+++ b/libgomp/testsuite/libgomp.fortran/metadirective-1.f90
@@ -1,4 +1,5 @@
-! { dg-do run }
+! { dg-do run { target { ! offload_target_nvptx } } }
+! { dg-do compile { target offload_target_nvptx } }
program test
implicit none
@@ -33,6 +34,10 @@ program test
contains
subroutine f (x, y, z)
integer :: x(N), y(N), z(N)
+ ! The following fails as on the host the target side cannot be
+ ! resolved - and the 'teams' or not status affects how 'target'
+ ! is called. -> See PR118694, esp. comment 9.
+ ! Note also the dg-do compile above for offload_target_nvptx
!$omp target map (to: x, y) map(from: z)
block
@@ -43,6 +48,7 @@ contains
z(i) = x(i) * y(i)
enddo
end block
+ ! { dg-bogus "'target' construct with nested 'teams' construct contains directives outside of the 'teams' construct" "PR118694" { xfail offload_target_nvptx } .-9 } */
end subroutine
subroutine g (x, y, z)
integer :: x(N), y(N), z(N)
@@ -56,6 +62,7 @@ contains
z(i) = x(i) * y(i)
enddo
end block
+ ! { dg-bogus "'target' construct with nested 'teams' construct contains directives outside of the 'teams' construct" "PR118694" { xfail offload_target_nvptx } .-9 } */
!$omp end target
end subroutine
end program
diff --git a/libgomp/testsuite/libgomp.fortran/omp_target_memset-2.f90 b/libgomp/testsuite/libgomp.fortran/omp_target_memset-2.f90
new file mode 100644
index 0000000..2641086
--- /dev/null
+++ b/libgomp/testsuite/libgomp.fortran/omp_target_memset-2.f90
@@ -0,0 +1,67 @@
+! PR libgomp/120444
+! Async version
+
+use omp_lib
+use iso_c_binding
+implicit none (type, external)
+integer(c_int) :: dev
+
+!$omp parallel do
+do dev = omp_initial_device, omp_get_num_devices ()
+block
+ integer(c_int) :: i, val, start, tail
+ type(c_ptr) :: ptr, ptr2, tmpptr
+ integer(c_int8_t), pointer, contiguous :: fptr(:)
+ integer(c_intptr_t) :: intptr
+ integer(c_size_t), parameter :: count = 1024
+ integer(omp_depend_kind) :: dep(1)
+
+ ptr = omp_target_alloc (count, dev)
+
+ !$omp depobj(dep(1)) depend(inout: ptr)
+
+ ! Play also around with the alignment - as hsa_amd_memory_fill operates
+ ! on multiples of 4 bytes (c_int32_t)
+
+ do start = 0, 31
+ do tail = 0, 31
+ val = iachar('0') + start + tail
+
+ tmpptr = transfer (transfer (ptr, intptr) + start, tmpptr)
+ ptr2 = omp_target_memset_async (tmpptr, val, count - start - tail, dev, 0)
+
+ if (.not. c_associated (tmpptr, ptr2)) stop 1
+
+ !$omp taskwait
+
+ !$omp target device(dev) is_device_ptr(ptr) depend(depobj: dep(1)) nowait
+ do i = 1 + start, int(count, c_int) - start - tail
+ call c_f_pointer (ptr, fptr, [count])
+ if (fptr(i) /= int (val, c_int8_t)) stop 2
+ fptr(i) = fptr(i) + 2_c_int8_t
+ end do
+ !$omp end target
+
+ ptr2 = omp_target_memset_async (tmpptr, val + 3, &
+ count - start - tail, dev, 1, dep)
+
+ !$omp target device(dev) is_device_ptr(ptr) depend(depobj: dep(1)) nowait
+ do i = 1 + start, int(count, c_int) - start - tail
+ call c_f_pointer (ptr, fptr, [count])
+ if (fptr(i) /= int (val + 3, c_int8_t)) stop 3
+ fptr(i) = fptr(i) - 1_c_int8_t
+ end do
+ !$omp end target
+
+ ptr2 = omp_target_memset_async (tmpptr, val - 3, &
+ count - start - tail, dev, 1, dep)
+
+ !$omp taskwait depend (depobj: dep(1))
+ end do
+ end do
+
+ !$omp depobj(dep(1)) destroy
+ call omp_target_free (ptr, dev);
+end block
+end do
+end
diff --git a/libgomp/testsuite/libgomp.fortran/omp_target_memset.f90 b/libgomp/testsuite/libgomp.fortran/omp_target_memset.f90
new file mode 100644
index 0000000..1ee184a
--- /dev/null
+++ b/libgomp/testsuite/libgomp.fortran/omp_target_memset.f90
@@ -0,0 +1,39 @@
+! PR libgomp/120444
+
+use omp_lib
+use iso_c_binding
+implicit none (type, external)
+
+integer(c_int) :: dev, i, val, start, tail
+type(c_ptr) :: ptr, ptr2, tmpptr
+integer(c_int8_t), pointer, contiguous :: fptr(:)
+integer(c_intptr_t) :: intptr
+integer(c_size_t), parameter :: count = 1024
+
+do dev = omp_initial_device, omp_get_num_devices ()
+ ptr = omp_target_alloc (count, dev)
+
+ ! Play also around with the alignment - as hsa_amd_memory_fill operates
+ ! on multiples of 4 bytes (c_int32_t)
+
+ do start = 0, 31
+ do tail = 0, 31
+ val = iachar('0') + start + tail
+
+ tmpptr = transfer (transfer (ptr, intptr) + start, tmpptr)
+ ptr2 = omp_target_memset (tmpptr, val, count - start - tail, dev)
+
+ if (.not. c_associated (tmpptr, ptr2)) stop 1
+
+ !$omp target device(dev) is_device_ptr(ptr)
+ do i = 1 + start, int(count, c_int) - start - tail
+ call c_f_pointer (ptr, fptr, [count])
+ if (fptr(i) /= int (val, c_int8_t)) stop 2
+ end do
+ !$omp end target
+ end do
+ end do
+
+ call omp_target_free (ptr, dev);
+end do
+end