Neko  0.8.1
A portable framework for high-order spectral element flow simulations
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 !
34 module user_intf
35  use field
36  use field_list, only : field_list_t
39  use coefs
40  use bc, only: bc_list_t
41  use mesh
42  use usr_inflow
43  use usr_scalar
45  use num_types
46  use json_module, only : json_file
47  use utils, only : neko_error, neko_warning
48  implicit none
49  private
50 
52  abstract interface
53  subroutine useric(u, v, w, p, params)
54  import field_t
55  import json_file
56  type(field_t), intent(inout) :: u
57  type(field_t), intent(inout) :: v
58  type(field_t), intent(inout) :: w
59  type(field_t), intent(inout) :: p
60  type(json_file), intent(inout) :: params
61  end subroutine useric
62  end interface
63 
65  abstract interface
66  subroutine useric_scalar(s, params)
67  import field_t
68  import json_file
69  type(field_t), intent(inout) :: s
70  type(json_file), intent(inout) :: params
71  end subroutine useric_scalar
72  end interface
73 
75  abstract interface
76  subroutine user_initialize_modules(t, u, v, w, p, coef, params)
77  import field_t
78  import json_file
79  import coef_t
80  import rp
81  real(kind=rp) :: t
82  type(field_t), intent(inout) :: u
83  type(field_t), intent(inout) :: v
84  type(field_t), intent(inout) :: w
85  type(field_t), intent(inout) :: p
86  type(coef_t), intent(inout) :: coef
87  type(json_file), intent(inout) :: params
88  end subroutine user_initialize_modules
89  end interface
90 
91 
93  abstract interface
94  subroutine usermsh(msh)
95  import mesh_t
96  type(mesh_t), intent(inout) :: msh
97  end subroutine usermsh
98  end interface
99 
101  abstract interface
102  subroutine usercheck(t, tstep, u, v, w, p, coef, param)
103  import field_t
104  import coef_t
105  import json_file
106  import rp
107  real(kind=rp), intent(in) :: t
108  integer, intent(in) :: tstep
109  type(field_t), intent(inout) :: u
110  type(field_t), intent(inout) :: v
111  type(field_t), intent(inout) :: w
112  type(field_t), intent(inout) :: p
113  type(coef_t), intent(inout) :: coef
114  type(json_file), intent(inout) :: param
115  end subroutine usercheck
116  end interface
117 
119  abstract interface
120  subroutine user_final_modules(t, param)
121  import json_file
122  import rp
123  real(kind=rp) :: t
124  type(json_file), intent(inout) :: param
125  end subroutine user_final_modules
126  end interface
127 
135  abstract interface
136  subroutine user_material_properties(t, tstep, rho, mu, cp, lambda, params)
137  import rp
138  import json_file
139  real(kind=rp), intent(in) :: t
140  integer, intent(in) :: tstep
141  real(kind=rp), intent(inout) :: rho, mu, cp, lambda
142  type(json_file), intent(inout) :: params
143  end subroutine user_material_properties
144  end interface
145 
146  type, public :: user_t
147  procedure(useric), nopass, pointer :: fluid_user_ic => null()
148  procedure(useric_scalar), nopass, pointer :: scalar_user_ic => null()
149  procedure(user_initialize_modules), nopass, pointer :: user_init_modules => null()
150  procedure(usermsh), nopass, pointer :: user_mesh_setup => null()
151  procedure(usercheck), nopass, pointer :: user_check => null()
152  procedure(user_final_modules), nopass, pointer :: user_finalize_modules => null()
153  procedure(fluid_source_compute_pointwise), nopass, pointer :: fluid_user_f => null()
154  procedure(fluid_source_compute_vector), nopass, pointer :: fluid_user_f_vector => null()
155  procedure(scalar_source_compute_pointwise), nopass, pointer :: scalar_user_f => null()
156  procedure(scalar_source_compute_vector), nopass, pointer :: scalar_user_f_vector => null()
157  procedure(usr_inflow_eval), nopass, pointer :: fluid_user_if => null()
158  procedure(field_dirichlet_update), nopass, pointer :: user_dirichlet_update => null()
159  procedure(usr_scalar_bc_eval), nopass, pointer :: scalar_user_bc => null()
161  procedure(user_material_properties), nopass, pointer :: material_properties => null()
162  contains
163  procedure, pass(u) :: init => user_intf_init
164  end type user_t
165 
168 contains
169 
171  subroutine user_intf_init(u)
172  class(user_t), intent(inout) :: u
173 
174  if (.not. associated(u%fluid_user_ic)) then
175  u%fluid_user_ic => dummy_user_ic
176  end if
177 
178  if (.not. associated(u%scalar_user_ic)) then
179  u%scalar_user_ic => dummy_user_ic_scalar
180  end if
181 
182  if (.not. associated(u%fluid_user_f)) then
183  u%fluid_user_f => dummy_user_f
184  end if
185 
186  if (.not. associated(u%fluid_user_f_vector)) then
187  u%fluid_user_f_vector => dummy_user_f_vector
188  end if
189 
190  if (.not. associated(u%scalar_user_f)) then
191  u%scalar_user_f => dummy_scalar_user_f
192  end if
193 
194  if (.not. associated(u%scalar_user_f_vector)) then
195  u%scalar_user_f_vector => dummy_user_scalar_f_vector
196  end if
197 
198  if (.not. associated(u%scalar_user_bc)) then
199  u%scalar_user_bc => dummy_scalar_user_bc
200  end if
201 
202  if (.not. associated(u%user_dirichlet_update)) then
203  u%user_dirichlet_update => dirichlet_do_nothing
204  end if
205 
206  if (.not. associated(u%user_mesh_setup)) then
207  u%user_mesh_setup => dummy_user_mesh_setup
208  end if
209 
210  if (.not. associated(u%user_check)) then
211  u%user_check => dummy_user_check
212  end if
213 
214  if (.not. associated(u%user_init_modules)) then
215  u%user_init_modules => dummy_user_init_no_modules
216  end if
217 
218  if (.not. associated(u%user_finalize_modules)) then
219  u%user_finalize_modules => dummy_user_final_no_modules
220  end if
221 
222  if (.not. associated(u%material_properties)) then
223  u%material_properties => dummy_user_material_properties
224  end if
225  end subroutine user_intf_init
226 
227 
228  !
229  ! Below is the dummy user interface
230  ! when running in pure turboNEKO mode
231  !
232 
234  subroutine dummy_user_ic(u, v, w, p, params)
235  type(field_t), intent(inout) :: u
236  type(field_t), intent(inout) :: v
237  type(field_t), intent(inout) :: w
238  type(field_t), intent(inout) :: p
239  type(json_file), intent(inout) :: params
240  call neko_error('Dummy user defined initial condition set')
241  end subroutine dummy_user_ic
242 
246  subroutine dummy_user_ic_scalar(s, params)
247  type(field_t), intent(inout) :: s
248  type(json_file), intent(inout) :: params
249  call neko_error('Dummy user defined scalar initial condition set')
250  end subroutine dummy_user_ic_scalar
251 
253  subroutine dummy_user_f_vector(f, t)
254  class(fluid_user_source_term_t), intent(inout) :: f
255  real(kind=rp), intent(in) :: t
256  call neko_error('Dummy user defined vector valued forcing set')
257  end subroutine dummy_user_f_vector
258 
260  subroutine dummy_user_f(u, v, w, j, k, l, e, t)
261  real(kind=rp), intent(inout) :: u
262  real(kind=rp), intent(inout) :: v
263  real(kind=rp), intent(inout) :: w
264  integer, intent(in) :: j
265  integer, intent(in) :: k
266  integer, intent(in) :: l
267  integer, intent(in) :: e
268  real(kind=rp), intent(in) :: t
269  call neko_error('Dummy user defined forcing set')
270  end subroutine dummy_user_f
271 
273  subroutine dummy_user_scalar_f_vector(f, t)
274  class(scalar_user_source_term_t), intent(inout) :: f
275  real(kind=rp), intent(in) :: t
276  call neko_error('Dummy user defined vector valued forcing set')
277  end subroutine dummy_user_scalar_f_vector
278 
280  subroutine dummy_scalar_user_f(s, j, k, l, e, t)
281  real(kind=rp), intent(inout) :: s
282  integer, intent(in) :: j
283  integer, intent(in) :: k
284  integer, intent(in) :: l
285  integer, intent(in) :: e
286  real(kind=rp), intent(in) :: t
287  call neko_error('Dummy user defined forcing set')
288  end subroutine dummy_scalar_user_f
289 
291  subroutine dummy_scalar_user_bc(s, x, y, z, nx, ny, nz, ix, iy, iz, ie, t, tstep)
292  real(kind=rp), intent(inout) :: s
293  real(kind=rp), intent(in) :: x
294  real(kind=rp), intent(in) :: y
295  real(kind=rp), intent(in) :: z
296  real(kind=rp), intent(in) :: nx
297  real(kind=rp), intent(in) :: ny
298  real(kind=rp), intent(in) :: nz
299  integer, intent(in) :: ix
300  integer, intent(in) :: iy
301  integer, intent(in) :: iz
302  integer, intent(in) :: ie
303  real(kind=rp), intent(in) :: t
304  integer, intent(in) :: tstep
305  call neko_warning('Dummy scalar user bc set, applied on all non-labeled zones')
306  end subroutine dummy_scalar_user_bc
307 
309  subroutine dummy_user_mesh_setup(msh)
310  type(mesh_t), intent(inout) :: msh
311  end subroutine dummy_user_mesh_setup
312 
314  subroutine dummy_user_check(t, tstep, u, v, w, p, coef, params)
315  real(kind=rp), intent(in) :: t
316  integer, intent(in) :: tstep
317  type(field_t), intent(inout) :: u
318  type(field_t), intent(inout) :: v
319  type(field_t), intent(inout) :: w
320  type(field_t), intent(inout) :: p
321  type(coef_t), intent(inout) :: coef
322  type(json_file), intent(inout) :: params
323  end subroutine dummy_user_check
324 
325  subroutine dummy_user_init_no_modules(t, u, v, w, p, coef, params)
326  real(kind=rp) :: t
327  type(field_t), intent(inout) :: u
328  type(field_t), intent(inout) :: v
329  type(field_t), intent(inout) :: w
330  type(field_t), intent(inout) :: p
331  type(coef_t), intent(inout) :: coef
332  type(json_file), intent(inout) :: params
333  end subroutine dummy_user_init_no_modules
334 
335  subroutine dummy_user_final_no_modules(t, params)
336  real(kind=rp) :: t
337  type(json_file), intent(inout) :: params
338  end subroutine dummy_user_final_no_modules
339 
340  subroutine dirichlet_do_nothing(dirichlet_field_list, dirichlet_bc_list, &
341  coef, t, tstep, which_solver)
342  type(field_list_t), intent(inout) :: dirichlet_field_list
343  type(bc_list_t), intent(inout) :: dirichlet_bc_list
344  type(coef_t), intent(inout) :: coef
345  real(kind=rp), intent(in) :: t
346  integer, intent(in) :: tstep
347  character(len=*), intent(in) :: which_solver
348  end subroutine dirichlet_do_nothing
349 
350  subroutine dummy_user_material_properties(t, tstep, rho, mu, cp, lambda,&
351  params)
352  real(kind=rp), intent(in) :: t
353  integer, intent(in) :: tstep
354  real(kind=rp), intent(inout) :: rho, mu, cp, lambda
355  type(json_file), intent(inout) :: params
356  end subroutine dummy_user_material_properties
357 
358 end module user_intf
Abstract interface defining a dirichlet condition on a list of fields.
Computes the source term and adds the result to fields.
Computes the source term and adds the result to fields.
Abstract interface for finalizating user variables.
Definition: user_intf.f90:120
Abstract interface for initilialization of modules.
Definition: user_intf.f90:76
Abstract interface for setting material properties.
Definition: user_intf.f90:136
Abstract interface for user defined check functions.
Definition: user_intf.f90:102
Abstract interface for user defined scalar initial conditions.
Definition: user_intf.f90:66
Abstract interface for user defined initial conditions.
Definition: user_intf.f90:53
Abstract interface for user defined mesh deformation functions.
Definition: user_intf.f90:94
Abstract interface defining a user defined inflow condition (pointwise)
Definition: usr_inflow.f90:79
Abstract interface defining a user defined scalar boundary condition (pointwise) Just imitating inflo...
Definition: usr_scalar.f90:77
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.
Implements material_properties_t type.
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.
Definition: user_intf.f90:254
subroutine dummy_user_ic_scalar(s, params)
Dummy user initial condition for scalar field.
Definition: user_intf.f90:247
subroutine dummy_user_final_no_modules(t, params)
Definition: user_intf.f90:336
subroutine user_intf_init(u)
User interface initialization.
Definition: user_intf.f90:172
subroutine dummy_scalar_user_f(s, j, k, l, e, t)
Dummy user (scalar) forcing.
Definition: user_intf.f90:281
subroutine dummy_user_f(u, v, w, j, k, l, e, t)
Dummy user (fluid) forcing.
Definition: user_intf.f90:261
subroutine dummy_user_mesh_setup(msh)
Dummy user mesh apply.
Definition: user_intf.f90:310
subroutine dummy_user_ic(u, v, w, p, params)
Dummy user initial condition.
Definition: user_intf.f90:235
subroutine dirichlet_do_nothing(dirichlet_field_list, dirichlet_bc_list, coef, t, tstep, which_solver)
Definition: user_intf.f90:342
subroutine, public dummy_user_material_properties(t, tstep, rho, mu, cp, lambda, params)
Definition: user_intf.f90:352
subroutine dummy_user_check(t, tstep, u, v, w, p, coef, params)
Dummy user check.
Definition: user_intf.f90:315
subroutine dummy_user_scalar_f_vector(f, t)
Dummy user (scalar) forcing.
Definition: user_intf.f90:274
subroutine dummy_scalar_user_bc(s, x, y, z, nx, ny, nz, ix, iy, iz, ie, t, tstep)
Dummy user boundary condition for scalar.
Definition: user_intf.f90:292
subroutine dummy_user_init_no_modules(t, u, v, w, p, coef, params)
Definition: user_intf.f90:326
Defines inflow dirichlet conditions.
Definition: usr_inflow.f90:34
Defines dirichlet conditions for scalars.
Definition: usr_scalar.f90:34
Utilities.
Definition: utils.f90:35
subroutine neko_warning(warning_msg)
Definition: utils.f90:191
A list of boundary conditions.
Definition: bc.f90:102
Coefficients defined on a given (mesh, ) tuple. Arrays use indices (i,j,k,e): element e,...
Definition: coef.f90:54
field_list_t, To be able to group fields together
Definition: field_list.f90:7
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...