xref: /llvm-project/flang/test/Lower/OpenMP/declare-target-func-and-subr.f90 (revision 00ab44ee66dbcf0d32819dbc6e4eefd1b7c48dfa)
1!RUN: %flang_fc1 -emit-hlfir -fopenmp -fopenmp-version=52 %s -o - | FileCheck %s --check-prefixes ALL,HOST
2!RUN: %flang_fc1 -emit-hlfir -fopenmp -fopenmp-version=52 -fopenmp-is-device %s -o - | FileCheck %s --check-prefixes ALL,DEVICE
3
4! Check specification valid forms of declare target with functions
5! utilising device_type and to clauses as well as the default
6! zero clause declare target
7
8! DEVICE-LABEL: func.func @_QPfunc_t_device()
9! DEVICE-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (to)>{{.*}}
10FUNCTION FUNC_T_DEVICE() RESULT(I)
11!$omp declare target to(FUNC_T_DEVICE) device_type(nohost)
12    INTEGER :: I
13    I = 1
14END FUNCTION FUNC_T_DEVICE
15
16! DEVICE-LABEL: func.func @_QPfunc_enter_device()
17! DEVICE-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (enter)>{{.*}}
18FUNCTION FUNC_ENTER_DEVICE() RESULT(I)
19!$omp declare target enter(FUNC_ENTER_DEVICE) device_type(nohost)
20    INTEGER :: I
21    I = 1
22END FUNCTION FUNC_ENTER_DEVICE
23
24! HOST-LABEL: func.func @_QPfunc_t_host()
25! HOST-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (host), capture_clause = (to)>{{.*}}
26FUNCTION FUNC_T_HOST() RESULT(I)
27!$omp declare target to(FUNC_T_HOST) device_type(host)
28    INTEGER :: I
29    I = 1
30END FUNCTION FUNC_T_HOST
31
32! HOST-LABEL: func.func @_QPfunc_enter_host()
33! HOST-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (host), capture_clause = (enter)>{{.*}}
34FUNCTION FUNC_ENTER_HOST() RESULT(I)
35!$omp declare target enter(FUNC_ENTER_HOST) device_type(host)
36    INTEGER :: I
37    I = 1
38END FUNCTION FUNC_ENTER_HOST
39
40! ALL-LABEL: func.func @_QPfunc_t_any()
41! ALL-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>{{.*}}
42FUNCTION FUNC_T_ANY() RESULT(I)
43!$omp declare target to(FUNC_T_ANY) device_type(any)
44    INTEGER :: I
45    I = 1
46END FUNCTION FUNC_T_ANY
47
48! ALL-LABEL: func.func @_QPfunc_enter_any()
49! ALL-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (enter)>{{.*}}
50FUNCTION FUNC_ENTER_ANY() RESULT(I)
51!$omp declare target enter(FUNC_ENTER_ANY) device_type(any)
52    INTEGER :: I
53    I = 1
54END FUNCTION FUNC_ENTER_ANY
55
56! ALL-LABEL: func.func @_QPfunc_default_t_any()
57! ALL-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>{{.*}}
58FUNCTION FUNC_DEFAULT_T_ANY() RESULT(I)
59!$omp declare target to(FUNC_DEFAULT_T_ANY)
60    INTEGER :: I
61    I = 1
62END FUNCTION FUNC_DEFAULT_T_ANY
63
64! ALL-LABEL: func.func @_QPfunc_default_enter_any()
65! ALL-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (enter)>{{.*}}
66FUNCTION FUNC_DEFAULT_ENTER_ANY() RESULT(I)
67!$omp declare target enter(FUNC_DEFAULT_ENTER_ANY)
68    INTEGER :: I
69    I = 1
70END FUNCTION FUNC_DEFAULT_ENTER_ANY
71
72! ALL-LABEL: func.func @_QPfunc_default_any()
73! ALL-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>{{.*}}
74FUNCTION FUNC_DEFAULT_ANY() RESULT(I)
75!$omp declare target
76    INTEGER :: I
77    I = 1
78END FUNCTION FUNC_DEFAULT_ANY
79
80! ALL-LABEL: func.func @_QPfunc_default_extendedlist()
81! ALL-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>{{.*}}
82FUNCTION FUNC_DEFAULT_EXTENDEDLIST() RESULT(I)
83!$omp declare target(FUNC_DEFAULT_EXTENDEDLIST)
84    INTEGER :: I
85    I = 1
86END FUNCTION FUNC_DEFAULT_EXTENDEDLIST
87
88!! -----
89
90! Check specification valid forms of declare target with subroutines
91! utilising device_type and to clauses as well as the default
92! zero clause declare target
93
94! DEVICE-LABEL: func.func @_QPsubr_t_device()
95! DEVICE-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (to)>{{.*}}
96SUBROUTINE SUBR_T_DEVICE()
97!$omp declare target to(SUBR_T_DEVICE) device_type(nohost)
98END
99
100! DEVICE-LABEL: func.func @_QPsubr_enter_device()
101! DEVICE-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (enter)>{{.*}}
102SUBROUTINE SUBR_ENTER_DEVICE()
103!$omp declare target enter(SUBR_ENTER_DEVICE) device_type(nohost)
104END
105
106! HOST-LABEL: func.func @_QPsubr_t_host()
107! HOST-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (host), capture_clause = (to)>{{.*}}
108SUBROUTINE SUBR_T_HOST()
109!$omp declare target to(SUBR_T_HOST) device_type(host)
110END
111
112! HOST-LABEL: func.func @_QPsubr_enter_host()
113! HOST-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (host), capture_clause = (enter)>{{.*}}
114SUBROUTINE SUBR_ENTER_HOST()
115!$omp declare target enter(SUBR_ENTER_HOST) device_type(host)
116END
117
118! ALL-LABEL: func.func @_QPsubr_t_any()
119! ALL-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>{{.*}}
120SUBROUTINE SUBR_T_ANY()
121!$omp declare target to(SUBR_T_ANY) device_type(any)
122END
123
124! ALL-LABEL: func.func @_QPsubr_enter_any()
125! ALL-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (enter)>{{.*}}
126SUBROUTINE SUBR_ENTER_ANY()
127!$omp declare target enter(SUBR_ENTER_ANY) device_type(any)
128END
129
130! ALL-LABEL: func.func @_QPsubr_default_t_any()
131! ALL-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>{{.*}}
132SUBROUTINE SUBR_DEFAULT_T_ANY()
133!$omp declare target to(SUBR_DEFAULT_T_ANY)
134END
135
136! ALL-LABEL: func.func @_QPsubr_default_enter_any()
137! ALL-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (enter)>{{.*}}
138SUBROUTINE SUBR_DEFAULT_ENTER_ANY()
139!$omp declare target enter(SUBR_DEFAULT_ENTER_ANY)
140END
141
142! ALL-LABEL: func.func @_QPsubr_default_any()
143! ALL-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>{{.*}}
144SUBROUTINE SUBR_DEFAULT_ANY()
145!$omp declare target
146END
147
148! ALL-LABEL: func.func @_QPsubr_default_extendedlist()
149! ALL-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>{{.*}}
150SUBROUTINE SUBR_DEFAULT_EXTENDEDLIST()
151!$omp declare target(SUBR_DEFAULT_EXTENDEDLIST)
152END
153
154!! -----
155
156! DEVICE-LABEL: func.func @_QPrecursive_declare_target
157! DEVICE-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (to)>{{.*}}
158RECURSIVE FUNCTION RECURSIVE_DECLARE_TARGET(INCREMENT) RESULT(K)
159!$omp declare target to(RECURSIVE_DECLARE_TARGET) device_type(nohost)
160    INTEGER :: INCREMENT, K
161    IF (INCREMENT == 10) THEN
162        K = INCREMENT
163    ELSE
164        K = RECURSIVE_DECLARE_TARGET(INCREMENT + 1)
165    END IF
166END FUNCTION RECURSIVE_DECLARE_TARGET
167
168! DEVICE-LABEL: func.func @_QPrecursive_declare_target_enter
169! DEVICE-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (enter)>{{.*}}
170RECURSIVE FUNCTION RECURSIVE_DECLARE_TARGET_ENTER(INCREMENT) RESULT(K)
171!$omp declare target enter(RECURSIVE_DECLARE_TARGET_ENTER) device_type(nohost)
172    INTEGER :: INCREMENT, K
173    IF (INCREMENT == 10) THEN
174        K = INCREMENT
175    ELSE
176        K = RECURSIVE_DECLARE_TARGET_ENTER(INCREMENT + 1)
177    END IF
178END FUNCTION RECURSIVE_DECLARE_TARGET_ENTER
179