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