Neko  0.8.99
A portable framework for high-order spectral element flow simulations
sigma_cpu.f90
Go to the documentation of this file.
1 ! Copyright (c) 2023-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 !
37 
38 module sigma_cpu
39  use num_types, only : rp
40  use field_list, only : field_list_t
43  use field, only : field_t
44  use operators, only : dudxyz
45  use coefs, only : coef_t
46  use gs_ops, only : gs_op_add
47  use math, only : neko_eps
48  implicit none
49  private
50 
51  public :: sigma_compute_cpu
52 
53 contains
54 
62  subroutine sigma_compute_cpu(t, tstep, coef, nut, delta, c)
63  real(kind=rp), intent(in) :: t
64  integer, intent(in) :: tstep
65  type(coef_t), intent(in) :: coef
66  type(field_t), intent(inout) :: nut
67  type(field_t), intent(in) :: delta
68  real(kind=rp), intent(in) :: c
69  ! This is the velocity gradient tensor
70  type(field_t), pointer :: g11, g12, g13, g21, g22, g23, g31, g32, g33
71  type(field_t), pointer :: u, v, w
72 
73  real(kind=rp) :: sigg11, sigg12, sigg13, sigg22, sigg23, sigg33
74  real(kind=rp) :: sigma1, sigma2, sigma3
75  real(kind=rp) :: invariant1, invariant2, invariant3
76  real(kind=rp) :: alpha1, alpha2, alpha3
77  real(kind=rp) :: dsigma
78  real(kind=rp) :: pi_3 = 4.0_rp/3.0_rp*atan(1.0_rp)
79  real(kind=rp) :: tmp1
80  real(kind=rp) :: eps
81 
82  integer :: temp_indices(9)
83  integer :: e, i
84 
85  ! some constant
86  eps = neko_eps
87 
88 
89  ! get fields from registry
90  u => neko_field_registry%get_field_by_name("u")
91  v => neko_field_registry%get_field_by_name("v")
92  w => neko_field_registry%get_field_by_name("w")
93 
94  call neko_scratch_registry%request_field(g11, temp_indices(1))
95  call neko_scratch_registry%request_field(g12, temp_indices(2))
96  call neko_scratch_registry%request_field(g13, temp_indices(3))
97  call neko_scratch_registry%request_field(g21, temp_indices(4))
98  call neko_scratch_registry%request_field(g22, temp_indices(5))
99  call neko_scratch_registry%request_field(g23, temp_indices(6))
100  call neko_scratch_registry%request_field(g31, temp_indices(7))
101  call neko_scratch_registry%request_field(g32, temp_indices(8))
102  call neko_scratch_registry%request_field(g33, temp_indices(9))
103 
104 
105  ! Compute the derivatives of the velocity (the components of the g tensor)
106  call dudxyz (g11%x, u%x, coef%drdx, coef%dsdx, coef%dtdx, coef)
107  call dudxyz (g12%x, u%x, coef%drdy, coef%dsdy, coef%dtdy, coef)
108  call dudxyz (g13%x, u%x, coef%drdz, coef%dsdz, coef%dtdz, coef)
109 
110  call dudxyz (g21%x, v%x, coef%drdx, coef%dsdx, coef%dtdx, coef)
111  call dudxyz (g22%x, v%x, coef%drdy, coef%dsdy, coef%dtdy, coef)
112  call dudxyz (g23%x, v%x, coef%drdz, coef%dsdz, coef%dtdz, coef)
113 
114  call dudxyz (g31%x, w%x, coef%drdx, coef%dsdx, coef%dtdx, coef)
115  call dudxyz (g32%x, w%x, coef%drdy, coef%dsdy, coef%dtdy, coef)
116  call dudxyz (g33%x, w%x, coef%drdz, coef%dsdz, coef%dtdz, coef)
117 
118  call coef%gs_h%op(g11, gs_op_add)
119  call coef%gs_h%op(g12, gs_op_add)
120  call coef%gs_h%op(g13, gs_op_add)
121  call coef%gs_h%op(g21, gs_op_add)
122  call coef%gs_h%op(g22, gs_op_add)
123  call coef%gs_h%op(g23, gs_op_add)
124  call coef%gs_h%op(g31, gs_op_add)
125  call coef%gs_h%op(g32, gs_op_add)
126  call coef%gs_h%op(g33, gs_op_add)
127 
128  do concurrent(i = 1:g11%dof%size())
129  g11%x(i,1,1,1) = g11%x(i,1,1,1) * coef%mult(i,1,1,1)
130  g12%x(i,1,1,1) = g12%x(i,1,1,1) * coef%mult(i,1,1,1)
131  g13%x(i,1,1,1) = g13%x(i,1,1,1) * coef%mult(i,1,1,1)
132  g21%x(i,1,1,1) = g21%x(i,1,1,1) * coef%mult(i,1,1,1)
133  g22%x(i,1,1,1) = g22%x(i,1,1,1) * coef%mult(i,1,1,1)
134  g23%x(i,1,1,1) = g23%x(i,1,1,1) * coef%mult(i,1,1,1)
135  g31%x(i,1,1,1) = g31%x(i,1,1,1) * coef%mult(i,1,1,1)
136  g32%x(i,1,1,1) = g32%x(i,1,1,1) * coef%mult(i,1,1,1)
137  g33%x(i,1,1,1) = g33%x(i,1,1,1) * coef%mult(i,1,1,1)
138  end do
139 
140  do concurrent(e = 1:coef%msh%nelv)
141  do concurrent(i = 1:coef%Xh%lxyz)
142  ! G_ij = g^t g = g_mi g_mj
143  sigg11 = g11%x(i,1,1,e)**2 + g21%x(i,1,1,e)**2 + g31%x(i,1,1,e)**2
144  sigg22 = g12%x(i,1,1,e)**2 + g22%x(i,1,1,e)**2 + g32%x(i,1,1,e)**2
145  sigg33 = g13%x(i,1,1,e)**2 + g23%x(i,1,1,e)**2 + g33%x(i,1,1,e)**2
146  sigg12 = g11%x(i,1,1,e)*g12%x(i,1,1,e) + &
147  g21%x(i,1,1,e)*g22%x(i,1,1,e) + &
148  g31%x(i,1,1,e)*g32%x(i,1,1,e)
149  sigg13 = g11%x(i,1,1,e)*g13%x(i,1,1,e) + &
150  g21%x(i,1,1,e)*g23%x(i,1,1,e) + &
151  g31%x(i,1,1,e)*g33%x(i,1,1,e)
152  sigg23 = g12%x(i,1,1,e)*g13%x(i,1,1,e) + &
153  g22%x(i,1,1,e)*g23%x(i,1,1,e) + &
154  g32%x(i,1,1,e)*g33%x(i,1,1,e)
155 
156  ! If LAPACK compute eigenvalues of the semi-definite positive matrix G
157  ! ..........to be done later on......
158  ! ELSE use the analytical method as done in the following
159 
160  ! eigenvalues with the analytical method of Hasan et al. (2001)
161  ! doi:10.1006/jmre.2001.2400
162  if (abs(sigg11) .lt. eps) then
163  sigg11 = 0.0_rp
164  end if
165  if (abs(sigg12) .lt. eps) then
166  sigg12 = 0.0_rp
167  end if
168  if (abs(sigg13) .lt. eps) then
169  sigg13 = 0.0_rp
170  end if
171  if (abs(sigg22) .lt. eps) then
172  sigg22 = 0.0_rp
173  end if
174  if (abs(sigg23) .lt. eps) then
175  sigg23 = 0.0_rp
176  end if
177  if (abs(sigg33) .lt. eps) then
178  sigg33 = 0.0_rp
179  end if
180 
181  if (abs(sigg12*sigg12 + &
182  sigg13*sigg13 + sigg23*sigg23) .lt. eps) then
183  ! G is diagonal
184  ! estimate the singular values according to:
185  sigma1 = sqrt(max(max(max(sigg11, sigg22), sigg33), 0.0_rp))
186  sigma3 = sqrt(max(min(min(sigg11, sigg22), sigg33), 0.0_rp))
187  invariant1 = sigg11 + sigg22 + sigg33
188  sigma2 = sqrt(abs(invariant1 - sigma1*sigma1 - sigma3*sigma3))
189  else
190 
191  ! estimation of invariants
192  invariant1 = sigg11 + sigg22 + sigg33
193  invariant2 = sigg11*sigg22 + sigg11*sigg33 + sigg22*sigg33 - &
194  (sigg12*sigg12 + sigg13*sigg13 + sigg23*sigg23)
195  invariant3 = sigg11*sigg22*sigg33 + &
196  2.0_rp*sigg12*sigg13*sigg23 - &
197  (sigg11*sigg23*sigg23 + sigg22*sigg13*sigg13 + &
198  sigg33*sigg12*sigg12)
199 
200  ! G is symmetric semi-definite positive matrix:
201  ! the invariants have to be larger-equal zero
202  ! which is obtained via forcing
203  invariant1 = max(invariant1, 0.0_rp)
204  invariant2 = max(invariant2, 0.0_rp)
205  invariant3 = max(invariant3, 0.0_rp)
206 
207  ! compute the following angles from the invariants
208  alpha1 = invariant1*invariant1/9.0_rp - invariant2/3.0_rp
209 
210  ! since alpha1 is always positive (see Hasan et al. (2001))
211  ! forcing is applied
212  alpha1 = max(alpha1, 0.0_rp)
213 
214  alpha2 = invariant1*invariant1*invariant1/27.0_rp - &
215  invariant1*invariant2/6.0_rp + invariant3/2.0_rp
216 
217  ! since acos(alpha2/(alpha1^(3/2)))/3.0_rp only valid for
218  ! alpha2^2 < alpha1^3.0_rp and arccos(x) only valid for -1<=x<=1
219  ! alpha3 is between 0 and pi/3
220  tmp1 = alpha2/sqrt(alpha1 * alpha1 * alpha1)
221 
222  if (tmp1 .le. -1.0_rp) then
223  ! alpha3=pi/3 -> cos(alpha3)=0.5
224  ! compute the singular values
225  sigma1 = sqrt(max(invariant1/3.0_rp + sqrt(alpha1), 0.0_rp))
226  sigma2 = sigma1
227  sigma3 = sqrt(invariant1/3.0_rp - 2.0_rp*sqrt(alpha1))
228 
229  elseif (tmp1 .ge. 1.0_rp) then
230  ! alpha3=0.0_rp -> cos(alpha3)=1.0
231  sigma1 = sqrt(max(invariant1/3.0_rp + 2.0_rp*sqrt(alpha1), &
232  0.0_rp))
233  sigma2 = sqrt(invariant1/3.0_rp - sqrt(alpha1))
234  sigma3 = sigma2
235  else
236  alpha3 = acos(tmp1)/3.0_rp
237 
238  if (abs(invariant3) .lt. eps) then
239  ! In case of Invariant3=0, one or more eigenvalues are equal to zero
240  ! Therefore force sigma3 to 0 and compute sigma1 and sigma2
241  sigma1 = sqrt(max(invariant1/3.0_rp + &
242  2.0_rp*sqrt(alpha1)*cos(alpha3), 0.0_rp))
243  sigma2 = sqrt(abs(invariant1 - sigma1*sigma1))
244  sigma3 = 0.0_rp
245  else
246  sigma1 = sqrt(max(invariant1/3.0_rp + &
247  2.0_rp*sqrt(alpha1)*cos(alpha3), 0.0_rp))
248  sigma2 = sqrt(invariant1/3.0_rp - &
249  2.0_rp*sqrt(alpha1)*cos(pi_3 + alpha3))
250  sigma3 = sqrt(abs(invariant1 - &
251  sigma1*sigma1-sigma2*sigma2))
252  end if ! Invariant3=0 ?
253  end if ! tmp1
254  end if ! G diagonal ?
255 
256  ! Estimate Dsigma
257  if (sigma1 .gt. 0.0_rp) then
258  dsigma = &
259  sigma3*(sigma1 - sigma2)*(sigma2 - sigma3)/(sigma1*sigma1)
260  else
261  dsigma = 0.0_rp
262  end if
263 
264  !clipping to avoid negative values
265  dsigma = max(dsigma, 0.0_rp)
266 
267  ! estimate turbulent viscosity
268 
269  nut%x(i,1,1,e) = (c*delta%x(i,1,1,e))**2 * dsigma
270 
271 
272  end do
273  end do
274 
275  call neko_scratch_registry%relinquish_field(temp_indices)
276  end subroutine sigma_compute_cpu
277 
278 end module sigma_cpu
279 
Coefficients.
Definition: coef.f90:34
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
Definition: math.f90:60
real(kind=rp), parameter, public neko_eps
Machine epsilon .
Definition: math.f90:70
integer, parameter, public rp
Global precision used in computations.
Definition: num_types.f90:12
Operators.
Definition: operators.f90:34
subroutine, public dudxyz(du, u, dr, ds, dt, coef)
Compute derivative of a scalar field along a single direction.
Definition: operators.f90:76
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.
Implements the CPU kernel for the sigma_t type. Following Nicoud et al. "Using singular values to bui...
Definition: sigma_cpu.f90:38
subroutine, public sigma_compute_cpu(t, tstep, coef, nut, delta, c)
Compute eddy viscosity on the CPU.
Definition: sigma_cpu.f90:63
Coefficients defined on a given (mesh, ) tuple. Arrays use indices (i,j,k,e): element e,...
Definition: coef.f90:55
field_list_t, To be able to group fields together
Definition: field_list.f90:13
#define max(a, b)
Definition: tensor.cu:40