1! { dg-additional-options "-fdump-tree-omplower" }
2
3module m
4  implicit none (type, external)
5contains
6  subroutine mod_proc(x)
7    integer :: x(2)
8      x = x + 5
9    end subroutine
10end module m
11
12program main
13  use m
14  implicit none (type, external)
15  if (any (foo() /= [48, 49])) stop 1
16contains
17  integer function fourty_two(y)
18    integer :: y
19    fourty_two = y + 42
20  end function
21
22  integer function wrapper (x, y)
23    integer :: x, y(2)
24    call mod_proc(y)
25    wrapper = fourty_two(x) + 1
26  end function
27
28  function foo()
29    integer :: foo(2)
30    integer :: a(2)
31    integer :: b, summed(2)
32    a = [1, 2]
33    b = -1
34    !$omp target map (tofrom: a, b, summed)
35      summed = wrapper (b, a)
36    !$omp end target
37    if (b /= -1) stop 2            ! unchanged
38    if (any (summed /= 42)) stop 3 ! b + 42 + 1 = 42
39    if (any (a /= [6, 7])) stop 4  ! [1, 2] + 5
40    foo = summed + a               ! [48, 49]
41  end function
42end
43
44! 3 times: mod_proc, fourty_two and wrapper:
45! { dg-final { scan-tree-dump-times "__attribute__..omp declare target" 3 "omplower" } }
46