OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
wrrest.F
Go to the documentation of this file.
1Copyright> OpenRadioss
2Copyright> Copyright (C) 1986-2025 Altair Engineering Inc.
3Copyright>
4Copyright> This program is free software: you can redistribute it and/or modify
5Copyright> it under the terms of the GNU Affero General Public License as published by
6Copyright> the Free Software Foundation, either version 3 of the License, or
7Copyright> (at your option) any later version.
8Copyright>
9Copyright> This program is distributed in the hope that it will be useful,
10Copyright> but WITHOUT ANY WARRANTY; without even the implied warranty of
11Copyright> MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12Copyright> GNU Affero General Public License for more details.
13Copyright>
14Copyright> You should have received a copy of the GNU Affero General Public License
15Copyright> along with this program. If not, see <https://www.gnu.org/licenses/>.
16Copyright>
17Copyright>
18Copyright> Commercial Alternative: Altair Radioss Software
19Copyright>
20Copyright> As an alternative to this open-source version, Altair also offers Altair Radioss
21Copyright> software under a commercial license. Contact Altair to discuss further if the
22Copyright> commercial version may interest you: https://www.altair.com/radioss/.
23!||====================================================================
24!|| fxbwrestp ../starter/source/restart/ddsplit/wrrest.F
25!||--- called by ------------------------------------------------------
26!|| ddsplit ../starter/source/restart/ddsplit/ddsplit.F
27!||--- calls -----------------------------------------------------
28!|| wrtsqi ../starter/source/output/tools/wrtsqi.F
29!|| wrtsqr ../starter/source/output/tools/wrtsqr.F
30!||====================================================================
31 SUBROUTINE fxbwrestp(
32 . FXBIPM_L , FXBRPM , FXBNOD_L , FXBMOD_L, FXBGLM_L,
33 . FXBCPM_L , FXBCPS_L , FXBLM_L , FXBFLS_L, FXBDLS_L,
34 . FXBDEP , FXBVIT , FXBACC , FXBELM_L, FXBSIG_L,
35 . FXBGRVI_L, FXBGRVR_L, LENNOD_L , LENMOD_L, LENGLM_L,
36 . LENCP_L , LENLM_L , LENFLS_L , LENDLS_L, LENELM_L,
37 . LENSIG_L , LENGRVI_L, LENGRVR_L, LEN_AM, ITASK)
38C-----------------------------------------------
39C I m p l i c i t T y p e s
40C-----------------------------------------------
41#include "implicit_f.inc"
42C-----------------------------------------------
43C C o m m o n B l o c k s
44C-----------------------------------------------
45#include "com04_c.inc"
46#include "scr05_c.inc"
47#include "scr15_c.inc"
48#include "units_fxbody_c.inc"
49#include "fxbcom.inc"
50C-----------------------------------------------
51C D u m m y A r g u m e n t s
52C-----------------------------------------------
53 INTEGER FXBIPM_L(NBIPM,*), FXBNOD_L(*), FXBELM_L(*), FXBGRVI_L(*),
54 . LENNOD_L, LENMOD_L, LENGLM_L, LENCP_L, LENLM_L, LENFLS_L,
55 . LENDLS_L, LENELM_L, LENSIG_L, LENGRVI_L, LENGRVR_L,LEN_AM
56 my_real
57 . FXBRPM(*), FXBMOD_L(*), FXBGLM_L(*), FXBCPM_L(*),
58 . FXBCPS_L(*), FXBLM_L(*), FXBFLS_L(*), FXBDLS_L(*),
59 . fxbdep(*), fxbvit(*), fxbacc(*), fxbsig_l(*),
60 . fxbgrvr_l(*)
61C-----------------------------------------------
62C L o c a l V a r i a b l e s
63C-----------------------------------------------
64 INTEGER LEN_IPM, LEN_MOD, NRECM, NRECS, I, IRCM0, IRCS0, IRCM1,
65 . IRCS1, LREC, IRCM, IRCS, J, ITASK
66
67 my_real
68 . VV(6)
69 INTEGER FILE_LEN
70 CHARACTER(LEN=256) :: SCR_FILE_NAME,SCR_FILE_NAME2
71 CHARACTER(LEN=4) :: CIT
72C--------------------------------------
73C ECRITURE DES ENTIERS
74C--------------------------------------
75 len_ipm=nbipm*nfxbody
76 IF (irform/5<=1) THEN
77 CALL wrtsqi (fxbipm_l,len_ipm,irform)
78 IF (lennod_l>0) CALL wrtsqi (fxbnod_l,lennod_l,irform)
79 IF (lenelm_l>0) CALL wrtsqi (fxbelm_l,lenelm_l,irform)
80 IF (lengrvi_l>0) CALL wrtsqi (fxbgrvi_l,lengrvi_l,irform)
81 ELSE
82 CALL write_i_c(fxbipm_l,len_ipm)
83 len_am = len_am + len_ipm
84 IF (lennod_l>0) CALL write_i_c(fxbnod_l,lennod_l)
85 IF (lennod_l>0) len_am = len_am + lennod_l
86 IF (lenelm_l>0) CALL write_i_c(fxbelm_l,lenelm_l)
87 IF (lenelm_l>0) len_am = len_am + lenelm_l
88 IF (lengrvi_l>0) CALL write_i_c(fxbgrvi_l,lengrvi_l)
89 IF (lengrvi_l>0) len_am = len_am + lengrvi_l
90 ENDIF
91C--------------------------------------
92C ECRITURE DES REELS
93C--------------------------------------
94 len_mod=lenmod_l*6
95 IF (irform/5<=1) THEN
96 IF (len_mod>0) CALL wrtsqr (fxbmod_l,len_mod,irform)
97 IF (lenglm_l>0) CALL wrtsqr (fxbglm_l,lenglm_l,irform)
98 IF (lencp_l>0) CALL wrtsqr (fxbcpm_l,lencp_l ,irform)
99 IF (lencp_l>0) CALL wrtsqr (fxbcps_l,lencp_l ,irform)
100 IF (lenlm_l>0) CALL wrtsqr (fxblm_l, lenlm_l ,irform)
101 IF (lenfls_l>0) CALL wrtsqr (fxbfls_l,lenfls,irform)
102 IF (lendls_l>0) CALL wrtsqr (fxbdls_l,lendls,irform)
103 CALL wrtsqr (fxbdep,lenvar,irform)
104 CALL wrtsqr (fxbvit,lenvar,irform)
105 CALL wrtsqr (fxbacc,lenvar,irform)
106 CALL wrtsqr (fxbrpm,lenrpm,irform)
107 IF (lensig_l>0) CALL wrtsqr (fxbsig_l,lensig_l,irform)
108 IF (lengrvr_l>0) CALL wrtsqr (fxbgrvr_l,lengrvr_l,irform)
109 ELSE
110 IF (len_mod>0) THEN
111 CALL write_db(fxbmod_l,len_mod)
112 len_am = len_am + len_mod
113 ENDIF
114 IF (lenglm_l>0) THEN
115 CALL write_db(fxbglm_l,lenglm_l)
116 len_am = len_am + lenglm_l
117 ENDIF
118 IF (lencp_l>0) THEN
119 CALL write_db(fxbcpm_l,lencp_l )
120 len_am = len_am + lencp_l
121 ENDIF
122 IF (lencp_l>0) THEN
123 CALL write_db(fxbcps_l,lencp_l )
124 len_am = len_am + lencp_l
125 ENDIF
126 IF (lenlm_l>0) THEN
127 CALL write_db(fxblm_l, lenlm_l )
128 len_am = len_am + lenlm_l
129 ENDIF
130 IF (lenfls_l>0) THEN
131 CALL write_db(fxbfls_l,lenfls_l)
132 len_am = len_am + lenfls_l
133 ENDIF
134 IF (lendls_l>0) THEN
135 CALL write_db(fxbdls_l,lendls_l)
136 len_am = len_am + lendls_l
137 ENDIF
138 CALL write_db(fxbdep,lenvar)
139 CALL write_db(fxbvit,lenvar)
140 CALL write_db(fxbacc,lenvar)
141 CALL write_db(fxbrpm,lenrpm)
142 len_am = len_am + 3*lenvar + lenrpm
143 IF (lensig_l>0) THEN
144 CALL write_db(fxbsig_l,lensig_l)
145 len_am = len_am + lensig_l
146 ENDIF
147 IF (lengrvr_l>0) THEN
148 CALL write_db(fxbgrvr_l,lengrvr_l)
149 len_am = len_am + lengrvr_l
150 ENDIF
151 ENDIF
152C Ecriture des fichiers de modes et de contraintes
153 nrecm=0
154 nrecs=0
155 DO i=1,nfxbody
156 ircm0=fxbipm_l(30,i)
157 ircs0=fxbipm_l(31,i)
158 ircm1=fxbipm_l(32,i)
159 ircs1=fxbipm_l(33,i)
160 nrecm=nrecm+ircm1-ircm0
161 nrecs=nrecs+ircs1-ircs0
162 ENDDO
163 ircm=0
164 ircs=0
165 lrec=6
166 DO i=1,nrecm
167 ircm=ircm+1
168 READ(ifxm_l+itask,rec=ircm) (vv(j),j=1,lrec)
169 CALL write_db(vv,lrec)
170 len_am = len_am + lrec
171 ENDDO
172 DO i=1,nrecs
173 ircs=ircs+1
174 READ(ifxs_l+itask,rec=ircs) (vv(j),j=1,lrec)
175 CALL write_db(vv,lrec)
176 len_am = len_am + lrec
177 ENDDO
178
179 CLOSE(ifxm_l+itask)
180 CLOSE(ifxs_l+itask)
181
182 ! Delete scratch file IFXM_L+ITASK
183 WRITE(cit,'(I4.4)')itask
184 scr_file_name ='SCR_FXM_'//rootnam(1:rootlen)//'_'//cit(1:4)//'.scr'
185 file_len=len_trim(scr_file_name)
186 CALL delete_user_file(scr_file_name,file_len)
187
188 ! Delete scratch file IFXS_L+ITASK
189 scr_file_name2='SCR_FXS_'//rootnam(1:rootlen)//'_'//cit(1:4)//'.scr'
190 file_len=len_trim(scr_file_name2)
191 CALL delete_user_file(scr_file_name2,file_len)
192C
193 RETURN
194 END
195
196!||====================================================================
197!|| eigwrest ../starter/source/restart/ddsplit/wrrest.F
198!||--- calls -----------------------------------------------------
199!|| wrtsqi ../starter/source/output/tools/wrtsqi.F
200!|| wrtsqr ../starter/source/output/tools/wrtsqr.F
201!||====================================================================
202 SUBROUTINE eigwrest(EIGIPM, EIGIBUF, EIGRPM)
203C-----------------------------------------------
204C I m p l i c i t T y p e s
205C-----------------------------------------------
206#include "implicit_f.inc"
207C-----------------------------------------------
208C C o m m o n B l o c k s
209C----------------------------------2-------------
210#include "units_c.inc"
211#include "com04_c.inc"
212#include "scr05_c.inc"
213#include "eigcom.inc"
214C-----------------------------------------------
215C D u m m y A r g u m e n t s
216C-----------------------------------------------
217 INTEGER EIGIPM(*), EIGIBUF(*)
218 my_real
219 . EIGRPM(*)
220C-----------------------------------------------
221C L o c a l V a r i a b l e s
222C-----------------------------------------------
223 INTEGER NRECM, IRCM, NBN, NBM, IAD, LREC, I, J
224 my_real
225 . vv(6)
226C--------------------------------------
227C ECRITURE DES ENTIERS
228C--------------------------------------
229 IF (irform/5<=1) THEN
230 CALL wrtsqi (eigipm,neig*neipm,irform)
231 CALL wrtsqi (eigibuf,leibuf,irform)
232 ELSE
233 CALL write_i_c(eigipm,neig*neipm)
234 CALL write_i_c(eigibuf,leibuf)
235 ENDIF
236C--------------------------------------
237C ECRITURE DES REELS
238C--------------------------------------
239 IF (irform/5<=1) THEN
240 CALL wrtsqr (eigrpm,neig*nerpm,irform)
241 ELSE
242 CALL write_db(eigrpm,neig*nerpm)
243 ENDIF
244C Ecriture du fichier des modes additionnels
245 nrecm=0
246 iad=1
247 DO i=1,neig
248 nbn=eigipm(iad+9)
249 nbm=eigipm(iad+13)
250 nrecm=nrecm+nbn*nbm
251 iad=iad+neipm
252 ENDDO
253C
254 ircm=0
255 lrec=6
256 DO i=1,nrecm
257 ircm=ircm+1
258 READ(ieigm,rec=ircm) (vv(j),j=1,lrec)
259 CALL write_db(vv,lrec)
260 ENDDO
261 CLOSE(ieigm)
262C
263 RETURN
264 END
265!||====================================================================
266!|| eigwrestp ../starter/source/restart/ddsplit/wrrest.F
267!||--- called by ------------------------------------------------------
268!|| ddsplit ../starter/source/restart/ddsplit/ddsplit.F
269!||--- calls -----------------------------------------------------
270!||====================================================================
271 SUBROUTINE eigwrestp(EIGIPM, EIGIBUF, EIGRPM, LEIBUF_L,LEN_AM)
272C-----------------------------------------------
273C I m p l i c i t T y p e s
274C-----------------------------------------------
275#include "implicit_f.inc"
276C-----------------------------------------------
277C C o m m o n B l o c k s
278C-----------------------------------------------
279#include "com04_c.inc"
280#include "eigcom.inc"
281C-----------------------------------------------
282C D u m m y A r g u m e n t s
283C-----------------------------------------------
284 INTEGER EIGIPM(*), EIGIBUF(*), LEIBUF_L,LEN_AM
285 my_real
286 . EIGRPM(*)
287C-----------------------------------------------
288C L o c a l V a r i a b l e s
289C-----------------------------------------------
290C--------------------------------------
291C ECRITURE DES ENTIERS
292C--------------------------------------
293 CALL write_i_c(eigipm,neig*neipm)
294 CALL write_i_c(eigibuf,leibuf_l)
295C--------------------------------------
296C ECRITURE DES REELS
297C--------------------------------------
298 CALL write_db(eigrpm,neig*nerpm)
299 len_am = len_am + neig*neipm + leibuf_l + neig*nerpm
300C
301 RETURN
302 END
303
304!||====================================================================
305!|| dswrest ../starter/source/restart/ddsplit/wrrest.F
306!||--- calls -----------------------------------------------------
307!|| wrtsqi ../starter/source/output/tools/wrtsqi.F
308!|| wrtsqr ../starter/source/output/tools/wrtsqr.F
309!||--- uses -----------------------------------------------------
310!|| dsgraph_mod ../starter/share/modules1/dsgraph_mod.F
311!||====================================================================
312 SUBROUTINE dswrest(GRAPHE)
313C-----------------------------------------------
314C M o d u l e s
315C-----------------------------------------------
316 USE dsgraph_mod
317C-----------------------------------------------
318C I m p l i c i t T y p e s
319C-----------------------------------------------
320#include "implicit_f.inc"
321C-----------------------------------------------
322C C o m m o n B l o c k s
323C-----------------------------------------------
324#include "com01_c.inc"
325#include "scr05_c.inc"
326C-----------------------------------------------
327C D u m m y A r g u m e n t s
328C-----------------------------------------------
329 TYPE(prgraph) :: GRAPHE(*)
330C-----------------------------------------------
331C L o c a l V a r i a b l e s
332C-----------------------------------------------
333 INTEGER I, J, TN(7), N, NDDL, DSNDDL, DSLEN, K, NSDEC
334 my_real
335 . cutfreq
336C
337 DO i=1,nsproc
338C--------------------------------------
339C Ecriture des parametres entiers
340C--------------------------------------
341 dsnddl=graphe(i)%NDDL
342 dslen=graphe(i)%NSUPEL
343 nsdec=graphe(i)%NSDEC
344 tn(1)=dsnddl
345 tn(2)=dslen
346 tn(3)=graphe(i)%NSLEVEL
347 tn(4)=nsdec
348 tn(5)=graphe(i)%NSVMAX
349 tn(6)=graphe(i)%IPRI
350 tn(7)=graphe(i)%NDDL_GLOB
351 n=7
352 IF (irform/5<=1) THEN
353 CALL wrtsqi(tn, n, irform)
354 ELSE
355 CALL write_i_c(tn, n)
356 ENDIF
357C--------------------------------------
358C Ecriture des parametres reels
359C--------------------------------------
360 n=1
361 cutfreq=graphe(i)%CUTFREQ
362 IF (irform/5<=1) THEN
363 CALL wrtsqr(cutfreq, n, irform)
364 ELSE
365 CALL write_db(cutfreq, n)
366 ENDIF
367C--------------------------------------
368C Ecriture du tableau des ddls
369C--------------------------------------
370 DO j=1,2
371 IF (irform/5<=1) THEN
372 CALL wrtsqi(graphe(i)%LSDDL(j,:), dsnddl, irform)
373 ELSE
374 CALL write_i_c(graphe(i)%LSDDL(j,:), dsnddl)
375 ENDIF
376 ENDDO
377 DEALLOCATE(graphe(i)%LSDDL)
378 IF (irform/5<=1) THEN
379 CALL wrtsqi(graphe(i)%LSDDL_GLOB, dsnddl, irform)
380 ELSE
381 CALL write_i_c(graphe(i)%LSDDL_GLOB, dsnddl)
382 ENDIF
383 DEALLOCATE(graphe(i)%LSDDL_GLOB)
384C--------------------------------------
385C Ecriture des superelements
386C--------------------------------------
387 DO j=1,dslen
388 tn(1)=graphe(i)%DGRAPH(j)%NDDL_I
389 tn(2)=graphe(i)%DGRAPH(j)%NDDL_F
390 tn(3)=graphe(i)%DGRAPH(j)%NSDMAX
391 nddl=tn(1)+tn(2)
392 IF (irform/5<=1) THEN
393 n=3
394 CALL wrtsqi(tn, n, irform)
395 CALL wrtsqi(graphe(i)%DGRAPH(j)%CHILD, nsdec, irform)
396 CALL wrtsqi(graphe(i)%DGRAPH(j)%DDLS, nddl, irform)
397 n=tn(3)+1
398 DO k=1,tn(2)
399 CALL wrtsqi(graphe(i)%DGRAPH(j)
400 . %IFAC(:,k), n, irform)
401 ENDDO
402 CALL wrtsqi(graphe(i)%DGRAPH(j)%IFACM, tn(2), irform)
403 ELSE
404 n=3
405 CALL write_i_c(tn, n)
406 CALL write_i_c(graphe(i)%DGRAPH(j)%CHILD, nsdec)
407 CALL write_i_c(graphe(i)%DGRAPH(j)%DDLS, nddl)
408 n=tn(3)+1
409 DO k=1,tn(2)
410 CALL write_i_c(graphe(i)%DGRAPH(j)
411 . %IFAC(:,k), n)
412 ENDDO
413 CALL write_i_c(graphe(i)%DGRAPH(j)%IFACM, tn(2))
414 ENDIF
415 DEALLOCATE(graphe(i)%DGRAPH(j)%CHILD)
416 DEALLOCATE(graphe(i)%DGRAPH(j)%DDLS)
417 DEALLOCATE(graphe(i)%DGRAPH(j)%IFAC,
418 . graphe(i)%DGRAPH(j)%IFACM)
419 ENDDO
420 DEALLOCATE(graphe(i)%DGRAPH)
421C
422 ENDDO
423C
424 RETURN
425 END
426
427!||====================================================================
428!|| dswrestp ../starter/source/restart/ddsplit/wrrest.F
429!||--- calls -----------------------------------------------------
430!||--- uses -----------------------------------------------------
431!|| dsgraph_mod ../starter/share/modules1/dsgraph_mod.F
432!||====================================================================
433 SUBROUTINE dswrestp(PGRAPH,LEN_IA,LEN_AM)
434C-----------------------------------------------
435C M o d u l e s
436C-----------------------------------------------
437 USE dsgraph_mod
438C-----------------------------------------------
439C I m p l i c i t T y p e s
440C-----------------------------------------------
441#include "implicit_f.inc"
442C-----------------------------------------------
443C D u m m y A r g u m e n t s
444C-----------------------------------------------
445 TYPE(prgraph) :: PGRAPH
446C-----------------------------------------------
447C L o c a l V a r i a b l e s
448C-----------------------------------------------
449 INTEGER I, J, TN(7), N, NDDL, DSNDDL, DSLEN, K, NSDEC,
450 . DSNDDL_GLOB,LEN_IA,LEN_AM
451 my_real
452 . cutfreq
453C--------------------------------------
454C Ecriture des parametres entiers
455C--------------------------------------
456 dsnddl=pgraph%NDDL
457 dslen=pgraph%NSUPEL
458 nsdec=pgraph%NSDEC
459 tn(1)=dsnddl
460 tn(2)=dslen
461 tn(3)=pgraph%NSLEVEL
462 tn(4)=nsdec
463 tn(5)=pgraph%NSVMAX
464 tn(6)=pgraph%IPRI
465 tn(7)=pgraph%NDDL_GLOB
466 n=7
467 CALL write_i_c(tn, n)
468 len_ia = len_ia + n
469C--------------------------------------
470C Ecriture des parametres reels
471C--------------------------------------
472 n=1
473 cutfreq=pgraph%CUTFREQ
474 CALL write_db(cutfreq, n)
475 len_am = len_am + n
476C--------------------------------------
477C Ecriture du tableau des ddls
478C--------------------------------------
479 DO j=1,2
480 CALL write_i_c(pgraph%LSDDL(j,:), dsnddl)
481 len_ia = len_ia + dsnddl
482 ENDDO
483 DEALLOCATE(pgraph%LSDDL)
484 CALL write_i_c(pgraph%LSDDL_GLOB, dsnddl)
485 len_ia = len_ia + dsnddl
486 DEALLOCATE(pgraph%LSDDL_GLOB)
487C--------------------------------------
488C Ecriture des superelements
489C--------------------------------------
490 DO j=1,dslen
491 tn(1)=pgraph%DGRAPH(j)%NDDL_I
492 tn(2)=pgraph%DGRAPH(j)%NDDL_F
493 tn(3)=pgraph%DGRAPH(j)%NSDMAX
494 nddl=tn(1)+tn(2)
495 n=3
496 CALL write_i_c(tn, n)
497 CALL write_i_c(pgraph%DGRAPH(j)%CHILD, nsdec)
498 CALL write_i_c(pgraph%DGRAPH(j)%DDLS, nddl)
499 len_ia = len_ia + n + nsdec + nddl
500 n=tn(3)+1
501 DO k=1,tn(2)
502 CALL write_i_c(pgraph%DGRAPH(j)
503 . %IFAC(:,k), n)
504 len_ia = len_ia + n
505 ENDDO
506 CALL write_i_c(pgraph%DGRAPH(j)%IFACM, tn(2))
507 len_ia = len_ia + tn(2)
508 DEALLOCATE(pgraph%DGRAPH(j)%CHILD)
509 DEALLOCATE(pgraph%DGRAPH(j)%DDLS)
510 DEALLOCATE(pgraph%DGRAPH(j)%IFAC,
511 . pgraph%DGRAPH(j)%IFACM)
512 ENDDO
513 DEALLOCATE(pgraph%DGRAPH)
514C
515 RETURN
516 END
517
518!||====================================================================
519!|| nfwrest ../starter/source/restart/ddsplit/wrrest.F
520!||--- calls -----------------------------------------------------
521!|| wrtsqi ../starter/source/output/tools/wrtsqi.F
522!|| wrtsqr ../starter/source/output/tools/wrtsqr.F
523!||====================================================================
524 SUBROUTINE nfwrest(IFLOW, RFLOW)
525C-----------------------------------------------
526C I m p l i c i t T y p e s
527C-----------------------------------------------
528#include "implicit_f.inc"
529C-----------------------------------------------
530C C o m m o n B l o c k s
531C-----------------------------------------------
532#include "scr05_c.inc"
533#include "flowcom.inc"
534C-----------------------------------------------
535C D u m m y A r g u m e n t s
536C-----------------------------------------------
537 INTEGER IFLOW(*)
538 my_real
539 . RFLOW(*)
540C-----------------------------------------------
541C L o c a l V a r i a b l e s
542C-----------------------------------------------
543C--------------------------------------
544C ECRITURE DES ENTIERS
545C--------------------------------------
546 IF (irform/5<=1) THEN
547 CALL wrtsqi (iflow,liflow,irform)
548 ELSE
549 CALL write_i_c(iflow,liflow)
550 ENDIF
551C--------------------------------------
552C ECRITURE DES REELS
553C--------------------------------------
554 IF (irform/5<=1) THEN
555 CALL wrtsqr (rflow,lrflow,irform)
556 ELSE
557 CALL write_db(rflow,lrflow)
558 ENDIF
559C
560 RETURN
561 END
562!||====================================================================
563!|| nfwrestp ../starter/source/restart/ddsplit/wrrest.F
564!||--- called by ------------------------------------------------------
565!|| ddsplit ../starter/source/restart/ddsplit/ddsplit.f
566!||--- calls -----------------------------------------------------
567!||====================================================================
568 SUBROUTINE nfwrestp(IFLOW, RFLOW,LEN_IA,LEN_AM)
569C-----------------------------------------------
570C I m p l i c i t T y p e s
571C-----------------------------------------------
572#include "implicit_f.inc"
573C-----------------------------------------------
574C C o m m o n B l o c k s
575C-----------------------------------------------
576#include "flowcom.inc"
577C-----------------------------------------------
578C D u m m y A r g u m e n t s
579C-----------------------------------------------
580 INTEGER IFLOW(*),LEN_IA,LEN_AM
581 my_real
582 . RFLOW(*)
583C-----------------------------------------------
584C L o c a l V a r i a b l e s
585C-----------------------------------------------
586C--------------------------------------
587C ECRITURE DES ENTIERS
588C--------------------------------------
589 CALL write_i_c(iflow,liflow)
590 len_ia = len_ia + liflow
591C--------------------------------------
592C ECRITURE DES REELS
593C--------------------------------------
594 CALL write_db(rflow,lrflow)
595 len_am = len_am + lrflow
596C
597 RETURN
598 END
599C
600
601C for shell heat transfer
602!||====================================================================
603!|| thcwrest ../starter/source/restart/ddsplit/wrrest.F
604!||--- calls -----------------------------------------------------
605!|| wrtsqr ../starter/source/output/tools/wrtsqr.F
606!||====================================================================
607 SUBROUTINE thcwrest(MCP,TEMP)
608C-----------------------------------------------
609C I m p l i c i t T y p e s
610C-----------------------------------------------
611#include "implicit_f.inc"
612C-----------------------------------------------
613C C o m m o n B l o c k s
614C-----------------------------------------------
615#include "com04_c.inc"
616#include "scr05_c.inc"
617C-----------------------------------------------
618C D u m m y A r g u m e n t s
619C-----------------------------------------------
620 my_real
621 . mcp(*),temp(*)
622C-----------------------------------------------
623C L o c a l V a r i a b l e s
624C-----------------------------------------------
625C--------------------------------------
626C ECRITURE DES REELS
627C--------------------------------------
628 IF (irform/5 <= 1) THEN
629 CALL wrtsqr (mcp,numnod,irform)
630 CALL wrtsqr (temp,numnod,irform)
631 ELSE
632 CALL write_db(mcp,numnod)
633 CALL write_db(temp,numnod)
634 ENDIF
635 RETURN
636 END
637
638C convection flux
639!||====================================================================
640!|| convwrest ../starter/source/restart/ddsplit/wrrest.F
641!||--- calls -----------------------------------------------------
642!|| wrtsqi ../starter/source/output/tools/wrtsqi.F
643!|| wrtsqr ../starter/source/output/tools/wrtsqr.F
644!||====================================================================
645 SUBROUTINE convwrest(IBCV,FCONV,NUMCONV,NICONV,LFACTHER)
646C-----------------------------------------------
647C I m p l i c i t T y p e s
648C-----------------------------------------------
649#include "implicit_f.inc"
650C-----------------------------------------------
651C C o m m o n B l o c k s
652C-----------------------------------------------
653#include "com04_c.inc"
654#include "scr05_c.inc"
655#include "param_c.inc"
656C-----------------------------------------------
657C D u m m y A r g u m e n t s
658C-----------------------------------------------
659 INTEGER ,INTENT(IN) :: NUMCONV
660 INTEGER ,INTENT(IN) :: NICONV
661 INTEGER ,INTENT(IN) :: LFACTHER
662 INTEGER :: IBCV(*)
663 my_real :: FCONV(*)
664C--------------------------------------
665C ECRITURE DES REELS
666C--------------------------------------
667 IF (irform/5 <= 1) THEN
668 CALL wrtsqr (fconv,lfacther*numconv,irform)
669 CALL wrtsqi (ibcv,niconv*numconv,irform)
670 ELSE
671 CALL write_db(fconv,lfacther*numconv)
672 CALL write_i_c(ibcv,niconv*numconv)
673 ENDIF
674 RETURN
675 END
676
677C for rigid_ material
678!||====================================================================
679!|| rigmatwrest ../starter/source/restart/ddsplit/wrrest.F
680!||--- calls -----------------------------------------------------
681!|| wrtsqi ../starter/source/output/tools/wrtsqi.F
682!|| wrtsqr ../starter/source/output/tools/wrtsqr.F
683!||====================================================================
684 SUBROUTINE rigmatwrest(RBYM ,IRBYM ,LCRBYM, WEIGHT)
685C-----------------------------------------------
686C I m p l i c i t T y p e s
687C-----------------------------------------------
688#include "implicit_f.inc"
689C-----------------------------------------------
690C C o m m o n B l o c k s
691C-----------------------------------------------
692#include "com04_c.inc"
693#include "scr05_c.inc"
694C-----------------------------------------------
695C D u m m y A r g u m e n t s
696C-----------------------------------------------
697 INTEGER IRBYM(*) ,LCRBYM(*),WEIGHT(*)
698 my_real
699 . RBYM(*)
700C-----------------------------------------------
701C L o c a l V a r i a b l e s
702C-----------------------------------------------
703C--------------------------------------
704C ECRITURE DES REELS
705C--------------------------------------
706 IF (irform/5 <= 1) THEN
707 CALL wrtsqr (rbym,nfrbym*nrbym,irform)
708 CALL wrtsqi (irbym,nirbym*nrbym,irform)
709 CALL wrtsqi (lcrbym,ngslnrbym,irform)
710 CALL wrtsqi (weight,nrbym,irform)
711 ELSE
712 CALL write_db(rbym,nfrbym*nrbym)
713 CALL write_i_c(irbym,nirbym*nrbym)
714 CALL write_i_c( lcrbym,ngslnrbym)
715 CALL write_i_c( weight,nrbym)
716
717 ENDIF
718 RETURN
719 END
720
721C for shell composite xfem
722!||====================================================================
723!|| plyxfem_wrest ../starter/source/restart/ddsplit/wrrest.F
724!||--- calls -----------------------------------------------------
725!|| wrtsqi ../starter/source/output/tools/wrtsqi.F
726!|| wrtsqr ../starter/source/output/tools/wrtsqr.F
727!||====================================================================
728 SUBROUTINE plyxfem_wrest(MS_PLY,ZI_PLY,IEL,INOD,ICODE,ISKEW)
729C-----------------------------------------------
730C I m p l i c i t T y p e s
731C-----------------------------------------------
732#include "implicit_f.inc"
733C-----------------------------------------------
734C C o m m o n B l o c k s
735C-----------------------------------------------
736#include "com01_c.inc"
737#include "com04_c.inc"
738#include "scr05_c.inc"
739#include "param_c.inc"
740C-----------------------------------------------
741C D u m m y A r g u m e n t s
742C-----------------------------------------------
743 my_real
744 . ms_ply(*),zi_ply(*)
745 INTEGER ICODE(*),ISKEW(*),IEL(*),INOD(*)
746C-----------------------------------------------
747C L o c a l V a r i a b l e s
748C-----------------------------------------------
749C--------------------------------------
750C ECRITURE DES REELS
751C--------------------------------------
752 IF(iplyxfem > 0 ) THEN
753 IF (irform/5 <= 1) THEN
754 CALL wrtsqr (ms_ply,nplyxfe*nplymax,irform)
755 CALL wrtsqr (zi_ply,nplyxfe*nplymax,irform)
756 CALL wrtsqi (inod,numnod,irform)
757 CALL wrtsqi (iel,numelc,irform)
758 ELSE
759 CALL write_db(ms_ply,nplyxfe*nplymax)
760 CALL write_db(zi_ply,nplyxfe*nplymax)
761 CALL write_i_c(inod,numnod)
762 CALL write_i_c(iel,numelc)
763 ENDIF
764 ENDIF
765C
766 IF(iplybcs > 0) THEN
767 IF (irform/5 <= 1) THEN
768 CALL wrtsqi (icode,numnod,irform)
769 CALL wrtsqi (iskew,numnod,irform)
770 ELSE
771 CALL write_i_c(icode,numnod)
772 CALL write_i_c(iskew,numnod)
773 ENDIF
774 ENDIF
775 RETURN
776 END
#define my_real
Definition cppsort.cpp:32
subroutine ddsplit(p, cep, cel, igeo, mat_elem, ipm, icode, iskew, iskn, insel, ibcslag, ipart, iparts, ipartq, ipartc, ipartt, ipartp, ipartr, iparttg, detonators, ipartx, npc, ixtg, group_param_tab, ixtg6, ixs, ixs10, ixs20, ixs16, ixq, ixc, ixt, ixp, ixr, itab, itabm1, gjbufi, nale, ale_connectivity, kxx, ixx, ibcl, ibfv, las, laccelm, nnlink, lllink, iparg, igrav, lgrav, ibvel, lbvel, iactiv, factiv, kinet, ipari, nprw, lprw, iexmad, npby, lpby, ixri, nstrf, ljoint, pornod, monvol, icontact, lagbuf, fr_iad, x, d, v, vr, dr, thke, dampr, damp, ms, in, tf, pm, skew, xframe, geo, eani, bufmat, bufgeo, bufsf, brmpc, gjbufr, w, veul, fill, dfill, wb, dsav, asav, msnf, spbuf, fac, vel, fsav, fzero, xlas, accelm, fbvel, gravfac, fr_wave, failwave, parts0, elbuf, rwl, rwsav, rby, rivet, secbuf, rvolu, rconx, nloc_dmg, fvmain, libagale, lenthg, lbufmat, lbufgeo, lbufsf, lenxlas, lnom_opt, lenlas, lenvolu, npts, cne, lcne, addcne, cni2, lcni2g, addcni2, cepi2, celi2, i2nsnt, probint, ddstat, pm1shf, dd_iad, kxsp, ixsp, nod2sp, cepsp, nthwa, nairwa, nmnt, l_mul_lag1, l_mul_lag, lwaspio, ipartsp, ispcond, pm1sph, wma, eigipm, eigibuf, eigrpm, iflow, rflow, memflow, iexlnk, fasolfr, iparth, fxbipm, fxbrpm, fxbnod, fxbmod, fxbglm, fxbcpm, fxbcps, fxblm, fxbfls, fxbdls, fxbdep, fxbvit, fxbacc, fxbelm, fxbsig, fxbgrvi, fxbgrvr, iadll, lll, ibmpc, lambda, lrbagale, iskwp, nskwp, isensp, nsensp, iaccp, naccp, ipart_state, mcp, temp, unitab, intstamp, iframe, clusters, partsav, ibft, fbft, ibcv, fconv, irbe3, lrbe3, frbe3, front_rm, rbym, irbym, lcrbym, inoise, fnoise, ms0, admsms, nom_sect, ispsym, sh4tree, sh3tree, ipadmesh, ibfflux, fbfflux, sh4trim, sh3trim, padmesh, msc, mstg, inc, intg, ptg, mcpc, mcptg, rcontact, acontact, pcontact, mscnd, incnd, mssa, mstr, msp, msrt, ibcr, fradia, dmelc, dmeltg, dmels, dmeltr, dmelp, dmelrt, res_sms, isphio, lprtsph, lonfsph, vsphio, sphveln, alph, ifill, ims, irbe2, lrbe2, ms_ply, zi_ply, inod_pxfem, iel_pxfem, icodply, iskwply, addcne_pxfem, cne_pxfem, cel_pxfem, ithvar, xdp, table, celsph, icfield, lcfield, cfield, msz2, itask, diag_sms, iloadp, lloadp, loadp, inod_crkxfem, iel_crkxfem, addcne_crkxfem, cne_crkxfem, cel_crkxfem, ibufssg_io, intercep, ibordnode, iedgesh, ibordedge, linale, nodedge, iedge, cep_crkxfem, iedge_tmp, crknodiad, elbuf_tab, nom_opt, lgauge, gauge, igaup, ngaup, nodlevxf, frontb_r2r, dflow, vflow, wflow, sph2sol, sol2sph, irst, elcutc, nodenr, kxfenod2elc, enrtag, intbuf_tab, i11flag, xfem_tab, lenthgr, rthbuf, ixig3d, kxig3d, knot, ipartig3d, wige, ncrkpart, indx_crk, crklvset, crkshell, crksky, crkavx, crkedge, sensors, stack, xfem_phantom, t8, tab_ump, poin_ump, sol2sph_typ, addcsrect, csrect, drape, loads, itagnd, icnds10, addcncnd, cepcnd, celcnd, cncnd, nativ_sms, i24maxnsne, multi_fvm, segquadfr, intbuf_fric_tab, subset, igrnod, igrbric, igrquad, igrsh4n, igrsh3n, igrtruss, igrbeam, igrspring, igrpart, igrsurf, igrslin, poin_part_shell, poin_part_tri, poin_part_sol, mid_pid_shell, mid_pid_tri, mid_pid_sol, tag_nm, nindx_nm, indx_nm, tag_scratch, nindx_scrt, indx_scrt, flag_24_25, numnod_l, tag_skn, multiple_skew, igrsurf_proc, knotlocpc, knotlocel, ale_elm, size_ale_elm, pinch_data, tag_skins6, ibcscyc, lbcscyc, t_monvol, indx_s, indx_q, indx_tg, face_elm_s, face_elm_q, face_elm_tg, nbr_th_monvol, ebcs_tab, kloadpinter, loadpinter, dgaploadint, s_loadpinter, len_cep, dynain_data, drapeg, user_windows, output, interfaces, number_load_cyl, loads_per_proc, python, dpl0cld, vel0cld, names_and_titles, bcs_per_proc, constraint_struct, glob_therm, pblast)
Definition ddsplit.F:336
subroutine wrtsqi(ia, l, iform)
Definition wrtsqi.F:36
subroutine wrtsqr(a, l, iform)
Definition wrtsqr.F:37
subroutine nfwrest(iflow, rflow)
Definition wrrest.F:525
subroutine plyxfem_wrest(ms_ply, zi_ply, iel, inod, icode, iskew)
Definition wrrest.F:729
subroutine thcwrest(mcp, temp)
Definition wrrest.F:608
subroutine nfwrestp(iflow, rflow, len_ia, len_am)
Definition wrrest.F:569
subroutine convwrest(ibcv, fconv, numconv, niconv, lfacther)
Definition wrrest.F:646
subroutine dswrestp(pgraph, len_ia, len_am)
Definition wrrest.F:434
subroutine eigwrest(eigipm, eigibuf, eigrpm)
Definition wrrest.F:203
subroutine dswrest(graphe)
Definition wrrest.F:313
subroutine fxbwrestp(fxbipm_l, fxbrpm, fxbnod_l, fxbmod_l, fxbglm_l, fxbcpm_l, fxbcps_l, fxblm_l, fxbfls_l, fxbdls_l, fxbdep, fxbvit, fxbacc, fxbelm_l, fxbsig_l, fxbgrvi_l, fxbgrvr_l, lennod_l, lenmod_l, lenglm_l, lencp_l, lenlm_l, lenfls_l, lendls_l, lenelm_l, lensig_l, lengrvi_l, lengrvr_l, len_am, itask)
Definition wrrest.F:38
subroutine rigmatwrest(rbym, irbym, lcrbym, weight)
Definition wrrest.F:685
subroutine eigwrestp(eigipm, eigibuf, eigrpm, leibuf_l, len_am)
Definition wrrest.F:272
program starter
Definition starter.F:39
subroutine write_db(a, n)
Definition write_db.F:140
void write_i_c(int *w, int *len)