Neko 0.9.99
A portable framework for high-order spectral element flow simulations
Loading...
Searching...
No Matches
scalar_user_source_term.f90
Go to the documentation of this file.
1! Copyright (c) 2024, 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!
36 use num_types, only : rp
37 use utils, only : neko_error
38 use source_term, only : source_term_t
39 use json_module, only : json_file
40 use field_list, only : field_list_t
41 use coefs, only : coef_t
42 use device, only : device_map, device_free
43 use device_math, only : device_add2
44 use math, only : add2
45 use dofmap, only : dofmap_t
46 use, intrinsic :: iso_c_binding
47 implicit none
48 private
49
51
60 type, public, extends(source_term_t) :: scalar_user_source_term_t
62 type(dofmap_t), pointer :: dm
64 real(kind=rp), allocatable :: s(:, :, :, :)
65
67 type(c_ptr) :: s_d = c_null_ptr
69 procedure(scalar_source_compute_pointwise), nopass, pointer :: &
70 compute_pw_ => null()
72 procedure(scalar_source_compute_vector), nopass, pointer :: &
73 compute_vector_ => null()
74 contains
76 procedure, pass(this) :: init => scalar_user_source_term_init
78 procedure, pass(this) :: init_from_components => &
81 procedure, pass(this) :: free => scalar_user_source_term_free
83 procedure, pass(this) :: compute_ => scalar_user_source_term_compute
85
86 abstract interface
87
90 subroutine scalar_source_compute_vector(this, t)
92 class(scalar_user_source_term_t), intent(inout) :: this
93 real(kind=rp), intent(in) :: t
94 end subroutine scalar_source_compute_vector
95 end interface
96
97 abstract interface
98
105 subroutine scalar_source_compute_pointwise(s, j, k, l, e, t)
106 import rp
107 real(kind=rp), intent(inout) :: s
108 integer, intent(in) :: j
109 integer, intent(in) :: k
110 integer, intent(in) :: l
111 integer, intent(in) :: e
112 real(kind=rp), intent(in) :: t
114 end interface
115
116contains
117
122 subroutine scalar_user_source_term_init(this, json, fields, coef)
123 class(scalar_user_source_term_t), intent(inout) :: this
124 type(json_file), intent(inout) :: json
125 type(field_list_t), intent(in), target :: fields
126 type(coef_t), intent(in), target :: coef
127
128 call neko_error("The user scalar source term &
129 &should be init from components")
130
131 end subroutine scalar_user_source_term_init
132
140 subroutine scalar_user_source_term_init_from_components(this, fields, coef, &
141 source_term_type, eval_vector, eval_pointwise)
142 class(scalar_user_source_term_t), intent(inout) :: this
143 type(field_list_t), intent(in), target :: fields
144 type(coef_t), intent(in) :: coef
145 character(len=*) :: source_term_type
146 procedure(scalar_source_compute_vector), optional :: eval_vector
147 procedure(scalar_source_compute_pointwise), optional :: eval_pointwise
148
149 call this%free()
150 call this%init_base(fields, coef, 0.0_rp, huge(0.0_rp))
151
152 this%dm => fields%dof(1)
153
154 allocate(this%s(this%dm%Xh%lx, this%dm%Xh%ly, this%dm%Xh%lz, &
155 this%dm%msh%nelv))
156
157 this%s = 0d0
158
159 if (neko_bcknd_device .eq. 1) then
160 call device_map(this%s, this%s_d, this%dm%size())
161 end if
162
163
164 if (trim(source_term_type) .eq. 'user_pointwise' .and. &
165 present(eval_pointwise)) then
166 if (neko_bcknd_device .eq. 1) then
167 call neko_error('Pointwise source terms not &
168 &supported on accelerators')
169 end if
170 this%compute_vector_ => pointwise_eval_driver
171 this%compute_pw_ => eval_pointwise
172 else if (trim(source_term_type) .eq. 'user_vector' .and. &
173 present(eval_vector)) then
174 this%compute_vector_ => eval_vector
175 else
176 call neko_error('Invalid fluid source term '//source_term_type)
177 end if
179
182 class(scalar_user_source_term_t), intent(inout) :: this
183
184 if (allocated(this%s)) deallocate(this%s)
185
186 if (c_associated(this%s_d)) call device_free(this%s_d)
187
188 nullify(this%compute_vector_)
189 nullify(this%compute_pw_)
190 nullify(this%dm)
191
192 call this%free_base()
193 end subroutine scalar_user_source_term_free
194
198 subroutine scalar_user_source_term_compute(this, t, tstep)
199 class(scalar_user_source_term_t), intent(inout) :: this
200 real(kind=rp), intent(in) :: t
201 integer, intent(in) :: tstep
202 integer :: n
203
204 if (t .ge. this%start_time .and. t .le. this%end_time) then
205 call this%compute_vector_(this, t)
206 n = this%fields%item_size(1)
207
208 if (neko_bcknd_device .eq. 1) then
209 call device_add2(this%fields%x_d(1), this%s_d, n)
210 else
211 call add2(this%fields%items(1)%ptr%x, this%s, n)
212 end if
213 end if
215
218 subroutine pointwise_eval_driver(this, t)
219 class(scalar_user_source_term_t), intent(inout) :: this
220 real(kind=rp), intent(in) :: t
221 integer :: j, k, l, e
222 integer :: jj, kk, ll, ee
223
224 select type (this)
226 do e = 1, size(this%s, 4)
227 ee = e
228 do l = 1, size(this%s, 3)
229 ll = l
230 do k = 1, size(this%s, 2)
231 kk = k
232 do j = 1, size(this%s, 1)
233 jj = j
234 call this%compute_pw_(this%s(j,k,l,e), jj, kk, ll, ee, t)
235 end do
236 end do
237 end do
238 end do
239 class default
240 call neko_error('Incorrect source type in pointwise eval driver!')
241 end select
242
243 end subroutine pointwise_eval_driver
244
Map a Fortran array to a device (allocate and associate)
Definition device.F90:57
Computes the source term and adds the result to fields.
Coefficients.
Definition coef.f90:34
subroutine, public device_add2(a_d, b_d, n)
Vector addition .
Device abstraction, common interface for various accelerators.
Definition device.F90:34
subroutine, public device_free(x_d)
Deallocate memory on the device.
Definition device.F90:185
Defines a mapping of the degrees of freedom.
Definition dofmap.f90:35
Definition math.f90:60
subroutine, public add2(a, b, n)
Vector addition .
Definition math.f90:586
Build configurations.
integer, parameter neko_bcknd_device
integer, parameter, public rp
Global precision used in computations.
Definition num_types.f90:12
Implements the scalar_user_source_term_t type.
subroutine pointwise_eval_driver(this, t)
Driver for all pointwise source term evaluatons.
subroutine scalar_user_source_term_init_from_components(this, fields, coef, source_term_type, eval_vector, eval_pointwise)
Constructor from components.
subroutine scalar_user_source_term_free(this)
Destructor.
subroutine scalar_user_source_term_init(this, json, fields, coef)
Constructor from JSON.
subroutine scalar_user_source_term_compute(this, t, tstep)
Computes the source term and adds the result to fields.
Implements the source_term_t type and a wrapper source_term_wrapper_t.
Utilities.
Definition utils.f90:35
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
A source-term for the scalar, with procedure pointers pointing to the actual implementation in the us...
Base abstract type for source terms.