Many tests in the `offload` project have requirements defined by which targets are not supported rather than which platforms are supported. This patch aims to streamline the requirement definitions by adding four new feature tags: `host`, `gpu`, `amdgpu`, and `nvidiagpu`.
39 lines
878 B
Fortran
39 lines
878 B
Fortran
! Offloading test checking interaction of allocatables
|
|
! with multi-dimensional bounds (3-D in this case) and
|
|
! a target region
|
|
! REQUIRES: flang, amdgpu
|
|
|
|
! RUN: %libomptarget-compile-fortran-run-and-check-generic
|
|
program main
|
|
integer, allocatable :: inArray(:,:,:)
|
|
integer, allocatable :: outArray(:,:,:)
|
|
|
|
allocate(inArray(3,3,3))
|
|
allocate(outArray(3,3,3))
|
|
|
|
do i = 1, 3
|
|
do j = 1, 3
|
|
do k = 1, 3
|
|
inArray(i, j, k) = 42
|
|
outArray(i, j, k) = 0
|
|
end do
|
|
end do
|
|
end do
|
|
|
|
!$omp target map(tofrom:inArray(1:3, 1:3, 2:2), outArray(1:3, 1:3, 1:3))
|
|
do j = 1, 3
|
|
do k = 1, 3
|
|
outArray(k, j, 2) = inArray(k, j, 2)
|
|
end do
|
|
end do
|
|
!$omp end target
|
|
|
|
print *, outArray
|
|
|
|
deallocate(inArray)
|
|
deallocate(outArray)
|
|
|
|
end program
|
|
|
|
! CHECK: 0 0 0 0 0 0 0 0 0 42 42 42 42 42 42 42 42 42 0 0 0 0 0 0 0 0 0
|