34 use,
intrinsic :: iso_c_binding, only: c_ptr, c_int
38 use mpi_f08,
only: mpi_sum, mpi_in_place, mpi_allreduce
46 s12_d, s13_d, s23_d, &
48 bind(c, name =
'hip_s_abs_compute')
49 use,
intrinsic :: iso_c_binding, only: c_ptr, c_int
51 type(c_ptr),
value :: s_abs_d, s11_d, s22_d, s33_d, &
58 l12_d, l13_d, l23_d, &
61 fuu_d, fvv_d, fww_d, &
62 fuv_d, fuw_d, fvw_d, n) &
63 bind(c, name =
'hip_lij_compute_part1')
64 use,
intrinsic :: iso_c_binding, only: c_ptr, c_int
66 type(c_ptr),
value :: l11_d, l22_d, l33_d, l12_d, l13_d, l23_d, &
67 u_d, v_d, w_d, fu_d, fv_d, fw_d, &
68 fuu_d, fvv_d, fww_d, fuv_d, fuw_d, fvw_d
74 l12_d, l13_d, l23_d, &
75 fuu_d, fvv_d, fww_d, &
76 fuv_d, fuw_d, fvw_d, n) &
77 bind(c, name =
'hip_lij_compute_part2')
78 use,
intrinsic :: iso_c_binding, only: c_ptr, c_int
80 type(c_ptr),
value :: l11_d, l22_d, l33_d, l12_d, l13_d, l23_d, &
81 fuu_d, fvv_d, fww_d, fuv_d, fuw_d, fvw_d
87 m12_d, m13_d, m23_d, &
88 s_abs_d, s11_d, s22_d, s33_d, &
89 s12_d, s13_d, s23_d, &
90 fs_abs_d, fs11_d, fs22_d, fs33_d, &
91 fs12_d, fs13_d, fs23_d, &
92 fsabss11_d, fsabss22_d, fsabss33_d, &
93 fsabss12_d, fsabss13_d, fsabss23_d, &
95 bind(c, name =
'hip_mij_compute_part1')
96 use,
intrinsic :: iso_c_binding, only: c_ptr, c_int
98 type(c_ptr),
value :: m11_d, m22_d, m33_d, &
99 m12_d, m13_d, m23_d, &
100 s_abs_d, s11_d, s22_d, s33_d, &
101 s12_d, s13_d, s23_d, &
102 fs_abs_d, fs11_d, fs22_d, fs33_d, &
103 fs12_d, fs13_d, fs23_d, &
104 fsabss11_d, fsabss22_d, fsabss33_d, &
105 fsabss12_d, fsabss13_d, fsabss23_d
106 real(c_rp) :: delta_ratio2
112 m12_d, m13_d, m23_d, &
113 l11_d, l22_d, l33_d, &
114 l12_d, l13_d, l23_d, &
115 fsabss11_d, fsabss22_d, fsabss33_d, &
116 fsabss12_d, fsabss13_d, fsabss23_d, &
117 num_d, den_d, c_dyn_d, delta_d, &
118 s_abs_d, nut_d, alpha, mult_d, n) &
119 bind(c, name =
'hip_mij_nut_compute_part2')
120 use,
intrinsic :: iso_c_binding, only: c_ptr, c_int
122 type(c_ptr),
value :: m11_d, m22_d, m33_d, &
123 m12_d, m13_d, m23_d, &
124 l11_d, l22_d, l33_d, &
125 l12_d, l13_d, l23_d, &
126 fsabss11_d, fsabss22_d, fsabss33_d, &
127 fsabss12_d, fsabss13_d, fsabss23_d, &
128 num_d, den_d, c_dyn_d, delta_d, s_abs_d, nut_d, mult_d
136 s12_d, s13_d, s23_d, &
138 bind(c, name =
'cuda_s_abs_compute')
139 use,
intrinsic :: iso_c_binding, only: c_ptr, c_int
141 type(c_ptr),
value :: s_abs_d, s11_d, s22_d, s33_d, &
148 l12_d, l13_d, l23_d, &
151 fuu_d, fvv_d, fww_d, &
152 fuv_d, fuw_d, fvw_d, n) &
153 bind(c, name =
'cuda_lij_compute_part1')
154 use,
intrinsic :: iso_c_binding, only: c_ptr, c_int
156 type(c_ptr),
value :: l11_d, l22_d, l33_d, l12_d, l13_d, l23_d, &
157 u_d, v_d, w_d, fu_d, fv_d, fw_d, &
158 fuu_d, fvv_d, fww_d, fuv_d, fuw_d, fvw_d
164 l12_d, l13_d, l23_d, &
165 fuu_d, fvv_d, fww_d, &
166 fuv_d, fuw_d, fvw_d, n) &
167 bind(c, name =
'cuda_lij_compute_part2')
168 use,
intrinsic :: iso_c_binding, only: c_ptr, c_int
170 type(c_ptr),
value :: l11_d, l22_d, l33_d, l12_d, l13_d, l23_d, &
171 fuu_d, fvv_d, fww_d, fuv_d, fuw_d, fvw_d
177 m12_d, m13_d, m23_d, &
178 s_abs_d, s11_d, s22_d, s33_d, &
179 s12_d, s13_d, s23_d, &
180 fs_abs_d, fs11_d, fs22_d, fs33_d, &
181 fs12_d, fs13_d, fs23_d, &
182 fsabss11_d, fsabss22_d, fsabss33_d, &
183 fsabss12_d, fsabss13_d, fsabss23_d, &
185 bind(c, name =
'cuda_mij_compute_part1')
186 use,
intrinsic :: iso_c_binding, only: c_ptr, c_int
188 type(c_ptr),
value :: m11_d, m22_d, m33_d, &
189 m12_d, m13_d, m23_d, &
190 s_abs_d, s11_d, s22_d, s33_d, &
191 s12_d, s13_d, s23_d, &
192 fs_abs_d, fs11_d, fs22_d, fs33_d, &
193 fs12_d, fs13_d, fs23_d, &
194 fsabss11_d, fsabss22_d, fsabss33_d, &
195 fsabss12_d, fsabss13_d, fsabss23_d
196 real(c_rp) :: delta_ratio2
202 m12_d, m13_d, m23_d, &
203 l11_d, l22_d, l33_d, &
204 l12_d, l13_d, l23_d, &
205 fsabss11_d, fsabss22_d, fsabss33_d, &
206 fsabss12_d, fsabss13_d, fsabss23_d, &
207 num_d, den_d, c_dyn_d, delta_d, &
208 s_abs_d, nut_d, alpha, mult_d, n) &
209 bind(c, name =
'cuda_mij_nut_compute_part2')
210 use,
intrinsic :: iso_c_binding, only: c_ptr, c_int
212 type(c_ptr),
value :: m11_d, m22_d, m33_d, &
213 m12_d, m13_d, m23_d, &
214 l11_d, l22_d, l33_d, &
215 l12_d, l13_d, l23_d, &
216 fsabss11_d, fsabss22_d, fsabss33_d, &
217 fsabss12_d, fsabss13_d, fsabss23_d, &
218 num_d, den_d, c_dyn_d, delta_d, s_abs_d, nut_d, mult_d
233 s12_d, s13_d, s23_d, &
235 type(c_ptr) :: s_abs_d, s11_d, s22_d, s33_d, &
240 s12_d, s13_d, s23_d, &
244 s12_d, s13_d, s23_d, &
247 call neko_error(
'opencl backend is not supported for device_s_abs_compute')
249 call neko_error(
'no device backend configured')
255 l12_d, l13_d, l23_d, &
258 fuu_d, fvv_d, fww_d, &
259 fuv_d, fuw_d, fvw_d, n)
260 type(c_ptr) :: l11_d, l22_d, l33_d, l12_d, l13_d, l23_d, &
261 u_d, v_d, w_d, fu_d, fv_d, fw_d, &
262 fuu_d, fvv_d, fww_d, fuv_d, fuw_d, fvw_d
266 l12_d, l13_d, l23_d, &
269 fuu_d, fvv_d, fww_d, &
270 fuv_d, fuw_d, fvw_d, n)
273 l12_d, l13_d, l23_d, &
276 fuu_d, fvv_d, fww_d, &
277 fuv_d, fuw_d, fvw_d, n)
279 call neko_error(
'opencl backend is not supported &
280 &for device_lij_compute_part1')
282 call neko_error(
'no device backend configured')
288 l12_d, l13_d, l23_d, &
289 fuu_d, fvv_d, fww_d, &
290 fuv_d, fuw_d, fvw_d, n)
291 type(c_ptr) :: l11_d, l22_d, l33_d, l12_d, l13_d, l23_d, &
292 fuu_d, fvv_d, fww_d, fuv_d, fuw_d, fvw_d
296 l12_d, l13_d, l23_d, &
297 fuu_d, fvv_d, fww_d, &
298 fuv_d, fuw_d, fvw_d, n)
301 l12_d, l13_d, l23_d, &
302 fuu_d, fvv_d, fww_d, &
303 fuv_d, fuw_d, fvw_d, n)
305 call neko_error(
'opencl backend is not supported &
306 &for device_lij_compute_part2')
308 call neko_error(
'no device backend configured')
314 m12_d, m13_d, m23_d, &
315 s_abs_d, s11_d, s22_d, s33_d, &
316 s12_d, s13_d, s23_d, &
317 fs_abs_d, fs11_d, fs22_d, fs33_d, &
318 fs12_d, fs13_d, fs23_d, &
319 fsabss11_d, fsabss22_d, fsabss33_d, &
320 fsabss12_d, fsabss13_d, fsabss23_d, &
322 type(c_ptr) :: m11_d, m22_d, m33_d, &
323 m12_d, m13_d, m23_d, &
324 s_abs_d, s11_d, s22_d, s33_d, &
325 s12_d, s13_d, s23_d, &
326 fs_abs_d, fs11_d, fs22_d, fs33_d, &
327 fs12_d, fs13_d, fs23_d, &
328 fsabss11_d, fsabss22_d, fsabss33_d, &
329 fsabss12_d, fsabss13_d, fsabss23_d
330 real(kind=
rp) :: delta_ratio2
335 m12_d, m13_d, m23_d, &
336 s_abs_d, s11_d, s22_d, s33_d, &
337 s12_d, s13_d, s23_d, &
338 fs_abs_d, fs11_d, fs22_d, fs33_d, &
339 fs12_d, fs13_d, fs23_d, &
340 fsabss11_d, fsabss22_d, fsabss33_d, &
341 fsabss12_d, fsabss13_d, fsabss23_d, &
345 m12_d, m13_d, m23_d, &
346 s_abs_d, s11_d, s22_d, s33_d, &
347 s12_d, s13_d, s23_d, &
348 fs_abs_d, fs11_d, fs22_d, fs33_d, &
349 fs12_d, fs13_d, fs23_d, &
350 fsabss11_d, fsabss22_d, fsabss33_d, &
351 fsabss12_d, fsabss13_d, fsabss23_d, &
354 call neko_error(
'opencl backend is not supported for &
355 &device_mij_compute_part1')
357 call neko_error(
'no device backend configured')
363 m12_d, m13_d, m23_d, &
364 l11_d, l22_d, l33_d, &
365 l12_d, l13_d, l23_d, &
366 fsabss11_d, fsabss22_d, fsabss33_d, &
367 fsabss12_d, fsabss13_d, fsabss23_d, &
368 num_d, den_d, c_dyn_d, delta_d, &
369 s_abs_d, nut_d, alpha, mult_d, n)
370 type(c_ptr) :: m11_d, m22_d, m33_d, &
371 m12_d, m13_d, m23_d, &
372 l11_d, l22_d, l33_d, &
373 l12_d, l13_d, l23_d, &
374 fsabss11_d, fsabss22_d, fsabss33_d, &
375 fsabss12_d, fsabss13_d, fsabss23_d, &
376 num_d, den_d, c_dyn_d, delta_d, s_abs_d, nut_d , mult_d
377 real(kind=
rp) :: alpha
382 m12_d, m13_d, m23_d, &
383 l11_d, l22_d, l33_d, &
384 l12_d, l13_d, l23_d, &
385 fsabss11_d, fsabss22_d, fsabss33_d, &
386 fsabss12_d, fsabss13_d, fsabss23_d, &
387 num_d, den_d, c_dyn_d, delta_d, &
388 s_abs_d, nut_d, alpha, mult_d, n)
391 m12_d, m13_d, m23_d, &
392 l11_d, l22_d, l33_d, &
393 l12_d, l13_d, l23_d, &
394 fsabss11_d, fsabss22_d, fsabss33_d, &
395 fsabss12_d, fsabss13_d, fsabss23_d, &
396 num_d, den_d, c_dyn_d, delta_d, &
397 s_abs_d, nut_d, alpha, mult_d, n)
399 call neko_error(
'opencl backend is not supported for &
400 &device_mij_nut_compute_part2')
402 call neko_error(
'no device backend configured')
407end module device_dynamic_smagorinsky_nut
void cuda_mij_nut_compute_part2(void *m11, void *m22, void *m33, void *m12, void *m13, void *m23, void *l11, void *l22, void *l33, void *l12, void *l13, void *l23, void *fsabss11, void *fsabss22, void *fsabss33, void *fsabss12, void *fsabss13, void *fsabss23, void *num, void *den, void *c_dyn, void *delta, void *s_abs, void *nut, real *alpha, void *mult, int *n)
void cuda_mij_compute_part1(void *m11, void *m22, void *m33, void *m12, void *m13, void *m23, void *s_abs, void *s11, void *s22, void *s33, void *s12, void *s13, void *s23, void *fs_abs, void *fs11, void *fs22, void *fs33, void *fs12, void *fs13, void *fs23, void *fsabss11, void *fsabss22, void *fsabss33, void *fsabss12, void *fsabss13, void *fsabss23, real *delta_ratio2, int *n)
void cuda_s_abs_compute(void *s_abs, void *s11, void *s22, void *s33, void *s12, void *s13, void *s23, int *n)
void cuda_lij_compute_part1(void *l11, void *l22, void *l33, void *l12, void *l13, void *l23, void *u, void *v, void *w, void *fu, void *fv, void *fw, void *fuu, void *fvv, void *fww, void *fuv, void *fuw, void *fvw, int *n)
void cuda_lij_compute_part2(void *l11, void *l22, void *l33, void *l12, void *l13, void *l23, void *fuu, void *fvv, void *fww, void *fuv, void *fuw, void *fvw, int *n)
type(mpi_comm) neko_comm
MPI communicator.
type(mpi_datatype) mpi_real_precision
MPI type for working precision of REAL types.
integer pe_size
MPI size of communicator.
subroutine, public device_lij_compute_part1(l11_d, l22_d, l33_d, l12_d, l13_d, l23_d, u_d, v_d, w_d, fu_d, fv_d, fw_d, fuu_d, fvv_d, fww_d, fuv_d, fuw_d, fvw_d, n)
part 1 of the computing of the lij field
subroutine, public device_mij_compute_part1(m11_d, m22_d, m33_d, m12_d, m13_d, m23_d, s_abs_d, s11_d, s22_d, s33_d, s12_d, s13_d, s23_d, fs_abs_d, fs11_d, fs22_d, fs33_d, fs12_d, fs13_d, fs23_d, fsabss11_d, fsabss22_d, fsabss33_d, fsabss12_d, fsabss13_d, fsabss23_d, delta_ratio2, n)
part 1 of the computing of the mij field
subroutine, public device_s_abs_compute(s_abs_d, s11_d, s22_d, s33_d, s12_d, s13_d, s23_d, n)
Compute the s_abs field for the Sigma model indevice.
subroutine, public device_lij_compute_part2(l11_d, l22_d, l33_d, l12_d, l13_d, l23_d, fuu_d, fvv_d, fww_d, fuv_d, fuw_d, fvw_d, n)
part 2 of the computing of the lij field
subroutine, public device_mij_nut_compute_part2(m11_d, m22_d, m33_d, m12_d, m13_d, m23_d, l11_d, l22_d, l33_d, l12_d, l13_d, l23_d, fsabss11_d, fsabss22_d, fsabss33_d, fsabss12_d, fsabss13_d, fsabss23_d, num_d, den_d, c_dyn_d, delta_d, s_abs_d, nut_d, alpha, mult_d, n)
part 1 of the computing of the mij field
integer, parameter, public c_rp
integer, parameter, public rp
Global precision used in computations.