Neko 0.9.99
A portable framework for high-order spectral element flow simulations
Loading...
Searching...
No Matches
dynamic_smagorinsky_device.f90
Go to the documentation of this file.
1! Copyright (c) 2024, The Neko Authors
2! All rights reserved.
3!
4! Redistribution and use in source and binary forms, with or without
5! modification, are permitted provided that the following conditions
6! are met:
7!
8! * Redistributions of source code must retain the above copyright
9! notice, this list of conditions and the following disclaimer.
10!
11! * Redistributions in binary form must reproduce the above
12! copyright notice, this list of conditions and the following
13! disclaimer in the documentation and/or other materials provided
14! with the distribution.
15!
16! * Neither the name of the authors nor the names of its
17! contributors may be used to endorse or promote products derived
18! from this software without specific prior written permission.
19!
20! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
21! "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
22! LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
23! FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
24! COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
25! INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
26! BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
27! LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
28! CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
29! LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
30! ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
31! POSSIBILITY OF SUCH DAMAGE.
32!
35 use num_types, only : rp
36 use field_list, only : field_list_t
39 use field, only : field_t
40 use operators, only : strain_rate
41 use coefs, only : coef_t
43 use gs_ops, only : gs_op_add
44 use device_math, only : device_col2
48 implicit none
49 private
50
52
53contains
54
67 subroutine dynamic_smagorinsky_compute_device(t, tstep, coef, nut, delta, &
68 c_dyn, test_filter, mij, lij, &
69 num, den)
70 real(kind=rp), intent(in) :: t
71 integer, intent(in) :: tstep
72 type(coef_t), intent(in) :: coef
73 type(field_t), intent(inout) :: nut
74 type(field_t), intent(in) :: delta
75 type(field_t), intent(inout) :: c_dyn
76 type(elementwise_filter_t), intent(inout) :: test_filter
77 type(field_t), intent(inout) :: mij(6), lij(6)
78 type(field_t), intent(inout) :: num, den
79
80 type(field_t), pointer :: u, v, w
81 type(field_t) :: c_dyn_curr
82 ! the strain rate tensor
83 type(field_t), pointer :: s11, s22, s33, s12, s13, s23, s_abs
84 real(kind=rp) :: alpha ! running averaging coefficient
85 integer :: temp_indices(7)
86 integer :: i
87
88 if (tstep .eq. 1) then
89 alpha = 1.0_rp
90 else
91 alpha = 0.9_rp
92 end if
93
94 u => neko_field_registry%get_field_by_name("u")
95 v => neko_field_registry%get_field_by_name("v")
96 w => neko_field_registry%get_field_by_name("w")
97
98 call neko_scratch_registry%request_field(s11, temp_indices(1))
99 call neko_scratch_registry%request_field(s22, temp_indices(2))
100 call neko_scratch_registry%request_field(s33, temp_indices(3))
101 call neko_scratch_registry%request_field(s12, temp_indices(4))
102 call neko_scratch_registry%request_field(s13, temp_indices(5))
103 call neko_scratch_registry%request_field(s23, temp_indices(6))
104 call neko_scratch_registry%request_field(s_abs, temp_indices(7))
105
106 ! Compute the strain rate tensor
107 call strain_rate(s11%x, s22%x, s33%x, s12%x, s13%x, s23%x, u, v, w, coef)
108
109 call coef%gs_h%op(s11%x, s11%dof%size(), gs_op_add)
110 call coef%gs_h%op(s22%x, s11%dof%size(), gs_op_add)
111 call coef%gs_h%op(s33%x, s11%dof%size(), gs_op_add)
112 call coef%gs_h%op(s12%x, s11%dof%size(), gs_op_add)
113 call coef%gs_h%op(s13%x, s11%dof%size(), gs_op_add)
114 call coef%gs_h%op(s23%x, s11%dof%size(), gs_op_add)
115
116 call device_s_abs_compute(s_abs%x_d, s11%x_d, s22%x_d, s33%x_d, &
117 s12%x_d, s13%x_d, s23%x_d, &
118 coef%mult_d, s11%dof%size())
119
120 call compute_lij_device(lij, u, v, w, test_filter, u%dof%size(), u%msh%nelv)
121 call compute_nut_device(nut, c_dyn, num, den, lij, mij, &
122 s11, s22, s33, s12, s13, s23, &
123 s_abs, test_filter, delta, alpha, &
124 u%dof%size(), u%msh%nelv)
125
126 call coef%gs_h%op(nut, gs_op_add)
127 call device_col2(nut%x_d, coef%mult_d, nut%dof%size())
128
129 call neko_scratch_registry%relinquish_field(temp_indices)
131
140 subroutine compute_lij_device(lij, u, v, w, test_filter, n, nelv)
141 type(field_t), intent(inout) :: lij(6)
142 type(field_t), pointer, intent(in) :: u, v, w
143 type(elementwise_filter_t), intent(inout) :: test_filter
144 integer, intent(in) :: n
145 integer, intent(inout) :: nelv
146 integer :: i
148 type(field_t), pointer :: fu, fv, fw, fuu, fvv, fww, fuv, fuw, fvw
149 integer :: temp_indices(9)
150
151 call neko_scratch_registry%request_field(fu, temp_indices(1))
152 call neko_scratch_registry%request_field(fv, temp_indices(2))
153 call neko_scratch_registry%request_field(fw, temp_indices(3))
154 call neko_scratch_registry%request_field(fuu, temp_indices(4))
155 call neko_scratch_registry%request_field(fvv, temp_indices(5))
156 call neko_scratch_registry%request_field(fww, temp_indices(6))
157 call neko_scratch_registry%request_field(fuv, temp_indices(7))
158 call neko_scratch_registry%request_field(fuw, temp_indices(8))
159 call neko_scratch_registry%request_field(fvw, temp_indices(9))
160
161 ! Use test filter for the velocity fields
162 call test_filter%filter_3d(fu%x, u%x, nelv)
163 call test_filter%filter_3d(fv%x, v%x, nelv)
164 call test_filter%filter_3d(fw%x, w%x, nelv)
165
166 !! ___ ___
167 !! Compute u_i*u_j and u_i*u_j
168 call device_lij_compute_part1(lij(1)%x_d, lij(2)%x_d, lij(3)%x_d, &
169 lij(4)%x_d, lij(5)%x_d, lij(6)%x_d, &
170 u%x_d, v%x_d, w%x_d, &
171 fu%x_d, fv%x_d, fw%x_d, &
172 fuu%x_d, fvv%x_d, fww%x_d, &
173 fuv%x_d, fuw%x_d, fvw%x_d, n)
174
175 !! Filter u_i*u_j by the test filter
176 call test_filter%filter_3d(fuu%x, fuu%x, nelv)
177 call test_filter%filter_3d(fvv%x, fvv%x, nelv)
178 call test_filter%filter_3d(fww%x, fww%x, nelv)
179 call test_filter%filter_3d(fuv%x, fuv%x, nelv)
180 call test_filter%filter_3d(fuw%x, fuw%x, nelv)
181 call test_filter%filter_3d(fvw%x, fvw%x, nelv)
182
183 !! Assember the final form
184 !! ___ ___ _______
185 !! L_ij = u_i*u_j - u_i*u_j
186 call device_lij_compute_part2(lij(1)%x_d, lij(2)%x_d, lij(3)%x_d, &
187 lij(4)%x_d, lij(5)%x_d, lij(6)%x_d, &
188 fuu%x_d, fvv%x_d, fww%x_d, &
189 fuv%x_d, fuw%x_d, fvw%x_d, n)
190 call neko_scratch_registry%relinquish_field(temp_indices)
191 end subroutine compute_lij_device
192
214 subroutine compute_nut_device(nut, c_dyn, num, den, lij, mij, &
215 s11, s22, s33, s12, s13, s23, &
216 s_abs, test_filter, delta, alpha, &
217 n, nelv)
218 type(field_t), intent(inout) :: nut, c_dyn
219 type(field_t), intent(inout) :: num, den
220 type(field_t), intent(in) :: lij(6)
221 type(field_t), intent(inout) :: mij(6)
222 type(field_t), intent(inout) :: s11, s22, s33, s12, s13, s23, s_abs
223 type(elementwise_filter_t), intent(inout) :: test_filter
224 type(field_t), intent(in) :: delta
225 real(kind=rp), intent(in) :: alpha
226 integer, intent(in) :: n
227 integer, intent(inout) :: nelv
228
229 real(kind=rp) :: delta_ratio2
230 integer :: temp_indices(13)
231 type(field_t), pointer :: fs11, fs22, fs33, fs12, fs13, fs23, fs_abs, &
232 fsabss11, fsabss22, fsabss33, &
233 fsabss12, fsabss13, fsabss23
234
235 delta_ratio2 = ((test_filter%nx-1.0_rp)/(test_filter%nt-1.0_rp))**2
236
237 call neko_scratch_registry%request_field(fs11, temp_indices(1))
238 call neko_scratch_registry%request_field(fs22, temp_indices(2))
239 call neko_scratch_registry%request_field(fs33, temp_indices(3))
240 call neko_scratch_registry%request_field(fs12, temp_indices(4))
241 call neko_scratch_registry%request_field(fs13, temp_indices(5))
242 call neko_scratch_registry%request_field(fs23, temp_indices(6))
243 call neko_scratch_registry%request_field(fsabss11, temp_indices(7))
244 call neko_scratch_registry%request_field(fsabss22, temp_indices(8))
245 call neko_scratch_registry%request_field(fsabss33, temp_indices(9))
246 call neko_scratch_registry%request_field(fsabss12, temp_indices(10))
247 call neko_scratch_registry%request_field(fsabss13, temp_indices(11))
248 call neko_scratch_registry%request_field(fsabss23, temp_indices(12))
249 call neko_scratch_registry%request_field(fs_abs, temp_indices(13))
250
251 !! Compute M_ij
252 !! _____ ____
253 !! Compute s_abs and s_ij
254 call test_filter%filter_3d(fs_abs%x, s_abs%x, nelv)
255 call test_filter%filter_3d(fs11%x, s11%x, nelv)
256 call test_filter%filter_3d(fs22%x, s22%x, nelv)
257 call test_filter%filter_3d(fs33%x, s33%x, nelv)
258 call test_filter%filter_3d(fs12%x, s12%x, nelv)
259 call test_filter%filter_3d(fs13%x, s13%x, nelv)
260 call test_filter%filter_3d(fs23%x, s23%x, nelv)
261
262 !! _____ ____
263 !! Compute (delta_test/delta)^2 s_abs*s_ij and s_abs*s_ij
264 call device_mij_compute_part1(mij(1)%x_d, mij(2)%x_d, mij(3)%x_d, &
265 mij(4)%x_d, mij(5)%x_d, mij(6)%x_d, &
266 s_abs%x_d, s11%x_d, s22%x_d, s33%x_d, &
267 s12%x_d, s13%x_d, s23%x_d, &
268 fs_abs%x_d, fs11%x_d, fs22%x_d, fs33%x_d, &
269 fs12%x_d, fs13%x_d, fs23%x_d, &
270 fsabss11%x_d, fsabss22%x_d, fsabss33%x_d, &
271 fsabss12%x_d, fsabss13%x_d, fsabss23%x_d, &
272 delta_ratio2, n)
273
274 !! Filter s_abs*s_ij by the test filter
275 call test_filter%filter_3d(fsabss11%x, fsabss11%x, nelv)
276 call test_filter%filter_3d(fsabss22%x, fsabss22%x, nelv)
277 call test_filter%filter_3d(fsabss33%x, fsabss33%x, nelv)
278 call test_filter%filter_3d(fsabss12%x, fsabss12%x, nelv)
279 call test_filter%filter_3d(fsabss13%x, fsabss13%x, nelv)
280 call test_filter%filter_3d(fsabss23%x, fsabss23%x, nelv)
281
282 !! Finalise the compute of Mij and nut
283 call device_mij_nut_compute_part2(mij(1)%x_d, mij(2)%x_d, mij(3)%x_d, &
284 mij(4)%x_d, mij(5)%x_d, mij(6)%x_d, &
285 lij(1)%x_d, lij(2)%x_d, lij(3)%x_d, &
286 lij(4)%x_d, lij(5)%x_d, lij(6)%x_d, &
287 fsabss11%x_d, fsabss22%x_d, fsabss33%x_d, &
288 fsabss12%x_d, fsabss13%x_d, fsabss23%x_d, &
289 num%x_d, den%x_d, c_dyn%x_d, delta%x_d, &
290 s_abs%x_d, nut%x_d, alpha, n)
291 call neko_scratch_registry%relinquish_field(temp_indices)
292 end subroutine compute_nut_device
293
295
Coefficients.
Definition coef.f90:34
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_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, n)
part 1 of the computing of the mij 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, mult_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_col2(a_d, b_d, n)
Vector multiplication .
Implements the device kernel for the smagorinsky_t type.
subroutine compute_nut_device(nut, c_dyn, num, den, lij, mij, s11, s22, s33, s12, s13, s23, s_abs, test_filter, delta, alpha, n, nelv)
Compute M_ij and nut on the device.
subroutine, public dynamic_smagorinsky_compute_device(t, tstep, coef, nut, delta, c_dyn, test_filter, mij, lij, num, den)
Compute eddy viscosity on the device.
subroutine compute_lij_device(lij, u, v, w, test_filter, n, nelv)
Compute Germano Identity on the device.
Implements explicit_filter_t.
Defines a registry for storing solution fields.
type(field_registry_t), target, public neko_field_registry
Global field registry.
Defines a field.
Definition field.f90:34
Defines Gather-scatter operations.
Definition gs_ops.f90:34
integer, parameter, public gs_op_add
Definition gs_ops.f90:36
integer, parameter, public rp
Global precision used in computations.
Definition num_types.f90:12
Operators.
Definition operators.f90:34
subroutine, public strain_rate(s11, s22, s33, s12, s13, s23, u, v, w, coef)
Compute the strain rate tensor, i.e 0.5 * du_i/dx_j + du_j/dx_i.
Defines a registry for storing and requesting temporary fields This can be used when you have a funct...
type(scratch_registry_t), target, public neko_scratch_registry
Global scratch registry.
Coefficients defined on a given (mesh, ) tuple. Arrays use indices (i,j,k,e): element e,...
Definition coef.f90:55
Implements the explicit filter for SEM.
field_list_t, To be able to group fields together