35module simulation_checkpoint
36 use num_types,
only: rp, sp, dp
37 use case,
only: case_t
38 use json_file_module,
only: json_file
39 use json_utils,
only: json_get_or_default
40 use scalar_scheme,
only: scalar_scheme_t
41 use time_state,
only: time_state_t
42 use chkp_output,
only: chkp_output_t
43 use field,
only: field_t
44 use mpi_f08,
only: mpi_wtime
45 use utils,
only: neko_error
46 use field_math,
only: field_copy, field_rzero
47 use profiler,
only: profiler_start_region, profiler_end_region
58 logical :: enabled = .false.
60 character(len=256) :: algorithm =
"linear"
62 character(len=256) :: filename =
"checkpoint"
64 character(len=8) :: fmt =
"chkp"
66 integer :: n_saves_memory = 10
68 logical :: keep_checkpoints = .true.
71 integer :: n_saves_disc = 0
72 integer :: n_timesteps = 0
73 integer :: first_valid_timestep = 2
74 integer :: loaded_checkpoint = -1
77 type(chkp_output_t) :: chkp_output
78 type(field_t),
dimension(:),
allocatable :: p_list
79 type(field_t),
dimension(:),
allocatable :: u_list
80 type(field_t),
dimension(:),
allocatable :: v_list
81 type(field_t),
dimension(:),
allocatable :: w_list
83 integer :: n_scalars = 0
84 type(field_t),
dimension(:),
allocatable :: s_list
88 generic,
public :: init => init_from_json, init_from_components
90 procedure,
public, pass(this) :: init_from_json => &
91 checkpoint_init_from_json
93 procedure,
public, pass(this) :: init_from_components => &
94 checkpoint_init_from_components
96 procedure,
public, pass(this) :: free => checkpoint_free
98 procedure,
public, pass(this) :: reset => checkpoint_reset
100 procedure,
public, pass(this) ::
save => checkpoint_save
102 procedure,
public, pass(this) :: restore => checkpoint_restore
112 module subroutine checkpoint_save_linear(this, neko_case)
113 class(simulation_checkpoint_t),
intent(inout) :: this
114 class(case_t),
intent(inout) :: neko_case
115 end subroutine checkpoint_save_linear
118 module subroutine checkpoint_restore_linear(this, neko_case, tstep)
119 class(simulation_checkpoint_t),
intent(inout) :: this
120 class(case_t),
target,
intent(inout) :: neko_case
121 integer,
intent(in) :: tstep
122 end subroutine checkpoint_restore_linear
131 subroutine checkpoint_init_from_json(this, neko_case, params)
132 class(simulation_checkpoint_t),
intent(inout) :: this
133 class(case_t),
target,
intent(inout) :: neko_case
134 type(json_file),
target,
intent(inout) :: params
135 integer :: n_saves_memory
136 character(len=:),
allocatable :: filename, algorithm, fmt
137 logical :: enabled, keep_checkpoints
139 call json_get_or_default(params,
"enabled", enabled, .false.)
140 if (.not. enabled)
return
142 call json_get_or_default(params,
"algorithm", algorithm,
"linear")
143 call json_get_or_default(params,
"n_memory", n_saves_memory, 10)
144 call json_get_or_default(params,
"filename", filename,
"checkpoint")
145 call json_get_or_default(params,
"format", fmt,
"chkp")
146 call json_get_or_default(params,
"keep_checkpoints", keep_checkpoints, &
149 call this%init_from_components(neko_case, algorithm, n_saves_memory, &
150 filename, fmt, keep_checkpoints)
151 end subroutine checkpoint_init_from_json
154 subroutine checkpoint_init_from_components(this, neko_case, algorithm, &
155 n_saves_memory, filename, fmt, keep_checkpoints)
156 class(simulation_checkpoint_t),
intent(inout),
target :: this
157 class(case_t),
target,
intent(inout) :: neko_case
158 character(len=*),
optional,
intent(in) :: algorithm
159 integer,
optional,
intent(in) :: n_saves_memory
160 character(len=*),
optional,
intent(in) :: filename
161 character(len=*),
optional,
intent(in) :: fmt
162 logical,
optional,
intent(in) :: keep_checkpoints
164 class(scalar_scheme_t),
pointer :: scalar_i
166 character(len=80) :: str
171 this%enabled = .true.
172 if (
present(algorithm)) this%algorithm = algorithm
173 if (
present(filename)) this%filename = filename
174 if (
present(n_saves_memory)) this%n_saves_memory = n_saves_memory
175 if (
present(fmt)) this%fmt = fmt
176 if (
present(keep_checkpoints)) this%keep_checkpoints = keep_checkpoints
178 if (
allocated(neko_case%scalars))
then
179 this%n_scalars =
size(neko_case%scalars%scalar_fields)
184 call this%chkp_output%init(neko_case%chkp, this%filename, fmt = this%fmt, &
188 allocate(this%p_list(this%n_saves_memory))
189 allocate(this%u_list(this%n_saves_memory))
190 allocate(this%v_list(this%n_saves_memory))
191 allocate(this%w_list(this%n_saves_memory))
192 if (this%n_scalars .gt. 0)
then
193 this%n_scalars =
size(neko_case%scalars%scalar_fields)
194 allocate(this%s_list(this%n_saves_memory * this%n_scalars))
197 do i = 1, this%n_saves_memory
198 write(str,
'(A,I0)')
"p_chkp_", i
199 call this%p_list(i)%init(neko_case%fluid%p%dof, str)
200 write(str,
'(A,I0)')
"u_chkp_", i
201 call this%u_list(i)%init(neko_case%fluid%u%dof, str)
202 write(str,
'(A,I0)')
"v_chkp_", i
203 call this%v_list(i)%init(neko_case%fluid%v%dof, str)
204 write(str,
'(A,I0)')
"w_chkp_", i
205 call this%w_list(i)%init(neko_case%fluid%w%dof, str)
206 if (this%n_scalars .gt. 0)
then
207 do j = 1, this%n_scalars
208 write(str,
'(A,I0,A,I0)')
"s_chkp_", i,
"_", j
209 scalar_i => neko_case%scalars%scalar_fields(j)
210 call this%s_list((i - 1) * this%n_scalars + j)%init(scalar_i%s%dof, str)
215 end subroutine checkpoint_init_from_components
218 subroutine checkpoint_free(this)
219 class(simulation_checkpoint_t),
intent(inout) :: this
221 character(len=1024) :: file_name
223 integer :: stat, unit
226 do i = 1, this%n_saves_memory
227 if (
allocated(this%p_list))
call this%p_list(i)%free()
228 if (
allocated(this%u_list))
call this%u_list(i)%free()
229 if (
allocated(this%v_list))
call this%v_list(i)%free()
230 if (
allocated(this%w_list))
call this%w_list(i)%free()
233 if (
allocated(this%s_list))
then
234 do i = 1,
size(this%s_list)
235 call this%s_list(i)%free()
240 if (
allocated(this%p_list))
deallocate(this%p_list)
241 if (
allocated(this%u_list))
deallocate(this%u_list)
242 if (
allocated(this%v_list))
deallocate(this%v_list)
243 if (
allocated(this%w_list))
deallocate(this%w_list)
244 if (
allocated(this%s_list))
deallocate(this%s_list)
247 if (.not. this%keep_checkpoints)
then
248 do i = this%n_timesteps, 1, -1
249 call this%chkp_output%set_counter(i)
250 file_name = this%chkp_output%file_%get_fname()
251 inquire(file = trim(file_name), exist = exists)
253 open(newunit = unit, file = trim(file_name), iostat = stat, &
255 if (stat .eq. 0)
close(unit, status =
'delete')
261 this%enabled = .false.
262 this%filename =
"checkpoint"
264 this%algorithm =
"linear"
265 this%n_saves_memory = 10
266 this%keep_checkpoints = .true.
268 this%n_saves_disc = 0
270 this%first_valid_timestep = 2
271 this%loaded_checkpoint = -1
273 end subroutine checkpoint_free
279 subroutine checkpoint_save(this, neko_case)
280 class(simulation_checkpoint_t),
intent(inout) :: this
281 class(case_t),
intent(inout) :: neko_case
283 if (.not. this%enabled)
return
285 call profiler_start_region(
"Checkpoint save")
288 this%n_timesteps = this%n_timesteps + 1
290 select case (this%algorithm)
292 call checkpoint_save_linear(this, neko_case)
294 call neko_error(
"Unknown checkpoint algorithm: " // this%algorithm)
297 call profiler_end_region(
"Checkpoint save")
298 end subroutine checkpoint_save
301 subroutine checkpoint_restore(this, neko_case, tstep)
302 class(simulation_checkpoint_t),
intent(inout) :: this
303 class(case_t),
target,
intent(inout) :: neko_case
304 integer,
intent(in) :: tstep
305 character(len=256) :: msg
307 if (.not. this%enabled)
return
309 call profiler_start_region(
"Checkpoint restore")
311 if (tstep .lt. 1 .or. tstep .gt. this%n_timesteps)
then
312 write(msg,
'(A,I0,A,I0,A)')
"Requested timestep ", tstep, &
313 " is out of range [1, ", this%n_timesteps,
"]"
314 call neko_error(trim(msg))
317 select case (this%algorithm)
319 call checkpoint_restore_linear(this, neko_case, tstep)
321 call neko_error(
"Unknown checkpoint algorithm: " // this%algorithm)
324 call profiler_end_region(
"Checkpoint restore")
325 end subroutine checkpoint_restore
331 subroutine checkpoint_reset(this)
332 class(simulation_checkpoint_t),
intent(inout) :: this
335 if (.not. this%enabled)
return
338 this%loaded_checkpoint = -1
339 this%n_saves_disc = 0
342 do i = 1, this%n_saves_memory
343 call field_rzero(this%p_list(i))
344 call field_rzero(this%u_list(i))
345 call field_rzero(this%v_list(i))
346 call field_rzero(this%w_list(i))
349 if (
allocated(this%s_list))
then
350 do i = 1,
size(this%s_list)
351 call field_rzero(this%s_list(i))
354 end subroutine checkpoint_reset
356end module simulation_checkpoint