aboutsummaryrefslogtreecommitdiff
path: root/libgomp/testsuite/libgomp.fortran/self_maps.f90
blob: 208fd1c71d5c64b7abc4ce0baceb074e0649417c (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
! Basic test whether self_maps work

module m
  !$omp requires self_maps
  implicit none (type, external)
  type t
    integer :: val
    type(t), pointer :: next
  end type t
contains
  subroutine init(p)
    integer :: i
    type(t), pointer :: p, x
    allocate(x)
    p => x
    do i = 1, 5
      x%val = i
      if (i < 5) then
        allocate(x%next)
        x => x%next
      end if
    end do
  end subroutine

  subroutine check(p)
    !$omp declare target enter(check)
    integer :: i
    type(t), pointer :: p, x
    x => p
    do i = 1, 5
      if (x%val /= i) stop 1
       x => x%next
    end do
end subroutine
end module

use omp_lib
use m
implicit none (type, external)
type(t), pointer :: linked
integer :: i

call init(linked)
do i = 0, omp_get_num_devices()
  !$omp target device(i)
    call check(linked)
  !$omp end target
end do
end