Neko 0.9.99
A portable framework for high-order spectral element flow simulations
Loading...
Searching...
No Matches
fluid_stats_simcomp.f90
Go to the documentation of this file.
1! Copyright (c) 2024, 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!
33!
36 use num_types, only : rp, dp, sp
37 use json_module, only : json_file
40 use field, only : field_t
41 use fluid_stats, only: fluid_stats_t
43 use case, only : case_t
44 use coefs, only : coef_t
45 use comm
46 use logger, only : log_size, neko_log
48 implicit none
49 private
50
65 type(fluid_stats_output_t) :: stats_output
67 real(kind=rp) :: start_time
68 real(kind=rp) :: time
69 contains
71 procedure, pass(this) :: init => fluid_stats_simcomp_init_from_json
73 procedure, pass(this) :: init_from_attributes => &
76 procedure, pass(this) :: free => fluid_stats_simcomp_free
78 procedure, pass(this) :: compute_ => fluid_stats_simcomp_compute
80 procedure, pass(this) :: output_ => fluid_stats_simcomp_compute
82 procedure, pass(this) :: restart_ => fluid_stats_simcomp_restart
84
85contains
86
90 subroutine fluid_stats_simcomp_init_from_json(this, json, case)
91 class(fluid_stats_simcomp_t), intent(inout) :: this
92 type(json_file), intent(inout) :: json
93 class(case_t), intent(inout), target :: case
94 character(len=:), allocatable :: filename
95 character(len=:), allocatable :: precision
96 character(len=20), allocatable :: fields(:)
97 character(len=:), allocatable :: hom_dir
98 character(len=:), allocatable :: stat_set
99 real(kind=rp) :: start_time
100 type(field_t), pointer :: u, v, w, p
101 type(coef_t), pointer :: coef
102
103 call this%init_base(json, case)
104 call json_get_or_default(json, 'avg_direction', &
105 hom_dir, 'none')
106 call json_get_or_default(json, 'start_time', &
107 start_time, 0.0_rp)
108 call json_get_or_default(json, 'set_of_stats', &
109 stat_set, 'full')
110
111 u => neko_field_registry%get_field("u")
112 v => neko_field_registry%get_field("v")
113 w => neko_field_registry%get_field("w")
114 p => neko_field_registry%get_field("p")
115 coef => case%fluid%c_Xh
116 call fluid_stats_simcomp_init_from_attributes(this, u, v, w, p, coef, &
117 start_time, hom_dir, stat_set)
118
120
129 subroutine fluid_stats_simcomp_init_from_attributes(this, u, v, w, p, coef, &
130 start_time, hom_dir, stat_set)
131 class(fluid_stats_simcomp_t), intent(inout) :: this
132 character(len=*), intent(in) :: hom_dir
133 character(len=*), intent(in) :: stat_set
134 real(kind=rp), intent(in) :: start_time
135 type(field_t), intent(inout) :: u, v, w, p
136 type(coef_t), intent(in) :: coef
137 character(len=LOG_SIZE) :: log_buf
138
139 call neko_log%section('Fluid stats')
140 write(log_buf, '(A,E15.7)') 'Start time: ', start_time
141 call neko_log%message(log_buf)
142 write(log_buf, '(A,A)') 'Set of statistics: ', trim(stat_set)
143 call neko_log%message(log_buf)
144 write(log_buf, '(A,A)') 'Averaging in direction: ', trim(hom_dir)
145 call neko_log%message(log_buf)
146
147
148 call this%stats%init(coef, u, v, w, p, stat_set)
149
150 this%start_time = start_time
151 this%time = start_time
152
153 call this%stats_output%init(this%stats, this%start_time, &
154 hom_dir = hom_dir, path = this%case%output_directory)
155
156 call this%case%output_controller%add(this%stats_output, &
157 this%output_controller%control_value, &
158 this%output_controller%control_mode)
159
160 call neko_log%end_section()
161
163
166 class(fluid_stats_simcomp_t), intent(inout) :: this
167 call this%free_base()
168 call this%stats%free()
169 end subroutine fluid_stats_simcomp_free
170
171 subroutine fluid_stats_simcomp_restart(this, t)
172 class(fluid_stats_simcomp_t), intent(inout) :: this
173 real(kind=rp), intent(in) :: t
174 if (t .gt. this%time) this%time = t
175 end subroutine fluid_stats_simcomp_restart
176
180 subroutine fluid_stats_simcomp_compute(this, t, tstep)
181 class(fluid_stats_simcomp_t), intent(inout) :: this
182 real(kind=rp), intent(in) :: t
183 integer, intent(in) :: tstep
184 real(kind=rp) :: delta_t
185 real(kind=rp) :: sample_start_time, sample_time
186 character(len=LOG_SIZE) :: log_buf
187 integer :: ierr
188
189 if (t .ge. this%start_time) then
190 delta_t = t - this%time
191
192 call mpi_barrier(neko_comm, ierr)
193
194 sample_start_time = mpi_wtime()
195
196 call this%stats%update(delta_t)
197 call mpi_barrier(neko_comm, ierr)
198 this%time = t
199
200 sample_time = mpi_wtime() - sample_start_time
201
202 call neko_log%section('Fluid stats')
203 write(log_buf, '(A,E15.7)') 'Sampling at time:', t
204 call neko_log%message(log_buf)
205 write(log_buf, '(A33,E15.7)') 'Simulationtime since last sample:', &
206 delta_t
207 call neko_log%message(log_buf)
208 write(log_buf, '(A,E15.7)') 'Sampling time (s):', sample_time
209 call neko_log%message(log_buf)
210 call neko_log%end_section()
211 end if
212
213 end subroutine fluid_stats_simcomp_compute
214
215end module fluid_stats_simcomp
Retrieves a parameter by name or assigns a provided default value. In the latter case also adds the m...
Retrieves a parameter by name or throws an error.
Defines a simulation case.
Definition case.f90:34
Coefficients.
Definition coef.f90:34
Definition comm.F90:1
type(mpi_comm) neko_comm
MPI communicator.
Definition comm.F90:16
Defines a registry for storing solution fields.
type(field_registry_t), target, public neko_field_registry
Global field registry.
Defines a field.
Definition field.f90:34
Implements fluid_stats_ouput_t.
Implements the fluid_stats_simcomp_t type.
subroutine fluid_stats_simcomp_compute(this, t, tstep)
fluid_stats, called depending on compute_control and compute_value
subroutine fluid_stats_simcomp_free(this)
Destructor.
subroutine fluid_stats_simcomp_init_from_json(this, json, case)
Constructor from json.
subroutine fluid_stats_simcomp_init_from_attributes(this, u, v, w, p, coef, start_time, hom_dir, stat_set)
Actual constructor.
subroutine fluid_stats_simcomp_restart(this, t)
Computes various statistics for the fluid fields. We use the Reynolds decomposition for a field u = ...
Utilities for retrieving parameters from the case files.
Logging routines.
Definition log.f90:34
type(log_t), public neko_log
Global log stream.
Definition log.f90:65
integer, parameter, public log_size
Definition log.f90:42
integer, parameter, public dp
Definition num_types.f90:9
integer, parameter, public sp
Definition num_types.f90:8
integer, parameter, public rp
Global precision used in computations.
Definition num_types.f90:12
Simulation components are objects that encapsulate functionality that can be fit to a particular comp...
subroutine compute_(this, t, tstep)
Dummy compute function.
subroutine restart_(this, t)
Dummy restart function.
Defines a container for all statistics.
Coefficients defined on a given (mesh, ) tuple. Arrays use indices (i,j,k,e): element e,...
Definition coef.f90:55
Defines an output for the fluid statistics computed using the fluid_stats_t object.
A simulation component that computes the velocity and pressure statistics up to 4th order....
Base abstract class for simulation components.