43 use json_module,
only: json_file
80 generic :: add => add_source_term, add_json_source_terms
82 procedure, pass(this) :: add_source_term => &
85 procedure, pass(this) :: add_json_source_terms => &
89 nopass,
deferred :: init_user_source
96 class(
source_term_t),
allocatable,
intent(inout) :: source_term
98 type(
coef_t),
intent(in) :: coef
99 character(len=*) :: type
100 type(
user_t),
intent(in) :: user
110 type(
coef_t),
target,
intent(in) :: coef
111 type(
user_t),
target,
intent(in) :: user
116 this%rhs_fields = rhs_fields
128 call this%rhs_fields%free()
130 if (
allocated(this%source_terms))
then
131 do i = 1,
size(this%source_terms)
132 call this%source_terms(i)%free()
134 deallocate(this%source_terms)
144 real(kind=
rp),
intent(in) :: t
145 integer,
intent(in) :: tstep
149 do i = 1, this%rhs_fields%size()
150 f => this%rhs_fields%get(i)
155 if (
allocated(this%source_terms))
then
157 do i = 1,
size(this%source_terms)
158 call this%source_terms(i)%source_term%compute(t, tstep)
162 do i = 1, this%rhs_fields%size()
163 f => this%rhs_fields%get(i)
167 call col2(f%x, this%coef%B, f%size())
178 type(json_file),
intent(inout) :: json
179 character(len=*),
intent(in) :: name
184 type(json_file) :: source_subdict
185 character(len=:),
allocatable :: type
186 integer :: n_sources, i, i0
188 if (json%valid_path(name))
then
190 call json%info(name, n_children = n_sources)
192 if (
allocated(this%source_terms))
then
193 i0 =
size(this%source_terms)
194 call move_alloc(this%source_terms, temp)
195 allocate(this%source_terms(i0 + n_sources))
196 if (
allocated(temp))
then
198 call move_alloc(temp(i)%source_term, this%source_terms(i)%source_term)
203 allocate(this%source_terms(n_sources))
209 call json_get(source_subdict,
"type", type)
212 if ((trim(type) .eq.
"user_vector") .or. &
213 (trim(type) .eq.
"user_pointwise"))
then
215 call this%init_user_source(this%source_terms(i+ i0)%source_term, &
216 this%rhs_fields, this%coef,
type, this%user)
219 this%source_terms(i + i0)%source_term%start_time, 0.0_rp)
221 this%source_terms(i + i0)%source_term%end_time, huge(0.0_rp))
224 call source_term_factory(this%source_terms(i + i0)%source_term, &
225 source_subdict, this%rhs_fields, this%coef)
239 integer :: n_sources, i
241 if (
allocated(this%source_terms))
then
242 n_sources =
size(this%source_terms)
247 call move_alloc(this%source_terms, temp)
248 allocate(this%source_terms(n_sources + 1))
250 if (
allocated(temp))
then
252 call move_alloc(temp(i)%source_term, &
253 this%source_terms(i)%source_term)
257 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.
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.