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  implicit none
49  private
50 
61  type, abstract, public :: source_term_handler_t
63  class(source_term_wrapper_t), allocatable :: source_terms(:)
65  type(field_list_t) :: rhs_fields
67  type(coef_t), pointer :: coef
69  type(user_t), pointer :: user
70 
71  contains
73  procedure, pass(this) :: init_base => source_term_handler_init_base
75  procedure, pass(this) :: free => source_term_handler_free
77  procedure, pass(this) :: compute => source_term_handler_compute
79  generic :: add => add_source_term, add_json_source_terms
81  procedure, pass(this) :: add_source_term => &
84  procedure, pass(this) :: add_json_source_terms => &
88  nopass, deferred :: init_user_source
89  end type source_term_handler_t
90 
91  abstract interface
92  subroutine source_term_handler_init_user_source(source_term, rhs_fields, &
93  coef, type, user)
95  class(source_term_t), allocatable, intent(inout) :: source_term
96  type(field_list_t) :: rhs_fields
97  type(coef_t), intent(inout) :: coef
98  character(len=*) :: type
99  type(user_t), intent(in) :: user
101  end interface
102 
103 contains
104 
106  subroutine source_term_handler_init_base(this, rhs_fields, coef, user)
107  class(source_term_handler_t), intent(inout) :: this
108  type(field_list_t), intent(in) :: rhs_fields
109  type(coef_t), target, intent(inout) :: coef
110  type(user_t), target, intent(in) :: user
111 
112  call this%free()
113 
114  ! We package the fields for the source term to operate on in a field list.
115  this%rhs_fields = rhs_fields
116  this%coef => coef
117  this%user => user
118 
119  end subroutine source_term_handler_init_base
120 
121 
123  subroutine source_term_handler_free(this)
124  class(source_term_handler_t), intent(inout) :: this
125  integer :: i
126 
127  call this%rhs_fields%free()
128 
129  if (allocated(this%source_terms)) then
130  do i = 1, size(this%source_terms)
131  call this%source_terms(i)%free()
132  end do
133  deallocate(this%source_terms)
134  end if
135 
136  end subroutine source_term_handler_free
137 
141  subroutine source_term_handler_compute(this, t, tstep)
142  class(source_term_handler_t), intent(inout) :: this
143  real(kind=rp), intent(in) :: t
144  integer, intent(in) :: tstep
145  integer :: i
146  type(field_t), pointer :: f
147 
148  do i = 1, this%rhs_fields%size()
149  f => this%rhs_fields%get(i)
150  call field_rzero(f)
151  end do
152 
153  ! Add contribution from all source terms. If time permits.
154  if (allocated(this%source_terms)) then
155  do i = 1, size(this%source_terms)
156  call this%source_terms(i)%source_term%compute(t, tstep)
157  end do
158  end if
159 
160  end subroutine source_term_handler_compute
161 
163  subroutine source_term_handler_add_json_source_terms(this, json, name)
164  class(source_term_handler_t), intent(inout) :: this
165  type(json_file), intent(inout) :: json
166  character(len=*), intent(in) :: name
167 
168  class(source_term_wrapper_t), dimension(:), allocatable :: temp
169 
170  ! A single source term as its own json_file.
171  type(json_file) :: source_subdict
172  character(len=:), allocatable :: type
173  integer :: n_sources, i, i0
174 
175  if (json%valid_path(name)) then
176  ! Get the number of source terms.
177  call json%info(name, n_children=n_sources)
178 
179  if (allocated(this%source_terms)) then
180  i0 = size(this%source_terms)
181  call move_alloc(this%source_terms, temp)
182  allocate(this%source_terms(i0 + n_sources))
183  if (allocated(temp)) then
184  do i = 1, i0
185  call move_alloc(temp(i)%source_term, this%source_terms(i)%source_term)
186  end do
187  end if
188  else
189  i0 = 0
190  allocate(this%source_terms(n_sources))
191  end if
192 
193  do i = 1, n_sources
194  ! Create a new json containing just the subdict for this source.
195  call json_extract_item(json, name, i, source_subdict)
196  call json_get(source_subdict, "type", type)
197 
198  ! The user source is treated separately
199  if ((trim(type) .eq. "user_vector") .or. &
200  (trim(type) .eq. "user_pointwise")) then
201 
202  call this%init_user_source(this%source_terms(i+ i0)%source_term, &
203  this%rhs_fields, this%coef, type, this%user)
204 
205  call json_get_or_default(source_subdict, "start_time", &
206  this%source_terms(i + i0)%source_term%start_time, 0.0_rp)
207  call json_get_or_default(source_subdict, "end_time", &
208  this%source_terms(i + i0)%source_term%end_time, huge(0.0_rp))
209  else
210 
211  call source_term_factory(this%source_terms(i + i0)%source_term, &
212  source_subdict, this%rhs_fields, this%coef)
213  end if
214  end do
215  end if
216 
218 
221  subroutine source_term_handler_add_source_term(this, source_term)
222  class(source_term_handler_t), intent(inout) :: this
223  class(source_term_t), intent(in) :: source_term
224  class(source_term_wrapper_t), dimension(:), allocatable :: temp
225 
226  integer :: n_sources, i
227 
228  n_sources = size(this%source_terms)
229  call move_alloc(this%source_terms, temp)
230  allocate(this%source_terms(n_sources + 1))
231 
232  if (allocated(temp)) then
233  do i = 1, n_sources
234  call move_alloc(temp(i)%source_term, this%source_terms(i)%source_term)
235  end do
236  end if
237 
238  this%source_terms(n_sources + 1)%source_term = source_term
239 
241 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:53
Retrieves a parameter by name or throws an error.
Definition: json_utils.f90:44
Coefficients.
Definition: coef.f90:34
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
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)
Definition: utils.f90:198
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.