53  use precon, 
only : 
pc_t, precon_factory, precon_destroy
 
   61  use json_module, 
only : json_file
 
   66  use mpi_f08, 
only : mpi_integer, mpi_sum
 
   84     character(len=:), 
allocatable :: name
 
  110     integer :: ksp_maxiter
 
  112     integer :: projection_dim
 
  114     integer :: projection_activ_step
 
  120     type(json_file), 
pointer :: params
 
  126     character(len=:), 
allocatable :: nut_field_name
 
  134     type(
field_t), 
pointer :: lambda_tot => null()
 
  136     real(kind=
rp) :: pr_turb
 
  140          user_material_properties => null()
 
 
  149     procedure, pass(this) :: set_material_properties => &
 
  152     procedure, pass(this) :: update_material_properties => &
 
 
  167          numerics_params, user, chkp, ulag, vlag, wlag, time_scheme, rho)
 
  179       type(
mesh_t), 
target, 
intent(in) :: msh
 
  180       type(
coef_t), 
target, 
intent(in) :: coef
 
  181       type(
gs_t), 
target, 
intent(inout) :: gs
 
  182       type(json_file), 
target, 
intent(inout) :: params
 
  183       type(json_file), 
target, 
intent(inout) :: numerics_params
 
  184       type(
user_t), 
target, 
intent(in) :: user
 
  185       type(
chkp_t), 
target, 
intent(inout) :: chkp
 
  188       type(
field_t), 
target, 
intent(in) :: rho
 
 
  199       type(
chkp_t), 
intent(inout) :: chkp
 
 
  241    type(
mesh_t), 
target, 
intent(in) :: msh
 
  242    type(
coef_t), 
target, 
intent(in) :: c_Xh
 
  243    type(
gs_t), 
target, 
intent(inout) :: gs_Xh
 
  244    type(json_file), 
target, 
intent(inout) :: params
 
  245    character(len=*), 
intent(in) :: scheme
 
  246    type(
user_t), 
target, 
intent(in) :: user
 
  247    type(
field_t), 
target, 
intent(in) :: rho
 
  249    character(len=LOG_SIZE) :: log_buf
 
  251    logical :: logical_val
 
  252    real(kind=
rp) :: real_val, solver_abstol
 
  253    integer :: integer_val, ierr
 
  254    character(len=:), 
allocatable :: solver_type, solver_precon
 
  255    type(json_file) :: precon_params
 
  256    real(kind=
rp) :: gjp_param_a, gjp_param_b
 
  266    call json_get(params, 
'name', this%name)
 
  269    call json_get(params, 
'solver.type', solver_type)
 
  270    call json_get(params, 
'solver.preconditioner.type', &
 
  272    call json_get(params, 
'solver.preconditioner', precon_params)
 
  273    call json_get(params, 
'solver.absolute_tolerance', &
 
  277         'solver.projection_space_size', &
 
  278         this%projection_dim, 0)
 
  280         'solver.projection_hold_steps', &
 
  281         this%projection_activ_step, 5)
 
  284    write(log_buf, 
'(A, A)') 
'Type       : ', trim(scheme)
 
  286    write(log_buf, 
'(A, A)') 
'Name       : ', trim(this%name)
 
  288    call neko_log%message(
'Ksp scalar : ('// trim(solver_type) // &
 
  289         ', ' // trim(solver_precon) // 
')')
 
  290    write(log_buf, 
'(A,ES13.6)') 
' `-abs tol :', solver_abstol
 
  294    this%dm_Xh => this%u%dof
 
  295    this%params => params
 
  299         ignore_existing = .true.)
 
  303    call this%slag%init(this%s, 2)
 
  311    call this%set_material_properties(params, 
user)
 
  317    if (params%valid_path(
'nut_field')) 
then 
  318       call json_get(params, 
'Pr_t', this%pr_turb)
 
  319       call json_get(params, 
'nut_field', this%nut_field_name)
 
  321       this%nut_field_name = 
"" 
  328    call this%f_Xh%init(this%dm_Xh, fld_name = 
"scalar_rhs")
 
  331    call this%source_term%init(this%f_Xh, this%c_Xh, 
user, this%name)
 
  332    call this%source_term%add(params, 
'source_terms')
 
  336         'solver.max_iterations', &
 
  340         logical_val, .false.)
 
  342         solver_type, integer_val, solver_abstol, logical_val)
 
  344         this%c_Xh, this%dm_Xh, this%gs_Xh, this%bcs, &
 
  345         solver_precon, precon_params)
 
 
  362    if (
allocated(this%ksp)) 
then 
  367    if (
allocated(this%pc)) 
then 
  368       call precon_destroy(this%pc)
 
  372    if (
allocated(this%name)) 
then 
  373       deallocate(this%name)
 
  376    call this%source_term%free()
 
  379    call this%slag%free()
 
  383    nullify(this%lambda_tot)
 
 
  392    if ( (.not. 
allocated(this%u%x)) .or. &
 
  393         (.not. 
allocated(this%v%x)) .or. &
 
  394         (.not. 
allocated(this%w%x)) .or. &
 
  395         (.not. 
allocated(this%s%x))) 
then 
  399    if (.not. 
allocated(this%ksp)) 
then 
  400       call neko_error(
'No Krylov solver for velocity defined')
 
  403    if (.not. 
associated(this%Xh)) 
then 
  407    if (.not. 
associated(this%dm_Xh)) 
then 
  411    if (.not. 
associated(this%c_Xh)) 
then 
  415    if (.not. 
associated(this%f_Xh)) 
then 
  419    if (.not. 
associated(this%params)) 
then 
  423    if (.not. 
associated(this%rho)) 
then 
 
  433    class(
ksp_t), 
allocatable, 
target, 
intent(inout) :: ksp
 
  434    integer, 
intent(in), 
value :: n
 
  435    integer, 
intent(in) :: max_iter
 
  436    character(len=*), 
intent(in) :: solver
 
  437    real(kind=
rp) :: abstol
 
  438    logical, 
intent(in) :: monitor
 
  440    call krylov_solver_factory(ksp, n, solver, max_iter, &
 
  441         abstol, monitor = monitor)
 
 
  448    class(
pc_t), 
allocatable, 
target, 
intent(inout) :: pc
 
  449    class(
ksp_t), 
target, 
intent(inout) :: ksp
 
  450    type(
coef_t), 
target, 
intent(in) :: coef
 
  451    type(
dofmap_t), 
target, 
intent(in) :: dof
 
  452    type(
gs_t), 
target, 
intent(inout) :: gs
 
  453    type(
bc_list_t), 
target, 
intent(inout) :: bclst
 
  454    character(len=*) :: pctype
 
  455    type(json_file), 
intent(inout) :: pcparams
 
  457    call precon_factory(pc, pctype)
 
  459    select type (pcp => pc)
 
  461       call pcp%init(coef, dof, gs)
 
  463       call pcp%init(coef, dof, gs)
 
  465       call pcp%init(coef, dof, gs)
 
  467       call pcp%init(coef, bclst, pcparams)
 
 
  484    type(
field_t), 
pointer :: lambda_factor
 
  486    call this%user_material_properties(this%name, this%material_properties, &
 
  490    if (len(trim(this%nut_field_name)) > 0) 
then 
  495       call field_col3(lambda_factor, this%cp, this%rho)
 
  496       call field_cmult2(lambda_factor, nut, 1.0_rp / this%pr_turb)
 
  497       call field_add3(this%lambda_tot, this%lambda, lambda_factor)
 
 
  517    type(json_file), 
intent(inout) :: params
 
  518    type(
user_t), 
target, 
intent(in) :: user
 
  519    character(len=LOG_SIZE) :: log_buf
 
  522    real(kind=
rp) :: const_cp, const_lambda
 
  537    call this%material_properties%init(2)
 
  538    call this%material_properties%assign(1, this%cp)
 
  539    call this%material_properties%assign(2, this%lambda)
 
  541    if (.not. 
associated(
user%material_properties, dummy_mp_ptr)) 
then 
  543       write(log_buf, 
'(A)') 
"Material properties must be set in the user " // &
 
  546       this%user_material_properties => 
user%material_properties
 
  548       call user%material_properties(this%name, this%material_properties, time)
 
  551       if (params%valid_path(
'Pe') .and. &
 
  552            (params%valid_path(
'lambda') .or. &
 
  553            params%valid_path(
'cp'))) 
then 
  554          call neko_error(
"To set the material properties for the scalar, " // &
 
  555               "either provide Pe OR lambda and cp in the case file.")
 
  557       else if (params%valid_path(
'Pe')) 
then 
  558          write(log_buf, 
'(A)') 
'Non-dimensional scalar material properties' //&
 
  561          write(log_buf, 
'(A)') 
'Specific heat capacity will be set to 1,' 
  563          write(log_buf, 
'(A)') 
'conductivity to 1/Pe. Assumes density is 1.' 
  567          call json_get(params, 
'Pe', const_lambda)
 
  568          write(log_buf, 
'(A,ES13.6)') 
'Pe         :', const_lambda
 
  574          const_lambda = 1.0_rp/const_lambda
 
  577          call json_get(params, 
'lambda', const_lambda)
 
  578          call json_get(params, 
'cp', const_cp)
 
  583    if (
associated(
user%material_properties, dummy_mp_ptr)) 
then 
  588       write(log_buf, 
'(A,ES13.6)') 
'lambda     :', const_lambda
 
  590       write(log_buf, 
'(A,ES13.6)') 
'cp         :', const_cp
 
 
Copy data between host and device (or device and device)
 
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...
 
Retrieves a parameter by name or throws an error.
 
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 for setting material properties.
 
Defines a boundary condition.
 
type(mpi_comm), public neko_comm
MPI communicator.
 
Jacobi preconditioner accelerator backend.
 
subroutine, public device_add2s2(a_d, b_d, c1, n, strm)
Vector addition with scalar multiplication  (multiplication on first argument)
 
subroutine, public device_cfill(a_d, c, n, strm)
Set all elements to a constant c .
 
Device abstraction, common interface for various accelerators.
 
integer, parameter, public device_to_host
 
Defines a dirichlet boundary condition.
 
Defines a mapping of the degrees of freedom.
 
Defines a zone as a subset of facets in a mesh.
 
Defines user dirichlet condition for a scalar field.
 
subroutine, public field_cmult2(a, b, c, n)
Multiplication by constant c .
 
subroutine, public field_cfill(a, c, n)
Set all elements to a constant c .
 
subroutine, public field_col3(a, b, c, n)
Vector multiplication with 3 vectors .
 
subroutine, public field_copy(a, b, n)
Copy a vector .
 
subroutine, public field_add3(a, b, c, n)
Vector addition .
 
Defines a registry for storing solution fields.
 
type(field_registry_t), target, public neko_field_registry
Global field registry.
 
Contains the field_serties_t type.
 
Utilities for retrieving parameters from the case files.
 
Implements the base abstract type for Krylov solvers plus helper types.
 
integer, parameter, public ksp_max_iter
Maximum number of iters.
 
integer, parameter, public neko_log_verbose
Verbose log level.
 
type(log_t), public neko_log
Global log stream.
 
integer, parameter, public log_size
 
subroutine, public cfill(a, c, n)
Set all elements to a constant c .
 
subroutine, public add2s2(a, b, c1, n)
Vector addition with scalar multiplication  (multiplication on second argument)
 
integer, parameter, public neko_msh_max_zlbls
Max num. zone labels.
 
integer, parameter, public neko_msh_max_zlbl_len
Max length of a zone label.
 
integer, parameter neko_bcknd_device
 
Defines a Neumann boundary condition.
 
integer, parameter, public rp
Global precision used in computations.
 
Contains the scalar_scheme_t type.
 
subroutine scalar_scheme_init(this, msh, c_xh, gs_xh, params, scheme, user, rho)
Initialize all related components of the current scheme.
 
subroutine scalar_scheme_precon_factory(pc, ksp, coef, dof, gs, bclst, pctype, pcparams)
Initialize a Krylov preconditioner.
 
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_validate(this)
Validate that all fields, solvers etc necessary for performing time-stepping are defined.
 
subroutine scalar_scheme_update_material_properties(this, time)
Call user material properties routine and update the values of lambda if necessary.
 
subroutine scalar_scheme_set_material_properties(this, params, user)
Set lamdba and cp.
 
Implements the scalar_source_term_t type.
 
Defines a registry for storing and requesting temporary fields This can be used when you have a funct...
 
type(scratch_registry_t), target, public neko_scratch_registry
Global scratch registry.
 
Implements the source_term_t type and a wrapper source_term_wrapper_t.
 
Defines a function space.
 
Jacobi preconditioner SX-Aurora backend.
 
Compound scheme for the advection and diffusion operators in a transport equation.
 
Module with things related to the simulation time.
 
Implements type time_step_controller.
 
Interfaces for user interaction with NEKO.
 
subroutine, public dummy_user_material_properties(scheme_name, properties, time)
 
subroutine, public neko_warning(warning_msg)
Reports a warning to standard output.
 
Base type for a boundary condition.
 
A list of allocatable `bc_t`. Follows the standard interface of lists.
 
Coefficients defined on a given (mesh, ) tuple. Arrays use indices (i,j,k,e): element e,...
 
Defines a jacobi preconditioner.
 
Generic Dirichlet boundary condition  on .
 
User defined dirichlet condition, for which the user can work with an entire field....
 
field_list_t, To be able to group fields together
 
Stores a series (sequence) of fields, logically connected to a base field, and arranged according to ...
 
Defines a jacobi preconditioner.
 
Type for storing initial and final residuals in a Krylov solver.
 
Base abstract type for a canonical Krylov method, solving .
 
A Neumann boundary condition for scalar fields. Sets the flux of the field to the chosen value.
 
Defines a canonical Krylov preconditioner.
 
Base type for a scalar advection-diffusion solver.
 
Wrapper contaning and executing the scalar source terms.
 
The function space for the SEM solution fields.
 
Defines a jacobi preconditioner for SX-Aurora.
 
Implements the logic to compute the time coefficients for the advection and diffusion operators in a ...
 
A struct that contains all info about the time, expand as needed.
 
Provides a tool to set time step dt.
 
A type collecting all the overridable user routines and flag to suppress type injection from custom m...