Neko 0.9.99
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 implicit none
50 private
51
62 type, abstract, public :: source_term_handler_t
64 class(source_term_wrapper_t), allocatable :: source_terms(:)
66 type(field_list_t) :: rhs_fields
68 type(coef_t), pointer :: coef
70 type(user_t), pointer :: user
71
72 contains
74 procedure, pass(this) :: init_base => source_term_handler_init_base
76 procedure, pass(this) :: free => source_term_handler_free
78 procedure, pass(this) :: compute => source_term_handler_compute
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
91
92 abstract interface
93 subroutine source_term_handler_init_user_source(source_term, rhs_fields, &
94 coef, type, user)
96 class(source_term_t), allocatable, intent(inout) :: source_term
97 type(field_list_t) :: rhs_fields
98 type(coef_t), intent(in) :: coef
99 character(len=*) :: type
100 type(user_t), intent(in) :: user
102 end interface
103
104contains
105
107 subroutine source_term_handler_init_base(this, rhs_fields, coef, user)
108 class(source_term_handler_t), intent(inout) :: this
109 type(field_list_t), intent(in) :: rhs_fields
110 type(coef_t), target, intent(in) :: coef
111 type(user_t), target, intent(in) :: user
112
113 call this%free()
114
115 ! We package the fields for the source term to operate on in a field list.
116 this%rhs_fields = rhs_fields
117 this%coef => coef
118 this%user => user
119
120 end subroutine source_term_handler_init_base
121
122
125 class(source_term_handler_t), intent(inout) :: this
126 integer :: i
127
128 call this%rhs_fields%free()
129
130 if (allocated(this%source_terms)) then
131 do i = 1, size(this%source_terms)
132 call this%source_terms(i)%free()
133 end do
134 deallocate(this%source_terms)
135 end if
136
137 end subroutine source_term_handler_free
138
142 subroutine source_term_handler_compute(this, t, tstep)
143 class(source_term_handler_t), intent(inout) :: this
144 real(kind=rp), intent(in) :: t
145 integer, intent(in) :: tstep
146 integer :: i
147 type(field_t), pointer :: f
148
149 do i = 1, this%rhs_fields%size()
150 f => this%rhs_fields%get(i)
151 call field_rzero(f)
152 end do
153
154 ! Add contribution from all source terms. If time permits.
155 if (allocated(this%source_terms)) then
156
157 do i = 1, size(this%source_terms)
158 call this%source_terms(i)%source_term%compute(t, tstep)
159 end do
160
161 ! Multiply by mass matrix
162 do i = 1, this%rhs_fields%size()
163 f => this%rhs_fields%get(i)
164 if (neko_bcknd_device .eq. 1) then
165 call device_col2(f%x_d, this%coef%B_d, f%size())
166 else
167 call col2(f%x, this%coef%B, f%size())
168 end if
169 end do
170
171 end if
172
173 end subroutine source_term_handler_compute
174
176 subroutine source_term_handler_add_json_source_terms(this, json, name)
177 class(source_term_handler_t), intent(inout) :: this
178 type(json_file), intent(inout) :: json
179 character(len=*), intent(in) :: name
180
181 class(source_term_wrapper_t), dimension(:), allocatable :: temp
182
183 ! A single source term as its own json_file.
184 type(json_file) :: source_subdict
185 character(len=:), allocatable :: type
186 integer :: n_sources, i, i0
187
188 if (json%valid_path(name)) then
189 ! Get the number of source terms.
190 call json%info(name, n_children = n_sources)
191
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
197 do i = 1, i0
198 call move_alloc(temp(i)%source_term, this%source_terms(i)%source_term)
199 end do
200 end if
201 else
202 i0 = 0
203 allocate(this%source_terms(n_sources))
204 end if
205
206 do i = 1, n_sources
207 ! Create a new json containing just the subdict for this source.
208 call json_extract_item(json, name, i, source_subdict)
209 call json_get(source_subdict, "type", type)
210
211 ! The user source is treated separately
212 if ((trim(type) .eq. "user_vector") .or. &
213 (trim(type) .eq. "user_pointwise")) then
214
215 call this%init_user_source(this%source_terms(i+ i0)%source_term, &
216 this%rhs_fields, this%coef, type, this%user)
217
218 call json_get_or_default(source_subdict, "start_time", &
219 this%source_terms(i + i0)%source_term%start_time, 0.0_rp)
220 call json_get_or_default(source_subdict, "end_time", &
221 this%source_terms(i + i0)%source_term%end_time, huge(0.0_rp))
222 else
223
224 call source_term_factory(this%source_terms(i + i0)%source_term, &
225 source_subdict, this%rhs_fields, this%coef)
226 end if
227 end do
228 end if
229
231
234 subroutine source_term_handler_add_source_term(this, source_term)
235 class(source_term_handler_t), intent(inout) :: this
236 class(source_term_t), intent(in) :: source_term
237 class(source_term_wrapper_t), dimension(:), allocatable :: temp
238
239 integer :: n_sources, i
240
241 if (allocated(this%source_terms)) then
242 n_sources = size(this%source_terms)
243 else
244 n_sources = 0
245 end if
246
247 call move_alloc(this%source_terms, temp)
248 allocate(this%source_terms(n_sources + 1))
249
250 if (allocated(temp)) then
251 do i = 1, n_sources
252 call move_alloc(temp(i)%source_term, &
253 this%source_terms(i)%source_term)
254 end do
255 end if
256
257 this%source_terms(n_sources + 1)%source_term = source_term
258
260end 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)
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:728
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_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.
Definition user_intf.f90:34
Coefficients defined on a given (mesh, ) tuple. Arrays use indices (i,j,k,e): element e,...
Definition coef.f90:55
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.