Neko  0.8.99
A portable framework for high-order spectral element flow simulations
scalar_scheme.f90
Go to the documentation of this file.
1 ! Copyright (c) 2022-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 
35 ! todo: module name
37  use gather_scatter, only : gs_t
38  use checkpoint, only : chkp_t
39  use num_types, only: rp
40  use field, only : field_t
41  use field_list, only: field_list_t
42  use space, only : space_t
43  use dofmap, only : dofmap_t
44  use krylov, only : ksp_t, krylov_solver_factory, krylov_solver_destroy, &
46  use coefs, only : coef_t
47  use dirichlet, only : dirichlet_t
48  use neumann, only : neumann_t
49  use jacobi, only : jacobi_t
50  use device_jacobi, only : device_jacobi_t
51  use sx_jacobi, only : sx_jacobi_t
52  use hsmg, only : hsmg_t
53  use precon, only : pc_t, precon_factory, precon_destroy
54  use bc, only : bc_t, bc_list_t, bc_list_free, bc_list_init, &
58  use facet_zone, only : facet_zone_t
60  use logger, only : neko_log, log_size
64  use json_module, only : json_file
65  use user_intf, only : user_t
67  use utils, only : neko_error
68  use comm, only: neko_comm, mpi_integer, mpi_sum
70  use math, only : cfill, add2s2
72  use neko_config, only : neko_bcknd_device
73  use field_series, only : field_series_t
75  implicit none
76 
78  type, abstract :: scalar_scheme_t
80  type(field_t), pointer :: u
82  type(field_t), pointer :: v
84  type(field_t), pointer :: w
86  type(field_t), pointer :: s
88  type(field_series_t) :: slag
90  type(space_t), pointer :: xh
92  type(dofmap_t), pointer :: dm_xh
94  type(gs_t), pointer :: gs_xh
96  type(coef_t), pointer :: c_xh
98  type(field_t), pointer :: f_xh => null()
102  class(ksp_t), allocatable :: ksp
104  integer :: ksp_maxiter
106  integer :: projection_dim
107 
108  integer :: projection_activ_step
110  class(pc_t), allocatable :: pc
112  type(dirichlet_t) :: dir_bcs(neko_msh_max_zlbls)
114  type(field_dirichlet_t) :: field_dir_bc
116  type(bc_list_t) :: field_dirichlet_bcs
118  type(neumann_t) :: neumann_bcs(neko_msh_max_zlbls)
120  type(usr_scalar_t) :: user_bc
122  integer :: n_dir_bcs = 0
124  integer :: n_neumann_bcs = 0
126  type(bc_list_t) :: bclst_dirichlet
128  type(bc_list_t) :: bclst_neumann
130  type(json_file), pointer :: params
132  type(mesh_t), pointer :: msh => null()
134  type(chkp_t) :: chkp
136  real(kind=rp), pointer :: lambda
138  type(field_t) :: lambda_field
140  character(len=:), allocatable :: nut_field_name
142  real(kind=rp), pointer :: rho
144  real(kind=rp), pointer :: cp
146  real(kind=rp) :: pr_turb
148  logical :: variable_material_properties = .false.
150  character(len=NEKO_MSH_MAX_ZLBL_LEN), allocatable :: bc_labels(:)
151  contains
153  procedure, pass(this) :: scheme_init => scalar_scheme_init
155  procedure, pass(this) :: scheme_free => scalar_scheme_free
157  procedure, pass(this) :: validate => scalar_scheme_validate
159  procedure, pass(this) :: set_user_bc => scalar_scheme_set_user_bc
161  procedure, pass(this) :: update_material_properties => &
164  procedure(scalar_scheme_init_intrf), pass(this), deferred :: init
166  procedure(scalar_scheme_free_intrf), pass(this), deferred :: free
168  procedure(scalar_scheme_step_intrf), pass(this), deferred :: step
170  procedure(scalar_scheme_restart_intrf), pass(this), deferred :: restart
171  end type scalar_scheme_t
172 
174  abstract interface
175  subroutine scalar_scheme_init_intrf(this, msh, coef, gs, params, user, &
176  material_properties, &
177  ulag, vlag, wlag, time_scheme)
178  import scalar_scheme_t
179  import json_file
180  import coef_t
181  import gs_t
182  import mesh_t
183  import user_t
184  import material_properties_t
185  import field_series_t
187  class(scalar_scheme_t), target, intent(inout) :: this
188  type(mesh_t), target, intent(inout) :: msh
189  type(coef_t), target, intent(inout) :: coef
190  type(gs_t), target, intent(inout) :: gs
191  type(json_file), target, intent(inout) :: params
192  type(user_t), target, intent(in) :: user
193  type(material_properties_t), intent(inout) :: material_properties
194  type(field_series_t), target, intent(in) :: ulag, vlag, wlag
195  type(time_scheme_controller_t), target, intent(in) :: time_scheme
196  end subroutine scalar_scheme_init_intrf
197  end interface
198 
200  abstract interface
201  subroutine scalar_scheme_restart_intrf(this, dtlag, tlag)
202  import scalar_scheme_t
203  import chkp_t
204  import rp
205  class(scalar_scheme_t), target, intent(inout) :: this
206  real(kind=rp) :: dtlag(10), tlag(10)
207  end subroutine scalar_scheme_restart_intrf
208  end interface
209 
211  abstract interface
212  subroutine scalar_scheme_free_intrf(this)
213  import scalar_scheme_t
214  class(scalar_scheme_t), intent(inout) :: this
215  end subroutine scalar_scheme_free_intrf
216  end interface
217 
219  abstract interface
220  subroutine scalar_scheme_step_intrf(this, t, tstep, dt, ext_bdf, &
221  dt_controller)
222  import scalar_scheme_t
225  import rp
226  class(scalar_scheme_t), intent(inout) :: this
227  real(kind=rp), intent(inout) :: t
228  integer, intent(inout) :: tstep
229  real(kind=rp), intent(in) :: dt
230  type(time_scheme_controller_t), intent(inout) :: ext_bdf
231  type(time_step_controller_t), intent(in) :: dt_controller
232  end subroutine scalar_scheme_step_intrf
233  end interface
234 
235 contains
236 
241  subroutine scalar_scheme_add_bcs(this, zones, bc_labels)
242  class(scalar_scheme_t), intent(inout) :: this
243  type(facet_zone_t), intent(inout) :: zones(NEKO_MSH_MAX_ZLBLS)
244  character(len=NEKO_MSH_MAX_ZLBL_LEN), intent(in) :: bc_labels(:)
245  character(len=NEKO_MSH_MAX_ZLBL_LEN) :: bc_label
246  integer :: i
247  real(kind=rp) :: dir_value, flux
248  logical :: bc_exists
249 
250  do i = 1, size(bc_labels)
251  bc_label = trim(bc_labels(i))
252  if (bc_label(1:2) .eq. 'd=') then
253 ! The idea of this commented piece of code is to merge bcs with the same
254 ! Dirichlet value into 1 so that one has less kernel launches. Currently
255 ! segfaults, needs investigation.
256 ! bc_exists = .false.
257 ! bc_idx = 0
258 ! do j = 1, i-1
259 ! if (bc_label .eq. bc_labels(j)) then
260 ! bc_exists = .true.
261 ! bc_idx = j
262 ! end if
263 ! end do
264 
265 ! if (bc_exists) then
266 ! call this%dir_bcs(j)%mark_zone(zones(i))
267 ! else
268  this%n_dir_bcs = this%n_dir_bcs + 1
269  call this%dir_bcs(this%n_dir_bcs)%init_base(this%c_Xh)
270  call this%dir_bcs(this%n_dir_bcs)%mark_zone(zones(i))
271  read(bc_label(3:), *) dir_value
272  call this%dir_bcs(this%n_dir_bcs)%set_g(dir_value)
273  call this%dir_bcs(this%n_dir_bcs)%finalize()
274  end if
275 
276  if (bc_label(1:2) .eq. 'n=') then
277  this%n_neumann_bcs = this%n_neumann_bcs + 1
278  call this%neumann_bcs(this%n_neumann_bcs)%init_base(this%c_Xh)
279  call this%neumann_bcs(this%n_neumann_bcs)%mark_zone(zones(i))
280  read(bc_label(3:), *) flux
281  call this%neumann_bcs(this%n_neumann_bcs)%finalize_neumann(flux)
282  end if
283 
285  if (bc_label(1:4) .eq. 'user') then
286  call this%user_bc%mark_zone(zones(i))
287  end if
288 
289  end do
290 
291  do i = 1, this%n_dir_bcs
292  call bc_list_add(this%bclst_dirichlet, this%dir_bcs(i))
293  end do
294 
295  ! Create list with just Neumann bcs
296  call bc_list_init(this%bclst_neumann, this%n_neumann_bcs)
297  do i = 1, this%n_neumann_bcs
298  call bc_list_add(this%bclst_neumann, this%neumann_bcs(i))
299  end do
300 
301  end subroutine scalar_scheme_add_bcs
302 
310  subroutine scalar_scheme_init(this, msh, c_Xh, gs_Xh, params, scheme, user, &
311  material_properties)
312  class(scalar_scheme_t), target, intent(inout) :: this
313  type(mesh_t), target, intent(inout) :: msh
314  type(coef_t), target, intent(inout) :: c_Xh
315  type(gs_t), target, intent(inout) :: gs_Xh
316  type(json_file), target, intent(inout) :: params
317  character(len=*), intent(in) :: scheme
318  type(user_t), target, intent(in) :: user
319  type(material_properties_t), target, intent(inout) :: material_properties
320  ! IO buffer for log output
321  character(len=LOG_SIZE) :: log_buf
322  ! Variables for retrieving json parameters
323  logical :: logical_val
324  real(kind=rp) :: real_val, solver_abstol
325  integer :: integer_val, ierr
326  character(len=:), allocatable :: solver_type, solver_precon
327 
328  this%u => neko_field_registry%get_field('u')
329  this%v => neko_field_registry%get_field('v')
330  this%w => neko_field_registry%get_field('w')
331 
332  call neko_log%section('Scalar')
333  call json_get(params, 'case.fluid.velocity_solver.type', solver_type)
334  call json_get(params, 'case.fluid.velocity_solver.preconditioner', &
335  solver_precon)
336  call json_get(params, 'case.fluid.velocity_solver.absolute_tolerance', &
337  solver_abstol)
338 
339  call json_get_or_default(params, &
340  'case.fluid.velocity_solver.projection_space_size', &
341  this%projection_dim, 20)
342  call json_get_or_default(params, &
343  'case.fluid.velocity_solver.projection_hold_steps', &
344  this%projection_activ_step, 5)
345 
346 
347  write(log_buf, '(A, A)') 'Type : ', trim(scheme)
348  call neko_log%message(log_buf)
349  call neko_log%message('Ksp scalar : ('// trim(solver_type) // &
350  ', ' // trim(solver_precon) // ')')
351  write(log_buf, '(A,ES13.6)') ' `-abs tol :', solver_abstol
352  call neko_log%message(log_buf)
353 
354  this%Xh => this%u%Xh
355  this%dm_Xh => this%u%dof
356  this%params => params
357  this%msh => msh
358  if (.not. neko_field_registry%field_exists('s')) then
359  call neko_field_registry%add_field(this%dm_Xh, 's')
360  end if
361  this%s => neko_field_registry%get_field('s')
362 
363  call this%slag%init(this%s, 2)
364 
365  this%gs_Xh => gs_xh
366  this%c_Xh => c_xh
367 
368  !
369  ! Material properties
370  !
371  this%rho => material_properties%rho
372  this%lambda => material_properties%lambda
373  this%cp => material_properties%cp
374 
375  write(log_buf, '(A,ES13.6)') 'rho :', this%rho
376  call neko_log%message(log_buf)
377  write(log_buf, '(A,ES13.6)') 'lambda :', this%lambda
378  call neko_log%message(log_buf)
379  write(log_buf, '(A,ES13.6)') 'cp :', this%cp
380  call neko_log%message(log_buf)
381 
382  !
383  ! Turbulence modelling and variable material properties
384  !
385  if (params%valid_path('case.scalar.nut_field')) then
386  call json_get(params, 'case.scalar.Pr_t', this%pr_turb)
387  call json_get(params, 'case.scalar.nut_field', this%nut_field_name)
388  this%variable_material_properties = .true.
389  else
390  this%nut_field_name = ""
391  end if
392 
393  ! Fill lambda field with the physical value
394  call this%lambda_field%init(this%dm_Xh, "lambda")
395  if (neko_bcknd_device .eq. 1) then
396  call device_cfill(this%lambda_field%x_d, this%lambda, &
397  this%lambda_field%size())
398  else
399  call cfill(this%lambda_field%x, this%lambda, this%lambda_field%size())
400  end if
401 
402  !
403  ! Setup scalar boundary conditions
404  !
405  call bc_list_init(this%bclst_dirichlet)
406  call this%user_bc%init_base(this%c_Xh)
407 
408  ! Read boundary types from the case file
409  allocate(this%bc_labels(neko_msh_max_zlbls))
410 
411  ! A filler value
412  this%bc_labels = "not"
413 
414  if (params%valid_path('case.scalar.boundary_types')) then
415  call json_get(params, 'case.scalar.boundary_types', this%bc_labels, &
416  'not')
417  end if
418 
419  !
420  ! Setup right-hand side field.
421  !
422  allocate(this%f_Xh)
423  call this%f_Xh%init(this%dm_Xh, fld_name = "scalar_rhs")
424 
425  ! Initialize the source term
426  call this%source_term%init(this%f_Xh, this%c_Xh, user)
427  call this%source_term%add(params, 'case.scalar.source_terms')
428 
429  call scalar_scheme_add_bcs(this, msh%labeled_zones, this%bc_labels)
430 
431  ! Mark BC zones
432  call this%user_bc%mark_zone(msh%wall)
433  call this%user_bc%mark_zone(msh%inlet)
434  call this%user_bc%mark_zone(msh%outlet)
435  call this%user_bc%mark_zone(msh%outlet_normal)
436  call this%user_bc%mark_zone(msh%sympln)
437  call this%user_bc%finalize()
438  if (this%user_bc%msk(0) .gt. 0) call bc_list_add(this%bclst_dirichlet, &
439  this%user_bc)
440 
441  ! Add field dirichlet BCs
442  call this%field_dir_bc%init_base(this%c_Xh)
443  call this%field_dir_bc%mark_zones_from_list(msh%labeled_zones, &
444  'd_s', this%bc_labels)
445  call this%field_dir_bc%finalize()
446  call mpi_allreduce(this%field_dir_bc%msk(0), integer_val, 1, &
447  mpi_integer, mpi_sum, neko_comm, ierr)
448  if (integer_val .gt. 0) call this%field_dir_bc%init_field('d_s')
449 
450  call bc_list_add(this%bclst_dirichlet, this%field_dir_bc)
451 
452  !
453  ! Associate our field dirichlet update to the user one.
454  !
455  this%field_dir_bc%update => user%user_dirichlet_update
456 
457  call bc_list_init(this%field_dirichlet_bcs, size = 1)
458  call bc_list_add(this%field_dirichlet_bcs, this%field_dir_bc)
459 
460 
461  ! todo parameter file ksp tol should be added
462  call json_get_or_default(params, &
463  'case.fluid.velocity_solver.max_iterations', &
464  integer_val, ksp_max_iter)
465  call json_get_or_default(params, &
466  'case.fluid.velocity_solver.monitor', &
467  logical_val, .false.)
468  call scalar_scheme_solver_factory(this%ksp, this%dm_Xh%size(), &
469  solver_type, integer_val, solver_abstol, logical_val)
470  call scalar_scheme_precon_factory(this%pc, this%ksp, &
471  this%c_Xh, this%dm_Xh, this%gs_Xh, this%bclst_dirichlet, solver_precon)
472 
473  call neko_log%end_section()
474 
475  end subroutine scalar_scheme_init
476 
477 
479  subroutine scalar_scheme_free(this)
480  class(scalar_scheme_t), intent(inout) :: this
481 
482  nullify(this%Xh)
483  nullify(this%dm_Xh)
484  nullify(this%gs_Xh)
485  nullify(this%c_Xh)
486  nullify(this%params)
487 
488  if (allocated(this%ksp)) then
489  call krylov_solver_destroy(this%ksp)
490  deallocate(this%ksp)
491  end if
492 
493  if (allocated(this%pc)) then
494  call precon_destroy(this%pc)
495  deallocate(this%pc)
496  end if
497 
498  if (allocated(this%bc_labels)) then
499  deallocate(this%bc_labels)
500  end if
501 
502  call this%source_term%free()
503 
504  call bc_list_free(this%bclst_dirichlet)
505  call bc_list_free(this%bclst_neumann)
506 
507  call this%lambda_field%free()
508  call this%slag%free()
509 
510  ! Free everything related to field dirichlet BCs
511  call bc_list_free(this%field_dirichlet_bcs)
512  call this%field_dir_bc%free()
513 
514  end subroutine scalar_scheme_free
515 
518  subroutine scalar_scheme_validate(this)
519  class(scalar_scheme_t), target, intent(inout) :: this
520 
521  if ( (.not. allocated(this%u%x)) .or. &
522  (.not. allocated(this%v%x)) .or. &
523  (.not. allocated(this%w%x)) .or. &
524  (.not. allocated(this%s%x))) then
525  call neko_error('Fields are not allocated')
526  end if
527 
528  if (.not. allocated(this%ksp)) then
529  call neko_error('No Krylov solver for velocity defined')
530  end if
531 
532  if (.not. associated(this%Xh)) then
533  call neko_error('No function space defined')
534  end if
535 
536  if (.not. associated(this%dm_Xh)) then
537  call neko_error('No dofmap defined')
538  end if
539 
540  if (.not. associated(this%c_Xh)) then
541  call neko_error('No coefficients defined')
542  end if
543 
544  if (.not. associated(this%f_Xh)) then
545  call neko_error('No rhs allocated')
546  end if
547 
548  if (.not. associated(this%params)) then
549  call neko_error('No parameters defined')
550  end if
551 
552  !
553  ! Setup checkpoint structure (if everything is fine)
554  !
555 ! @todo no io for now
556 ! call this%chkp%init(this%u, this%v, this%w, this%p)
557 
558  end subroutine scalar_scheme_validate
559 
562  subroutine scalar_scheme_solver_factory(ksp, n, solver, max_iter, &
563  abstol, monitor)
564  class(ksp_t), allocatable, target, intent(inout) :: ksp
565  integer, intent(in), value :: n
566  integer, intent(in) :: max_iter
567  character(len=*), intent(in) :: solver
568  real(kind=rp) :: abstol
569  logical, intent(in) :: monitor
570 
571  call krylov_solver_factory(ksp, n, solver, max_iter, &
572  abstol, monitor = monitor)
573 
574  end subroutine scalar_scheme_solver_factory
575 
577  subroutine scalar_scheme_precon_factory(pc, ksp, coef, dof, gs, bclst, &
578  pctype)
579  class(pc_t), allocatable, target, intent(inout) :: pc
580  class(ksp_t), target, intent(inout) :: ksp
581  type(coef_t), target, intent(inout) :: coef
582  type(dofmap_t), target, intent(inout) :: dof
583  type(gs_t), target, intent(inout) :: gs
584  type(bc_list_t), target, intent(inout) :: bclst
585  character(len=*) :: pctype
586 
587  call precon_factory(pc, pctype)
588 
589  select type (pcp => pc)
590  type is (jacobi_t)
591  call pcp%init(coef, dof, gs)
592  type is (sx_jacobi_t)
593  call pcp%init(coef, dof, gs)
594  type is (device_jacobi_t)
595  call pcp%init(coef, dof, gs)
596  type is (hsmg_t)
597  if (len_trim(pctype) .gt. 4) then
598  if (index(pctype, '+') .eq. 5) then
599  call pcp%init(dof%msh, dof%Xh, coef, dof, gs, bclst, &
600  trim(pctype(6:)))
601  else
602  call neko_error('Unknown coarse grid solver')
603  end if
604  else
605  call pcp%init(dof%msh, dof%Xh, coef, dof, gs, bclst)
606  end if
607  end select
608 
609  call ksp%set_pc(pc)
610 
611  end subroutine scalar_scheme_precon_factory
612 
615  subroutine scalar_scheme_set_user_bc(this, usr_eval)
616  class(scalar_scheme_t), intent(inout) :: this
617  procedure(usr_scalar_bc_eval) :: usr_eval
618 
619  call this%user_bc%set_eval(usr_eval)
620 
621  end subroutine scalar_scheme_set_user_bc
622 
625  class(scalar_scheme_t), intent(inout) :: this
626  type(field_t), pointer :: nut
627  integer :: n
628  ! Factor to transform nu_t to lambda_t
629  real(kind=rp) :: lambda_factor
630 
631  lambda_factor = this%rho*this%cp/this%pr_turb
632 
633  if (this%variable_material_properties) then
634  nut => neko_field_registry%get_field(this%nut_field_name)
635  n = nut%size()
636  if (neko_bcknd_device .eq. 1) then
637  call device_cfill(this%lambda_field%x_d, this%lambda, n)
638  call device_add2s2(this%lambda_field%x_d, nut%x_d, lambda_factor, n)
639  else
640  call cfill(this%lambda_field%x, this%lambda, n)
641  call add2s2(this%lambda_field%x, nut%x, lambda_factor, n)
642  end if
643  end if
644 
646 
647 
648 end module scalar_scheme
Abstract interface defining a dirichlet condition on a list of fields.
Retrieves a parameter by name or assigns a provided default value. In the latter case also adds the m...
Definition: json_utils.f90:53
Retrieves a parameter by name or throws an error.
Definition: json_utils.f90:44
Abstract interface to dealocate a scalar formulation.
Abstract interface to initialize a scalar formulation.
Abstract interface to restart a scalar formulation.
Abstract interface to compute a time-step.
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
subroutine, public bc_list_add(bclst, bc)
Add a condition to a list of boundary conditions.
Definition: bc.f90:501
subroutine, public bc_list_init(bclst, size)
Constructor for a list of boundary conditions.
Definition: bc.f90:460
subroutine, public bc_list_free(bclst)
Destructor for a list of boundary conditions.
Definition: bc.f90:487
subroutine, public bc_list_apply_scalar(bclst, x, n, t, tstep)
Apply a list of boundary conditions to a scalar field.
Definition: bc.f90:526
Defines a checkpoint.
Definition: checkpoint.f90:34
Coefficients.
Definition: coef.f90:34
Definition: comm.F90:1
type(mpi_comm) neko_comm
MPI communicator.
Definition: comm.F90:16
Jacobi preconditioner accelerator backend.
subroutine, public device_add2s2(a_d, b_d, c1, n)
Vector addition with scalar multiplication (multiplication on first argument)
subroutine, public device_cfill(a_d, c, n)
Set all elements to a constant c .
Defines a dirichlet boundary condition.
Definition: dirichlet.f90:34
Defines a mapping of the degrees of freedom.
Definition: dofmap.f90:35
Defines a zone as a subset of facets in a mesh.
Definition: facet_zone.f90:34
Defines inflow dirichlet conditions.
Defines a registry for storing solution fields.
type(field_registry_t), target, public neko_field_registry
Global field registry.
Stores a series fields.
Defines a field.
Definition: field.f90:34
Gather-scatter.
Krylov preconditioner.
Definition: pc_hsmg.f90:61
Jacobi preconditioner.
Definition: pc_jacobi.f90:34
Utilities for retrieving parameters from the case files.
Definition: json_utils.f90:34
Implements the base abstract type for Krylov solvers plus helper types.
Definition: krylov.f90:34
integer, parameter, public ksp_max_iter
Maximum number of iters.
Definition: krylov.f90:51
Logging routines.
Definition: log.f90:34
type(log_t), public neko_log
Global log stream.
Definition: log.f90:61
integer, parameter, public log_size
Definition: log.f90:40
Implements material_properties_t type.
Definition: math.f90:60
subroutine, public cfill(a, c, n)
Set all elements to a constant c .
Definition: math.f90:314
subroutine, public add2s2(a, b, c1, n)
Vector addition with scalar multiplication (multiplication on second argument)
Definition: math.f90:633
Defines a mesh.
Definition: mesh.f90:34
integer, parameter, public neko_msh_max_zlbls
Max num. zone labels.
Definition: mesh.f90:56
integer, parameter, public neko_msh_max_zlbl_len
Max length of a zone label.
Definition: mesh.f90:58
Build configurations.
Definition: neko_config.f90:34
integer, parameter neko_bcknd_device
Definition: neko_config.f90:44
Defines a Neumann boundary condition.
Definition: neumann.f90:34
integer, parameter, public rp
Global precision used in computations.
Definition: num_types.f90:12
Krylov preconditioner.
Definition: precon.f90:34
Contains the scalar_scheme_t type.
subroutine scalar_scheme_init(this, msh, c_Xh, gs_Xh, params, scheme, user, material_properties)
Initialize all related components of the current scheme.
subroutine scalar_scheme_add_bcs(this, zones, bc_labels)
Initialize boundary conditions.
subroutine scalar_scheme_free(this)
Deallocate a scalar formulation.
subroutine scalar_scheme_solver_factory(ksp, n, solver, max_iter, abstol, monitor)
Initialize a linear solver.
subroutine scalar_scheme_set_user_bc(this, usr_eval)
Initialize a user defined scalar bc.
subroutine scalar_scheme_validate(this)
Validate that all fields, solvers etc necessary for performing time-stepping are defined.
subroutine scalar_scheme_update_material_properties(this)
Update the values of lambda_field if necessary.
subroutine scalar_scheme_precon_factory(pc, ksp, coef, dof, gs, bclst, pctype)
Initialize a Krylov preconditioner.
Implements the scalar_source_term_t type.
Implements the source_term_t type and a wrapper source_term_wrapper_t.
Definition: source_term.f90:34
Defines a function space.
Definition: space.f90:34
Jacobi preconditioner SX-Aurora backend.
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 dirichlet conditions for scalars.
Definition: usr_scalar.f90:34
Utilities.
Definition: utils.f90:35
A list of boundary conditions.
Definition: bc.f90:104
Base type for a boundary condition.
Definition: bc.f90:51
Coefficients defined on a given (mesh, ) tuple. Arrays use indices (i,j,k,e): element e,...
Definition: coef.f90:55
Defines a jacobi preconditioner.
Generic Dirichlet boundary condition on .
Definition: dirichlet.f90:44
User defined dirichlet condition, for which the user can work with an entire field....
field_list_t, To be able to group fields together
Definition: field_list.f90:13
Defines a jacobi preconditioner.
Definition: pc_jacobi.f90:45
Base abstract type for a canonical Krylov method, solving .
Definition: krylov.f90:66
Contains all the material properties necessary in the simulation.
Generic Neumann boundary condition. This sets the flux of the field to the chosen value.
Definition: neumann.f90:48
Defines a canonical Krylov preconditioner.
Definition: precon.f90:40
Base type for a scalar advection-diffusion solver.
Wrapper contaning and executing the scalar source terms.
The function space for the SEM solution fields.
Definition: space.f90:62
Defines a jacobi preconditioner for SX-Aurora.
Implements the logic to compute the time coefficients for the advection and diffusion operators in a ...
Provides a tool to set time step dt.
User defined dirichlet condition for scalars.
Definition: usr_scalar.f90:45