Neko 0.9.99
A portable framework for high-order spectral element flow simulations
Loading...
Searching...
No Matches
simulation.f90
Go to the documentation of this file.
1! Copyright (c) 2020-2021, 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 mpi_f08
36 use case, only : case_t
37 use num_types, only : rp, dp
39 use file, only : file_t
40 use logger, only : log_size, neko_log
41 use jobctrl, only : jobctrl_time_limit
47 implicit none
48 private
49
50 public :: neko_solve
51
52contains
53
55 subroutine neko_solve(C)
56 type(case_t), target, intent(inout) :: c
57 real(kind=rp) :: t, cfl
58 real(kind=dp) :: start_time_org, start_time, end_time, tstep_start_time
59 character(len=LOG_SIZE) :: log_buf
60 integer :: tstep
61 character(len=:), allocatable :: restart_file
62 logical :: output_at_end, found
63 ! for variable_tsteping
64 real(kind=rp) :: cfl_avrg = 0.0_rp
65 type(time_step_controller_t) :: dt_controller
66 real(kind=rp) :: rho, mu, cp, lambda
67
68 t = 0d0
69 tstep = 0
70 call neko_log%section('Starting simulation')
71 write(log_buf, '(A, E15.7,A,E15.7,A)') 'T : [', 0d0, ',', c%end_time, ')'
72 call neko_log%message(log_buf)
73 call dt_controller%init(c%params)
74 if (.not. dt_controller%if_variable_dt) then
75 write(log_buf, '(A, E15.7)') 'dt : ', c%dt
76 call neko_log%message(log_buf)
77 else
78 write(log_buf, '(A, E15.7)') 'CFL : ', dt_controller%set_cfl
79 call neko_log%message(log_buf)
80 end if
81
82 call c%params%get('case.restart_file', restart_file, found)
83 if (found .and. len_trim(restart_file) .gt. 0) then
84 ! Restart the case
85 call simulation_restart(c, t)
86
87 ! Restart the simulation components
88 call neko_simcomps%restart(t)
89 end if
90
92 call neko_log%section('Postprocessing')
93 call c%output_controller%execute(t, tstep)
94
95 call c%usr%user_init_modules(t, c%fluid%u, c%fluid%v, c%fluid%w,&
96 c%fluid%p, c%fluid%c_Xh, c%params)
97 call neko_log%end_section()
98 call neko_log%newline()
99
100 call profiler_start
101 cfl = c%fluid%compute_cfl(c%dt)
102 start_time_org = mpi_wtime()
103
104 do while (t .lt. c%end_time .and. (.not. jobctrl_time_limit()))
105 call profiler_start_region('Time-Step')
106 tstep = tstep + 1
107 start_time = mpi_wtime()
108 tstep_start_time = start_time
109 if (dt_controller%dt_last_change .eq. 0) then
110 cfl_avrg = cfl
111 end if
112 call dt_controller%set_dt(c%dt, cfl, cfl_avrg, tstep)
113 !calculate the cfl after the possibly varied dt
114 cfl = c%fluid%compute_cfl(c%dt)
115
116 call neko_log%status(t, c%end_time)
117 write(log_buf, '(A,I6)') 'Time-step: ', tstep
118 call neko_log%message(log_buf)
119 call neko_log%begin()
120
121 write(log_buf, '(A,E15.7,1x,A,E15.7)') 'CFL:', cfl, 'dt:', c%dt
122 call neko_log%message(log_buf)
123 call simulation_settime(t, c%dt, c%ext_bdf, c%tlag, c%dtlag, tstep)
124
125 ! Run the preprocessing
126 call neko_log%section('Preprocessing')
127 call neko_simcomps%preprocess(t, tstep)
128 call neko_log%end_section()
129
130 call neko_log%section('Fluid')
131 call c%fluid%step(t, tstep, c%dt, c%ext_bdf, dt_controller)
132 end_time = mpi_wtime()
133 write(log_buf, '(A,E15.7)') &
134 'Fluid step time (s): ', end_time-start_time
135 call neko_log%message(log_buf)
136 write(log_buf, '(A,E15.7)') &
137 'Total elapsed time (s):', end_time-start_time_org
138 call neko_log%end_section(log_buf)
139
140 ! Scalar step
141 if (allocated(c%scalar)) then
142 start_time = mpi_wtime()
143 call neko_log%section('Scalar')
144 call c%scalar%step(t, tstep, c%dt, c%ext_bdf, dt_controller)
145 end_time = mpi_wtime()
146 write(log_buf, '(A,E15.7)') &
147 'Scalar step time: ', end_time-start_time
148 call neko_log%message(log_buf)
149 write(log_buf, '(A,E15.7)') &
150 'Total elapsed time (s):', end_time-start_time_org
151 call neko_log%end_section(log_buf)
152
154 cp = c%scalar%cp
155 lambda = c%scalar%lambda
156 end if
157
158 call neko_log%section('Postprocessing')
159 ! Execute all simulation components
160 call neko_simcomps%compute(t, tstep)
161
162
164 rho = c%fluid%rho
165 mu = c%fluid%mu
166
167 ! Update material properties
168 call c%usr%material_properties(t, tstep, rho, mu, cp, lambda, c%params)
169
171 c%fluid%rho = rho
172 c%fluid%mu = mu
173 call c%fluid%update_material_properties()
174
175 if (allocated(c%scalar)) then
176 c%scalar%cp = cp
177 c%scalar%lambda = lambda
178 call c%scalar%update_material_properties()
179 end if
180
181 call c%usr%user_check(t, tstep, c%fluid%u, c%fluid%v, c%fluid%w, &
182 c%fluid%p, c%fluid%c_Xh, c%params)
183
184 call c%output_controller%execute(t, tstep)
185
186 call neko_log%end_section()
187 end_time = mpi_wtime()
188 call neko_log%section('Step summary')
189 write(log_buf, '(A,I8,A,E15.7)') &
190 'Total time for step ', tstep, ' (s): ', end_time-tstep_start_time
191 call neko_log%message(log_buf)
192 write(log_buf, '(A,E15.7)') &
193 'Total elapsed time (s): ', end_time-start_time_org
194 call neko_log%message(log_buf)
195 call neko_log%end_section()
196 call neko_log%end()
198 end do
199 call profiler_stop
200
201 call json_get_or_default(c%params, 'case.output_at_end',&
202 output_at_end, .true.)
203 call c%output_controller%execute(t, tstep, output_at_end)
204
205 if (.not. (output_at_end) .and. t .lt. c%end_time) then
206 call simulation_joblimit_chkp(c, t)
207 end if
208
209 call c%usr%user_finalize_modules(t, c%params)
210
211 call neko_log%end_section('Normal end.')
212
213 end subroutine neko_solve
214
215 subroutine simulation_settime(t, dt, ext_bdf, tlag, dtlag, step)
216 real(kind=rp), intent(inout) :: t
217 real(kind=rp), intent(in) :: dt
218 type(time_scheme_controller_t), intent(inout) :: ext_bdf
219 real(kind=rp), dimension(10) :: tlag
220 real(kind=rp), dimension(10) :: dtlag
221 integer, intent(in) :: step
222 integer :: i
223
224
225 do i = 10, 2, -1
226 tlag(i) = tlag(i-1)
227 dtlag(i) = dtlag(i-1)
228 end do
229
230 dtlag(1) = dt
231 tlag(1) = t
232 if (ext_bdf%ndiff .eq. 0) then
233 dtlag(2) = dt
234 tlag(2) = t
235 end if
236
237 t = t + dt
238
239 call ext_bdf%set_coeffs(dtlag)
240
241 end subroutine simulation_settime
242
244 subroutine simulation_restart(C, t)
245 implicit none
246 type(case_t), intent(inout) :: C
247 real(kind=rp), intent(inout) :: t
248 integer :: i
249 type(file_t) :: chkpf, previous_meshf
250 character(len=LOG_SIZE) :: log_buf
251 character(len=:), allocatable :: restart_file
252 character(len=:), allocatable :: restart_mesh_file
253 real(kind=rp) :: tol
254 logical :: found, check_cont
255
256 call c%params%get('case.restart_file', restart_file, found)
257 call c%params%get('case.restart_mesh_file', restart_mesh_file,&
258 found)
259
260 if (found) then
261 previous_meshf = file_t(trim(restart_mesh_file))
262 call previous_meshf%read(c%fluid%chkp%previous_mesh)
263 end if
264
265 call c%params%get('case.mesh2mesh_tolerance', tol,&
266 found)
267
268 if (found) c%fluid%chkp%mesh2mesh_tol = tol
269
270 chkpf = file_t(trim(restart_file))
271 call chkpf%read(c%fluid%chkp)
272 c%dtlag = c%fluid%chkp%dtlag
273 c%tlag = c%fluid%chkp%tlag
274
275 !Free the previous mesh, dont need it anymore
276 do i = 1, size(c%dtlag)
277 call c%ext_bdf%set_coeffs(c%dtlag)
278 end do
279
280 call c%fluid%restart(c%dtlag, c%tlag)
281 call c%fluid%chkp%previous_mesh%free()
282 if (allocated(c%scalar)) &
283 call c%scalar%restart( c%dtlag, c%tlag)
284
285 t = c%fluid%chkp%restart_time()
286 call neko_log%section('Restarting from checkpoint')
287 write(log_buf, '(A,A)') 'File : ', &
288 trim(restart_file)
289 call neko_log%message(log_buf)
290 write(log_buf, '(A,E15.7)') 'Time : ', t
291 call neko_log%message(log_buf)
292 call neko_log%end_section()
293
294 call c%output_controller%set_counter(t)
295 end subroutine simulation_restart
296
299 type(case_t), intent(inout) :: C
300 real(kind=rp), intent(inout) :: t
301 type(file_t) :: chkpf
302 character(len=:), allocatable :: chkp_format
303 character(len=LOG_SIZE) :: log_buf
304 character(len=10) :: format_str
305 logical :: found
306
307 call c%params%get('case.checkpoint_format', chkp_format, found)
308 call c%fluid%chkp%sync_host()
309 format_str = '.chkp'
310 if (found) then
311 if (chkp_format .eq. 'hdf5') then
312 format_str = '.h5'
313 end if
314 end if
315 chkpf = file_t(c%output_directory // 'joblimit'//trim(format_str))
316 call chkpf%write(c%fluid%chkp, t)
317 write(log_buf, '(A)') '! saving checkpoint >>>'
318 call neko_log%message(log_buf)
319
320 end subroutine simulation_joblimit_chkp
321
322end module simulation
323
324
Retrieves a parameter by name or assigns a provided default value. In the latter case also adds the m...
Defines a simulation case.
Definition case.f90:34
Module for file I/O operations.
Definition file.f90:34
Job control.
Definition jobctrl.f90:34
logical function, public jobctrl_time_limit()
Check if the job's time limit has been reached.
Definition jobctrl.f90:107
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 rp
Global precision used in computations.
Definition num_types.f90:12
Profiling interface.
Definition profiler.F90:34
subroutine, public profiler_start
Start profiling.
Definition profiler.F90:52
subroutine, public profiler_start_region(name, region_id)
Started a named (name) profiler region.
Definition profiler.F90:78
subroutine, public profiler_end_region(name, region_id)
End the most recently started profiler region.
Definition profiler.F90:109
subroutine, public profiler_stop
Stop profiling.
Definition profiler.F90:65
Contains the simcomp_executor_t type.
type(simcomp_executor_t), target, public neko_simcomps
Global variable for the simulation component driver.
Simulation driver.
subroutine simulation_settime(t, dt, ext_bdf, tlag, dtlag, step)
subroutine, public neko_solve(c)
Main driver to solve a case C.
subroutine simulation_restart(c, t)
Restart a case C from a given checkpoint.
subroutine simulation_joblimit_chkp(c, t)
Write a checkpoint at joblimit.
Compound scheme for the advection and diffusion operators in a transport equation.
Implements type time_step_controller.
A wrapper around a polymorphic generic_file_t that handles its init. This is essentially a factory fo...
Definition file.f90:54
Implements the logic to compute the time coefficients for the advection and diffusion operators in a ...