xref: /llvm-project/offload/test/offloading/fortran/explicit-and-implicit-record-field-mapping.f90 (revision e532241b021cd48bad303721757c1194bc844775)
1! REQUIRES: flang, amdgpu
2
3! RUN: %libomptarget-compile-fortran-generic
4! RUN: env LIBOMPTARGET_INFO=16 %libomptarget-run-generic 2>&1 | %fcheck-generic
5module test
6implicit none
7
8TYPE field_type
9  REAL, DIMENSION(:,:), ALLOCATABLE :: density0, density1
10END TYPE field_type
11
12TYPE tile_type
13  TYPE(field_type) :: field
14  INTEGER          :: tile_neighbours(4)
15END TYPE tile_type
16
17TYPE chunk_type
18  INTEGER                                    :: filler
19  TYPE(tile_type), DIMENSION(:), ALLOCATABLE :: tiles
20END TYPE chunk_type
21
22end module test
23
24program reproducer
25  use test
26  implicit none
27  integer          :: i, j
28  TYPE(chunk_type) :: chunk
29
30  allocate(chunk%tiles(2))
31  do i = 1, 2
32    allocate(chunk%tiles(i)%field%density0(2, 2))
33    allocate(chunk%tiles(i)%field%density1(2, 2))
34    do j = 1, 4
35      chunk%tiles(i)%tile_neighbours(j) = j * 10
36    end do
37  end do
38
39  !$omp target enter data map(alloc:       &
40  !$omp  chunk%tiles(2)%field%density0)
41
42  !$omp target
43    chunk%tiles(2)%field%density0(1,1) = 25
44    chunk%tiles(2)%field%density0(1,2) = 50
45    chunk%tiles(2)%field%density0(2,1) = 75
46    chunk%tiles(2)%field%density0(2,2) = 100
47  !$omp end target
48
49  !$omp target exit data map(from:         &
50  !$omp  chunk%tiles(2)%field%density0)
51
52  if (chunk%tiles(2)%field%density0(1,1) /= 25) then
53    print*, "======= Test Failed! ======="
54    stop 1
55  end if
56
57  if (chunk%tiles(2)%field%density0(1,2) /= 50) then
58    print*, "======= Test Failed! ======="
59    stop 1
60  end if
61
62  if (chunk%tiles(2)%field%density0(2,1) /= 75) then
63    print*, "======= Test Failed! ======="
64    stop 1
65  end if
66
67  if (chunk%tiles(2)%field%density0(2,2) /= 100) then
68    print*, "======= Test Failed! ======="
69    stop 1
70  end if
71
72  do j = 1, 4
73    if (chunk%tiles(2)%tile_neighbours(j) /= j * 10) then
74      print*, "======= Test Failed! ======="
75      stop 1
76    end if
77  end do
78
79  print *, "======= Test Passed! ======="
80end program reproducer
81
82! CHECK: "PluginInterface" device {{[0-9]+}} info: Launching kernel {{.*}}
83! CHECK: ======= Test Passed! =======
84