Loading [MathJax]/jax/output/HTML-CSS/config.js
Neko 0.9.99
A portable framework for high-order spectral element flow simulations
All Classes Namespaces Files Functions Variables Typedefs Enumerator Macros Pages
source_term.f90
Go to the documentation of this file.
1! Copyright (c) 2023, The Neko Authors
2! All rights reserved.
3!
4! Redistribution and use in source and binary forms, with or without
5! modification, are permitted provided that the following conditions
6! are met:
7!
8! * Redistributions of source code must retain the above copyright
9! notice, this list of conditions and the following disclaimer.
10!
11! * Redistributions in binary form must reproduce the above
12! copyright notice, this list of conditions and the following
13! disclaimer in the documentation and/or other materials provided
14! with the distribution.
15!
16! * Neither the name of the authors nor the names of its
17! contributors may be used to endorse or promote products derived
18! from this software without specific prior written permission.
19!
20! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
21! "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
22! LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
23! FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
24! COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
25! INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
26! BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
27! LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
28! CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
29! LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
30! ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
31! POSSIBILITY OF SUCH DAMAGE.
32!
35 use num_types, only : rp
36 use coefs, only : coef_t
37 use field_list, only : field_list_t
38 use json_module, only : json_file
39 implicit none
40 private
41
43 type, abstract, public :: source_term_t
45 type(field_list_t) :: fields
47 type(coef_t), pointer :: coef => null()
49 real(kind=rp) :: start_time = 0.0_rp
51 real(kind=rp) :: end_time = huge(0.0_rp)
52 contains
54 procedure, pass(this) :: init_base => source_term_init_base
56 procedure, pass(this) :: free_base => source_term_free_base
58 procedure, pass(this) :: compute => source_term_compute_wrapper
60 procedure(source_term_init), pass(this), deferred :: init
62 procedure(source_term_free), pass(this), deferred :: free
64 procedure(source_term_compute), pass(this), deferred :: compute_
65 end type source_term_t
66
67
69 type, public :: source_term_wrapper_t
71 class(source_term_t), allocatable :: source_term
72 contains
74 procedure, pass(this) :: free => source_term_wrapper_free
76
77 abstract interface
78
82 subroutine source_term_init(this, json, fields, coef)
83 import source_term_t, json_file, field_list_t, coef_t
84 class(source_term_t), intent(inout) :: this
85 type(json_file), intent(inout) :: json
86 type(field_list_t), intent(in), target :: fields
87 type(coef_t), intent(in), target :: coef
88 end subroutine source_term_init
89 end interface
90
91 abstract interface
92
93 subroutine source_term_free(this)
94 import source_term_t
95 class(source_term_t), intent(inout) :: this
96 end subroutine source_term_free
97 end interface
98
99 abstract interface
100
103 subroutine source_term_compute(this, t, tstep)
104 import source_term_t, rp
105 class(source_term_t), intent(inout) :: this
106 real(kind=rp), intent(in) :: t
107 integer, intent(in) :: tstep
108 end subroutine source_term_compute
109 end interface
110
111 interface
112
117 module subroutine source_term_factory(object, json, fields, coef)
118 class(source_term_t), allocatable, intent(inout) :: object
119 type(json_file), intent(inout) :: json
120 type(field_list_t), intent(inout) :: fields
121 type(coef_t), intent(inout) :: coef
122 end subroutine source_term_factory
123 end interface
124
125 interface
126
129 module subroutine source_term_allocator(object, type_name)
130 class(source_term_t), allocatable, intent(inout) :: object
131 character(len=:), allocatable, intent(in) :: type_name
132 end subroutine source_term_allocator
133 end interface
134
135 !
136 ! Machinery for injecting user-defined types
137 !
138
142 abstract interface
143 subroutine source_term_allocate(obj)
144 import source_term_t
145 class(source_term_t), allocatable, intent(inout) :: obj
146 end subroutine source_term_allocate
147 end interface
148
149 interface
150
151 module subroutine register_source_term(type_name, allocator)
152 character(len=*), intent(in) :: type_name
153 procedure(source_term_allocate), pointer, intent(in) :: allocator
154 end subroutine register_source_term
155 end interface
156
157 ! A name-allocator pair for user-defined types. A helper type to define a
158 ! registry of custom allocators.
159 type allocator_entry
160 character(len=20) :: type_name
161 procedure(source_term_allocate), pointer, nopass :: allocator
162 end type allocator_entry
163
165 type(allocator_entry), allocatable :: source_term_registry(:)
166
168 integer :: source_term_registry_size = 0
169
170 public :: source_term_factory, source_term_allocator, register_source_term, &
171 source_term_allocate
172
173contains
174
181 subroutine source_term_init_base(this, fields, coef, start_time, end_time)
182 class(source_term_t), intent(inout) :: this
183 type(field_list_t) :: fields
184 type(coef_t), intent(in), target :: coef
185 real(kind=rp), intent(in) :: start_time
186 real(kind=rp), intent(in) :: end_time
187 integer :: n_fields, i
188
189 this%coef => coef
190 this%start_time = start_time
191 this%end_time = end_time
192 n_fields = fields%size()
193
194 call this%fields%init(n_fields)
195
196 ! A lot of attribute nesting here due to Fortran needing wrapper types
197 ! but this is just pointer assignement for the fields.
198 do i = 1, n_fields
199 call this%fields%assign(i, fields%get(i))
200 end do
201 end subroutine source_term_init_base
202
204 subroutine source_term_free_base(this)
205 class(source_term_t), intent(inout) :: this
206
207 call this%fields%free()
208 nullify(this%coef)
209 end subroutine source_term_free_base
210
212 subroutine source_term_wrapper_free(this)
213 class(source_term_wrapper_t), intent(inout) :: this
214 integer :: n_fields, i
215
216 if (allocated(this%source_term)) then
217 call this%source_term%free()
218 deallocate(this%source_term)
219 end if
220 end subroutine source_term_wrapper_free
221
225 subroutine source_term_compute_wrapper(this, t, tstep)
226 class(source_term_t), intent(inout) :: this
227 real(kind=rp), intent(in) :: t
228 integer, intent(in) :: tstep
229
230 if (t .ge. this%start_time .and. t .le. this%end_time) then
231 call this%compute_(t, tstep)
232 end if
233
234 end subroutine source_term_compute_wrapper
235end module source_term
Computes the source term and adds the result to fields.
The common constructor using a JSON object.
Coefficients.
Definition coef.f90:34
integer, parameter, public rp
Global precision used in computations.
Definition num_types.f90:12
Implements the source_term_t type and a wrapper source_term_wrapper_t.
subroutine source_term_wrapper_free(this)
Destructor for the source_term_wrapper_t type.
subroutine source_term_compute_wrapper(this, t, tstep)
Executes compute_ based on time conditions.
subroutine source_term_free_base(this)
Destructor for the source_term_t (base) type.
subroutine source_term_init_base(this, fields, coef, start_time, end_time)
Constructor for the source_term_t (base) type.
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.