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
fluid_scheme_base.f90
Go to the documentation of this file.
1! Copyright (c) 2025, 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!
34 use bc, only : bc_t
35 use checkpoint, only : chkp_t
36 use coefs, only: coef_t
37 use dirichlet, only : dirichlet_t
38 use dofmap, only : dofmap_t
39 use field, only : field_t
41 use gather_scatter, only : gs_t
42 use json_module, only : json_file
43 use logger, only : log_size
44 use num_types, only : rp
45 use checkpoint, only : chkp_t
47 use space, only : space_t, gll
51 use user_intf, only : user_t
52 use usr_inflow, only : usr_inflow_eval
53 use utils, only : neko_error
54 use bc_list, only : bc_list_t
55 implicit none
56 private
57 public :: fluid_scheme_base_t, fluid_scheme_base_factory
58
60 type, abstract :: fluid_scheme_base_t
62 character(len=:), allocatable :: name
63
64 type(space_t) :: xh
65 type(dofmap_t) :: dm_xh
66 type(gs_t) :: gs_xh
67 type(coef_t) :: c_xh
68
69 type(time_scheme_controller_t), allocatable :: ext_bdf
70
72 type(field_t), pointer :: u => null()
73 type(field_t), pointer :: v => null()
74 type(field_t), pointer :: w => null()
75 type(field_t), pointer :: p => null()
76 type(field_series_t) :: ulag, vlag, wlag
77
79 type(chkp_t), pointer :: chkp => null()
80
82 real(kind=rp) :: rho
83 type(field_t) :: rho_field
84
86 type(field_t), pointer :: f_x => null()
88 type(field_t), pointer :: f_y => null()
90 type(field_t), pointer :: f_z => null()
91
93 ! List of boundary conditions for pressure
94 type(bc_list_t) :: bcs_prs
95 ! List of boundary conditions for velocity
96 type(bc_list_t) :: bcs_vel
97
98 type(json_file), pointer :: params
99 type(mesh_t), pointer :: msh => null()
100
102 character(len=NEKO_MSH_MAX_ZLBL_LEN), allocatable :: bc_labels(:)
103
105 real(kind=rp) :: mu
106
108 type(field_t) :: mu_field
109
111 logical :: variable_material_properties = .false.
113 logical :: freeze = .false.
114
115 contains
117 procedure(fluid_scheme_base_init_intrf), pass(this), deferred :: init
119 procedure(fluid_scheme_base_free_intrf), pass(this), deferred :: free
121 procedure(fluid_scheme_base_step_intrf), pass(this), deferred :: step
123 procedure(fluid_scheme_base_restart_intrf), pass(this), deferred :: restart
124 ! Setup boundary conditions
125 procedure(fluid_scheme_setup_bcs_intrf), pass(this), deferred :: setup_bcs
126
128 procedure(validate_intrf), pass(this), deferred :: validate
130 procedure(fluid_scheme_base_compute_cfl_intrf), pass(this), deferred :: compute_cfl
133 end type fluid_scheme_base_t
134
136 abstract interface
137 subroutine fluid_base_init_all_intrf(this, msh, lx, params, kspv_init, &
138 kspp_init, scheme, user)
140 import mesh_t
141 import json_file
142 import user_t
143 import rp
144 import log_size
145 class(fluid_scheme_base_t), target, intent(inout) :: this
146 type(mesh_t), target, intent(inout) :: msh
147 integer, intent(inout) :: lx
148 type(json_file), target, intent(inout) :: params
149 type(user_t), target, intent(in) :: user
150 logical :: kspv_init
151 logical :: kspp_init
152 character(len=*), intent(in) :: scheme
153 real(kind=rp) :: abs_tol
154 integer :: integer_val, ierr
155 logical :: logical_val
156 character(len=:), allocatable :: solver_type, precon_type
157 character(len=LOG_SIZE) :: log_buf
158 real(kind=rp) :: gjp_param_a, gjp_param_b
159 end subroutine fluid_base_init_all_intrf
160 end interface
161
163 abstract interface
164 subroutine fluid_base_init_common_intrf(this, msh, lx, params, scheme, &
165 user, kspv_init)
167 import mesh_t
168 import json_file
169 import user_t
170 import dirichlet_t
171 import log_size
172 import rp
173 class(fluid_scheme_base_t), target, intent(inout) :: this
174 type(mesh_t), target, intent(inout) :: msh
175 integer, intent(inout) :: lx
176 character(len=*), intent(in) :: scheme
177 type(json_file), target, intent(inout) :: params
178 type(user_t), target, intent(in) :: user
179 logical, intent(in) :: kspv_init
180 type(dirichlet_t) :: bdry_mask
181 character(len=LOG_SIZE) :: log_buf
182 real(kind=rp), allocatable :: real_vec(:)
183 real(kind=rp) :: real_val, kappa, b, z0
184 logical :: logical_val
185 integer :: integer_val, ierr
186 type(json_file) :: wm_json
187 character(len=:), allocatable :: string_val1, string_val2
188 end subroutine fluid_base_init_common_intrf
189 end interface
190
192 abstract interface
193 subroutine fluid_base_free_intrf(this)
195 class(fluid_scheme_base_t), intent(inout) :: this
196 end subroutine fluid_base_free_intrf
197 end interface
198
200 abstract interface
201 subroutine fluid_scheme_base_init_intrf(this, msh, lx, params, user, chkp)
203 import json_file
204 import mesh_t
205 import user_t
206 import chkp_t
208 class(fluid_scheme_base_t), target, intent(inout) :: this
209 type(mesh_t), target, intent(inout) :: msh
210 integer, intent(in) :: lx
211 type(json_file), target, intent(inout) :: params
212 type(user_t), target, intent(in) :: user
213 type(chkp_t), target, intent(inout) :: chkp
214 end subroutine fluid_scheme_base_init_intrf
215 end interface
216
218 abstract interface
221 class(fluid_scheme_base_t), intent(inout) :: this
222 end subroutine fluid_scheme_base_free_intrf
223 end interface
224
226 abstract interface
227 subroutine fluid_scheme_base_step_intrf(this, t, tstep, dt, ext_bdf, &
228 dt_controller)
232 import rp
233 class(fluid_scheme_base_t), target, intent(inout) :: this
234 real(kind=rp), intent(in) :: t
235 integer, intent(in) :: tstep
236 real(kind=rp), intent(in) :: dt
237 type(time_scheme_controller_t), intent(in) :: ext_bdf
238 type(time_step_controller_t), intent(in) :: dt_controller
239 end subroutine fluid_scheme_base_step_intrf
240 end interface
241
243 abstract interface
244 subroutine fluid_scheme_base_restart_intrf(this, chkp)
246 import rp
247 import chkp_t
248 class(fluid_scheme_base_t), target, intent(inout) :: this
249 type(chkp_t), intent(inout) :: chkp
251 end interface
252
254 abstract interface
255 subroutine fluid_scheme_setup_bcs_intrf(this, user, params)
256 import fluid_scheme_base_t, user_t, json_file
257 class(fluid_scheme_base_t), intent(inout) :: this
258 type(user_t), target, intent(in) :: user
259 type(json_file), intent(inout) :: params
260 end subroutine fluid_scheme_setup_bcs_intrf
261 end interface
262
264 abstract interface
265 subroutine validate_intrf(this)
267 class(fluid_scheme_base_t), target, intent(inout) :: this
268 end subroutine validate_intrf
269 end interface
270
272 abstract interface
275 import json_file
276 import user_t
277 class(fluid_scheme_base_t), intent(inout) :: this
278 end subroutine update_material_properties
279 end interface
280
282 abstract interface
283 function fluid_scheme_base_compute_cfl_intrf(this, dt) result(c)
285 import rp
286 class(fluid_scheme_base_t), intent(in) :: this
287 real(kind=rp), intent(in) :: dt
288 real(kind=rp) :: c
290 end interface
291
292 interface
293
294 module subroutine fluid_scheme_base_factory(object, type_name)
295 class(fluid_scheme_base_t), intent(inout), allocatable :: object
296 character(len=*) :: type_name
297 end subroutine fluid_scheme_base_factory
298 end interface
299end module fluid_scheme_base
Initialize common data for the current scheme.
Abstract interface to dealocate a fluid formulation.
Abstract interface to initialize a fluid formulation.
Abstract interface to restart a fluid scheme.
Abstract interface to compute a time-step.
Abstract interface to setup boundary conditions.
Abstract interface to sets rho and mu.
Abstract interface to validate the user inflow.
Abstract interface defining a user defined inflow condition (pointwise)
Defines a list of bc_t.
Definition bc_list.f90:34
Defines a boundary condition.
Definition bc.f90:34
Defines a checkpoint.
Coefficients.
Definition coef.f90:34
Defines a dirichlet boundary condition.
Definition dirichlet.f90:34
Defines a mapping of the degrees of freedom.
Definition dofmap.f90:35
Stores a series fields.
Defines a field.
Definition field.f90:34
Gather-scatter.
Logging routines.
Definition log.f90:34
integer, parameter, public log_size
Definition log.f90:42
Defines a mesh.
Definition mesh.f90:34
integer, parameter, public neko_msh_max_zlbl_len
Max length of a zone label.
Definition mesh.f90:58
integer, parameter, public rp
Global precision used in computations.
Definition num_types.f90:12
Defines a function space.
Definition space.f90:34
integer, parameter, public gll
Definition space.f90:48
Compound scheme for the advection and diffusion operators in a transport equation.
Implements type time_step_controller.
Interfaces for user interaction with NEKO.
Definition user_intf.f90:34
Defines inflow dirichlet conditions.
Utilities.
Definition utils.f90:35
Base type for a boundary condition.
Definition bc.f90:57
A list of allocatable `bc_t`. Follows the standard interface of lists.
Definition bc_list.f90:47
Coefficients defined on a given (mesh, ) tuple. Arrays use indices (i,j,k,e): element e,...
Definition coef.f90:55
Generic Dirichlet boundary condition on .
Definition dirichlet.f90:47
Base type of all fluid formulations.
The function space for the SEM solution fields.
Definition space.f90:62
Implements the logic to compute the time coefficients for the advection and diffusion operators in a ...
A type collecting all the overridable user routines.