Neko  0.8.1
A portable framework for high-order spectral element flow simulations
fluid_source_term.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 !
36  use neko_config, only : neko_bcknd_device
37  use num_types, only : rp
41  use field, only : field_t
42  use field_list, only : field_list_t
43  use json_utils, only : json_get
44  use json_module, only : json_file, json_core, json_value
45  use coefs, only : coef_t
46  use user_intf, only : user_t
47  use utils, only : neko_warning
48  implicit none
49  private
50 
55  type, public :: fluid_source_term_t
57  class(source_term_wrapper_t), allocatable :: source_terms(:)
59  type(field_t), pointer :: f_x => null()
61  type(field_t), pointer :: f_y => null()
63  type(field_t), pointer :: f_z => null()
64  contains
66  procedure, pass(this) :: init => fluid_source_term_init
68  procedure, pass(this) :: free => fluid_source_term_free
70  procedure, pass(this) :: compute => fluid_source_term_compute
72  procedure, nopass, private :: init_user_source
73 
74  end type fluid_source_term_t
75 
76 contains
77 
79  subroutine fluid_source_term_init(this, json, f_x, f_y, f_z, coef, user)
80  class(fluid_source_term_t), intent(inout) :: this
81  type(json_file), intent(inout) :: json
82  type(field_t), pointer, intent(in) :: f_x, f_y, f_z
83  type(coef_t), intent(inout) :: coef
84  type(user_t), intent(in) :: user
85 
86  type(field_list_t) :: rhs_fields
87  ! Json low-level manipulator.
88  type(json_core) :: core
89  ! Pointer to the source_terms JSON object and the individual sources.
90  type(json_value), pointer :: source_object, source_pointer
91  ! Buffer for serializing the json.
92  character(len=:), allocatable :: buffer
93  ! A single source term as its own json_file.
94  type(json_file) :: source_subdict
95  ! Source type
96  character(len=:), allocatable :: type
97  ! Dummy source strenth values
98  real(kind=rp) :: values(3)
99  logical :: found
100  integer :: n_sources, i
101 
102  call this%free()
103 
104  this%f_x => f_x
105  this%f_y => f_y
106  this%f_z => f_z
107 
108 
109  if (json%valid_path('case.fluid.source_terms')) then
110  ! We package the fields for the source term to operate on in a field list.
111  allocate(rhs_fields%fields(3))
112  rhs_fields%fields(1)%f => f_x
113  rhs_fields%fields(2)%f => f_y
114  rhs_fields%fields(3)%f => f_z
115 
116  call json%get_core(core)
117  call json%get('case.fluid.source_terms', source_object, found)
118 
119  n_sources = core%count(source_object)
120  allocate(this%source_terms(n_sources))
121 
122 
123  do i=1, n_sources
124  ! Create a new json containing just the subdict for this source.
125  call core%get_child(source_object, i, source_pointer, found)
126  call core%print_to_string(source_pointer, buffer)
127  call source_subdict%load_from_string(buffer)
128  call json_get(source_subdict, "type", type)
129 
130  ! The user source is treated separately
131  if ((trim(type) .eq. "user_vector") .or. &
132  (trim(type) .eq. "user_pointwise")) then
133 
134  if (source_subdict%valid_path("start_time") .or. &
135  source_subdict%valid_path("end_time")) then
136  call neko_warning("The start_time and end_time parameters have&
137  & no effect on the fluid user source term")
138  end if
139 
140  call init_user_source(this%source_terms(i)%source_term, &
141  rhs_fields, coef, type, user)
142  else
143 
144  call source_term_factory(this%source_terms(i)%source_term, &
145  source_subdict, rhs_fields, coef)
146  end if
147  end do
148  end if
149 
150  end subroutine fluid_source_term_init
151 
159  subroutine init_user_source(source_term, rhs_fields, coef, type, user)
160  class(source_term_t), allocatable, intent(inout) :: source_term
161  type(field_list_t) :: rhs_fields
162  type(coef_t), intent(inout) :: coef
163  character(len=*) :: type
164  type(user_t), intent(in) :: user
165 
167 
168  select type (source_term)
169  type is (fluid_user_source_term_t)
170  call source_term%init_from_components(rhs_fields, coef, type, &
171  user%fluid_user_f_vector, &
172  user%fluid_user_f)
173  end select
174  end subroutine init_user_source
175 
177  subroutine fluid_source_term_free(this)
178  class(fluid_source_term_t), intent(inout) :: this
179  integer :: i
180 
181  nullify(this%f_x)
182  nullify(this%f_y)
183  nullify(this%f_z)
184 
185  if (allocated(this%source_terms)) then
186  do i=1, size(this%source_terms)
187  call this%source_terms(i)%free()
188  end do
189  deallocate(this%source_terms)
190  end if
191 
192  end subroutine fluid_source_term_free
193 
197  subroutine fluid_source_term_compute(this, t, tstep)
198  class(fluid_source_term_t), intent(inout) :: this
199  real(kind=rp), intent(in) :: t
200  integer, intent(in) :: tstep
201  integer :: i, n
202 
203  this%f_x = 0.0_rp
204  this%f_y = 0.0_rp
205  this%f_z = 0.0_rp
206 
207  ! Add contribution from all source terms.
208  if (allocated(this%source_terms)) then
209  do i=1, size(this%source_terms)
210  call this%source_terms(i)%source_term%compute(t, tstep)
211  end do
212  end if
213 
214  end subroutine fluid_source_term_compute
215 end module fluid_source_term
Retrieves a parameter by name or throws an error.
Definition: json_utils.f90:44
Coefficients.
Definition: coef.f90:34
Defines a field.
Definition: field.f90:34
Implements the fluid_source_term_t type.
subroutine init_user_source(source_term, rhs_fields, coef, type, user)
Initialize the user source term.
subroutine fluid_source_term_init(this, json, f_x, f_y, f_z, coef, user)
Costructor.
subroutine fluid_source_term_compute(this, t, tstep)
Add all the source term to the passed right-hand side fields.
subroutine fluid_source_term_free(this)
Destructor.
Implements the fluid_user_source_term_t type.
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
Defines a factory subroutine for source terms.
subroutine, public source_term_factory(source_term, json, fields, coef)
Source term factory. Both constructs and initializes the object.
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 neko_warning(warning_msg)
Definition: utils.f90:191
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
Wrapper contaning and executing the fluid source terms.
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
A helper type that is needed to have an array of polymorphic objects.
Definition: source_term.f90:70