Neko  0.8.1
A portable framework for high-order spectral element flow simulations
fluid_user_source_term.f90
Go to the documentation of this file.
1 ! Copyright (c) 2020-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 neko_config, only : neko_bcknd_device
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) :: fluid_user_source_term_t
62  type(dofmap_t), pointer :: dm
64  real(kind=rp), allocatable :: u(:, :, :, :)
66  real(kind=rp), allocatable :: v(:, :, :, :)
68  real(kind=rp), allocatable :: w(:, :, :, :)
69 
71  type(c_ptr) :: u_d = c_null_ptr
73  type(c_ptr) :: v_d = c_null_ptr
75  type(c_ptr) :: w_d = c_null_ptr
77  procedure(fluid_source_compute_pointwise), nopass, pointer :: compute_pw_ &
78  => null()
80  procedure(fluid_source_compute_vector), nopass, pointer :: compute_vector_&
81  => null()
82  contains
84  procedure, pass(this) :: init => fluid_user_source_term_init
86  procedure, pass(this) :: init_from_components => &
89  procedure, pass(this) :: free => fluid_user_source_term_free
91  procedure, pass(this) :: compute_ => fluid_user_source_term_compute
93 
94  abstract interface
95 
98  subroutine fluid_source_compute_vector(this, t)
100  class(fluid_user_source_term_t), intent(inout) :: this
101  real(kind=rp), intent(in) :: t
102  end subroutine fluid_source_compute_vector
103  end interface
104 
105  abstract interface
106 
115  subroutine fluid_source_compute_pointwise(u, v, w, j, k, l, e, t)
116  import rp
117  real(kind=rp), intent(inout) :: u
118  real(kind=rp), intent(inout) :: v
119  real(kind=rp), intent(inout) :: w
120  integer, intent(in) :: j
121  integer, intent(in) :: k
122  integer, intent(in) :: l
123  integer, intent(in) :: e
124  real(kind=rp), intent(in) :: t
125  end subroutine fluid_source_compute_pointwise
126  end interface
127 
128 contains
129 
134  subroutine fluid_user_source_term_init(this, json, fields, coef)
135  class(fluid_user_source_term_t), intent(inout) :: this
136  type(json_file), intent(inout) :: json
137  type(field_list_t), intent(inout), target :: fields
138  type(coef_t), intent(inout) :: coef
139 
140  call neko_error("The user fluid source term should be init from components")
141 
142  end subroutine fluid_user_source_term_init
143 
151  subroutine fluid_user_source_term_init_from_components(this, fields, coef, &
152  source_term_type, eval_vector, eval_pointwise)
153  class(fluid_user_source_term_t), intent(inout) :: this
154  type(field_list_t), intent(inout), target :: fields
155  type(coef_t), intent(inout) :: coef
156  character(len=*) :: source_term_type
157  procedure(fluid_source_compute_vector), optional :: eval_vector
158  procedure(fluid_source_compute_pointwise), optional :: eval_pointwise
159 
160  call this%free()
161  call this%init_base(fields, coef, 0.0_rp, huge(0.0_rp))
162 
163  this%dm => fields%fields(1)%f%dof
164 
165  allocate(this%u(this%dm%Xh%lx, this%dm%Xh%ly, this%dm%Xh%lz, &
166  this%dm%msh%nelv))
167  allocate(this%v(this%dm%Xh%lx, this%dm%Xh%ly, this%dm%Xh%lz, &
168  this%dm%msh%nelv))
169  allocate(this%w(this%dm%Xh%lx, this%dm%Xh%ly, this%dm%Xh%lz, &
170  this%dm%msh%nelv))
171 
172  this%u = 0d0
173  this%v = 0d0
174  this%w = 0d0
175 
176  if (neko_bcknd_device .eq. 1) then
177  call device_map(this%u, this%u_d, this%dm%size())
178  call device_map(this%v, this%v_d, this%dm%size())
179  call device_map(this%w, this%w_d, this%dm%size())
180  end if
181 
182 
183  if (trim(source_term_type) .eq. 'user_pointwise' .and. &
184  present(eval_pointwise)) then
185  if (neko_bcknd_device .eq. 1) then
186  call neko_error('Pointwise source terms not supported on accelerators')
187  end if
188  this%compute_vector_ => pointwise_eval_driver
189  this%compute_pw_ => eval_pointwise
190  else if (trim(source_term_type) .eq. 'user_vector' .and. &
191  present(eval_vector)) then
192  this%compute_vector_ => eval_vector
193  else
194  call neko_error('Invalid fluid source term '//source_term_type)
195  end if
197 
200  class(fluid_user_source_term_t), intent(inout) :: this
201 
202  if (allocated(this%u)) deallocate(this%u)
203  if (allocated(this%v)) deallocate(this%v)
204  if (allocated(this%w)) deallocate(this%w)
205 
206  if (c_associated(this%u_d)) call device_free(this%u_d)
207  if (c_associated(this%v_d)) call device_free(this%v_d)
208  if (c_associated(this%w_d)) call device_free(this%w_d)
209 
210  nullify(this%compute_vector_)
211  nullify(this%compute_pw_)
212  nullify(this%dm)
213 
214  call this%free_base()
215  end subroutine fluid_user_source_term_free
216 
220  subroutine fluid_user_source_term_compute(this, t, tstep)
221  class(fluid_user_source_term_t), intent(inout) :: this
222  real(kind=rp), intent(in) :: t
223  integer, intent(in) :: tstep
224  integer :: n
225 
226  call this%compute_vector_(this, t)
227  n = this%fields%fields(1)%f%dof%size()
228 
229  if (neko_bcknd_device .eq. 1) then
230  call device_add2(this%fields%fields(1)%f%x_d, this%u_d, n)
231  call device_add2(this%fields%fields(2)%f%x_d, this%v_d, n)
232  call device_add2(this%fields%fields(3)%f%x_d, this%w_d, n)
233  else
234  call add2(this%fields%fields(1)%f%x, this%u, n)
235  call add2(this%fields%fields(2)%f%x, this%v, n)
236  call add2(this%fields%fields(3)%f%x, this%w, n)
237  end if
238 
239  end subroutine fluid_user_source_term_compute
240 
243  subroutine pointwise_eval_driver(this, t)
244  class(fluid_user_source_term_t), intent(inout) :: this
245  real(kind=rp), intent(in) :: t
246  integer :: j, k, l, e
247  integer :: jj, kk, ll, ee
248 
249  select type (this)
250  type is (fluid_user_source_term_t)
251  do e = 1, size(this%u, 4)
252  ee = e
253  do l = 1, size(this%u, 3)
254  ll = l
255  do k = 1, size(this%u, 2)
256  kk = k
257  do j = 1, size(this%u, 1)
258  jj =j
259  call this%compute_pw_(this%u(j,k,l,e), &
260  this%v(j,k,l,e), &
261  this%w(j,k,l,e), &
262  jj, kk, ll, ee, t)
263  end do
264  end do
265  end do
266  end do
267  class default
268  call neko_error('Incorrect source type in pointwise eval driver!')
269  end select
270 
271  end subroutine pointwise_eval_driver
272 
273 end module fluid_user_source_term
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)
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:172
Defines a mapping of the degrees of freedom.
Definition: dofmap.f90:35
Implements the fluid_user_source_term_t type.
subroutine pointwise_eval_driver(this, t)
Driver for all pointwise source term evaluatons.
subroutine fluid_user_source_term_compute(this, t, tstep)
Computes the source term and adds the result to fields.
subroutine fluid_user_source_term_init(this, json, fields, coef)
Costructor from JSON.
subroutine fluid_user_source_term_init_from_components(this, fields, coef, source_term_type, eval_vector, eval_pointwise)
Costructor from components.
subroutine fluid_user_source_term_free(this)
Destructor.
Definition: math.f90:60
subroutine, public add2(a, b, n)
Vector addition .
Definition: math.f90:503
Build configurations.
Definition: neko_config.f90:34
integer, parameter neko_bcknd_device
Definition: neko_config.f90:44
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.
Definition: source_term.f90:34
Utilities.
Definition: utils.f90:35
Coefficients defined on a given (mesh, ) tuple. Arrays use indices (i,j,k,e): element e,...
Definition: coef.f90:54
field_list_t, To be able to group fields together
Definition: field_list.f90:7
A source-term for the fluid, with procedure pointers pointing to the actual implementation in the use...
Base abstract type for source terms.
Definition: source_term.f90:44