Neko  0.8.99
A portable framework for high-order spectral element flow simulations
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 utils, only: neko_warning
47  use field_math, only: field_rzero
48  use math, only : col2
49  use device_math, only : device_col2
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
72 
73  contains
75  procedure, pass(this) :: init_base => source_term_handler_init_base
77  procedure, pass(this) :: free => source_term_handler_free
79  procedure, pass(this) :: compute => source_term_handler_compute
81  generic :: add => add_source_term, add_json_source_terms
83  procedure, pass(this) :: add_source_term => &
86  procedure, pass(this) :: add_json_source_terms => &
90  nopass, deferred :: init_user_source
91  end type source_term_handler_t
92 
93  abstract interface
94  subroutine source_term_handler_init_user_source(source_term, rhs_fields, &
95  coef, type, user)
97  class(source_term_t), allocatable, intent(inout) :: source_term
98  type(field_list_t) :: rhs_fields
99  type(coef_t), intent(inout) :: coef
100  character(len=*) :: type
101  type(user_t), intent(in) :: user
103  end interface
104 
105 contains
106 
108  subroutine source_term_handler_init_base(this, rhs_fields, coef, user)
109  class(source_term_handler_t), intent(inout) :: this
110  type(field_list_t), intent(in) :: rhs_fields
111  type(coef_t), target, intent(inout) :: coef
112  type(user_t), target, intent(in) :: user
113 
114  call this%free()
115 
116  ! We package the fields for the source term to operate on in a field list.
117  this%rhs_fields = rhs_fields
118  this%coef => coef
119  this%user => user
120 
121  end subroutine source_term_handler_init_base
122 
123 
125  subroutine source_term_handler_free(this)
126  class(source_term_handler_t), intent(inout) :: this
127  integer :: i
128 
129  call this%rhs_fields%free()
130 
131  if (allocated(this%source_terms)) then
132  do i = 1, size(this%source_terms)
133  call this%source_terms(i)%free()
134  end do
135  deallocate(this%source_terms)
136  end if
137 
138  end subroutine source_term_handler_free
139 
143  subroutine source_term_handler_compute(this, t, tstep)
144  class(source_term_handler_t), intent(inout) :: this
145  real(kind=rp), intent(in) :: t
146  integer, intent(in) :: tstep
147  integer :: i
148  type(field_t), pointer :: f
149 
150  do i = 1, this%rhs_fields%size()
151  f => this%rhs_fields%get(i)
152  call field_rzero(f)
153  end do
154 
155  ! Add contribution from all source terms. If time permits.
156  if (allocated(this%source_terms)) then
157 
158  do i = 1, size(this%source_terms)
159  call this%source_terms(i)%source_term%compute(t, tstep)
160  end do
161 
162  ! Multiply by mass matrix
163  do i = 1, this%rhs_fields%size()
164  f => this%rhs_fields%get(i)
165  if (neko_bcknd_device .eq. 1) then
166  call device_col2(f%x_d, this%coef%B_d, f%size())
167  else
168  call col2(f%x, this%coef%B, f%size())
169  end if
170  end do
171 
172  end if
173 
174  end subroutine source_term_handler_compute
175 
177  subroutine source_term_handler_add_json_source_terms(this, json, name)
178  class(source_term_handler_t), intent(inout) :: this
179  type(json_file), intent(inout) :: json
180  character(len=*), intent(in) :: name
181 
182  class(source_term_wrapper_t), dimension(:), allocatable :: temp
183 
184  ! A single source term as its own json_file.
185  type(json_file) :: source_subdict
186  character(len=:), allocatable :: type
187  integer :: n_sources, i, i0
188 
189  if (json%valid_path(name)) then
190  ! Get the number of source terms.
191  call json%info(name, n_children = n_sources)
192 
193  if (allocated(this%source_terms)) then
194  i0 = size(this%source_terms)
195  call move_alloc(this%source_terms, temp)
196  allocate(this%source_terms(i0 + n_sources))
197  if (allocated(temp)) then
198  do i = 1, i0
199  call move_alloc(temp(i)%source_term, this%source_terms(i)%source_term)
200  end do
201  end if
202  else
203  i0 = 0
204  allocate(this%source_terms(n_sources))
205  end if
206 
207  do i = 1, n_sources
208  ! Create a new json containing just the subdict for this source.
209  call json_extract_item(json, name, i, source_subdict)
210  call json_get(source_subdict, "type", type)
211 
212  ! The user source is treated separately
213  if ((trim(type) .eq. "user_vector") .or. &
214  (trim(type) .eq. "user_pointwise")) then
215 
216  call this%init_user_source(this%source_terms(i+ i0)%source_term, &
217  this%rhs_fields, this%coef, type, this%user)
218 
219  call json_get_or_default(source_subdict, "start_time", &
220  this%source_terms(i + i0)%source_term%start_time, 0.0_rp)
221  call json_get_or_default(source_subdict, "end_time", &
222  this%source_terms(i + i0)%source_term%end_time, huge(0.0_rp))
223  else
224 
225  call source_term_factory(this%source_terms(i + i0)%source_term, &
226  source_subdict, this%rhs_fields, this%coef)
227  end if
228  end do
229  end if
230 
232 
235  subroutine source_term_handler_add_source_term(this, source_term)
236  class(source_term_handler_t), intent(inout) :: this
237  class(source_term_t), intent(in) :: source_term
238  class(source_term_wrapper_t), dimension(:), allocatable :: temp
239 
240  integer :: n_sources, i
241 
242  if (allocated(this%source_terms)) then
243  n_sources = size(this%source_terms)
244  else
245  n_sources = 0
246  end if
247 
248  call move_alloc(this%source_terms, temp)
249  allocate(this%source_terms(n_sources + 1))
250 
251  if (allocated(temp)) then
252  do i = 1, n_sources
253  call move_alloc(temp(i)%source_term, &
254  this%source_terms(i)%source_term)
255  end do
256  end if
257 
258  this%source_terms(n_sources + 1)%source_term = source_term
259 
261 end module source_term_handler
Retrieves a parameter by name or assigns a provided default value. In the latter case also adds the m...
Definition: json_utils.f90:54
Retrieves a parameter by name or throws an error.
Definition: json_utils.f90:45
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.
Definition: field_math.f90:88
Defines a field.
Definition: field.f90:34
Utilities for retrieving parameters from the case files.
Definition: json_utils.f90:34
Definition: math.f90:60
subroutine, public col2(a, b, n)
Vector multiplication .
Definition: math.f90:729
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_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.
Definition: source_term.f90:34
Interfaces for user interaction with NEKO.
Definition: user_intf.f90:34
Utilities.
Definition: utils.f90:35
subroutine, public neko_warning(warning_msg)
Reports a warning to standard output.
Definition: utils.f90:245
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
Definition: field_list.f90:13
Base abstract type for source terms.
Definition: source_term.f90:43
A helper type that is needed to have an array of polymorphic objects.
Definition: source_term.f90:69
Abstract class for handling source terms.