Neko 1.99.2
A portable framework for high-order spectral element flow simulations
Loading...
Searching...
No Matches
source_term_handler.f90
Go to the documentation of this file.
1
2! Copyright (c) 2023, The Neko Authors
3! All rights reserved.
4!
5! Redistribution and use in source and binary forms, with or without
6! modification, are permitted provided that the following conditions
7! are met:
8!
9! * Redistributions of source code must retain the above copyright
10! notice, this list of conditions and the following disclaimer.
11!
12! * Redistributions in binary form must reproduce the above
13! copyright notice, this list of conditions and the following
14! disclaimer in the documentation and/or other materials provided
15! with the distribution.
16!
17! * Neither the name of the authors nor the names of its
18! contributors may be used to endorse or promote products derived
19! from this software without specific prior written permission.
20!
21! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
22! "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
23! LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
24! FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
25! COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
26! INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
27! BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
28! LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
29! CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
30! LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
31! ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
32! POSSIBILITY OF SUCH DAMAGE.
33!
37 use num_types, only: rp
39 source_term_factory
40 use field, only: field_t
41 use field_list, only: field_list_t
43 use json_module, only: json_file
44 use coefs, only: coef_t
45 use user_intf, only: user_t
46 use field_math, only: field_rzero
47 use math, only : col2
48 use device_math, only : device_col2
49 use time_state, only : time_state_t
50 implicit none
51 private
52
63 type, abstract, public :: source_term_handler_t
65 class(source_term_wrapper_t), allocatable :: source_terms(:)
67 type(field_list_t) :: rhs_fields
69 type(coef_t), pointer :: coef
71 type(user_t), pointer :: user
73 character(len=:), allocatable :: scheme_name
74
75 contains
77 procedure, pass(this) :: init_base => source_term_handler_init_base
79 procedure, pass(this) :: free => source_term_handler_free
81 procedure, pass(this) :: compute => source_term_handler_compute
83 generic :: add => add_source_term, add_json_source_terms
85 procedure, pass(this) :: add_source_term => &
88 procedure, pass(this) :: add_json_source_terms => &
92 nopass, deferred :: init_user_source
94
95 abstract interface
96 subroutine source_term_handler_init_user_source(source_term, rhs_fields, &
97 coef, user, scheme_name)
99 class(source_term_t), allocatable, intent(inout) :: source_term
100 type(field_list_t) :: rhs_fields
101 type(coef_t), intent(in) :: coef
102 type(user_t), intent(in) :: user
103 character(len=*), intent(in) :: scheme_name
105 end interface
106
107contains
108
110 subroutine source_term_handler_init_base(this, rhs_fields, coef, user, &
111 scheme_name)
112 class(source_term_handler_t), intent(inout) :: this
113 type(field_list_t), intent(in) :: rhs_fields
114 type(coef_t), target, intent(in) :: coef
115 type(user_t), target, intent(in) :: user
116 character(len=*), intent(in) :: scheme_name
117
118 call this%free()
119
120 ! We package the fields for the source term to operate on in a field list.
121 this%rhs_fields = rhs_fields
122 this%coef => coef
123 this%user => user
124 this%scheme_name = trim(scheme_name)
125
126 end subroutine source_term_handler_init_base
127
128
131 class(source_term_handler_t), intent(inout) :: this
132 integer :: i
133
134 call this%rhs_fields%free()
135
136 if (allocated(this%source_terms)) then
137 do i = 1, size(this%source_terms)
138 call this%source_terms(i)%free()
139 end do
140 deallocate(this%source_terms)
141 end if
142
143 nullify(this%coef)
144 nullify(this%user)
145
146 if (allocated(this%scheme_name)) then
147 deallocate(this%scheme_name)
148 end if
149
150 end subroutine source_term_handler_free
151
154 subroutine source_term_handler_compute(this, time)
155 class(source_term_handler_t), intent(inout) :: this
156 type(time_state_t), intent(in) :: time
157 integer :: i
158 type(field_t), pointer :: f
159
160 do i = 1, this%rhs_fields%size()
161 f => this%rhs_fields%get(i)
162 call field_rzero(f)
163 end do
164
165 ! Add contribution from all source terms. If time permits.
166 if (allocated(this%source_terms)) then
167
168 do i = 1, size(this%source_terms)
169 call this%source_terms(i)%source_term%compute(time)
170 end do
171
172 ! Multiply by mass matrix
173 do i = 1, this%rhs_fields%size()
174 f => this%rhs_fields%get(i)
175 if (neko_bcknd_device .eq. 1) then
176 call device_col2(f%x_d, this%coef%B_d, f%size())
177 else
178 call col2(f%x, this%coef%B, f%size())
179 end if
180 end do
181
182 end if
183
184 end subroutine source_term_handler_compute
185
187 subroutine source_term_handler_add_json_source_terms(this, json, name)
188 class(source_term_handler_t), intent(inout) :: this
189 type(json_file), intent(inout) :: json
190 character(len=*), intent(in) :: name
191
192 class(source_term_wrapper_t), dimension(:), allocatable :: temp
193
194 ! A single source term as its own json_file.
195 type(json_file) :: source_subdict
196 character(len=:), allocatable :: type
197 integer :: n_sources, i, i0
198
199 if (json%valid_path(name)) then
200 ! Get the number of source terms.
201 call json%info(name, n_children = n_sources)
202
203 if (allocated(this%source_terms)) then
204 i0 = size(this%source_terms)
205 call move_alloc(this%source_terms, temp)
206 allocate(this%source_terms(i0 + n_sources))
207 if (allocated(temp)) then
208 do i = 1, i0
209 call move_alloc(temp(i)%source_term, &
210 this%source_terms(i)%source_term)
211 end do
212 end if
213 else
214 i0 = 0
215 allocate(this%source_terms(n_sources))
216 end if
217
218 do i = 1, n_sources
219 ! Create a new json containing just the subdict for this source.
220 call json_extract_item(json, name, i, source_subdict)
221 call json_get(source_subdict, "type", type)
222
223 ! The user source is treated separately
224 if (trim(type) .eq. "user") then
225
226 call this%init_user_source(this%source_terms(i+ i0)%source_term, &
227 this%rhs_fields, this%coef, this%user, this%scheme_name)
228
229 call json_get_or_default(source_subdict, "start_time", &
230 this%source_terms(i + i0)%source_term%start_time, 0.0_rp)
231 call json_get_or_default(source_subdict, "end_time", &
232 this%source_terms(i + i0)%source_term%end_time, huge(0.0_rp))
233 else
234 call source_term_factory(this%source_terms(i + i0)%source_term, &
235 source_subdict, this%rhs_fields, this%coef, &
236 this%scheme_name)
237 end if
238 end do
239 end if
240
242
245 subroutine source_term_handler_add_source_term(this, source_term)
246 class(source_term_handler_t), intent(inout) :: this
247 class(source_term_t), intent(in) :: source_term
248 class(source_term_wrapper_t), dimension(:), allocatable :: temp
249
250 integer :: n_sources, i
251
252 if (allocated(this%source_terms)) then
253 n_sources = size(this%source_terms)
254 else
255 n_sources = 0
256 end if
257
258 call move_alloc(this%source_terms, temp)
259 allocate(this%source_terms(n_sources + 1))
260
261 if (allocated(temp)) then
262 do i = 1, n_sources
263 call move_alloc(temp(i)%source_term, &
264 this%source_terms(i)%source_term)
265 end do
266 end if
267
268 this%source_terms(n_sources + 1)%source_term = source_term
269
271end module source_term_handler
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.
Coefficients.
Definition coef.f90:34
subroutine, public device_col2(a_d, b_d, n, strm)
Vector multiplication .
subroutine, public field_rzero(a, n)
Zero a real vector.
Defines a field.
Definition field.f90:34
Utilities for retrieving parameters from the case files.
Definition math.f90:60
subroutine, public col2(a, b, n)
Vector multiplication .
Definition math.f90:854
Build configurations.
integer, parameter neko_bcknd_device
integer, parameter, public rp
Global precision used in computations.
Definition num_types.f90:12
Implements the source_term_handler_t type.
subroutine source_term_handler_free(this)
Destructor.
subroutine source_term_handler_init_base(this, rhs_fields, coef, user, scheme_name)
Constructor.
subroutine source_term_handler_compute(this, time)
Add all the source term to the passed right-hand side fields.
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.
Module with things related to the simulation time.
Interfaces for user interaction with NEKO.
Definition user_intf.f90:34
Coefficients defined on a given (mesh, ) tuple. Arrays use indices (i,j,k,e): element e,...
Definition coef.f90:56
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.
A struct that contains all info about the time, expand as needed.
A type collecting all the overridable user routines and flag to suppress type injection from custom m...