43  use json_module, 
only: json_file
 
   81     generic :: add => add_source_term, add_json_source_terms
 
   83     procedure, pass(this) :: add_source_term => &
 
   86     procedure, pass(this) :: add_json_source_terms => &
 
   90          nopass, 
deferred :: init_user_source
 
 
   97       class(
source_term_t), 
allocatable, 
intent(inout) :: source_term
 
   99       type(
coef_t), 
intent(inout) :: coef
 
  100       character(len=*) :: type
 
  101       type(
user_t), 
intent(in) :: user
 
 
  111    type(
coef_t), 
target, 
intent(inout) :: coef
 
  112    type(
user_t), 
target, 
intent(in) :: user
 
  117    this%rhs_fields = rhs_fields
 
 
  129    call this%rhs_fields%free()
 
  131    if (
allocated(this%source_terms)) 
then 
  132       do i = 1, 
size(this%source_terms)
 
  133          call this%source_terms(i)%free()
 
  135       deallocate(this%source_terms)
 
 
  145    real(kind=
rp), 
intent(in) :: t
 
  146    integer, 
intent(in) :: tstep
 
  150    do i = 1, this%rhs_fields%size()
 
  151       f => this%rhs_fields%get(i)
 
  156    if (
allocated(this%source_terms)) 
then 
  158       do i = 1, 
size(this%source_terms)
 
  159          call this%source_terms(i)%source_term%compute(t, tstep)
 
  163       do i = 1, this%rhs_fields%size()
 
  164          f => this%rhs_fields%get(i)
 
  168             call col2(f%x, this%coef%B, f%size())
 
 
  179    type(json_file), 
intent(inout) :: json
 
  180    character(len=*), 
intent(in) :: name
 
  185    type(json_file) :: source_subdict
 
  186    character(len=:), 
allocatable :: type
 
  187    integer :: n_sources, i, i0
 
  189    if (json%valid_path(name)) 
then 
  191       call json%info(name, n_children = n_sources)
 
  193       if (
allocated(this%source_terms)) 
then 
  194          i0 = 
size(this%source_terms)
 
  195          call move_alloc(this%source_terms, temp)
 
  196          allocate(this%source_terms(i0 + n_sources))
 
  197          if (
allocated(temp)) 
then 
  199                call move_alloc(temp(i)%source_term, this%source_terms(i)%source_term)
 
  204          allocate(this%source_terms(n_sources))
 
  210          call json_get(source_subdict, 
"type", type)
 
  213          if ((trim(type) .eq. 
"user_vector") .or. &
 
  214               (trim(type) .eq. 
"user_pointwise")) 
then 
  216             call this%init_user_source(this%source_terms(i+ i0)%source_term, &
 
  217                  this%rhs_fields, this%coef, 
type, this%user)
 
  220                  this%source_terms(i + i0)%source_term%start_time, 0.0_rp)
 
  222                  this%source_terms(i + i0)%source_term%end_time, huge(0.0_rp))
 
  225             call source_term_factory(this%source_terms(i + i0)%source_term, &
 
  226                  source_subdict, this%rhs_fields, this%coef)
 
 
  240    integer :: n_sources, i
 
  242    if (
allocated(this%source_terms)) 
then 
  243       n_sources = 
size(this%source_terms)
 
  248    call move_alloc(this%source_terms, temp)
 
  249    allocate(this%source_terms(n_sources + 1))
 
  251    if (
allocated(temp)) 
then 
  253          call move_alloc(temp(i)%source_term, &
 
  254               this%source_terms(i)%source_term)
 
  258    this%source_terms(n_sources + 1)%source_term = 
source_term 
 
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.
 
subroutine, public device_col2(a_d, b_d, n)
Vector multiplication .
 
subroutine, public field_rzero(a, n)
Zero a real vector.
 
Utilities for retrieving parameters from the case files.
 
subroutine, public col2(a, b, n)
Vector multiplication .
 
integer, parameter neko_bcknd_device
 
integer, parameter, public rp
Global precision used in computations.
 
Implements the source_term_handler_t type.
 
subroutine source_term_handler_compute(this, t, tstep)
Add all the source term to the passed right-hand side fields.
 
subroutine source_term_handler_init_base(this, rhs_fields, coef, user)
Constructor.
 
subroutine source_term_handler_free(this)
Destructor.
 
subroutine source_term_handler_add_json_source_terms(this, json, name)
Read from the json file and initialize the source terms.
 
subroutine source_term_handler_add_source_term(this, source_term)
Add new source term to the list.
 
Implements the source_term_t type and a wrapper source_term_wrapper_t.
 
Interfaces for user interaction with NEKO.
 
subroutine, public neko_warning(warning_msg)
Reports a warning to standard output.
 
Coefficients defined on a given (mesh, ) tuple. Arrays use indices (i,j,k,e): element e,...
 
field_list_t, To be able to group fields together
 
Base abstract type for source terms.
 
A helper type that is needed to have an array of polymorphic objects.
 
Abstract class for handling source terms.