xref: /llvm-project/flang/test/Lower/OpenMP/declare-target-implicit-func-and-subr-cap-enter.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-target-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! CHECK-LABEL: func.func @_QPimplicitly_captured_twice
7! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (enter)>{{.*}}}
8function implicitly_captured_twice() result(k)
9   integer :: i
10   i = 10
11   k = i
12end function implicitly_captured_twice
13
14! CHECK-LABEL: func.func @_QPtarget_function_twice_host
15! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (host), capture_clause = (enter)>{{.*}}}
16function target_function_twice_host() result(i)
17!$omp declare target enter(target_function_twice_host) device_type(host)
18   integer :: i
19   i = implicitly_captured_twice()
20end function target_function_twice_host
21
22! DEVICE-LABEL: func.func @_QPtarget_function_twice_device
23! DEVICE-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (enter)>{{.*}}}
24function target_function_twice_device() result(i)
25!$omp declare target enter(target_function_twice_device) device_type(nohost)
26   integer :: i
27   i = implicitly_captured_twice()
28end function target_function_twice_device
29
30!! -----
31
32! DEVICE-LABEL: func.func @_QPimplicitly_captured_nest
33! DEVICE-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (enter)>{{.*}}}
34function implicitly_captured_nest() result(k)
35   integer :: i
36   i = 10
37   k = i
38end function implicitly_captured_nest
39
40! DEVICE-LABEL: func.func @_QPimplicitly_captured_one
41! DEVICE-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (enter){{.*}}}
42function implicitly_captured_one() result(k)
43   k = implicitly_captured_nest()
44end function implicitly_captured_one
45
46! DEVICE-LABEL: func.func @_QPimplicitly_captured_two
47! DEVICE-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (enter)>{{.*}}}
48function implicitly_captured_two() result(k)
49   integer :: i
50   i = 10
51   k = i
52end function implicitly_captured_two
53
54! DEVICE-LABEL: func.func @_QPtarget_function_test
55! DEVICE-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (enter)>{{.*}}}
56function target_function_test() result(j)
57!$omp declare target enter(target_function_test) device_type(nohost)
58   integer :: i, j
59   i = implicitly_captured_one()
60   j = implicitly_captured_two() + i
61end function target_function_test
62
63!! -----
64
65! CHECK-LABEL: func.func @_QPimplicitly_captured_nest_twice
66! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (enter)>{{.*}}}
67function implicitly_captured_nest_twice() result(k)
68   integer :: i
69   i = 10
70   k = i
71end function implicitly_captured_nest_twice
72
73! CHECK-LABEL: func.func @_QPimplicitly_captured_one_twice
74! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (enter)>{{.*}}}
75function implicitly_captured_one_twice() result(k)
76   k = implicitly_captured_nest_twice()
77end function implicitly_captured_one_twice
78
79! CHECK-LABEL: func.func @_QPimplicitly_captured_two_twice
80! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (enter)>{{.*}}}
81function implicitly_captured_two_twice() result(k)
82   integer :: i
83   i = 10
84   k = i
85end function implicitly_captured_two_twice
86
87! DEVICE-LABEL: func.func @_QPtarget_function_test_device
88! DEVICE-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (enter)>{{.*}}}
89function target_function_test_device() result(j)
90   !$omp declare target enter(target_function_test_device) device_type(nohost)
91   integer :: i, j
92   i = implicitly_captured_one_twice()
93   j = implicitly_captured_two_twice() + i
94end function target_function_test_device
95
96! CHECK-LABEL: func.func @_QPtarget_function_test_host
97! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (host), capture_clause = (enter)>{{.*}}}
98function target_function_test_host() result(j)
99   !$omp declare target enter(target_function_test_host) device_type(host)
100   integer :: i, j
101   i = implicitly_captured_one_twice()
102   j = implicitly_captured_two_twice() + i
103end function target_function_test_host
104
105!! -----
106
107! DEVICE-LABEL: func.func @_QPimplicitly_captured_with_dev_type_recursive
108! DEVICE-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (enter)>{{.*}}}
109recursive function implicitly_captured_with_dev_type_recursive(increment) result(k)
110!$omp declare target enter(implicitly_captured_with_dev_type_recursive) device_type(host)
111   integer :: increment, k
112   if (increment == 10) then
113      k = increment
114   else
115      k = implicitly_captured_with_dev_type_recursive(increment + 1)
116   end if
117end function implicitly_captured_with_dev_type_recursive
118
119! DEVICE-LABEL: func.func @_QPtarget_function_with_dev_type_recurse
120! DEVICE-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (enter)>{{.*}}}
121function target_function_with_dev_type_recurse() result(i)
122!$omp declare target enter(target_function_with_dev_type_recurse) device_type(nohost)
123   integer :: i
124   i = implicitly_captured_with_dev_type_recursive(0)
125end function target_function_with_dev_type_recurse
126
127!! -----
128
129module test_module
130contains
131! CHECK-LABEL: func.func @_QMtest_modulePimplicitly_captured_nest_twice
132! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (enter)>{{.*}}}
133   function implicitly_captured_nest_twice() result(i)
134      integer :: i
135      i = 10
136   end function implicitly_captured_nest_twice
137
138! CHECK-LABEL: func.func @_QMtest_modulePimplicitly_captured_one_twice
139! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (enter)>{{.*}}}
140   function implicitly_captured_one_twice() result(k)
141      !$omp declare target enter(implicitly_captured_one_twice) device_type(host)
142      k = implicitly_captured_nest_twice()
143   end function implicitly_captured_one_twice
144
145! DEVICE-LABEL: func.func @_QMtest_modulePimplicitly_captured_two_twice
146! DEVICE-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (enter)>{{.*}}}
147   function implicitly_captured_two_twice() result(y)
148      integer :: y
149      y = 5
150   end function implicitly_captured_two_twice
151
152! DEVICE-LABEL: func.func @_QMtest_modulePtarget_function_test_device
153! DEVICE-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (enter)>{{.*}}}
154   function target_function_test_device() result(j)
155      !$omp declare target enter(target_function_test_device) device_type(nohost)
156      integer :: i, j
157      i = implicitly_captured_one_twice()
158      j = implicitly_captured_two_twice() + i
159   end function target_function_test_device
160end module test_module
161
162!! -----
163
164program mb
165   interface
166      subroutine caller_recursive
167         !$omp declare target enter(caller_recursive) device_type(nohost)
168      end subroutine
169
170      recursive subroutine implicitly_captured_recursive(increment)
171         integer :: increment
172      end subroutine
173   end interface
174end program
175
176! DEVICE-LABEL: func.func @_QPimplicitly_captured_recursive
177! DEVICE-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (enter)>{{.*}}}
178recursive subroutine implicitly_captured_recursive(increment)
179   integer :: increment
180   if (increment == 10) then
181      return
182   else
183      call implicitly_captured_recursive(increment + 1)
184   end if
185end subroutine
186
187! DEVICE-LABEL: func.func @_QPcaller_recursive
188! DEVICE-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (enter)>{{.*}}}
189subroutine caller_recursive
190!$omp declare target enter(caller_recursive) device_type(nohost)
191   call implicitly_captured_recursive(0)
192end subroutine
193