Loading [MathJax]/extensions/tex2jax.js
Neko 0.9.1
A portable framework for high-order spectral element flow simulations
All Classes Namespaces Files Functions Variables Typedefs Enumerator Macros Pages
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
38 use space
39 use device
40 use field, only : field_t
41 use utils, only : neko_error
42 use mesh, only: mesh_t
43 implicit none
44 private
45
46 type, public :: chkp_t
47 type(field_t), pointer :: u => null()
48 type(field_t), pointer :: v => null()
49 type(field_t), pointer :: w => null()
50 type(field_t), pointer :: p => null()
51
52
53 !
54 ! Optional payload
55 !
56 type(field_series_t), pointer :: ulag => null()
57 type(field_series_t), pointer :: vlag => null()
58 type(field_series_t), pointer :: wlag => null()
59
60 real(kind=rp), pointer :: tlag(:) => null()
61 real(kind=rp), pointer :: dtlag(:) => null()
62
64 type(field_t), pointer :: abx1 => null()
65 type(field_t), pointer :: abx2 => null()
66 type(field_t), pointer :: aby1 => null()
67 type(field_t), pointer :: aby2 => null()
68 type(field_t), pointer :: abz1 => null()
69 type(field_t), pointer :: abz2 => null()
70
71
72 type(field_t), pointer :: s => null()
73 type(field_series_t), pointer :: slag => null()
74
75 type(field_t), pointer :: abs1 => null()
76 type(field_t), pointer :: abs2 => null()
77
78 real(kind=dp) :: t
79 type(mesh_t) :: previous_mesh
80 type(space_t) :: previous_xh
81 real(kind=rp) :: mesh2mesh_tol = 1d-6
82
83 contains
84 procedure, pass(this) :: init => chkp_init
85 procedure, pass(this) :: sync_host => chkp_sync_host
86 procedure, pass(this) :: sync_device => chkp_sync_device
87 procedure, pass(this) :: add_lag => chkp_add_lag
88 procedure, pass(this) :: add_scalar => chkp_add_scalar
89 procedure, pass(this) :: restart_time => chkp_restart_time
90 final :: chkp_free
91 end type chkp_t
92
93contains
94
96 subroutine chkp_init(this, u, v, w, p)
97 class(chkp_t), intent(inout) :: this
98 type(field_t), intent(in), target :: u
99 type(field_t), intent(in), target :: v
100 type(field_t), intent(in), target :: w
101 type(field_t), intent(in), target :: p
102
103 ! Check that all velocity components are defined on the same
104 ! function space
105 if ( u%Xh .ne. v%Xh .or. &
106 u%Xh .ne. w%Xh ) then
107 call neko_error('Different function spaces for each velocity component')
108 end if
109
110 ! Check that both velocity and pressure is defined on the same mesh
111 if ( u%msh%nelv .ne. p%msh%nelv ) then
112 call neko_error('Velocity and pressure defined on different meshes')
113 end if
114
115 this%u => u
116 this%v => v
117 this%w => w
118 this%p => p
119
120 this%t = 0d0
121
122 end subroutine chkp_init
123
125 subroutine chkp_free(this)
126 type(chkp_t), intent(inout) :: this
127
128 nullify(this%u)
129 nullify(this%v)
130 nullify(this%w)
131 nullify(this%p)
132
133 nullify(this%ulag)
134 nullify(this%vlag)
135 nullify(this%wlag)
136
137 end subroutine chkp_free
138
140 subroutine chkp_sync_host(this)
141 class(chkp_t), intent(inout) :: this
142
143 if (neko_bcknd_device .eq. 1) then
144 associate(u=>this%u, v=>this%v, w=>this%w, &
145 ulag=>this%ulag, vlag=>this%vlag, wlag=>this%wlag, &
146 p=>this%p)
147
148 if (associated(this%u) .and. associated(this%v) .and. &
149 associated(this%w) .and. associated(this%p)) then
150 call device_memcpy(u%x, u%x_d, u%dof%size(), device_to_host, sync=.false.)
151 call device_memcpy(v%x, v%x_d, v%dof%size(), device_to_host, sync=.false.)
152 call device_memcpy(w%x, w%x_d, w%dof%size(), device_to_host, sync=.false.)
153 call device_memcpy(p%x, p%x_d, p%dof%size(), device_to_host, sync=.false.)
154 end if
155
156 if (associated(this%ulag) .and. associated(this%vlag) .and. &
157 associated(this%wlag)) then
158 call device_memcpy(ulag%lf(1)%x, ulag%lf(1)%x_d, &
159 u%dof%size(), device_to_host, sync=.false.)
160 call device_memcpy(ulag%lf(2)%x, ulag%lf(2)%x_d, &
161 u%dof%size(), device_to_host, sync=.false.)
162
163 call device_memcpy(vlag%lf(1)%x, vlag%lf(1)%x_d, &
164 v%dof%size(), device_to_host, sync=.false.)
165 call device_memcpy(vlag%lf(2)%x, vlag%lf(2)%x_d, &
166 v%dof%size(), device_to_host, sync=.false.)
167
168 call device_memcpy(wlag%lf(1)%x, wlag%lf(1)%x_d, &
169 w%dof%size(), device_to_host, sync=.false.)
170 call device_memcpy(wlag%lf(2)%x, wlag%lf(2)%x_d, &
171 w%dof%size(), device_to_host, sync=.false.)
172 call device_memcpy(this%abx1%x, this%abx1%x_d, &
173 w%dof%size(), device_to_host, sync=.false.)
174 call device_memcpy(this%abx2%x, this%abx2%x_d, &
175 w%dof%size(), device_to_host, sync=.false.)
176 call device_memcpy(this%aby1%x, this%aby1%x_d, &
177 w%dof%size(), device_to_host, sync=.false.)
178 call device_memcpy(this%aby2%x, this%aby2%x_d, &
179 w%dof%size(), device_to_host, sync=.false.)
180 call device_memcpy(this%abz1%x, this%abz1%x_d, &
181 w%dof%size(), device_to_host, sync=.false.)
182 call device_memcpy(this%abz2%x, this%abz2%x_d, &
183 w%dof%size(), device_to_host, sync=.false.)
184 end if
185 if (associated(this%s)) then
186 call device_memcpy(this%s%x, this%s%x_d, &
187 this%s%dof%size(), device_to_host, sync=.false.)
188 call device_memcpy(this%slag%lf(1)%x, this%slag%lf(1)%x_d, &
189 this%s%dof%size(), device_to_host, sync=.false.)
190 call device_memcpy(this%slag%lf(2)%x, this%slag%lf(2)%x_d, &
191 this%s%dof%size(), device_to_host, sync=.false.)
192 call device_memcpy(this%abs1%x, this%abs1%x_d, &
193 w%dof%size(), device_to_host, sync=.false.)
194 call device_memcpy(this%abs2%x, this%abs2%x_d, &
195 w%dof%size(), device_to_host, sync=.false.)
196 end if
197 end associate
198 call device_sync(glb_cmd_queue)
199 end if
200
201 end subroutine chkp_sync_host
202
204 subroutine chkp_sync_device(this)
205 class(chkp_t), intent(inout) :: this
206
207 if (neko_bcknd_device .eq. 1) then
208 associate(u=>this%u, v=>this%v, w=>this%w, &
209 ulag=>this%ulag, vlag=>this%vlag, wlag=>this%wlag,&
210 p=>this%p)
211
212 if (associated(this%u) .and. associated(this%v) .and. &
213 associated(this%w)) then
214 call device_memcpy(u%x, u%x_d, u%dof%size(), &
215 host_to_device, sync=.false.)
216 call device_memcpy(v%x, v%x_d, v%dof%size(), &
217 host_to_device, sync=.false.)
218 call device_memcpy(w%x, w%x_d, w%dof%size(), &
219 host_to_device, sync=.false.)
220 call device_memcpy(p%x, p%x_d, p%dof%size(), &
221 host_to_device, sync=.false.)
222 end if
223
224 if (associated(this%ulag) .and. associated(this%vlag) .and. &
225 associated(this%wlag)) then
226 call device_memcpy(ulag%lf(1)%x, ulag%lf(1)%x_d, u%dof%size(), &
227 host_to_device, sync=.false.)
228 call device_memcpy(ulag%lf(2)%x, ulag%lf(2)%x_d, u%dof%size(), &
229 host_to_device, sync=.false.)
230
231 call device_memcpy(vlag%lf(1)%x, vlag%lf(1)%x_d, v%dof%size(), &
232 host_to_device, sync=.false.)
233 call device_memcpy(vlag%lf(2)%x, vlag%lf(2)%x_d, v%dof%size(), &
234 host_to_device, sync=.false.)
235
236 call device_memcpy(wlag%lf(1)%x, wlag%lf(1)%x_d, w%dof%size(), &
237 host_to_device, sync=.false.)
238 call device_memcpy(wlag%lf(2)%x, wlag%lf(2)%x_d, w%dof%size(), &
239 host_to_device, sync=.false.)
240 end if
241 if (associated(this%s)) then
242 call device_memcpy(this%s%x, this%s%x_d, this%s%dof%size(), &
243 host_to_device, sync=.false.)
244
245 call device_memcpy(this%slag%lf(1)%x, this%slag%lf(1)%x_d, &
246 this%s%dof%size(), host_to_device, sync=.false.)
247 call device_memcpy(this%slag%lf(2)%x, this%slag%lf(2)%x_d, &
248 this%s%dof%size(), host_to_device, sync=.false.)
249 call device_memcpy(this%abs1%x, this%abs1%x_d, &
250 w%dof%size(), host_to_device, sync=.false.)
251 call device_memcpy(this%abs2%x, this%abs2%x_d, &
252 w%dof%size(), host_to_device, sync=.false.)
253 end if
254 end associate
255 end if
256
257 end subroutine chkp_sync_device
258
260 subroutine chkp_add_lag(this, ulag, vlag, wlag)
261 class(chkp_t), intent(inout) :: this
262 type(field_series_t), target :: ulag
263 type(field_series_t), target :: vlag
264 type(field_series_t), target :: wlag
265
266 this%ulag => ulag
267 this%vlag => vlag
268 this%wlag => wlag
269
270 end subroutine chkp_add_lag
271
273 subroutine chkp_add_scalar(this, s)
274 class(chkp_t), intent(inout) :: this
275 type(field_t), target :: s
276
277 this%s => s
278
279 end subroutine chkp_add_scalar
280
281
283 pure function chkp_restart_time(this) result(rtime)
284 class(chkp_t), intent(in) :: this
285 real(kind=dp) :: rtime
286
287 rtime = this%t
288 end function chkp_restart_time
289
290end module checkpoint
Copy data between host and device (or device and device)
Definition device.F90:51
Synchronize a device or stream.
Definition device.F90:87
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.
subroutine chkp_add_scalar(this, s)
Add scalars.
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.
Device abstraction, common interface for various accelerators.
Definition device.F90:34
integer, parameter, public device_to_host
Definition device.F90:47
Stores a series fields.
Defines a field.
Definition field.f90:34
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
The function space for the SEM solution fields.
Definition space.f90:62