xref: /llvm-project/offload/test/offloading/fortran/target-map-allocatable-map-scopes.f90 (revision 372344995568cae076477a8b0e98fcdec7c49379)
1! Offloading test checking interaction of allocatables with target in different
2! scopes
3! REQUIRES: flang, amdgpu
4
5! RUN: %libomptarget-compile-fortran-run-and-check-generic
6module test
7    contains
8  subroutine func_arg(arg_alloc)
9    integer,  allocatable, intent (inout) :: arg_alloc(:)
10
11  !$omp target map(tofrom: arg_alloc)
12    do index = 1, 10
13      arg_alloc(index) = arg_alloc(index) + index
14    end do
15  !$omp end target
16
17    print *, arg_alloc
18  end subroutine func_arg
19end module
20
21subroutine func
22    integer,  allocatable :: local_alloc(:)
23    allocate(local_alloc(10))
24
25  !$omp target map(tofrom: local_alloc)
26    do index = 1, 10
27      local_alloc(index) = index
28    end do
29  !$omp end target
30
31    print *, local_alloc
32
33    deallocate(local_alloc)
34end subroutine func
35
36
37program main
38  use test
39  integer,  allocatable :: map_ptr(:)
40
41  allocate(map_ptr(10))
42
43  !$omp target map(tofrom: map_ptr)
44    do index = 1, 10
45      map_ptr(index) = index
46    end do
47  !$omp end target
48
49   call func
50
51   print *, map_ptr
52
53   call func_arg(map_ptr)
54
55   deallocate(map_ptr)
56end program
57
58! CHECK: 1 2 3 4 5 6 7 8 9 10
59! CHECK: 1 2 3 4 5 6 7 8 9 10
60! CHECK: 2 4 6 8 10 12 14 16 18 20
61