xref: /llvm-project/flang/test/Lower/OpenMP/declare-target-implicit-tarop-cap.f90 (revision 00ab44ee66dbcf0d32819dbc6e4eefd1b7c48dfa)
1!RUN: %flang_fc1 -emit-hlfir -fopenmp -fopenmp-version=52 %s -o - | FileCheck %s
2!RUN: %flang_fc1 -emit-hlfir -fopenmp -fopenmp-version=52 -fopenmp-is-device %s -o - | FileCheck %s  --check-prefix=DEVICE
3!RUN: bbc -emit-hlfir -fopenmp -fopenmp-version=52 %s -o - | FileCheck %s
4!RUN: bbc -emit-hlfir -fopenmp -fopenmp-version=52 -fopenmp-is-target-device %s -o - | FileCheck %s --check-prefix=DEVICE
5
6! DEVICE-LABEL: func.func @_QPimplicit_capture
7! DEVICE-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (to)>{{.*}}}
8function implicit_capture() result(i)
9   implicit none
10   integer :: i
11   i = 1
12end function implicit_capture
13
14subroutine subr_target()
15   integer :: n
16!$omp target map(tofrom:n)
17   n = implicit_capture()
18!$omp end target
19end subroutine
20
21!! -----
22
23! CHECK-LABEL: func.func @_QPimplicitly_captured_nest_twice
24! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>{{.*}}}
25function implicitly_captured_nest_twice() result(i)
26   integer :: i
27   i = 10
28end function implicitly_captured_nest_twice
29
30! CHECK-LABEL: func.func @_QPimplicitly_captured_one_twice
31! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>{{.*}}}
32function implicitly_captured_one_twice() result(k)
33!$omp declare target to(implicitly_captured_one_twice) device_type(host)
34   k = implicitly_captured_nest_twice()
35end function implicitly_captured_one_twice
36
37! CHECK-LABEL: func.func @_QPimplicitly_captured_nest_twice_enter
38! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (host), capture_clause = (enter)>{{.*}}}
39function implicitly_captured_nest_twice_enter() result(i)
40   integer :: i
41   i = 10
42end function implicitly_captured_nest_twice_enter
43
44! CHECK-LABEL: func.func @_QPimplicitly_captured_one_twice_enter
45! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (host), capture_clause = (enter)>{{.*}}}
46function implicitly_captured_one_twice_enter() result(k)
47!$omp declare target enter(implicitly_captured_one_twice_enter) device_type(host)
48   k = implicitly_captured_nest_twice_enter()
49end function implicitly_captured_one_twice_enter
50
51! DEVICE-LABEL: func.func @_QPimplicitly_captured_two_twice
52! DEVICE-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (to)>{{.*}}}
53function implicitly_captured_two_twice() result(y)
54   integer :: y
55   y = 5
56end function implicitly_captured_two_twice
57
58
59function target_function_test_device() result(j)
60   integer :: i, j
61   !$omp target map(tofrom: i, j)
62   i = implicitly_captured_one_twice()
63   j = implicitly_captured_two_twice() + i
64   !$omp end target
65end function target_function_test_device
66
67!! -----
68
69! DEVICE-LABEL: func.func @_QPimplicitly_captured_recursive
70! DEVICE-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (to)>{{.*}}}
71recursive function implicitly_captured_recursive(increment) result(k)
72   integer :: increment, k
73   if (increment == 10) then
74      k = increment
75   else
76      k = implicitly_captured_recursive(increment + 1)
77   end if
78end function implicitly_captured_recursive
79
80function target_function_recurse() result(i)
81   integer :: i
82   !$omp target map(tofrom: i)
83   i = implicitly_captured_recursive(0)
84   !$omp end target
85end function target_function_recurse
86