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
61 character(len=:),
allocatable :: restart_file
62 logical :: output_at_end, found
64 real(kind=
rp) :: cfl_avrg = 0.0_rp
66 real(kind=
rp) :: rho, mu, cp, lambda
70 call neko_log%section(
'Starting simulation')
71 write(log_buf,
'(A, E15.7,A,E15.7,A)')
'T : [', 0d0,
',', c%end_time,
')'
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
78 write(log_buf,
'(A, E15.7)')
'CFL : ', dt_controller%set_cfl
82 call c%params%get(
'case.restart_file', restart_file, found)
83 if (found .and. len_trim(restart_file) .gt. 0)
then
92 call neko_log%section(
'Postprocessing')
93 call c%output_controller%execute(t, tstep)
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)
101 cfl = c%fluid%compute_cfl(c%dt)
102 start_time_org = mpi_wtime()
107 start_time = mpi_wtime()
108 tstep_start_time = start_time
109 if (dt_controller%dt_last_change .eq. 0)
then
112 call dt_controller%set_dt(c%dt, cfl, cfl_avrg, tstep)
114 cfl = c%fluid%compute_cfl(c%dt)
117 write(log_buf,
'(A,I6)')
'Time-step: ', tstep
121 write(log_buf,
'(A,E15.7,1x,A,E15.7)')
'CFL:', cfl,
'dt:', c%dt
126 call neko_log%section(
'Preprocessing')
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
136 write(log_buf,
'(A,E15.7)') &
137 'Total elapsed time (s):', end_time-start_time_org
141 if (
allocated(c%scalar))
then
142 start_time = mpi_wtime()
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
149 write(log_buf,
'(A,E15.7)') &
150 'Total elapsed time (s):', end_time-start_time_org
155 lambda = c%scalar%lambda
158 call neko_log%section(
'Postprocessing')
168 call c%usr%material_properties(t, tstep, rho, mu, cp, lambda, c%params)
173 call c%fluid%update_material_properties()
175 if (
allocated(c%scalar))
then
177 c%scalar%lambda = lambda
178 call c%scalar%update_material_properties()
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)
184 call c%output_controller%execute(t, tstep)
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
192 write(log_buf,
'(A,E15.7)') &
193 'Total elapsed time (s): ', end_time-start_time_org
202 output_at_end, .true.)
203 call c%output_controller%execute(t, tstep, output_at_end)
205 if (.not. (output_at_end) .and. t .lt. c%end_time)
then
209 call c%usr%user_finalize_modules(t, c%params)
211 call neko_log%end_section(
'Normal end.')
246 type(
case_t),
intent(inout) :: C
247 real(kind=
rp),
intent(inout) :: t
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
254 logical :: found, check_cont
256 call c%params%get(
'case.restart_file', restart_file, found)
257 call c%params%get(
'case.restart_mesh_file', restart_mesh_file,&
261 previous_meshf =
file_t(trim(restart_mesh_file))
262 call previous_meshf%read(c%fluid%chkp%previous_mesh)
265 call c%params%get(
'case.mesh2mesh_tolerance', tol,&
268 if (found) c%fluid%chkp%mesh2mesh_tol = tol
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
276 do i = 1,
size(c%dtlag)
277 call c%ext_bdf%set_coeffs(c%dtlag)
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)
285 t = c%fluid%chkp%restart_time()
286 call neko_log%section(
'Restarting from checkpoint')
287 write(log_buf,
'(A,A)')
'File : ', &
290 write(log_buf,
'(A,E15.7)')
'Time : ', t
294 call c%output_controller%set_counter(t)