1 ! Offloading test with runtine call to ompx_dump_mapping_tables
2 ! Fortran array writing some values and printing the variable mapped to device
3 ! correctly receives the updates made on the device.
5 ! UNSUPPORTED: nvptx64-nvidia-cuda-LTO
6 ! UNSUPPORTED: aarch64-unknown-linux-gnu
7 ! UNSUPPORTED: aarch64-unknown-linux-gnu-LTO
8 ! UNSUPPORTED: x86_64-pc-linux-gnu
9 ! UNSUPPORTED: x86_64-pc-linux-gnu-LTO
11 ! RUN: %libomptarget-compile-fortran-run-and-check-generic
13 program map_dump_example
15 SUBROUTINE ompx_dump_mapping_tables() BIND(C
)
16 END SUBROUTINE ompx_dump_mapping_tables
27 ! CHECK: omptarget device 0 info: OpenMP Host-Device pointer mappings after block
28 ! CHECK-NEXT: omptarget device 0 info: Host Ptr Target Ptr Size (B) DynRefCount HoldRefCount Declaration
29 ! CHECK-NEXT: omptarget device 0 info: {{(0x[0-9a-f]{16})}} {{(0x[0-9a-f]{16})}} 20000000 1 0 {{.*}} at a(:n):21:11
31 !$omp target enter data map(to:A(:N))
32 call ompx_dump_mapping_tables()
33 !$omp target parallel do
37 !$omp target exit data map(from:A)