xref: /llvm-project/offload/test/offloading/fortran/target-map-local-intrinisc-sized-param.f90 (revision 5137c209f0c19668d06e48cc4293e4c01a77c964)
1*5137c209Sagozillon! Offloading test checking interaction of an local array
2*5137c209Sagozillon! sized utilising an input parameter and the size intrinsic
3*5137c209Sagozillon! when being mapped to device.
4*5137c209Sagozillon! REQUIRES: flang, amdgpu
5*5137c209Sagozillon
6*5137c209Sagozillon! RUN: %libomptarget-compile-fortran-run-and-check-generic
7*5137c209Sagozillonmodule mod
8*5137c209Sagozillon    use iso_fortran_env, only: real64
9*5137c209Sagozillon    implicit none
10*5137c209Sagozilloncontains
11*5137c209Sagozillon    subroutine test(a)
12*5137c209Sagozillon        implicit none
13*5137c209Sagozillon        integer :: i
14*5137c209Sagozillon        real(kind=real64), dimension(:) :: a
15*5137c209Sagozillon        real(kind=real64), dimension(size(a, 1)) :: b
16*5137c209Sagozillon
17*5137c209Sagozillon!$omp target map(tofrom: b)
18*5137c209Sagozillon        do i = 1, 10
19*5137c209Sagozillon            b(i) = i
20*5137c209Sagozillon        end do
21*5137c209Sagozillon!$omp end target
22*5137c209Sagozillon
23*5137c209Sagozillon        print *, b
24*5137c209Sagozillon    end subroutine
25*5137c209Sagozillonend module mod
26*5137c209Sagozillon
27*5137c209Sagozillonprogram main
28*5137c209Sagozillon    use mod
29*5137c209Sagozillon    real(kind=real64), allocatable :: a(:)
30*5137c209Sagozillon    allocate(a(10))
31*5137c209Sagozillon
32*5137c209Sagozillon    do i = 1, 10
33*5137c209Sagozillon        a(i) = i
34*5137c209Sagozillon    end do
35*5137c209Sagozillon
36*5137c209Sagozillon    call test(a)
37*5137c209Sagozillonend program main
38*5137c209Sagozillon
39*5137c209Sagozillon!CHECK: 1. 2. 3. 4. 5. 6. 7. 8. 9. 10.
40