Neko  0.8.1
A portable framework for high-order spectral element flow simulations
source_term.f90
Go to the documentation of this file.
1 ! Copyright (c) 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
36  use num_types, only : rp
37  use coefs, only : coef_t
38  use field_list, only : field_list_t
39  use json_module, only : json_file
40  implicit none
41  private
42 
44  type, abstract, public:: source_term_t
46  type(field_list_t) :: fields
48  type(coef_t), pointer :: coef => null()
50  real(kind=rp) :: start_time = 0.0_rp
52  real(kind=rp) :: end_time = huge(0.0_rp)
53  contains
55  procedure, pass(this) :: init_base => source_term_init_base
57  procedure, pass(this) :: free_base => source_term_free_base
59  procedure, pass(this) :: compute => source_term_compute_wrapper
61  procedure(source_term_init), pass(this), deferred :: init
63  procedure(source_term_free), pass(this), deferred :: free
65  procedure(source_term_compute), pass(this), deferred :: compute_
66  end type source_term_t
67 
68 
70  type, public :: source_term_wrapper_t
72  class(source_term_t), allocatable :: source_term
73  contains
75  procedure, pass(this) :: free => source_term_wrapper_free
76  end type source_term_wrapper_t
77 
78  abstract interface
79 
83  subroutine source_term_init(this, json, fields, coef)
84  import source_term_t, json_file, field_list_t, coef_t
85  class(source_term_t), intent(inout) :: this
86  type(json_file), intent(inout) :: json
87  type(field_list_t), intent(inout), target :: fields
88  type(coef_t), intent(inout) :: coef
89  end subroutine source_term_init
90  end interface
91 
92  abstract interface
93 
94  subroutine source_term_free(this)
95  import source_term_t
96  class(source_term_t), intent(inout) :: this
97  end subroutine source_term_free
98  end interface
99 
100  abstract interface
101 
104  subroutine source_term_compute(this, t, tstep)
105  import source_term_t, rp
106  class(source_term_t), intent(inout) :: this
107  real(kind=rp), intent(in) :: t
108  integer, intent(in) :: tstep
109  end subroutine source_term_compute
110  end interface
111 
112 contains
113 
120  subroutine source_term_init_base(this, fields, coef, start_time, end_time)
121  class(source_term_t), intent(inout) :: this
122  type(field_list_t) :: fields
123  type(coef_t), intent(inout), target :: coef
124  real(kind=rp), intent(in) :: start_time
125  real(kind=rp), intent(in) :: end_time
126  integer :: n_fields, i
127 
128  this%coef => coef
129  this%start_time = start_time
130  this%end_time = end_time
131  n_fields = size(fields%fields)
132  allocate(this%fields%fields(n_fields))
133 
134  ! A lot of attribute nesting here due to Fortran needing wrapper types
135  ! but this is just pointer assignement for the fields.
136  do i=1, n_fields
137  this%fields%fields(i)%f => fields%fields(i)%f
138  end do
139  end subroutine source_term_init_base
140 
142  subroutine source_term_free_base(this)
143  class(source_term_t), intent(inout) :: this
144 
145  call this%fields%free()
146  nullify(this%coef)
147  end subroutine source_term_free_base
148 
150  subroutine source_term_wrapper_free(this)
151  class(source_term_wrapper_t), intent(inout) :: this
152  integer :: n_fields, i
153 
154  if (allocated(this%source_term)) then
155  call this%source_term%free()
156  deallocate(this%source_term)
157  end if
158  end subroutine source_term_wrapper_free
159 
163  subroutine source_term_compute_wrapper(this, t, tstep)
164  class(source_term_t), intent(inout) :: this
165  real(kind=rp), intent(in) :: t
166  integer, intent(in) :: tstep
167 
168  if (t .ge. this%start_time .and. t .le. this%end_time) then
169  call this%compute_(t, tstep)
170  end if
171 
172  end subroutine source_term_compute_wrapper
173 end module source_term
Computes the source term and adds the result to fields.
The common constructor using a JSON object.
Definition: source_term.f90:83
Coefficients.
Definition: coef.f90:34
Build configurations.
Definition: neko_config.f90:34
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
subroutine source_term_wrapper_free(this)
Destructor for the source_term_wrapper_t type.
subroutine source_term_compute_wrapper(this, t, tstep)
Executes compute_ based on time conditions.
subroutine source_term_free_base(this)
Destructor for the source_term_t (base) type.
subroutine source_term_init_base(this, fields, coef, start_time, end_time)
Constructor for the source_term_t (base) type.
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
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