Neko 1.0.0
A portable framework for high-order spectral element flow simulations
Loading...
Searching...
No Matches
checkpoint.f90
Go to the documentation of this file.
1! Copyright (c) 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 neko_config
36 use num_types, only : rp, dp
39 use space, only : space_t, operator(.ne.)
42 use field, only : field_t, field_ptr_t
43 use utils, only : neko_error
44 use mesh, only: mesh_t
45 use math, only : neko_eps
46 implicit none
47 private
48
49 type, public :: chkp_t
50 type(field_t), pointer :: u => null()
51 type(field_t), pointer :: v => null()
52 type(field_t), pointer :: w => null()
53 type(field_t), pointer :: p => null()
54
55
56 !
57 ! Optional payload
58 !
59 type(field_series_t), pointer :: ulag => null()
60 type(field_series_t), pointer :: vlag => null()
61 type(field_series_t), pointer :: wlag => null()
62
63 real(kind=rp), pointer :: tlag(:) => null()
64 real(kind=rp), pointer :: dtlag(:) => null()
65
67 type(field_t), pointer :: abx1 => null()
68 type(field_t), pointer :: abx2 => null()
69 type(field_t), pointer :: aby1 => null()
70 type(field_t), pointer :: aby2 => null()
71 type(field_t), pointer :: abz1 => null()
72 type(field_t), pointer :: abz2 => null()
73
74
75 type(field_t), pointer :: s => null()
76 type(field_series_t), pointer :: slag => null()
77 type(field_t), pointer :: abs1 => null()
78 type(field_t), pointer :: abs2 => null()
79
80 type(field_series_list_t) :: scalar_lags
81
83 type(field_ptr_t), allocatable :: scalar_abx1(:)
84 type(field_ptr_t), allocatable :: scalar_abx2(:)
85
86 real(kind=dp) :: t
87 type(mesh_t) :: previous_mesh
88 type(space_t) :: previous_xh
89 real(kind=rp) :: mesh2mesh_tol = neko_eps*1e3_rp
90
91 contains
92 procedure, pass(this) :: init => chkp_init
93 procedure, pass(this) :: sync_host => chkp_sync_host
94 procedure, pass(this) :: sync_device => chkp_sync_device
95 procedure, pass(this) :: add_lag => chkp_add_lag
96 procedure, pass(this) :: add_scalar => chkp_add_scalar
97 procedure, pass(this) :: restart_time => chkp_restart_time
98 final :: chkp_free
99 end type chkp_t
100
101contains
102
104 subroutine chkp_init(this, u, v, w, p)
105 class(chkp_t), intent(inout) :: this
106 type(field_t), intent(in), target :: u
107 type(field_t), intent(in), target :: v
108 type(field_t), intent(in), target :: w
109 type(field_t), intent(in), target :: p
110
111 ! Check that all velocity components are defined on the same
112 ! function space
113 if ( u%Xh .ne. v%Xh .or. &
114 u%Xh .ne. w%Xh ) then
115 call neko_error('Different function spaces for each velocity component')
116 end if
117
118 ! Check that both velocity and pressure is defined on the same mesh
119 if ( u%msh%nelv .ne. p%msh%nelv ) then
120 call neko_error('Velocity and pressure defined on different meshes')
121 end if
122
123 this%u => u
124 this%v => v
125 this%w => w
126 this%p => p
127
128 this%t = 0d0
129
130 end subroutine chkp_init
131
133 subroutine chkp_free(this)
134 type(chkp_t), intent(inout) :: this
135
136 nullify(this%u)
137 nullify(this%v)
138 nullify(this%w)
139 nullify(this%p)
140
141 nullify(this%ulag)
142 nullify(this%vlag)
143 nullify(this%wlag)
144
145 ! Scalar cleanup
146 nullify(this%s)
147 nullify(this%slag)
148 nullify(this%abs1)
149 nullify(this%abs2)
150
151 ! Free scalar lag list if it was initialized
152 if (allocated(this%scalar_lags%items)) then
153 call this%scalar_lags%free()
154 end if
155
156 ! Free multi-scalar ABX field arrays
157 if (allocated(this%scalar_abx1)) then
158 deallocate(this%scalar_abx1)
159 end if
160 if (allocated(this%scalar_abx2)) then
161 deallocate(this%scalar_abx2)
162 end if
163
164 end subroutine chkp_free
165
167 subroutine chkp_sync_host(this)
168 class(chkp_t), intent(inout) :: this
169 integer :: i, j
170
171 if (neko_bcknd_device .eq. 1) then
172 associate(u=>this%u, v=>this%v, w=>this%w, &
173 ulag=>this%ulag, vlag=>this%vlag, wlag=>this%wlag, &
174 p=>this%p)
175
176 if (associated(this%u) .and. associated(this%v) .and. &
177 associated(this%w) .and. associated(this%p)) then
178 call device_memcpy(u%x, u%x_d, u%dof%size(), device_to_host, sync=.false.)
179 call device_memcpy(v%x, v%x_d, v%dof%size(), device_to_host, sync=.false.)
180 call device_memcpy(w%x, w%x_d, w%dof%size(), device_to_host, sync=.false.)
181 call device_memcpy(p%x, p%x_d, p%dof%size(), device_to_host, sync=.false.)
182 end if
183
184 if (associated(this%ulag) .and. associated(this%vlag) .and. &
185 associated(this%wlag)) then
186 call device_memcpy(ulag%lf(1)%x, ulag%lf(1)%x_d, &
187 u%dof%size(), device_to_host, sync=.false.)
188 call device_memcpy(ulag%lf(2)%x, ulag%lf(2)%x_d, &
189 u%dof%size(), device_to_host, sync=.false.)
190
191 call device_memcpy(vlag%lf(1)%x, vlag%lf(1)%x_d, &
192 v%dof%size(), device_to_host, sync=.false.)
193 call device_memcpy(vlag%lf(2)%x, vlag%lf(2)%x_d, &
194 v%dof%size(), device_to_host, sync=.false.)
195
196 call device_memcpy(wlag%lf(1)%x, wlag%lf(1)%x_d, &
197 w%dof%size(), device_to_host, sync=.false.)
198 call device_memcpy(wlag%lf(2)%x, wlag%lf(2)%x_d, &
199 w%dof%size(), device_to_host, sync=.false.)
200 call device_memcpy(this%abx1%x, this%abx1%x_d, &
201 w%dof%size(), device_to_host, sync=.false.)
202 call device_memcpy(this%abx2%x, this%abx2%x_d, &
203 w%dof%size(), device_to_host, sync=.false.)
204 call device_memcpy(this%aby1%x, this%aby1%x_d, &
205 w%dof%size(), device_to_host, sync=.false.)
206 call device_memcpy(this%aby2%x, this%aby2%x_d, &
207 w%dof%size(), device_to_host, sync=.false.)
208 call device_memcpy(this%abz1%x, this%abz1%x_d, &
209 w%dof%size(), device_to_host, sync=.false.)
210 call device_memcpy(this%abz2%x, this%abz2%x_d, &
211 w%dof%size(), device_to_host, sync=.false.)
212 end if
213 if (associated(this%s)) then
214 call device_memcpy(this%s%x, this%s%x_d, &
215 this%s%dof%size(), device_to_host, sync=.false.)
216 call device_memcpy(this%slag%lf(1)%x, this%slag%lf(1)%x_d, &
217 this%s%dof%size(), device_to_host, sync=.false.)
218 call device_memcpy(this%slag%lf(2)%x, this%slag%lf(2)%x_d, &
219 this%s%dof%size(), device_to_host, sync=.false.)
220 call device_memcpy(this%abs1%x, this%abs1%x_d, &
221 w%dof%size(), device_to_host, sync=.false.)
222 call device_memcpy(this%abs2%x, this%abs2%x_d, &
223 w%dof%size(), device_to_host, sync=.false.)
224 end if
225
226 ! Multi-scalar lag field synchronization
227 if (allocated(this%scalar_lags%items) .and. this%scalar_lags%size() > 0) then
228 do i = 1, this%scalar_lags%size()
229 block
230 type(field_series_t), pointer :: slag
231 integer :: slag_size, dof_size
232 slag => this%scalar_lags%get(i)
233 slag_size = slag%size()
234 dof_size = slag%f%dof%size()
235 do j = 1, slag_size
236 call device_memcpy(slag%lf(j)%x, slag%lf(j)%x_d, &
237 dof_size, device_to_host, sync=.false.)
238 end do
239 end block
240 end do
241 end if
242
243 ! Multi-scalar ABX field synchronization
244 if (allocated(this%scalar_abx1) .and. allocated(this%scalar_abx2)) then
245 do i = 1, size(this%scalar_abx1)
246 call device_memcpy(this%scalar_abx1(i)%ptr%x, this%scalar_abx1(i)%ptr%x_d, &
247 this%scalar_abx1(i)%ptr%dof%size(), device_to_host, sync=.false.)
248 call device_memcpy(this%scalar_abx2(i)%ptr%x, this%scalar_abx2(i)%ptr%x_d, &
249 this%scalar_abx2(i)%ptr%dof%size(), device_to_host, sync=.false.)
250 end do
251 end if
252 end associate
253 call device_sync(glb_cmd_queue)
254 end if
255
256 end subroutine chkp_sync_host
257
259 subroutine chkp_sync_device(this)
260 class(chkp_t), intent(inout) :: this
261 integer :: i, j
262
263 if (neko_bcknd_device .eq. 1) then
264 associate(u=>this%u, v=>this%v, w=>this%w, &
265 ulag=>this%ulag, vlag=>this%vlag, wlag=>this%wlag,&
266 p=>this%p)
267
268 if (associated(this%u) .and. associated(this%v) .and. &
269 associated(this%w)) then
270 call device_memcpy(u%x, u%x_d, u%dof%size(), &
271 host_to_device, sync=.false.)
272 call device_memcpy(v%x, v%x_d, v%dof%size(), &
273 host_to_device, sync=.false.)
274 call device_memcpy(w%x, w%x_d, w%dof%size(), &
275 host_to_device, sync=.false.)
276 call device_memcpy(p%x, p%x_d, p%dof%size(), &
277 host_to_device, sync=.false.)
278 end if
279
280 if (associated(this%ulag) .and. associated(this%vlag) .and. &
281 associated(this%wlag)) then
282 call device_memcpy(ulag%lf(1)%x, ulag%lf(1)%x_d, u%dof%size(), &
283 host_to_device, sync=.false.)
284 call device_memcpy(ulag%lf(2)%x, ulag%lf(2)%x_d, u%dof%size(), &
285 host_to_device, sync=.false.)
286
287 call device_memcpy(vlag%lf(1)%x, vlag%lf(1)%x_d, v%dof%size(), &
288 host_to_device, sync=.false.)
289 call device_memcpy(vlag%lf(2)%x, vlag%lf(2)%x_d, v%dof%size(), &
290 host_to_device, sync=.false.)
291
292 call device_memcpy(wlag%lf(1)%x, wlag%lf(1)%x_d, w%dof%size(), &
293 host_to_device, sync=.false.)
294 call device_memcpy(wlag%lf(2)%x, wlag%lf(2)%x_d, w%dof%size(), &
295 host_to_device, sync=.false.)
296 end if
297 if (associated(this%s)) then
298 call device_memcpy(this%s%x, this%s%x_d, this%s%dof%size(), &
299 host_to_device, sync=.false.)
300
301 call device_memcpy(this%slag%lf(1)%x, this%slag%lf(1)%x_d, &
302 this%s%dof%size(), host_to_device, sync=.false.)
303 call device_memcpy(this%slag%lf(2)%x, this%slag%lf(2)%x_d, &
304 this%s%dof%size(), host_to_device, sync=.false.)
305 call device_memcpy(this%abs1%x, this%abs1%x_d, &
306 w%dof%size(), host_to_device, sync=.false.)
307 call device_memcpy(this%abs2%x, this%abs2%x_d, &
308 w%dof%size(), host_to_device, sync=.false.)
309 end if
310
311 ! Multi-scalar lag field synchronization
312 if (allocated(this%scalar_lags%items) .and. this%scalar_lags%size() > 0) then
313 do i = 1, this%scalar_lags%size()
314 block
315 type(field_series_t), pointer :: slag
316 integer :: slag_size, dof_size
317 slag => this%scalar_lags%get(i)
318 slag_size = slag%size()
319 dof_size = slag%f%dof%size()
320 do j = 1, slag_size
321 call device_memcpy(slag%lf(j)%x, slag%lf(j)%x_d, &
322 dof_size, host_to_device, sync=.false.)
323 end do
324 end block
325 end do
326 end if
327
328 ! Multi-scalar ABX field synchronization
329 if (allocated(this%scalar_abx1) .and. allocated(this%scalar_abx2)) then
330 do i = 1, size(this%scalar_abx1)
331 call device_memcpy(this%scalar_abx1(i)%ptr%x, this%scalar_abx1(i)%ptr%x_d, &
332 this%scalar_abx1(i)%ptr%dof%size(), host_to_device, sync=.false.)
333 call device_memcpy(this%scalar_abx2(i)%ptr%x, this%scalar_abx2(i)%ptr%x_d, &
334 this%scalar_abx2(i)%ptr%dof%size(), host_to_device, sync=.false.)
335 end do
336 end if
337 end associate
338 end if
339
340 end subroutine chkp_sync_device
341
343 subroutine chkp_add_lag(this, ulag, vlag, wlag)
344 class(chkp_t), intent(inout) :: this
345 type(field_series_t), target :: ulag
346 type(field_series_t), target :: vlag
347 type(field_series_t), target :: wlag
348
349 this%ulag => ulag
350 this%vlag => vlag
351 this%wlag => wlag
352
353 end subroutine chkp_add_lag
354
355
356
358 subroutine chkp_add_scalar(this, s, slag, abs1, abs2)
359 class(chkp_t), intent(inout) :: this
360 type(field_t), target, intent(in) :: s
361 type(field_series_t), target, intent(in) :: slag
362 type(field_t), target, intent(in), optional :: abs1, abs2
363
364 this%s => s
365 this%slag => slag
366
367 if (present(abs1)) this%abs1 => abs1
368 if (present(abs2)) this%abs2 => abs2
369
370 end subroutine chkp_add_scalar
371
372
374 pure function chkp_restart_time(this) result(rtime)
375 class(chkp_t), intent(in) :: this
376 real(kind=dp) :: rtime
377
378 rtime = this%t
379 end function chkp_restart_time
380
381end module checkpoint
Copy data between host and device (or device and device)
Definition device.F90:71
Synchronize a device or stream.
Definition device.F90:107
Defines a checkpoint.
subroutine chkp_sync_host(this)
Synchronize checkpoint with device.
subroutine chkp_init(this, u, v, w, p)
Initialize checkpoint structure with mandatory data.
subroutine chkp_sync_device(this)
Synchronize device with checkpoint.
pure real(kind=dp) function chkp_restart_time(this)
Return restart time from a loaded checkpoint.
subroutine chkp_free(this)
Reset checkpoint.
subroutine chkp_add_lag(this, ulag, vlag, wlag)
Add lagged velocity terms.
subroutine chkp_add_scalar(this, s, slag, abs1, abs2)
Add a scalar to checkpointing.
Device abstraction, common interface for various accelerators.
Definition device.F90:34
integer, parameter, public host_to_device
Definition device.F90:47
integer, parameter, public device_to_host
Definition device.F90:47
type(c_ptr), bind(C), public glb_cmd_queue
Global command queue.
Definition device.F90:51
Contains the field_series_list_t type for managing multiple field series.
Contains the field_serties_t type.
Defines a field.
Definition field.f90:34
Definition math.f90:60
real(kind=rp), parameter, public neko_eps
Machine epsilon .
Definition math.f90:69
Defines a mesh.
Definition mesh.f90:34
Build configurations.
integer, parameter neko_bcknd_device
integer, parameter, public dp
Definition num_types.f90:9
integer, parameter, public rp
Global precision used in computations.
Definition num_types.f90:12
Defines a function space.
Definition space.f90:34
Utilities.
Definition utils.f90:35
field_ptr_t, To easily obtain a pointer to a field
Definition field.f90:82
Stores a series (sequence) of fields, logically connected to a base field, and arranged according to ...
A list of field series pointers, used for managing multiple scalar lag fields.
The function space for the SEM solution fields.
Definition space.f90:63