Bump version to 19.1.0-rc3
[llvm-project.git] / offload / test / offloading / fortran / target-map-allocatable-map-scopes.f90
blob4a97a9ade91cdcbf2d018bedbbddc6870fbc3998
1 ! Offloading test checking interaction of allocatables
2 ! with target in different scopes
3 ! REQUIRES: flang, amdgpu
5 ! RUN: %libomptarget-compile-fortran-run-and-check-generic
6 module test
7 contains
8 subroutine func_arg(arg_alloc)
9 integer, allocatable, intent (inout) :: arg_alloc(:)
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
17 print *, arg_alloc
18 end subroutine func_arg
19 end module
21 subroutine func
22 integer, allocatable :: local_alloc(:)
23 allocate(local_alloc(10))
25 !$omp target map(tofrom: local_alloc)
26 do index = 1, 10
27 local_alloc(index) = index
28 end do
29 !$omp end target
31 print *, local_alloc
33 deallocate(local_alloc)
34 end subroutine func
37 program main
38 use test
39 integer, allocatable :: map_ptr(:)
41 allocate(map_ptr(10))
43 !$omp target map(tofrom: map_ptr)
44 do index = 1, 10
45 map_ptr(index) = index
46 end do
47 !$omp end target
49 call func
51 print *, map_ptr
53 call func_arg(map_ptr)
55 deallocate(map_ptr)
56 end program
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