Loading [MathJax]/jax/output/HTML-CSS/config.js
Neko 0.9.1
A portable framework for high-order spectral element flow simulations
All Classes Namespaces Files Functions Variables Typedefs Enumerator Macros Pages
user_intf.f90
Go to the documentation of this file.
1! Copyright (c) 2020-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 field, only : field_t
36 use field_list, only : field_list_t
41 use coefs, only : coef_t
42 use bc, only: bc_list_t
43 use mesh, only : mesh_t
47 use num_types, only : rp
48 use json_module, only : json_file, json_core, json_value
50 use utils, only : neko_error, neko_warning
51 use logger, only : neko_log
52 implicit none
53 private
54
56 abstract interface
57 subroutine useric(u, v, w, p, params)
58 import field_t
59 import json_file
60 type(field_t), intent(inout) :: u
61 type(field_t), intent(inout) :: v
62 type(field_t), intent(inout) :: w
63 type(field_t), intent(inout) :: p
64 type(json_file), intent(inout) :: params
65 end subroutine useric
66 end interface
67
69 abstract interface
70 subroutine useric_scalar(s, params)
71 import field_t
72 import json_file
73 type(field_t), intent(inout) :: s
74 type(json_file), intent(inout) :: params
75 end subroutine useric_scalar
76 end interface
77
79 abstract interface
80 subroutine user_initialize_modules(t, u, v, w, p, coef, params)
81 import field_t
82 import json_file
83 import coef_t
84 import rp
85 real(kind=rp) :: t
86 type(field_t), intent(inout) :: u
87 type(field_t), intent(inout) :: v
88 type(field_t), intent(inout) :: w
89 type(field_t), intent(inout) :: p
90 type(coef_t), intent(inout) :: coef
91 type(json_file), intent(inout) :: params
92 end subroutine user_initialize_modules
93 end interface
94
96 abstract interface
97 subroutine user_simcomp_init(params)
98 import json_file
99 type(json_file), intent(inout) :: params
100 end subroutine user_simcomp_init
101 end interface
102
104 abstract interface
105 subroutine usermsh(msh)
106 import mesh_t
107 type(mesh_t), intent(inout) :: msh
108 end subroutine usermsh
109 end interface
110
112 abstract interface
113 subroutine usercheck(t, tstep, u, v, w, p, coef, param)
114 import field_t
115 import coef_t
116 import json_file
117 import rp
118 real(kind=rp), intent(in) :: t
119 integer, intent(in) :: tstep
120 type(field_t), intent(inout) :: u
121 type(field_t), intent(inout) :: v
122 type(field_t), intent(inout) :: w
123 type(field_t), intent(inout) :: p
124 type(coef_t), intent(inout) :: coef
125 type(json_file), intent(inout) :: param
126 end subroutine usercheck
127 end interface
128
130 abstract interface
131 subroutine user_final_modules(t, param)
132 import json_file
133 import rp
134 real(kind=rp) :: t
135 type(json_file), intent(inout) :: param
136 end subroutine user_final_modules
137 end interface
138
146 abstract interface
147 subroutine user_material_properties(t, tstep, rho, mu, cp, lambda, params)
148 import rp
149 import json_file
150 real(kind=rp), intent(in) :: t
151 integer, intent(in) :: tstep
152 real(kind=rp), intent(inout) :: rho, mu, cp, lambda
153 type(json_file), intent(inout) :: params
154 end subroutine user_material_properties
155 end interface
156
157 type, public :: user_t
159 procedure(useric), nopass, pointer :: fluid_user_ic => null()
160 procedure(useric_scalar), nopass, pointer :: scalar_user_ic => null()
161 procedure(user_initialize_modules), nopass, pointer :: user_init_modules => null()
162 procedure(user_simcomp_init), nopass, pointer :: init_user_simcomp => null()
163 procedure(usermsh), nopass, pointer :: user_mesh_setup => null()
164 procedure(usercheck), nopass, pointer :: user_check => null()
165 procedure(user_final_modules), nopass, pointer :: user_finalize_modules => null()
166 procedure(fluid_source_compute_pointwise), nopass, pointer :: fluid_user_f => null()
167 procedure(fluid_source_compute_vector), nopass, pointer :: fluid_user_f_vector => null()
168 procedure(scalar_source_compute_pointwise), nopass, pointer :: scalar_user_f => null()
169 procedure(scalar_source_compute_vector), nopass, pointer :: scalar_user_f_vector => null()
170 procedure(usr_inflow_eval), nopass, pointer :: fluid_user_if => null()
171 procedure(field_dirichlet_update), nopass, pointer :: user_dirichlet_update => null()
172 procedure(usr_scalar_bc_eval), nopass, pointer :: scalar_user_bc => null()
174 procedure(user_material_properties), nopass, pointer :: material_properties => null()
175 contains
176 procedure, pass(u) :: init => user_intf_init
177 end type user_t
178
182contains
183
185 subroutine user_intf_init(u)
186 class(user_t), intent(inout) :: u
187 logical :: user_extended = .false.
188 character(len=256), dimension(13) :: extensions
189 integer :: i, n
190
191 n = 0
192 if (.not. associated(u%fluid_user_ic)) then
193 u%fluid_user_ic => dummy_user_ic
194 else
195 user_extended = .true.
196 n = n + 1
197 write(extensions(n), '(A)') '- Fluid initial condition'
198 end if
199
200 if (.not. associated(u%scalar_user_ic)) then
201 u%scalar_user_ic => dummy_user_ic_scalar
202 else
203 user_extended = .true.
204 n = n + 1
205 write(extensions(n), '(A)') '- Scalar initial condition'
206 end if
207
208 if (.not. associated(u%fluid_user_f)) then
209 u%fluid_user_f => dummy_user_f
210 else
211 user_extended = .true.
212 n = n + 1
213 write(extensions(n), '(A)') '- Fluid source term'
214 end if
215
216 if (.not. associated(u%fluid_user_f_vector)) then
217 u%fluid_user_f_vector => dummy_user_f_vector
218 else
219 user_extended = .true.
220 n = n + 1
221 write(extensions(n), '(A)') '- Fluid source term vector'
222 end if
223
224 if (.not. associated(u%scalar_user_f)) then
225 u%scalar_user_f => dummy_scalar_user_f
226 else
227 user_extended = .true.
228 n = n + 1
229 write(extensions(n), '(A)') '- Scalar source term'
230 end if
231
232 if (.not. associated(u%scalar_user_f_vector)) then
233 u%scalar_user_f_vector => dummy_user_scalar_f_vector
234 else
235 user_extended = .true.
236 n = n + 1
237 write(extensions(n), '(A)') '- Scalar source term vector'
238 end if
239
240 if (.not. associated(u%scalar_user_bc)) then
241 u%scalar_user_bc => dummy_scalar_user_bc
242 else
243 user_extended = .true.
244 n = n + 1
245 write(extensions(n), '(A)') '- Scalar boundary condition'
246 end if
247
248 if (.not. associated(u%user_dirichlet_update)) then
249 u%user_dirichlet_update => dirichlet_do_nothing
250 else
251 user_extended = .true.
252 n = n + 1
253 write(extensions(n), '(A)') '- Dirichlet boundary condition'
254 end if
255
256 if (.not. associated(u%user_mesh_setup)) then
257 u%user_mesh_setup => dummy_user_mesh_setup
258 else
259 user_extended = .true.
260 n = n + 1
261 write(extensions(n), '(A)') '- Mesh setup'
262 end if
263
264 if (.not. associated(u%user_check)) then
265 u%user_check => dummy_user_check
266 else
267 user_extended = .true.
268 n = n + 1
269 write(extensions(n), '(A)') '- User check'
270 end if
271
272 if (.not. associated(u%user_init_modules)) then
273 u%user_init_modules => dummy_user_init_no_modules
274 else
275 user_extended = .true.
276 n = n + 1
277 write(extensions(n), '(A)') '- Initialize modules'
278 end if
279
280 if (.not. associated(u%init_user_simcomp)) then
281 u%init_user_simcomp => dummy_user_init_no_simcomp
282 end if
283
284 if (.not. associated(u%user_finalize_modules)) then
285 u%user_finalize_modules => dummy_user_final_no_modules
286 else
287 user_extended = .true.
288 n = n + 1
289 write(extensions(n), '(A)') '- Finalize modules'
290 end if
291
292 if (.not. associated(u%material_properties)) then
293 u%material_properties => dummy_user_material_properties
294 else
295 user_extended = .true.
296 n = n + 1
297 write(extensions(n), '(A)') '- Material properties'
298 end if
299
300 if (user_extended) then
301 call neko_log%section('User defined extensions')
302
303 do i = 1, n
304 call neko_log%message(extensions(i))
305 end do
306
307 call neko_log%end_section()
308 end if
309
310 end subroutine user_intf_init
311
312
313 !
314 ! Below is the dummy user interface
315 ! when running in pure turboNEKO mode
316 !
317
319 subroutine dummy_user_ic(u, v, w, p, params)
320 type(field_t), intent(inout) :: u
321 type(field_t), intent(inout) :: v
322 type(field_t), intent(inout) :: w
323 type(field_t), intent(inout) :: p
324 type(json_file), intent(inout) :: params
325 call neko_error('Dummy user defined initial condition set')
326 end subroutine dummy_user_ic
327
331 subroutine dummy_user_ic_scalar(s, params)
332 type(field_t), intent(inout) :: s
333 type(json_file), intent(inout) :: params
334 call neko_error('Dummy user defined scalar initial condition set')
335 end subroutine dummy_user_ic_scalar
336
338 subroutine dummy_user_f_vector(f, t)
339 class(fluid_user_source_term_t), intent(inout) :: f
340 real(kind=rp), intent(in) :: t
341 call neko_error('Dummy user defined vector valued forcing set')
342 end subroutine dummy_user_f_vector
343
345 subroutine dummy_user_f(u, v, w, j, k, l, e, t)
346 real(kind=rp), intent(inout) :: u
347 real(kind=rp), intent(inout) :: v
348 real(kind=rp), intent(inout) :: w
349 integer, intent(in) :: j
350 integer, intent(in) :: k
351 integer, intent(in) :: l
352 integer, intent(in) :: e
353 real(kind=rp), intent(in) :: t
354 call neko_error('Dummy user defined forcing set')
355 end subroutine dummy_user_f
356
359 class(scalar_user_source_term_t), intent(inout) :: f
360 real(kind=rp), intent(in) :: t
361 call neko_error('Dummy user defined vector valued forcing set')
362 end subroutine dummy_user_scalar_f_vector
363
365 subroutine dummy_scalar_user_f(s, j, k, l, e, t)
366 real(kind=rp), intent(inout) :: s
367 integer, intent(in) :: j
368 integer, intent(in) :: k
369 integer, intent(in) :: l
370 integer, intent(in) :: e
371 real(kind=rp), intent(in) :: t
372 call neko_error('Dummy user defined forcing set')
373 end subroutine dummy_scalar_user_f
374
376 subroutine dummy_scalar_user_bc(s, x, y, z, nx, ny, nz, ix, iy, iz, ie, t, tstep)
377 real(kind=rp), intent(inout) :: s
378 real(kind=rp), intent(in) :: x
379 real(kind=rp), intent(in) :: y
380 real(kind=rp), intent(in) :: z
381 real(kind=rp), intent(in) :: nx
382 real(kind=rp), intent(in) :: ny
383 real(kind=rp), intent(in) :: nz
384 integer, intent(in) :: ix
385 integer, intent(in) :: iy
386 integer, intent(in) :: iz
387 integer, intent(in) :: ie
388 real(kind=rp), intent(in) :: t
389 integer, intent(in) :: tstep
390 call neko_warning('Dummy scalar user bc set, applied on all non-labeled zones')
391 end subroutine dummy_scalar_user_bc
392
394 subroutine dummy_user_mesh_setup(msh)
395 type(mesh_t), intent(inout) :: msh
396 end subroutine dummy_user_mesh_setup
397
399 subroutine dummy_user_check(t, tstep, u, v, w, p, coef, params)
400 real(kind=rp), intent(in) :: t
401 integer, intent(in) :: tstep
402 type(field_t), intent(inout) :: u
403 type(field_t), intent(inout) :: v
404 type(field_t), intent(inout) :: w
405 type(field_t), intent(inout) :: p
406 type(coef_t), intent(inout) :: coef
407 type(json_file), intent(inout) :: params
408 end subroutine dummy_user_check
409
410 subroutine dummy_user_init_no_modules(t, u, v, w, p, coef, params)
411 real(kind=rp) :: t
412 type(field_t), intent(inout) :: u
413 type(field_t), intent(inout) :: v
414 type(field_t), intent(inout) :: w
415 type(field_t), intent(inout) :: p
416 type(coef_t), intent(inout) :: coef
417 type(json_file), intent(inout) :: params
418 end subroutine dummy_user_init_no_modules
419
420 subroutine dummy_user_init_no_simcomp(params)
421 type(json_file), intent(inout) :: params
422 end subroutine dummy_user_init_no_simcomp
423
424 subroutine dummy_user_final_no_modules(t, params)
425 real(kind=rp) :: t
426 type(json_file), intent(inout) :: params
427 end subroutine dummy_user_final_no_modules
428
429 subroutine dirichlet_do_nothing(dirichlet_field_list, dirichlet_bc_list, &
430 coef, t, tstep, which_solver)
431 type(field_list_t), intent(inout) :: dirichlet_field_list
432 type(bc_list_t), intent(inout) :: dirichlet_bc_list
433 type(coef_t), intent(inout) :: coef
434 real(kind=rp), intent(in) :: t
435 integer, intent(in) :: tstep
436 character(len=*), intent(in) :: which_solver
437 end subroutine dirichlet_do_nothing
438
439 subroutine dummy_user_material_properties(t, tstep, rho, mu, cp, lambda,&
440 params)
441 real(kind=rp), intent(in) :: t
442 integer, intent(in) :: tstep
443 real(kind=rp), intent(inout) :: rho, mu, cp, lambda
444 type(json_file), intent(inout) :: params
445 end subroutine dummy_user_material_properties
446
447 ! ========================================================================== !
448 ! Helper functions for user defined interfaces
449
454 function simulation_component_user_settings(name, params) result(comp_subdict)
455 character(len=*), intent(in) :: name
456 type(json_file), intent(inout) :: params
457 type(json_file) :: comp_subdict
458
459 type(json_core) :: core
460 type(json_value), pointer :: simcomp_object
461 character(len=:), allocatable :: current_type
462 integer :: n_simcomps
463 integer :: i
464 logical :: found, is_user
465
466 call params%get_core(core)
467 call params%get(simcomp_object)
468 call params%info('', n_children=n_simcomps)
469
470 found = .false.
471 do i = 1, n_simcomps
472 call json_extract_item(core, simcomp_object, i, comp_subdict)
473 call json_get_or_default(comp_subdict, "is_user", is_user, .false.)
474 if (.not. is_user) cycle
475
476 call json_get(comp_subdict, "type", current_type)
477 if (trim(current_type) .eq. trim(name)) then
478 found = .true.
479 exit
480 end if
481 end do
482
483 if (.not. found) then
484 call neko_error("User-defined simulation component " &
485 // trim(name) // " not found in case file.")
486 end if
487
489
490
497end module user_intf
Abstract interface defining a dirichlet condition on a list of fields.
Computes the source term and adds the result to fields.
Retrieves a parameter by name or assigns a provided default value. In the latter case also adds the m...
Retrieves a parameter by name or throws an error.
Computes the source term and adds the result to fields.
Abstract interface for finalizating user variables.
Abstract interface for initilialization of modules.
Definition user_intf.f90:80
Abstract interface for setting material properties.
Abstract interface for adding user defined simulation components.
Definition user_intf.f90:97
Abstract interface for user defined check functions.
Abstract interface for user defined scalar initial conditions.
Definition user_intf.f90:70
Abstract interface for user defined initial conditions.
Definition user_intf.f90:57
Abstract interface for user defined mesh deformation functions.
Abstract interface defining a user defined inflow condition (pointwise)
Abstract interface defining a user defined scalar boundary condition (pointwise) Just imitating inflo...
Defines a boundary condition.
Definition bc.f90:34
Coefficients.
Definition coef.f90:34
Defines inflow dirichlet conditions.
Defines a field.
Definition field.f90:34
Implements the fluid_user_source_term_t type.
Utilities for retrieving parameters from the case files.
Logging routines.
Definition log.f90:34
type(log_t), public neko_log
Global log stream.
Definition log.f90:65
Defines a mesh.
Definition mesh.f90:34
integer, parameter, public rp
Global precision used in computations.
Definition num_types.f90:12
Implements the scalar_user_source_term_t type.
Interfaces for user interaction with NEKO.
Definition user_intf.f90:34
subroutine dummy_user_f_vector(f, t)
Dummy user (fluid) forcing.
subroutine dummy_user_ic_scalar(s, params)
Dummy user initial condition for scalar field.
type(json_file) function, public simulation_component_user_settings(name, params)
JSON extraction helper function for simulation components.
subroutine dummy_user_final_no_modules(t, params)
subroutine user_intf_init(u)
User interface initialization.
subroutine dummy_user_init_no_simcomp(params)
subroutine dummy_scalar_user_f(s, j, k, l, e, t)
Dummy user (scalar) forcing.
subroutine dummy_user_f(u, v, w, j, k, l, e, t)
Dummy user (fluid) forcing.
subroutine dummy_user_mesh_setup(msh)
Dummy user mesh apply.
subroutine dummy_user_ic(u, v, w, p, params)
Dummy user initial condition.
subroutine dirichlet_do_nothing(dirichlet_field_list, dirichlet_bc_list, coef, t, tstep, which_solver)
subroutine, public dummy_user_material_properties(t, tstep, rho, mu, cp, lambda, params)
subroutine dummy_user_check(t, tstep, u, v, w, p, coef, params)
Dummy user check.
subroutine dummy_user_scalar_f_vector(f, t)
Dummy user (scalar) forcing.
subroutine dummy_scalar_user_bc(s, x, y, z, nx, ny, nz, ix, iy, iz, ie, t, tstep)
Dummy user boundary condition for scalar.
subroutine dummy_user_init_no_modules(t, u, v, w, p, coef, params)
Defines inflow dirichlet conditions.
Defines dirichlet conditions for scalars.
Utilities.
Definition utils.f90:35
subroutine, public neko_warning(warning_msg)
Reports a warning to standard output.
Definition utils.f90:245
A list of boundary conditions.
Definition bc.f90:104
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
A source-term for the fluid, with procedure pointers pointing to the actual implementation in the use...
A source-term for the scalar, with procedure pointers pointing to the actual implementation in the us...
User defined dirichlet condition for inlet (vector valued)
User defined dirichlet condition for scalars.