Loading [MathJax]/extensions/tex2jax.js
Neko 0.9.99
A portable framework for high-order spectral element flow simulations
All Classes Namespaces Files Functions Variables Typedefs Enumerator Macros Pages
shear_stress.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!
36 use num_types, only : rp
37 use bc, only : bc_t
38 use, intrinsic :: iso_c_binding, only : c_ptr
39 use utils, only : neko_error
40 use coefs, only : coef_t
41 use symmetry, only : symmetry_t
42 use neumann, only : neumann_t
43 use json_module, only : json_file
44 use json_utils, only : json_get
45 implicit none
46 private
47
50 type, public, extends(bc_t) :: shear_stress_t
51 ! This bc takes care of setting the wall-normal component to zero.
52 ! It can be passed to associated bc lists, which take care of masking
53 ! changes in residuals and solution increments.
55
57 type(neumann_t) :: neumann_x
59 type(neumann_t) :: neumann_y
61 type(neumann_t) :: neumann_z
62 contains
63 procedure, pass(this) :: apply_scalar => shear_stress_apply_scalar
64 procedure, pass(this) :: apply_vector => shear_stress_apply_vector
65 procedure, pass(this) :: apply_scalar_dev => shear_stress_apply_scalar_dev
66 procedure, pass(this) :: apply_vector_dev => shear_stress_apply_vector_dev
68 procedure, pass(this) :: init => shear_stress_init
70 procedure, pass(this) :: init_from_components => &
72 procedure, pass(this) :: set_stress_scalar => &
74 procedure, pass(this) :: set_stress_array => &
77 generic :: set_stress => set_stress_scalar, set_stress_array
79 procedure, pass(this) :: free => shear_stress_free
81 procedure, pass(this) :: finalize => shear_stress_finalize
82 end type shear_stress_t
83
84contains
85
87 subroutine shear_stress_apply_scalar(this, x, n, t, tstep, strong)
88 class(shear_stress_t), intent(inout) :: this
89 integer, intent(in) :: n
90 real(kind=rp), intent(inout), dimension(n) :: x
91 real(kind=rp), intent(in), optional :: t
92 integer, intent(in), optional :: tstep
93 logical, intent(in), optional :: strong
94 integer :: i, m, k, facet
95 ! Store non-linear index
96 integer :: idx(4)
97
98 call neko_error("The shear stress bc is not applicable to scalar fields.")
99
100 end subroutine shear_stress_apply_scalar
101
104 subroutine shear_stress_apply_vector(this, x, y, z, n, t, tstep, strong)
105 class(shear_stress_t), intent(inout) :: this
106 integer, intent(in) :: n
107 real(kind=rp), intent(inout), dimension(n) :: x
108 real(kind=rp), intent(inout), dimension(n) :: y
109 real(kind=rp), intent(inout), dimension(n) :: z
110 real(kind=rp), intent(in), optional :: t
111 integer, intent(in), optional :: tstep
112 logical, intent(in), optional :: strong
113 logical :: strong_ = .true.
114
115 if (present(strong)) strong_ = strong
116
117 if (strong_) then
118 call this%symmetry%apply_vector(x, y, z, n, t, tstep, .true.)
119 else
120 call this%neumann_x%apply_scalar(x, n, t, tstep, .false.)
121 call this%neumann_y%apply_scalar(y, n, t, tstep, .false.)
122 call this%neumann_z%apply_scalar(z, n, t, tstep, .false.)
123 end if
124
125 end subroutine shear_stress_apply_vector
126
129 subroutine shear_stress_apply_scalar_dev(this, x_d, t, tstep, strong)
130 class(shear_stress_t), intent(inout), target :: this
131 type(c_ptr) :: x_d
132 real(kind=rp), intent(in), optional :: t
133 integer, intent(in), optional :: tstep
134 logical, intent(in), optional :: strong
135
136 call neko_error("shear_stress bc not implemented on the device")
137
138 end subroutine shear_stress_apply_scalar_dev
139
142 subroutine shear_stress_apply_vector_dev(this, x_d, y_d, z_d, t, tstep, &
143 strong)
144 class(shear_stress_t), intent(inout), target :: this
145 type(c_ptr) :: x_d
146 type(c_ptr) :: y_d
147 type(c_ptr) :: z_d
148 real(kind=rp), intent(in), optional :: t
149 integer, intent(in), optional :: tstep
150 logical, intent(in), optional :: strong
151
152 call neko_error("shear_stress bc not implemented on the device")
153
154 end subroutine shear_stress_apply_vector_dev
155
159 subroutine shear_stress_init(this, coef, json)
160 class(shear_stress_t), target, intent(inout) :: this
161 type(coef_t), intent(in) :: coef
162 type(json_file), intent(inout) ::json
163 real(kind=rp), allocatable :: value(:)
164
165 call json_get(json, 'value', value)
166
167 if (size(value) .ne. 3) then
168 call neko_error ("The shear stress vector provided for the shear stress &
169 & boundary condition should have 3 components.")
170 end if
171
172 call this%init_from_components(coef, value)
173 end subroutine shear_stress_init
174
178 subroutine shear_stress_init_from_components(this, coef, value)
179 class(shear_stress_t), target, intent(inout) :: this
180 type(coef_t), intent(in) :: coef
181 real(kind=rp), intent(in) :: value(3)
182
183 call this%init_base(coef)
184 this%strong = .false.
185
186 call this%symmetry%free()
187 call this%symmetry%init_from_components(this%coef)
188
189 call this%neumann_x%free()
190 call this%neumann_y%free()
191 call this%neumann_z%free()
192
193 call this%neumann_x%init_from_components(this%coef, value(1))
194 call this%neumann_y%init_from_components(this%coef, value(2))
195 call this%neumann_z%init_from_components(this%coef, value(3))
196
198
199 subroutine shear_stress_finalize(this)
200 class(shear_stress_t), target, intent(inout) :: this
201
202 call this%finalize_base()
203
204 call this%symmetry%mark_facets(this%marked_facet)
205 call this%symmetry%finalize()
206
207
208 call this%neumann_x%mark_facets(this%marked_facet)
209 call this%neumann_y%mark_facets(this%marked_facet)
210 call this%neumann_z%mark_facets(this%marked_facet)
211
212 call this%neumann_x%finalize()
213 call this%neumann_y%finalize()
214 call this%neumann_z%finalize()
215
216 end subroutine shear_stress_finalize
217
219 subroutine shear_stress_set_stress_scalar(this, tau_x, tau_y, tau_z)
220 class(shear_stress_t), intent(inout) :: this
221 real(kind=rp), intent(in) :: tau_x
222 real(kind=rp), intent(in) :: tau_y
223 real(kind=rp), intent(in) :: tau_z
224
225 ! Calls finalize and allocates the flux arrays
226 call this%neumann_x%set_flux(tau_x)
227 call this%neumann_y%set_flux(tau_y)
228 call this%neumann_z%set_flux(tau_z)
229
230
231 end subroutine shear_stress_set_stress_scalar
232
234 subroutine shear_stress_set_stress_array(this, tau_x, tau_y, tau_z)
235 class(shear_stress_t), intent(inout) :: this
236 real(kind=rp), intent(in) :: tau_x(this%msk(0))
237 real(kind=rp), intent(in) :: tau_y(this%msk(0))
238 real(kind=rp), intent(in) :: tau_z(this%msk(0))
239
240 call this%neumann_x%set_flux(tau_x)
241 call this%neumann_y%set_flux(tau_y)
242 call this%neumann_z%set_flux(tau_z)
243
244 end subroutine shear_stress_set_stress_array
245
247 subroutine shear_stress_free(this)
248 class(shear_stress_t), target, intent(inout) :: this
249 call this%free_base
250 call this%symmetry%free
251
252 call this%neumann_x%free
253 call this%neumann_y%free
254 call this%neumann_z%free
255
256 end subroutine shear_stress_free
257end module shear_stress
Retrieves a parameter by name or throws an error.
Defines a boundary condition.
Definition bc.f90:34
Coefficients.
Definition coef.f90:34
Utilities for retrieving parameters from the case files.
Defines a Neumann boundary condition.
Definition neumann.f90:34
integer, parameter, public rp
Global precision used in computations.
Definition num_types.f90:12
Defines a shear stress boundary condition for a vector field. Maintainer: Timofey Mukha.
subroutine shear_stress_apply_vector_dev(this, x_d, y_d, z_d, t, tstep, strong)
Boundary condition apply for a generic shear_stress condition to vectors x, y and z (device version)
subroutine shear_stress_init_from_components(this, coef, value)
Constructor from components.
subroutine shear_stress_free(this)
Destructor.
subroutine shear_stress_apply_scalar(this, x, n, t, tstep, strong)
Apply shear stress for a scalar field x.
subroutine shear_stress_finalize(this)
subroutine shear_stress_set_stress_array(this, tau_x, tau_y, tau_z)
Set the shear stress components.
subroutine shear_stress_apply_vector(this, x, y, z, n, t, tstep, strong)
Boundary condition apply for a generic shear_stress condition to vectors x, y and z.
subroutine shear_stress_set_stress_scalar(this, tau_x, tau_y, tau_z)
Set the value of the shear stress vector using 3 scalars.
subroutine shear_stress_init(this, coef, json)
Constructor.
subroutine shear_stress_apply_scalar_dev(this, x_d, t, tstep, strong)
Boundary condition apply for a generic shear_stress condition to a vector x (device version)
Mixed Dirichlet-Neumann axis aligned symmetry plane.
Definition symmetry.f90:34
Utilities.
Definition utils.f90:35
Base type for a boundary condition.
Definition bc.f90:57
Coefficients defined on a given (mesh, ) tuple. Arrays use indices (i,j,k,e): element e,...
Definition coef.f90:55
A Neumann boundary condition for scalar fields. Sets the flux of the field to the chosen value.
Definition neumann.f90:51
A shear stress boundary condition.
Mixed Dirichlet-Neumann symmetry plane condition.
Definition symmetry.f90:49