17 subroutine fstr_read_restart(cstep,substep,step_count,ctime,dtime,hecMESH,fstrSOLID,fstrPARAM,contactNode)
19 integer,
intent(out) :: cstep
20 integer,
intent(out) :: substep
21 integer,
intent(out) :: step_count
22 real(kind=kreal),
intent(out) :: ctime
23 real(kind=kreal),
intent(out) :: dtime
24 integer,
intent(out) :: contactNode
25 type (hecmwST_local_mesh),
intent(in) :: hecMESH
26 type (fstr_solid),
intent(inout) :: fstrSOLID
29 integer :: i,j,restrt_step(3),nif(2),istat(1),nload_prev(1),naux(2)
30 real(kind=kreal) :: times(3)
32 call hecmw_restart_open()
34 call hecmw_restart_read_int(restrt_step)
35 if( fstrparam%restart_version >= 5 )
then
36 if(
myrank == 0 )
write(*,*)
'Reading restart file as new format(>=ver5.0)'
37 call hecmw_restart_read_real(times)
38 call hecmw_restart_read_int(fstrsolid%NRstat_i)
39 call hecmw_restart_read_real(fstrsolid%NRstat_r)
40 call hecmw_restart_read_int(istat)
42 if(
myrank == 0 )
write(*,*)
'Reading restart file as old format(<ver5.0)'
44 call hecmw_restart_read_int(nload_prev)
45 if( nload_prev(1)>0 )
then
46 allocate(fstrsolid%step_ctrl_restart%Load(nload_prev(1)))
47 call hecmw_restart_read_int(fstrsolid%step_ctrl_restart%Load)
50 call hecmw_restart_read_real(fstrsolid%unode)
51 call hecmw_restart_read_real(fstrsolid%unode_bak)
52 call hecmw_restart_read_real(fstrsolid%QFORCE)
54 do i= 1, hecmesh%n_elem
55 if (hecmw_is_etype_link( fstrsolid%elements(i)%etype )) cycle
56 if (hecmw_is_etype_patch( fstrsolid%elements(i)%etype )) cycle
57 do j= 1,
size(fstrsolid%elements(i)%gausses)
58 call hecmw_restart_read_int(nif)
59 call hecmw_restart_read_real(fstrsolid%elements(i)%gausses(j)%strain)
60 call hecmw_restart_read_real(fstrsolid%elements(i)%gausses(j)%strain_bak)
61 call hecmw_restart_read_real(fstrsolid%elements(i)%gausses(j)%stress)
62 call hecmw_restart_read_real(fstrsolid%elements(i)%gausses(j)%stress_bak)
63 if( nif(1)>0 )
call hecmw_restart_read_int(fstrsolid%elements(i)%gausses(j)%istatus)
64 if( nif(2)>0 )
call hecmw_restart_read_real(fstrsolid%elements(i)%gausses(j)%fstatus)
66 call hecmw_restart_read_int(naux)
68 call hecmw_restart_read_real(fstrsolid%elements(i)%aux(:,j))
72 if(
associated( fstrsolid%contacts ) )
then
73 call hecmw_restart_read_int(nif)
75 do i= 1, fstrsolid%n_contacts
76 do j= 1,
size(fstrsolid%contacts(i)%slave)
77 call hecmw_restart_read_int(nif)
78 fstrsolid%contacts(i)%states(j)%surface = nif(1)
79 fstrsolid%contacts(i)%states(j)%state = nif(2)
80 call hecmw_restart_read_real(fstrsolid%contacts(i)%states(j)%lpos)
81 call hecmw_restart_read_real(fstrsolid%contacts(i)%states(j)%direction)
82 call hecmw_restart_read_real(fstrsolid%contacts(i)%states(j)%multiplier)
83 call hecmw_restart_read_real(fstrsolid%contacts(i)%states(j)%tangentForce_trial)
84 call hecmw_restart_read_real(fstrsolid%contacts(i)%states(j)%tangentForce_final)
89 call hecmw_restart_close()
91 cstep = restrt_step(1)
92 substep = restrt_step(2) + 1
93 step_count = restrt_step(3)
94 if( fstrparam%restart_version >= 5 )
then
97 fstrsolid%AutoINC_stat = istat(1)
98 if( dabs(times(1)-times(3)) < 1.d-10 )
then
102 do i=1,
size(fstrsolid%step_ctrl)
103 fstrsolid%step_ctrl(i)%starttime = fstrsolid%step_ctrl(i)%starttime + times(3)
106 ctime = fstrsolid%step_ctrl(cstep)%starttime
107 ctime = ctime + dble(substep-1)*fstrsolid%step_ctrl(cstep)%initdt
108 dtime = fstrsolid%step_ctrl(cstep)%initdt
109 if( dabs(ctime-fstrsolid%step_ctrl(cstep)%starttime-fstrsolid%step_ctrl(cstep)%elapsetime) < 1.d-10 )
then
119 subroutine fstr_write_restart(cstep,cstep_ext,substep,step_count,ctime,dtime,hecMESH, &
120 & fstrSOLID,fstrPARAM,is_StepFinished,contactNode)
122 integer,
intent(in) :: cstep
123 integer,
intent(in) :: cstep_ext
124 integer,
intent(in) :: substep
125 integer,
intent(in) :: step_count
126 real(kind=kreal),
intent(in) :: ctime
127 real(kind=kreal),
intent(in) :: dtime
128 logical,
intent(in) :: is_StepFinished
129 integer,
intent(in) :: contactNode
130 type (hecmwST_local_mesh),
intent(in) :: hecMESH
131 type (fstr_solid),
intent(in) :: fstrSOLID
134 integer :: i,j,restrt_step(3),nif(2),istat(1),nload_prev(1),naux(2)
135 real(kind=kreal) :: times(3)
137 restrt_step(1) = cstep_ext
138 restrt_step(2) = substep
139 restrt_step(3) = step_count
142 if( is_stepfinished )
then
145 times(3) = fstrsolid%step_ctrl(cstep)%starttime
147 istat(1) = fstrsolid%AutoINC_stat
148 call hecmw_restart_add_int(restrt_step,
size(restrt_step))
149 if( fstrparam%restart_version >= 5 )
then
150 call hecmw_restart_add_real(times,
size(times))
151 call hecmw_restart_add_int(fstrsolid%NRstat_i,
size(fstrsolid%NRstat_i))
152 call hecmw_restart_add_real(fstrsolid%NRstat_r,
size(fstrsolid%NRstat_r))
153 call hecmw_restart_add_int(istat,1)
156 if( is_stepfinished )
then
157 if(
associated(fstrsolid%step_ctrl(cstep)%Load) ) nload_prev(1) =
size(fstrsolid%step_ctrl(cstep)%Load)
158 call hecmw_restart_add_int(nload_prev,1)
159 if( nload_prev(1)>0 )
call hecmw_restart_add_int(fstrsolid%step_ctrl(cstep)%Load,nload_prev(1))
162 if(
associated(fstrsolid%step_ctrl(cstep-1)%Load) ) nload_prev(1) =
size(fstrsolid%step_ctrl(cstep-1)%Load)
163 call hecmw_restart_add_int(nload_prev,1)
164 if( nload_prev(1)>0 )
call hecmw_restart_add_int(fstrsolid%step_ctrl(cstep-1)%Load,nload_prev(1))
166 if(
associated(fstrsolid%step_ctrl_restart%Load) ) nload_prev(1) =
size(fstrsolid%step_ctrl_restart%Load)
167 call hecmw_restart_add_int(nload_prev,1)
168 if( nload_prev(1)>0 )
call hecmw_restart_add_int(fstrsolid%step_ctrl_restart%Load,nload_prev(1))
172 call hecmw_restart_add_real(fstrsolid%unode,
size(fstrsolid%unode))
173 call hecmw_restart_add_real(fstrsolid%unode_bak,
size(fstrsolid%unode_bak))
174 call hecmw_restart_add_real(fstrsolid%QFORCE,
size(fstrsolid%QFORCE))
176 do i= 1, hecmesh%n_elem
177 if (hecmw_is_etype_link( fstrsolid%elements(i)%etype )) cycle
178 if (hecmw_is_etype_patch( fstrsolid%elements(i)%etype )) cycle
179 do j= 1,
size(fstrsolid%elements(i)%gausses)
181 if(
associated(fstrsolid%elements(i)%gausses(j)%istatus) ) nif(1)=
size(fstrsolid%elements(i)%gausses(j)%istatus)
182 if(
associated(fstrsolid%elements(i)%gausses(j)%fstatus) ) nif(2)=
size(fstrsolid%elements(i)%gausses(j)%fstatus)
183 call hecmw_restart_add_int(nif,
size(nif))
184 call hecmw_restart_add_real(fstrsolid%elements(i)%gausses(j)%strain,
size(fstrsolid%elements(i)%gausses(j)%strain))
185 call hecmw_restart_add_real(fstrsolid%elements(i)%gausses(j)%strain_bak,
size(fstrsolid%elements(i)%gausses(j)%strain_bak))
186 call hecmw_restart_add_real(fstrsolid%elements(i)%gausses(j)%stress,
size(fstrsolid%elements(i)%gausses(j)%stress))
187 call hecmw_restart_add_real(fstrsolid%elements(i)%gausses(j)%stress_bak,
size(fstrsolid%elements(i)%gausses(j)%stress_bak))
189 call hecmw_restart_add_int(fstrsolid%elements(i)%gausses(j)%istatus,
size(fstrsolid%elements(i)%gausses(j)%istatus))
192 call hecmw_restart_add_real(fstrsolid%elements(i)%gausses(j)%fstatus,
size(fstrsolid%elements(i)%gausses(j)%fstatus))
196 if(
associated(fstrsolid%elements(i)%aux) ) naux=shape(fstrsolid%elements(i)%aux)
197 call hecmw_restart_add_int(naux,
size(naux))
199 call hecmw_restart_add_real(fstrsolid%elements(i)%aux(:,j),naux(1))
203 if(
associated( fstrsolid%contacts ) )
then
205 call hecmw_restart_add_int(nif,
size(nif))
206 do i= 1, fstrsolid%n_contacts
207 do j= 1,
size(fstrsolid%contacts(i)%slave)
208 nif(1) = fstrsolid%contacts(i)%states(j)%surface
209 nif(2) = fstrsolid%contacts(i)%states(j)%state
210 call hecmw_restart_add_int(nif,
size(nif))
211 call hecmw_restart_add_real(fstrsolid%contacts(i)%states(j)%lpos,
size(fstrsolid%contacts(i)%states(j)%lpos))
212 call hecmw_restart_add_real(fstrsolid%contacts(i)%states(j)%direction,
size(fstrsolid%contacts(i)%states(j)%direction))
213 call hecmw_restart_add_real(fstrsolid%contacts(i)%states(j)%multiplier,
size(fstrsolid%contacts(i)%states(j)%multiplier))
214 call hecmw_restart_add_real(fstrsolid%contacts(i)%states(j)%tangentForce_trial, &
215 size(fstrsolid%contacts(i)%states(j)%tangentForce_trial))
216 call hecmw_restart_add_real(fstrsolid%contacts(i)%states(j)%tangentForce_final, &
217 size(fstrsolid%contacts(i)%states(j)%tangentForce_final))
222 call hecmw_restart_write()
230 integer,
intent(out) :: cstep
231 integer,
intent(out),
optional :: contactNode
232 type (hecmwST_local_mesh),
intent(in) :: hecMESH
233 type (fstr_solid),
intent(inout) :: fstrSOLID
234 type ( fstr_dynamic),
intent(inout) :: fstrDYNAMIC
237 integer :: i,j,restrt_step(1),nif(2),naux(2)
238 real(kind=kreal) ::
data(2)
240 call hecmw_restart_open()
242 call hecmw_restart_read_int(restrt_step)
243 cstep = restrt_step(1)
244 call hecmw_restart_read_real(fstrsolid%unode)
245 call hecmw_restart_read_real(fstrsolid%QFORCE)
247 do i= 1, hecmesh%n_elem
248 if (hecmw_is_etype_link( fstrsolid%elements(i)%etype )) cycle
249 if (hecmw_is_etype_patch( fstrsolid%elements(i)%etype )) cycle
250 do j= 1,
size(fstrsolid%elements(i)%gausses)
251 call hecmw_restart_read_int(nif)
252 call hecmw_restart_read_real(fstrsolid%elements(i)%gausses(j)%strain)
253 call hecmw_restart_read_real(fstrsolid%elements(i)%gausses(j)%strain_bak)
254 call hecmw_restart_read_real(fstrsolid%elements(i)%gausses(j)%stress)
255 call hecmw_restart_read_real(fstrsolid%elements(i)%gausses(j)%stress_bak)
256 if( nif(1)>0 )
call hecmw_restart_read_int(fstrsolid%elements(i)%gausses(j)%istatus)
257 if( nif(2)>0 )
call hecmw_restart_read_real(fstrsolid%elements(i)%gausses(j)%fstatus)
259 call hecmw_restart_read_int(naux)
261 call hecmw_restart_read_real(fstrsolid%elements(i)%aux(:,j))
265 if(
present(contactnode))
then
266 call hecmw_restart_read_int(nif)
268 do i= 1, fstrsolid%n_contacts
269 do j= 1,
size(fstrsolid%contacts(i)%slave)
270 call hecmw_restart_read_int(nif)
271 fstrsolid%contacts(i)%states(j)%surface = nif(1)
272 fstrsolid%contacts(i)%states(j)%state = nif(2)
273 call hecmw_restart_read_real(fstrsolid%contacts(i)%states(j)%lpos)
274 call hecmw_restart_read_real(fstrsolid%contacts(i)%states(j)%direction)
275 call hecmw_restart_read_real(fstrsolid%contacts(i)%states(j)%multiplier)
276 call hecmw_restart_read_real(fstrsolid%contacts(i)%states(j)%tangentForce_trial)
277 call hecmw_restart_read_real(fstrsolid%contacts(i)%states(j)%tangentForce_final)
282 call hecmw_restart_read_int(restrt_step)
283 fstrdynamic%idx_eqa = restrt_step(1)
284 call hecmw_restart_read_real(data)
285 fstrdynamic%t_curr =
data(1)
286 fstrdynamic%strainEnergy =
data(2)
287 if( fstrdynamic%idx_eqa == 1 )
then
288 call hecmw_restart_read_real(fstrdynamic%DISP(:,1))
289 call hecmw_restart_read_real(fstrdynamic%VEL(:,1))
290 call hecmw_restart_read_real(fstrdynamic%ACC(:,1))
292 call hecmw_restart_read_real(fstrdynamic%DISP(:,1))
293 call hecmw_restart_read_real(fstrdynamic%DISP(:,3))
295 do i= 1, hecmesh%n_elem
296 if (hecmw_is_etype_link( fstrsolid%elements(i)%etype )) cycle
297 if (hecmw_is_etype_patch( fstrsolid%elements(i)%etype )) cycle
298 call hecmw_restart_read_real(fstrsolid%elements(i)%equiForces)
301 call hecmw_restart_close()
309 integer,
intent(in) :: cstep
310 integer,
intent(in),
optional :: contactNode
311 type (hecmwST_local_mesh),
intent(in) :: hecMESH
312 type (fstr_solid),
intent(in) :: fstrSOLID
313 type ( fstr_dynamic),
intent(in) :: fstrDYNAMIC
316 integer :: i,j,restrt_step(1),nif(2),naux(2)
317 real(kind=kreal) ::
data(2)
319 restrt_step(1) = cstep
320 call hecmw_restart_add_int(restrt_step,
size(restrt_step))
321 call hecmw_restart_add_real(fstrsolid%unode,
size(fstrsolid%unode))
322 call hecmw_restart_add_real(fstrsolid%QFORCE,
size(fstrsolid%QFORCE))
324 do i= 1, hecmesh%n_elem
325 if (hecmw_is_etype_link( fstrsolid%elements(i)%etype )) cycle
326 if (hecmw_is_etype_patch( fstrsolid%elements(i)%etype )) cycle
327 do j= 1,
size(fstrsolid%elements(i)%gausses)
329 if(
associated(fstrsolid%elements(i)%gausses(j)%istatus) ) nif(1)=
size(fstrsolid%elements(i)%gausses(j)%istatus)
330 if(
associated(fstrsolid%elements(i)%gausses(j)%fstatus) ) nif(2)=
size(fstrsolid%elements(i)%gausses(j)%fstatus)
331 call hecmw_restart_add_int(nif,
size(nif))
332 call hecmw_restart_add_real(fstrsolid%elements(i)%gausses(j)%strain,
size(fstrsolid%elements(i)%gausses(j)%strain))
333 call hecmw_restart_add_real(fstrsolid%elements(i)%gausses(j)%strain_bak,
size(fstrsolid%elements(i)%gausses(j)%strain_bak))
334 call hecmw_restart_add_real(fstrsolid%elements(i)%gausses(j)%stress,
size(fstrsolid%elements(i)%gausses(j)%stress))
335 call hecmw_restart_add_real(fstrsolid%elements(i)%gausses(j)%stress_bak,
size(fstrsolid%elements(i)%gausses(j)%stress_bak))
337 call hecmw_restart_add_int(fstrsolid%elements(i)%gausses(j)%istatus,
size(fstrsolid%elements(i)%gausses(j)%istatus))
340 call hecmw_restart_add_real(fstrsolid%elements(i)%gausses(j)%fstatus,
size(fstrsolid%elements(i)%gausses(j)%fstatus))
344 if(
associated(fstrsolid%elements(i)%aux) ) naux=shape(fstrsolid%elements(i)%aux)
345 call hecmw_restart_add_int(naux,
size(naux))
347 call hecmw_restart_add_real(fstrsolid%elements(i)%aux(:,j),naux(1))
351 if(
present(contactnode))
then
353 call hecmw_restart_add_int(nif,
size(nif))
354 do i= 1, fstrsolid%n_contacts
355 do j= 1,
size(fstrsolid%contacts(i)%slave)
356 nif(1) = fstrsolid%contacts(i)%states(j)%surface
357 nif(2) = fstrsolid%contacts(i)%states(j)%state
358 call hecmw_restart_add_int(nif,
size(nif))
359 call hecmw_restart_add_real(fstrsolid%contacts(i)%states(j)%lpos,
size(fstrsolid%contacts(i)%states(j)%lpos))
360 call hecmw_restart_add_real(fstrsolid%contacts(i)%states(j)%direction,
size(fstrsolid%contacts(i)%states(j)%direction))
361 call hecmw_restart_add_real(fstrsolid%contacts(i)%states(j)%multiplier,
size(fstrsolid%contacts(i)%states(j)%multiplier))
362 call hecmw_restart_add_real(fstrsolid%contacts(i)%states(j)%tangentForce_trial, &
363 size(fstrsolid%contacts(i)%states(j)%tangentForce_trial))
364 call hecmw_restart_add_real(fstrsolid%contacts(i)%states(j)%tangentForce_final, &
365 size(fstrsolid%contacts(i)%states(j)%tangentForce_final))
370 restrt_step(1) = fstrdynamic%idx_eqa
371 call hecmw_restart_add_int(restrt_step,
size(restrt_step))
372 data(1) = fstrdynamic%t_curr
373 data(2) = fstrdynamic%strainEnergy
374 call hecmw_restart_add_real(
data,
size(data))
375 if( fstrdynamic%idx_eqa == 1 )
then
376 call hecmw_restart_add_real(fstrdynamic%DISP(:,1),
size(fstrdynamic%DISP(:,1)))
377 call hecmw_restart_add_real(fstrdynamic%VEL(:,1),
size(fstrdynamic%VEL(:,1)))
378 call hecmw_restart_add_real(fstrdynamic%ACC(:,1),
size(fstrdynamic%ACC(:,1)))
380 call hecmw_restart_add_real(fstrdynamic%DISP(:,1),
size(fstrdynamic%DISP(:,1)))
381 call hecmw_restart_add_real(fstrdynamic%DISP(:,3),
size(fstrdynamic%DISP(:,3)))
383 do i= 1, hecmesh%n_elem
384 if (hecmw_is_etype_link( fstrsolid%elements(i)%etype )) cycle
385 if (hecmw_is_etype_patch( fstrsolid%elements(i)%etype )) cycle
386 call hecmw_restart_add_real(fstrsolid%elements(i)%equiForces,
size(fstrsolid%elements(i)%equiForces))
389 call hecmw_restart_write()