Neko-TOP
A portable framework for high-order spectral element flow toplogy optimization.
Loading...
Searching...
No Matches
checkpoint.f90
1! Copyright (c) 2025, 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!
33module simulation_checkpoint
34 use num_types, only: rp, sp, dp
35 use case, only: case_t
36 use json_file_module, only: json_file
37 use json_utils, only: json_get_or_default
38 use scalar_scheme, only: scalar_scheme_t
39 use time_state, only: time_state_t
40 use chkp_output, only: chkp_output_t
41 use field, only: field_t
42 use mpi_f08, only: mpi_wtime
43 use utils, only: neko_error
44 use field_math, only: field_copy, field_rzero
45 use profiler, only: profiler_start_region, profiler_end_region
46 implicit none
47 private
48
50 private
51
52 ! ----------------------------------------------------------------------- !
53 ! User parameters
54
56 logical :: enabled = .false.
58 character(len=256) :: algorithm = "linear"
60 character(len=256) :: filename = "checkpoint"
62 character(len=8) :: fmt = "chkp"
64 integer :: n_saves_memory = 10
66 logical :: keep_checkpoints = .true.
67
68 ! Internal parameters
69 integer :: n_saves_disc = 0
70 integer :: n_timesteps = 0
71 integer :: first_valid_timestep = 2
72 integer :: loaded_checkpoint = -1
73
74 ! Structures to hold the checkpoint data
75 type(chkp_output_t) :: chkp_output
76 type(field_t), dimension(:), allocatable :: p_list
77 type(field_t), dimension(:), allocatable :: u_list
78 type(field_t), dimension(:), allocatable :: v_list
79 type(field_t), dimension(:), allocatable :: w_list
80
81 integer :: n_scalars = 0
82 type(field_t), dimension(:), allocatable :: s_list
83
84 contains
86 generic, public :: init => init_from_json, init_from_components
88 procedure, public, pass(this) :: init_from_json => &
89 checkpoint_init_from_json
91 procedure, public, pass(this) :: init_from_components => &
92 checkpoint_init_from_components
94 procedure, public, pass(this) :: free => checkpoint_free
96 procedure, public, pass(this) :: reset => checkpoint_reset
98 procedure, public, pass(this) :: save => checkpoint_save
100 procedure, public, pass(this) :: restore => checkpoint_restore
101
103
104 ! ========================================================================== !
105 ! Module procedures for our algorithm implementations.
106
107
108 interface
109
110 module subroutine checkpoint_save_linear(this, neko_case)
111 class(simulation_checkpoint_t), intent(inout) :: this
112 class(case_t), intent(inout) :: neko_case
113 end subroutine checkpoint_save_linear
114
116 module subroutine checkpoint_restore_linear(this, neko_case, tstep)
117 class(simulation_checkpoint_t), intent(inout) :: this
118 class(case_t), target, intent(inout) :: neko_case
119 integer, intent(in) :: tstep
120 end subroutine checkpoint_restore_linear
121 end interface
122
123contains
124
125 ! ========================================================================== !
126 ! Initialization and deallocation
127
129 subroutine checkpoint_init_from_json(this, neko_case, params)
130 class(simulation_checkpoint_t), intent(inout) :: this
131 class(case_t), target, intent(inout) :: neko_case
132 type(json_file), target, intent(inout) :: params
133 integer :: n_saves_memory
134 character(len=:), allocatable :: filename, algorithm, fmt
135 logical :: enabled, keep_checkpoints
136
137 call json_get_or_default(params, "enabled", enabled, .false.)
138 if (.not. enabled) return
139
140 call json_get_or_default(params, "algorithm", algorithm, "linear")
141 call json_get_or_default(params, "n_memory", n_saves_memory, 10)
142 call json_get_or_default(params, "filename", filename, "checkpoint")
143 call json_get_or_default(params, "format", fmt, "chkp")
144 call json_get_or_default(params, "keep_checkpoints", keep_checkpoints, &
145 .true.)
146
147 call this%init_from_components(neko_case, algorithm, n_saves_memory, &
148 filename, fmt, keep_checkpoints)
149 end subroutine checkpoint_init_from_json
150
152 subroutine checkpoint_init_from_components(this, neko_case, algorithm, &
153 n_saves_memory, filename, fmt, keep_checkpoints)
154 class(simulation_checkpoint_t), intent(inout), target :: this
155 class(case_t), target, intent(inout) :: neko_case
156 character(len=*), optional, intent(in) :: algorithm
157 integer, optional, intent(in) :: n_saves_memory
158 character(len=*), optional, intent(in) :: filename
159 character(len=*), optional, intent(in) :: fmt
160 logical, optional, intent(in) :: keep_checkpoints
161
162 class(scalar_scheme_t), pointer :: scalar_i
163 integer :: i, j
164 character(len=80) :: str
165
166 call this%free()
167
168 ! Set internal parameters
169 this%enabled = .true.
170 if (present(algorithm)) this%algorithm = algorithm
171 if (present(filename)) this%filename = filename
172 if (present(n_saves_memory)) this%n_saves_memory = n_saves_memory
173 if (present(fmt)) this%fmt = fmt
174 if (present(keep_checkpoints)) this%keep_checkpoints = keep_checkpoints
175
176 if (allocated(neko_case%scalars)) then
177 this%n_scalars = size(neko_case%scalars%scalar_fields)
178 end if
179
180
181 ! Initialize the Neko checkpoint output
182 call this%chkp_output%init(neko_case%chkp, this%filename, fmt = this%fmt, &
183 overwrite = .true.)
184
185 ! Allocate the RAM Checkpoints
186 allocate(this%p_list(this%n_saves_memory))
187 allocate(this%u_list(this%n_saves_memory))
188 allocate(this%v_list(this%n_saves_memory))
189 allocate(this%w_list(this%n_saves_memory))
190 if (this%n_scalars .gt. 0) then
191 this%n_scalars = size(neko_case%scalars%scalar_fields)
192 allocate(this%s_list(this%n_saves_memory * this%n_scalars))
193 end if
194
195 do i = 1, this%n_saves_memory
196 write(str, '(A,I0)') "p_chkp_", i
197 call this%p_list(i)%init(neko_case%fluid%p%dof, str)
198 write(str, '(A,I0)') "u_chkp_", i
199 call this%u_list(i)%init(neko_case%fluid%u%dof, str)
200 write(str, '(A,I0)') "v_chkp_", i
201 call this%v_list(i)%init(neko_case%fluid%v%dof, str)
202 write(str, '(A,I0)') "w_chkp_", i
203 call this%w_list(i)%init(neko_case%fluid%w%dof, str)
204 if (this%n_scalars .gt. 0) then
205 do j = 1, this%n_scalars
206 write(str, '(A,I0,A,I0)') "s_chkp_", i, "_", j
207 scalar_i => neko_case%scalars%scalar_fields(j)
208 call this%s_list((i - 1) * this%n_scalars + j)%init(scalar_i%s%dof, str)
209 end do
210 end if
211 end do
212
213 end subroutine checkpoint_init_from_components
214
216 subroutine checkpoint_free(this)
217 class(simulation_checkpoint_t), intent(inout) :: this
218 integer :: i
219
220 ! Free the RAM Checkpoints
221 do i = 1, this%n_saves_memory
222 if (allocated(this%p_list)) call this%p_list(i)%free()
223 if (allocated(this%u_list)) call this%u_list(i)%free()
224 if (allocated(this%v_list)) call this%v_list(i)%free()
225 if (allocated(this%w_list)) call this%w_list(i)%free()
226 end do
227
228 if (allocated(this%s_list)) then
229 do i = 1, size(this%s_list)
230 call this%s_list(i)%free()
231 end do
232 this%n_scalars = 0
233 end if
234
235 if (allocated(this%p_list)) deallocate(this%p_list)
236 if (allocated(this%u_list)) deallocate(this%u_list)
237 if (allocated(this%v_list)) deallocate(this%v_list)
238 if (allocated(this%w_list)) deallocate(this%w_list)
239 if (allocated(this%s_list)) deallocate(this%s_list)
240
241 ! Delete the checkpoint file list
242 ! call this%chkp_output%free()
243 if (.not. this%keep_checkpoints) then
244 call system("rm -f $(ls | grep -E '" // &
245 trim(this%filename) // "[0-9]{5}\.(chkp|h5)$')")
246 end if
247
248 ! Reset to default values
249 this%enabled = .false.
250 this%filename = "checkpoint"
251 this%fmt = "chkp"
252 this%algorithm = "linear"
253 this%n_saves_memory = 10
254 this%keep_checkpoints = .true.
255
256 this%n_saves_disc = 0
257 this%n_timesteps = 0
258 this%first_valid_timestep = 2
259 this%loaded_checkpoint = -1
260
261 end subroutine checkpoint_free
262
263 ! ========================================================================== !
264 ! Saving and Restoring
265
267 subroutine checkpoint_save(this, neko_case)
268 class(simulation_checkpoint_t), intent(inout) :: this
269 class(case_t), intent(inout) :: neko_case
270
271 if (.not. this%enabled) return
272
273 call profiler_start_region("Checkpoint save")
274
275 ! Update the number of recorded timesteps
276 this%n_timesteps = this%n_timesteps + 1
277
278 select case (this%algorithm)
279 case ("linear")
280 call checkpoint_save_linear(this, neko_case)
281 case default
282 call neko_error("Unknown checkpoint algorithm: " // this%algorithm)
283 end select
284
285 call profiler_end_region("Checkpoint save")
286 end subroutine checkpoint_save
287
289 subroutine checkpoint_restore(this, neko_case, tstep)
290 class(simulation_checkpoint_t), intent(inout) :: this
291 class(case_t), target, intent(inout) :: neko_case
292 integer, intent(in) :: tstep
293 character(len=256) :: msg
294
295 if (.not. this%enabled) return
296
297 call profiler_start_region("Checkpoint restore")
298
299 if (tstep .lt. 1 .or. tstep .gt. this%n_timesteps) then
300 write(msg, '(A,I0,A,I0,A)') "Requested timestep ", tstep, &
301 " is out of range [1, ", this%n_timesteps, "]"
302 call neko_error(trim(msg))
303 end if
304
305 select case (this%algorithm)
306 case ("linear")
307 call checkpoint_restore_linear(this, neko_case, tstep)
308 case default
309 call neko_error("Unknown checkpoint algorithm: " // this%algorithm)
310 end select
311
312 call profiler_end_region("Checkpoint restore")
313 end subroutine checkpoint_restore
314
315 ! ========================================================================== !
316 ! Meta handling
317
319 subroutine checkpoint_reset(this)
320 class(simulation_checkpoint_t), intent(inout) :: this
321 integer :: i
322
323 if (.not. this%enabled) return
324
325 ! Reset our checkpoints
326 this%loaded_checkpoint = -1
327 this%n_saves_disc = 0
328 this%n_timesteps = 0
329
330 do i = 1, this%n_saves_memory
331 call field_rzero(this%p_list(i))
332 call field_rzero(this%u_list(i))
333 call field_rzero(this%v_list(i))
334 call field_rzero(this%w_list(i))
335 end do
336
337 if (allocated(this%s_list)) then
338 do i = 1, size(this%s_list)
339 call field_rzero(this%s_list(i))
340 end do
341 end if
342 end subroutine checkpoint_reset
343
344end module simulation_checkpoint