165
166
167
169 USE nodal_arrays_mod
170 USE connectivity_mod
174 USE mat_elem_mod
176 USE intbufdef_mod
177 USE int8_mod
180 USE multi_fvm_mod
182 USE intbuf_fric_mod
189 USE sensor_mod
190 USE ebcs_mod
192 USE pblast_mod
195 USE loads_mod
199 USE output_mod
200USE interfaces_mod
201 USE python_funct_mod
206 USE bcs_mod , only : bcs
207 USE skew_mod
213 USE elbufdef_mod
214 use write_inivel_mod , only : write_inivel
215 use glob_therm_mod
216 use write_ale_grid_mod , only : write_ale_grid
217 use write_bcs_wall_mod , only : write_bcs_wall
218 use rbe3_mod
219 use restart_rbe3pen_mod, only : write_rrbe3pen
220 use checksum_output_option_mod, only : checksum_restart_write
221
222
223
224#include "implicit_f.inc"
225
226
227
228 TYPE(nodal_arrays_) :: NODES
229 TYPE(connectivity_) :: ELEMENTS
230 INTEGER, INTENT(IN) :: NDRAPE
231 INTEGER, INTENT(IN) :: IMPL_S
232 INTEGER, INTENT(IN) :: IMPL_S0
233 my_real,
INTENT(INOUT) :: mcp(numnod)
234 my_real,
INTENT(INOUT) :: temp(numnod)
235 INTEGER, INTENT(INOUT) :: NEIPM, LEIBUF, NERPM
236 INTEGER, INTENT(INOUT) :: EIGIPM(NEIPM,NEIG),EIGIBUF(LEIBUF)
237 my_real,
INTENT(INOUT) :: eigrpm(nerpm,neig)
238 INTEGER, INTENT(IN) :: FORNEQS(3,NUMNOD)
239 INTEGER IAF(*),ICH,ADDCNE(*)
241 TYPE(ELBUF_STRUCT_), TARGET, DIMENSION(NGROUP) :: ELBUF_TAB
242 TYPE(ELBUF_STRUCT_), TARGET, DIMENSION(NGROUP,NXEL) :: XFEM_TAB
243 TYPE(INTBUF_STRUCT_) INTBUF_TAB(*)
244 TYPE(MULTI_FVM_STRUCT), INTENT(INOUT) :: MULTI_FVM
245
246 TYPE(H3D_DATABASE), INTENT(IN) :: H3D_DATA
247 TYPE(INTBUF_FRIC_STRUCT_) INTBUF_FRIC_TAB(
248TYPE(SUBSET_), TARGET, DIMENSION(NSUBS) :: SUBSET
249 TYPE(PINCH) :: PINCH_DATA
250 TYPE(t_ale_connectivity), INTENT(IN) :: ALE_CONNECTIVITY
251 TYPE(MONVOL_STRUCT_), DIMENSION(NVOLU), INTENT(IN) :: T_MONVOL
252 TYPE(t_ebcs_tab), INTENT(INOUT) :: EBCS_TAB
253 TYPE(DYNAIN_DATABASE) ,INTENT(IN) :: DYNAIN_DATA
254 TYPE(USER_WINDOWS_) ,INTENT(IN) :: USER_WINDOWS
255 TYPE(OUTPUT_) ,INTENT(INOUT) :: OUTPUT
256 TYPE(INTERFACES_) ,INTENT(IN) :: INTERFACES
257 TYPE(SENSORS_)INTENT(IN) :: SENSORS
258 TYPE(LOADS_) ,INTENT(IN) :: LOADS
259 TYPE(MAT_ELEM_) ,INTENT(IN) :: MAT_ELEM
260 TYPE(PYTHON_) ,INTENT(INOUT) :: PYTHON
261 TYPE(NAMES_AND_TITLES_),INTENT(IN) :: NAMES_AND_TITLES
262 TYPE(SKEW_),INTENT(IN) :: SKEWS
263 TYPE(IMPBUF_STRUCT_), TARGET :: IMPBUF_TAB
264 TYPE(UNIT_TYPE_) :: UNITAB
265 TYPE (STACK_PLY) :: STACK
266 TYPE() :: DRAPE_SH3N(),DRAPE_SH4N(NUMELC_DRAPE)
267 TYPE(DRAPEG_) :: DRAPEG
268 type (glob_therm_) ,intent(inout) :: GLOB_THERM
269 TYPE(PBLAST_) ,INTENT(INOUT) :: PBLAST
270 TYPE(RBE3_) ,INTENT(INOUT) :: RBE3
271
272
273
274#include "chara_c.inc"
275#include "couple_c.inc"
276#include "com01_c.inc"
277#include "com04_c.inc"
278#include "com06_c.inc"
279#include "com_xfem1.inc"
280#include "intstamp_c.inc"
281#include "param_c.inc"
282#include "parit_c.inc"
283#include "scr03_c.inc"
284#include "scr05_c.inc"
285#include "scr07_c.inc"
286#include "scr14_c.inc"
287#include "scr16_c.inc"
288#include "scr19_c.inc"
289#include "scrcut_c.inc"
290#include "scrfs_c.inc"
291#include "scrnoi_c.inc"
292#include "scr_fac_c.inc"
293#include "sms_c.inc"
294#include "spmd_c.inc"
295#include "tabsiz_c.inc"
296#include "task_c.inc"
297#include "units_c.inc"
298#include "remesh_c.inc"
299#include "sphcom.inc"
300#include "inter18.inc"
301
302
303
304 INTEGER I,J,LEN,IFILNAM(2148), IFIL,LEN_G,LEN_M,LENG,LEN_S,IXEL,
305 . FLAG_XFEM
306 CHARACTER FILNAM*100, FILNAMR*100, FILNAMG*128,
307 . PROCNAM*4, CHRUNR*4,PLAST*4
308 CHARACTER*1 IJK(26)
309 INTEGER LHEADER,LVARINT,LVARREA,LMXVINT,LMXVREA,M
310 parameter(lheader=15)
311 parameter(lmxvint=4000)
312 parameter(lmxvrea=1000+30*maxlaw+30)
313 INTEGER TABHEAD(LHEADER),TABVINT(LMXVINT)
315 . tabvrea(lmxvrea), entmp(100)
316 INTEGER MY_ILEN,MY_RLEN,LTABLE, LENI, LENR
317
318 INTEGER ::
319 CHARACTER(len=2048) :: TMP_NAME
320 INTEGER, DIMENSION(NVOLU) :: NTRI
321 INTEGER :: II, NS_DIFF, ITMP
322 INTEGER :: MY_SIZE
323 INTEGER,DIMENSION(LTITLE) :: ITITLE
324 INTEGER :: SKEW_LEN
325 INTEGER, INTENT(IN) :: LIFLOW
326 INTEGER, INTENT(IN) :: LRFLOW
327 INTEGER, INTENT(IN), DIMENSION(LIFLOW) :: IFLOW
328 INTEGER, INTENT(IN), DIMENSION(LRFLOW) :: RFLOW
329 INTEGER :: NPT
330
331
332
333 INTEGER, DIMENSION(:), ALLOCATABLE :: BUFFER
334 INTEGER :: BUFFER_SIZE
335
336
337 INTEGER,INTENT(INOUT) :: RESTSIZE
338
339 DATA ijk/'I','J','K','L','M','N','O''P''Q''R',
340 . 'S','T','U','V','W','X','Y','Z','A','B',
341 . 'C','D','E','F','G','H'/
342
343
344
345 ipari0 = iparit
346 sfr_elem = SIZE(nodes%BOUNDARY,1)
347 siad_elem = SIZE(nodes%BOUNDARY_ADD,1) * SIZE(nodes%BOUNDARY_ADD,2)
348 CALL wrcomi(lmxvint,lvarint,tabvint,1,multi_fvm,h3d_data,dynain_data,
349 . interfaces%PARAMETERS,sensors,loads,glob_therm,pblast)
350
351 entmp(1) = output%TH%WFEXT
352 entmp
353 entmp(3) = econtv
354 entmp(4) = epor
355 entmp(5) = glob_therm%HEAT_STORED
356 entmp(6) = glob_therm%HEAT_MECA
357 entmp(7) = glob_therm%HEAT_CONV
358 entmp(8) = glob_therm%HEAT_RADIA
359 entmp(9) = glob_therm%HEAT_FFLUX
360 entmp(10)= econtd
361 entmp(11)= econt_cumu
363 IF(ispmd/=0) THEN
364 output%TH%WFEXT = zero
365 ehour = zero
366 econtv = zero
367 epor = zero
368 glob_therm%HEAT_STORED = zero
369 glob_therm%HEAT_MECA = zero
370 glob_therm%HEAT_CONV = zero
371 glob_therm%HEAT_RADIA = zero
372 glob_therm%HEAT_FFLUX = zero
373 econtd = zero
374 econt_cumu = zero
375 ELSE
376 output%TH%WFEXT = entmp(1)
377 ehour = entmp(2)
378 econtv= entmp(3)
379 epor = entmp(4)
380 glob_therm%HEAT_STORED = entmp(5)
381 glob_therm%HEAT_MECA = entmp(6)
382 glob_therm%HEAT_CONV = entmp(7)
383 glob_therm%HEAT_RADIA = entmp(8)
384 glob_therm%HEAT_FFLUX = entmp(9)
385 econtd = entmp(10)
386 econt_cumu = entmp(11)
387 ENDIF
388
389 IF(
ale%GRID%NWALE == 2)
THEN
390 entmp(1) =
ale%GRID%VGZ
392 IF(ispmd==0)
ale%GRID%VGZ = entmp(1)
393 ENDIF
394
395 CALL wrcomr(lmxvrea,lvarrea,tabvrea,dynain_data,interfaces%PARAMETERS,
396 . output,glob_therm)
397
398
399
400 WRITE(chrunr,'(I4.4)')irun
401 WRITE(procnam,'(I4.4)')ispmd+1
402 filnam=rootnam(1:rootlen)//'_'//chrunr//'_'//procnam
403 WRITE(plast,'(I4.4)')nspmd
404 filnamg=rootnam(1:rootlen)//'_'//chrunr//'_[0001-'//plast//']'
405 leng = rootlen+17
406 len = rootlen + 10
407 filnamr = filnam
408 ifil = 2
409 IF(ich/=0)ifil
410 IF(multirestTHEN
411 irprev
412 filnam'_'//ijk(irprev)
413 len = len+2
414 filnamg=filnamg(1:leng)//'_'//ijk(irprev)
415 leng = leng+2
416 ENDIF
417 filnam=filnam(1:len)//'.rst'
418 len = len +4
419 filnamg=filnamg(1:leng)//'.rst'
420 leng = leng+4
421
424
425 DO i = 1, len_tmp_name
426 ifilnam(i) = ichar(tmp_name(i:i))
427 END DO
429 IF (irform/5==2) THEN
430 CALL open_c(ifilnam,len_tmp_name,0)
431 ELSEIF (irform/5==3) THEN
432 CALL open_c(ifilnam,len_tmp_name,3)
433 ELSEIF (irform/5==4) THEN
434 CALL open_c(ifilnam,len_tmp_name,6)
435 ENDIF
436 DO i = 1, len
437 ifilnam(i) = ichar(filnam(i:i))
438 END DO
440
441
442
444 ititle(i) = ichar( names_and_titles%TITLE(i:i) )
445 ENDDO
447
448
449
450
451 tabhead(1) =iradios
452
453 tabhead(2) =iresfil
454
455 tabhead(3) =itestv
456
457 tabhead(4) =irun
458
459 icodrun =1
460 tabhead(5) =icodrun
461
462 tabhead(6) =codvers
463
464 tabhead(7) =iminver
465
466 tabhead(8) =isrcver
467
468 tabhead(9) =invers
469
470 tabhead(10)=scodver
471
472 tabhead(11)=sminver
473
474 tabhead(12)=ssrcver
475
476 tabhead(13)=invstr
477
478 tabhead(14) =lvarint
479 tabhead(15)=lvarrea
482
483
484
486
487
488
489 CALL checksum_restart_write(output%CHECKSUM)
490
491
492
493 len_g = npropgi*numgeo
494 len_m = npropmi*nummat
495 len_s = npart
496 CALL write_i_c(nodes%NODGLOB,nodes%NUMNOD)
497
499
501
503
505
507
509
511
513
515
517
518 CALL python_serialize(python,buffer, buffer_size)
520
522
524
526
528
530
532
534
536
538
540
542
544
546
547 IF (iale + ieuler + ialelag + glob_therm%ITHERM /= 0) THEN
548 itmp = SIZE(ale_connectivity%ee_connect%iad_connect)
550 CALL write_i_c(ale_connectivity%ee_connect%iad_connect, itmp)
551
552 itmp = SIZE(ale_connectivity%ee_connect%connected)
554 CALL write_i_c(ale_connectivity%ee_connect%connected, itmp)
555
556 itmp = SIZE(ale_connectivity%ee_connect%type)
558 CALL write_i_c(ale_connectivity%ee_connect%type, itmp)
559
560 itmp = SIZE(ale_connectivity%ee_connect%iface2)
562 CALL write_i_c(ale_connectivity%ee_connect%iface2, itmp)
563 ENDIF
564
566
568
569 IF(iale > 0 .AND.
ale%GRID%NWALE == 6 .OR. inter18_autoparam == 1 .OR. inter18_is_variable_gap_defined)
THEN
574 ENDIF
575 IF (iale > 0 .AND. (
ale%GRID%NWALE < 2 .OR.
ale%GRID%NWALE == 5.OR.
ale%GRID%NWALE == 7))
THEN
576 CALL write_i_c(ale_connectivity%NN_CONNECT%IAD_CONNECT, numnod + 1)
577 CALL write_i_c(ale_connectivity%NN_CONNECT%CONNECTED, ale_connectivity%NN_CONNECT%IAD_CONNECT(numnod + 1))
578 ENDIF
579 IF (iale > 0 .AND.
ale%GRID%NWALE == 6 .OR. inter18_autoparam == 1 .OR. inter18_is_variable_gap_defined)
THEN
580 CALL write_i_c(ale_connectivity%NE_CONNECT%IAD_CONNECT, numnod + 1)
581 CALL write_i_c(ale_connectivity%NE_CONNECT%CONNECTED,
582 . ale_connectivity%NE_CONNECT%IAD_CONNECT(numnod + 1))
583 ENDIF
584
585 ns_diff = 0
586 IF (multi_fvm%NS_DIFF) THEN
587 ns_diff = 1
588 ENDIF
590 IF (ns_diff == 1) THEN
591 CALL write_i_c(ale_connectivity%IDGLOB%ID,
592 . numels + nsvois + numelq + nqvois + numeltg + ntgvois)
593 ENDIF
594
596
598
600
602
604
606
608
610
612
614
616
618
620
622
624
626
628
629 IF(nsphsol/=0)THEN
630
632
634
636
638 END IF
639
641
642 IF (nintloadp>0) THEN
645 ENDIF
646
648
650
652
653
654
657 CALL write_i_c(ebcs_tab%nebcs_parallel, 1)
659 leni = 0
660 lenr = 0
661 IF (ebcs_tab%nebcs > 0) THEN
662
663 CALL write_i_c(ebcs_tab%my_typ,ebcs_tab%nebcs)
664 ENDIF
665
666
667 IF (ebcs_tab%nebcs_loc +ebcs_tab%nebcs_parallel + ebcs_tab%nebcs_fvm> 0) THEN
668 DO ii = 1, ebcs_tab%nebcs_fvm + ebcs_tab%nebcs_loc + ebcs_tab%nebcs_parallel
669 CALL ebcs_tab%tab(ii)%poly%write_common_data(leni, lenr)
670 CALL ebcs_tab%tab(ii)%poly%write_data(leni, lenr)
671 ENDDO
672 ENDIF
673
674
676
678
680
682
684
686
688
690
692
694
696
698
700
702
703 CALL write_i_c(rbe3%IRBE3,rbe3%NRBE3*irbe3_variables)
704
706
708
710
712
714
716
718
719
720
722
723
725
727
729
731
733
735
737
739
741
743
745
747
749
751
753
755
757
759
761
763
765
767
768 DO ii = 1, nvolu
769 ntri(ii) = t_monvol(ii)%NB_FILL_TRI
770 ENDDO
771
773 DO ii = 1, nvolu
774 IF (ntri(ii) > 0) THEN
775 CALL write_i_c(t_monvol(ii)%FILL_TRI(1:3* ntri(ii)), 3* ntri(ii))
776 ENDIF
777 ENDDO
778
780
781 IF(ns10e > 0)THEN
783 ENDIF
784
786
787 CALL thsurf_write_restart(output%TH%TH_SURF,2)
788
790
791 CALL write_i_c(nodes%BOUNDARY_ADD,siad_elem)
792
794
796
798
800
802
804
806
807 CALL write_i_c(rbe3%mpi%IAD_RBE3,nspmd+1)
808
810
812
814
816
818
820
822
824
826
828
830
832
834
836
837 CALL write_i_c(rbe3%mpi%FR_RBE3,rbe3%mpi%fr_rbe3_sz)
838
839 CALL write_i_c(rbe3%mpi%FR_RBE3MP,rbe3%mpi%fr_rbe3_sz)
840
842
844
846
848
850
852
854
856
858
860
862
864
866
867 CALL write_i_c(interfaces%SPMD_ARRAYS%FR_EDG,2*nbddedgt)
868
869 CALL write_i_c(interfaces%SPMD_ARRAYS%IAD_FREDG,(nspmd+1)*ninter25)
870
872
874
876
878
880
882
884
886
888
890
892
894
896
898
900
902
904
906
908
910
912
914
916
918
919 IF(icrack3d > 0)THEN
923 ENDIF
924
925
928
929
930 IF(iparit==1)THEN
931 CALL write_i_c(elements%PON%ADSKY,numnod+1)
932 CALL write_i_c(elements%PON%PROCNE,
SIZE(elements%PON%PROCNE))
933 IF(i2nsnt>0)THEN
935 ENDIF
937 IF(ns10e>0) THEN
939 ENDIF
941 CALL write_i_c(elements%PON%IADS ,
SIZE(elements%PON%IADS))
942 CALL write_i_c(elements%PON%IADS10 ,
SIZE(elements%PON%IADS10 ))
943 CALL write_i_c(elements%PON%IADS20 ,
SIZE(elements%PON%IADS20
944 CALL write_i_c(elements%PON%IADS16 ,
SIZE(elements%PON%IADS16 ))
945 CALL write_i_c(elements%PON%IADQ ,
SIZE(elements%PON%IADQ ))
946 CALL write_i_c(elements%PON%IADC ,
SIZE(elements%PON%IADC ))
947 CALL write_i_c(elements%PON%IAD_TRUSS ,
SIZE(elements%PON%IAD_TRUSS))
948 CALL write_i_c(elements%PON%IAD_BEAM ,
SIZE(elements%PON%IAD_BEAM ))
949 CALL write_i_c(elements%PON%IAD_SPRING ,
SIZE(elements%PON%IAD_SPRING ))
950 CALL write_i_c(elements%PON%IAD_TG ,
SIZE(elements%PON%IAD_TG ))
951 CALL write_i_c(elements%PON%IAD_TG6 ,
SIZE(elements%PON%IAD_TG6 ))
952 CALL write_i_c(elements%PON%IAD_MV ,
SIZE(elements%PON%IAD_MV ))
953 CALL write_i_c(elements%PON%IAD_CONLD ,
SIZE(elements%PON%IAD_CONLD
954 CALL write_i_c(elements%PON%IAD_CONV ,
SIZE(elements%PON%IAD_CONV))
955 CALL write_i_c(elements%PON%IAD_RADIA ,
SIZE(elements%PON%IAD_RADIA))
956 CALL write_i_c(elements%PON%IAD_LOADP ,
SIZE(elements%PON%IAD_LOADP))
957 CALL write_i_c(elements%PON%IAD_FXFLUX ,
SIZE(elements%PON%IAD_FXFLUX))
958
959
960
971
972
973
974 IF(iplyxfem > 0) THEN
976
979 ENDIF
980
981
982
983 IF(icrack3d > 0) THEN
989 ENDIF
990 ENDIF
991
992
993 IF(ebcs_tab%nebcs_parallel>0) THEN
994 DO i=1,ebcs_tab%nebcs
995 IF(ebcs_tab%my_typ(i)==10 .or. ebcs_tab%my_typ(i)==11) THEN
996 my_size = ebcs_tab%tab(i)%poly%nb_elem
997 CALL write_i_c(ebcs_parithon(i)%ELEM_ADRESS,4*my_size)
998 ENDIF
999 ENDDO
1000 ENDIF
1001
1002
1005
1008
1009 IF(nadmesh /= 0)THEN
1013 len=abs(lsh4trim)
1015 len=abs(lsh3trim)
1017 END IF
1018
1019
1020
1022 . interfaces%PARAMETERS)
1023
1024
1025
1027
1028
1029
1030 IF(nintstamp /= 0)THEN
1032 END IF
1033
1034
1035
1036 IF(ninterfric /= 0)THEN
1037 CALL intfric_wresti(intbuf_fric_tab
1038 END IF
1039
1040
1041
1042 IF(ntable /= 0)THEN
1044 END IF
1045
1047
1048 IF (nloadc>0)THEN
1051 ENDIF
1052 IF (nloadp>0)THEN
1055 ENDIF
1056 IF (pblast%NLOADP_B>0)THEN
1057 CALL pblast_write_engine(pblast)
1058 ENDIF
1059
1060 IF (loads%NLOAD_CYL > 0) THEN
1062 ENDIF
1063
1064 IF(icrack3d > 0)THEN
1070 END IF
1071
1072 IF(numelig3d > 0)THEN
1074
1076 ENDIF
1077
1079
1080
1081
1082 IF(nbcscyc > 0)THEN
1085 ENDIF
1086
1087
1088
1089 itmp = bcs%NUM_WALL
1091 IF(bcs%NUM_WALL > 0)THEN
1092 DO i=1, bcs%NUM_WALL
1093 CALL write_bcs_wall(bcs%WALL(i))
1094 ENDDO
1095 ENDIF
1096
1097
1098
1100
1101
1102
1104
1106
1108
1110
1112
1114
1116
1118
1120
1121 IF (n2d >0) THEN
1123 ENDIF
1124
1126
1128
1130
1132
1134
1135 skew_len = skews%N_SKEW_VAR * skews%TOTAL_SKEW_NUMBER
1137
1139
1141
1143
1145
1147
1149
1151
1153
1155
1157
1158 IF (multi_fvm%IS_USED) THEN
1159 CALL write_db(multi_fvm%PRES_SHIFT, 1)
1160 IF (n2d == 0) THEN
1161 CALL write_db(multi_fvm%VEL(1, :), numels)
1162 CALL write_db(multi_fvm%VEL(2, :), numels)
1163 CALL write_db(multi_fvm%VEL(3, :), numels)
1164 ELSE
1165 CALL write_db(multi_fvm%VEL(1, :), numelq + numeltg)
1166 CALL write_db(multi_fvm%VEL(2, :), numelq + numeltg)
1167 CALL write_db(multi_fvm%VEL(3, :), numelq + numeltg)
1168 ENDIF
1169 ENDIF
1170
1172
1174
1176
1178
1180
1182
1184
1186
1188
1190
1192
1194
1196
1198
1200
1202
1204
1206
1208
1209 CALL write_db(gauge,llgauge*nbgauge)
1210
1212
1214
1215 CALL write_db(rbe3%FRBE3,rbe3%frbe3_sz)
1216
1217 CALL write_rrbe3pen(rbe3%PEN)
1218
1219 CALL write_db(factiv,lractiv*nactiv)
1220
1222
1224
1226
1228
1230
1232
1233 flag_xfem = 0
1235
1236
1237 IF (icrack3d > 0) THEN
1238 flag_xfem = 1
1239 DO ixel=1,nxel
1241 ENDDO
1242 ENDIF
1243
1245
1247
1249
1251
1253
1255
1257
1259
1261
1263
1267
1268
1269
1271 . interfaces%PARAMETERS)
1272
1273
1274
1276
1277
1278
1279 IF (iresmd==0.AND.npsav>=25) THEN
1280
1281 IF(nspmd > 1)
1283 IF (ispmd/=0)THEN
1284 DO m=1,npsav*npart
1285 partsav(m) = zero
1286 ENDDO
1287 ENDIF
1289 ENDIF
1290 IF(nnoise>0)THEN
1292 CALL write_db(af(mf01),6*ncnois*nnoise+1)
1293 ENDIF
1294
1295
1296 IF (iresmd==1) THEN
1299
1301 ENDIF
1302
1303 IF (iresp == 1) THEN
1306 ENDIF
1307
1308
1309 my_ilen = 4*nrlink+nrlink*(nspmd+2)
1310 . +lllink+lllink*
min(1,iparit)
1311 . +nsflsw+8*ntflsw+44*ncuts
1313 my_rlen = 9*nsflsw+7*ncuts
1319
1320
1326
1327 IF(nadmesh /= 0 .OR. irest_mselt /= 0)THEN
1333 END IF
1334
1335 IF(irest_mselt /= 0)THEN
1340 END IF
1341
1342 IF(nadmesh /= 0)THEN
1343 CALL write_db(padmesh,kpadmesh*npart)
1344 IF(glob_therm%ITHERM_FE > 0)THEN
1347 END IF
1348 END IF
1349
1355 ENDIF
1356
1357 IF(istatcnd /= 0)THEN
1360 ENDIF
1361
1362
1363
1364 IF(nintstamp /= 0)THEN
1366 END IF
1367
1368 IF(h3d_data%N_SCAL_SKID > 0) THEN
1369 IF(nintstamp/=0) THEN
1370 CALL write_db(pskids, h3d_data%N_SCAL_SKID*numnodg)
1371 ELSE
1372 CALL write_db(pskids, h3d_data%N_SCAL_SKID*numnod)
1373 ENDIF
1374 ENDIF
1375
1377 IF(nintstamp/=0.AND.nspmd > 1 ) THEN
1378 IF(ispmd == 0)
CALL write_db(fcont_max, 3*numnodg)
1379 ELSE
1381 ENDIF
1382 ENDIF
1383
1387 ENDIF
1388
1390 CALL write_db(fcont2_max, 3*numnod)
1391 ENDIF
1393 CALL write_db(fncont2_max, 3*numnod)
1394 CALL write_db(ftcont2_max, 3*numnod)
1395 CALL write_db(npcont2_max, 3*numnod)
1396 ENDIF
1397
1399 CALL write_db(fcont2_min, 3*numnod)
1400 ENDIF
1402 CALL write_db(fncont2_min, 3*numnod)
1403 CALL write_db(ftcont2_min, 3*numnod)
1404 CALL write_db(npcont2_min, 3*numnod)
1405 ENDIF
1406
1410 ENDIF
1413 IF(nintstamp/=0)
CALL write_db(efricg_stamp, numnodg)
1414 ENDIF
1415
1416
1417
1418 IF(ninterfric /= 0)THEN
1419 CALL intfric_wrestr(intbuf_fric_tab,ninterfric)
1420 END IF
1421
1424 IF(idtmins==1)THEN
1426 ELSEIF(idtmins==2)THEN
1433 END IF
1434 IF(idtmins/=0.OR.idtmins_int/=0)THEN
1436 END IF
1437
1438 IF(idtmins==2.OR.idtmins_int/=0) THEN
1439
1441
1443 END IF
1444
1445 IF (isms_selec /= 0) THEN
1447 ENDIF
1448
1449
1450
1451 IF(ntable /= 0)THEN
1453 END IF
1454
1455
1456
1457#ifdef DNC
1458 CALL eng_wrt_mds()
1459#endif
1460
1461
1462
1463 IF(slinale > 0)THEN
1465 END IF
1466
1467
1468
1469 CALL write_ale_grid()
1470
1471
1472
1474
1475
1476
1477 IF (neig>0) THEN
1478 CALL eigwrest(eigipm, eigibuf, eigrpm)
1479 ENDIF
1480
1481
1482
1483 DO i = 1, nslipring
1491
1498
1500
1510
1524
1525 ENDDO
1526
1527 ENDDO
1528
1529 DO i = 1, nretractor
1565 DO j=1,2
1570 ENDIF
1571 ENDDO
1572 ENDDO
1573
1574 IF (n_anchor_remote > 0) THEN
1577 ENDIF
1578
1579 IF (n_anchor_remote_send > 0) THEN
1582 ENDIF
1583
1584 IF ((nslipring_g + nretractor_g >0).AND.(ispmd == 0)) THEN
1592 ENDDO
1593 ENDIF
1594 ENDIF
1595
1596
1597
1598
1605
1606 IF (nconld > 0) THEN
1609 ENDIF
1610
1611
1612
1616 ENDIF
1617
1618 IF (nflow>0)
CALL nfwrest(iflow, rflow)
1619
1621
1622 IF (impl_s>0) THEN
1625 ENDIF
1626
1627 IF(glob_therm%ITHERM_FE > 0 )
CALL thcwrest(mcp, temp)
1628
1630
1632
1634
1635
1636 IF (glob_therm%NUMCONV > 0) THEN
1638 END IF
1639 IF (glob_therm%NUMRADIA > 0) THEN
1641 END IF
1642 IF (glob_therm%NFXFLUX > 0) THEN
1644 END IF
1645 IF (glob_therm%NFXTEMP > 0) THEN
1647 END IF
1648
1649
1650 IF (iplyxfem > 0)THEN
1655 ENDIF
1656
1657 IF (nloadc > 0)
CALL write_db(cfield,lfacload*nloadc)
1658 IF (nloadp > 0)
CALL write_db(loadp,lfacload*nloadp)
1659 IF (nintloadp > 0)
CALL write_db(dgaploadint,ninter*nloadp_hyd)
1660
1661
1662 IF (loads%NINIVELT>0) CALL write_inivel(loads%NINIVELT,loads%INIVELT)
1663
1664
1665 IF (icrack3d > 0) THEN
1668 ENDIF
1669
1671
1673
1675
1676 IF (sknot > 0)
CALL write_db(knot,sknot)
1677 IF (sknotlocpc > 0)
CALL write_db(knotlocpc,sknotlocpc)
1678 IF (sknotlocel > 0)
CALL write_db(knotlocel,sknotlocel)
1679 IF (numelig3d > 0)
CALL write_db(wige,numnod)
1680
1681 IF(ipart_stack >0)
CALL stack_wrest(stack%IGEO,stack%GEO,stack%PM )
1682
1683 IF (ndrape > 0)
CALL drape_wrest(drape_sh4n , drape_sh3n,drapeg)
1684
1686
1687
1688
1691
1692
1693
1695
1696
1698
1699 IF(ispmd==0)THEN
1700 WRITE (iout,1000) filnamg(1:leng)
1701 WRITE (istdo,1050) filnamg(1:leng)
1702 ENDIF
1703
1704 1000 FORMAT (/4x,' RESTART FILES:',1x,a,' WRITTEN'/
1705 . 4x,' -------------'/)
1706 1050 FORMAT (4x,' RESTART FILES:',1x,a,' written')
1707
1708 RETURN
subroutine compress_i_nnz(array, len)
subroutine compress_r_nnz(array, len)
subroutine wrcomi(lmxvint, lvarint, tabvint, isp, multi_fvm, h3d_data, dynain_data, inter_parameters, sensors, loads, glob_therm, pblast)
subroutine drape_wrest(drape_sh4n, drape_sh3n, drapeg)
subroutine plyxfem_wrestanim()
subroutine ply_info_wrest(ply_info)
subroutine crkxfem_wrestanim(crkedge, crksky, indx_crk, xedge4n, xedge3n)
subroutine crkxfem_wrest(inod, iel, nodlevxf)
subroutine nitschewrest(forneqs)
subroutine fxtempwrest(ibft, fbft, glob_therm)
subroutine radiawrest(ibcr, fradia, glob_therm)
subroutine stack_wrest(igeo, geo, pm)
subroutine plyxfem_wravuply()
subroutine impwrest(nimpr)
subroutine alelag_wrest()
subroutine imp_trans(r_imp)
subroutine fxfluxwrest(ibfflux, fbfflux, glob_therm)
type(alefvm_buffer_), target alefvm_buffer
type(alefvm_param_), target alefvm_param
integer, dimension(:), allocatable id_damp_vrel
integer, dimension(:), allocatable fr_damp_vrel
integer, dimension(:), pointer iadcnd
integer, dimension(:), pointer fr_cndm
integer, dimension(:), pointer procncnd
integer, dimension(:), pointer icnds10
integer, dimension(:), pointer addcncnd
integer, dimension(:), pointer iad_cndm
type(surf_), dimension(:), allocatable, target igrsurf
type(surf_), dimension(:), allocatable, target igrslin
character(len=outfile_char_len) outfile_name
type(intstamp_data), dimension(:), allocatable intstamp
integer, parameter ltitle
integer, dimension(:), allocatable poin_ump
integer, dimension(:), allocatable iconx
integer, dimension(:), allocatable, target igrv
integer, dimension(:), allocatable fr_sec
integer, dimension(:), allocatable iad_rby
integer, dimension(:), allocatable id_global_vois
integer, dimension(:), allocatable fr_nbedge
integer, dimension(:), allocatable iadrbmk
integer, dimension(:), allocatable fr_mad
integer, dimension(:), allocatable ibcv
integer, dimension(:), allocatable lagbuf
integer, dimension(:), allocatable ixx
integer, dimension(:), allocatable, target lpby
integer, dimension(:), allocatable fr_rl
integer, dimension(:), allocatable, target ixs
integer, dimension(:), allocatable iad_rbym2
integer, dimension(:), allocatable iad_i2m
integer, dimension(:), allocatable iad_cut
integer, dimension(:), allocatable lgrav
integer, dimension(:), allocatable, target npby
integer, dimension(:), allocatable kxig3d
integer, dimension(:), allocatable iadmv3
integer, dimension(:), allocatable face_vois
integer, dimension(:), pointer iframe
integer, dimension(:), pointer madfail
integer, dimension(:), allocatable lesdvois
integer, dimension(:), allocatable lnrcvois
integer, dimension(:), allocatable nativ0_sms
integer, dimension(:), allocatable newfront
integer, dimension(:), allocatable iadc_crkxfem
integer, dimension(:), allocatable nodpor
integer, dimension(:), allocatable ilink
integer, dimension(:), allocatable llink
integer, dimension(:), allocatable madclnod
integer, dimension(:,:), allocatable ipadmesh
integer, dimension(:), allocatable lbvel
integer, dimension(:), allocatable lprtsph
integer, dimension(:), allocatable nbsdvois
integer, dimension(:), allocatable lnodpor
integer, dimension(:), allocatable ibcr
integer, dimension(:), allocatable ne_nercvois
integer, dimension(:), allocatable iadmv2
integer, dimension(:), allocatable neflsw
integer, dimension(:), allocatable ixig3d
integer, dimension(:), allocatable linale
type(cluster_), dimension(:), allocatable cluster
integer, dimension(:), allocatable iactiv
integer, dimension(:), allocatable crknodiad
integer, dimension(:), allocatable ne_lercvois
integer, dimension(:), allocatable ibcslag
integer, dimension(:), allocatable ibufssg_io
integer, dimension(:,:), allocatable sh4tree
integer, dimension(:), allocatable fr_lagf
integer, dimension(:), allocatable ispsym
integer, dimension(:), allocatable sh4trim
integer, dimension(:), allocatable addcsrect
integer, dimension(:), allocatable ipm
integer, dimension(:), allocatable, target ipart
integer, dimension(:), allocatable iadwal
integer, dimension(:), allocatable fr_nor
integer, dimension(:), allocatable isphio
integer, dimension(:), allocatable fr_i18
integer, dimension(:), allocatable, target ipari
integer, dimension(:), allocatable fr_rbym2
integer, dimension(:), allocatable igaup
integer, dimension(:), allocatable iad_rbm
integer, dimension(:), allocatable iskew_ply
integer, dimension(:), allocatable nnflsw
integer, dimension(:), allocatable nercvois
type(failwave_str_) failwave
integer, dimension(:), allocatable ispcond
integer, dimension(:), allocatable ibordnode
integer, dimension(:), allocatable sh3trim
integer, dimension(:), allocatable iadrbk
integer, dimension(:), allocatable iecran
integer, dimension(:), allocatable, target iedgesh
integer, dimension(:), allocatable fr_i2m
integer, dimension(:), allocatable ixt
integer, dimension(:), allocatable lnlink
integer, dimension(:), allocatable ibftemp
integer, dimension(:), allocatable ibfv
integer, dimension(:), allocatable iaccp
integer, dimension(:), allocatable, target iel_crkxfem
integer, dimension(:), allocatable iadi18
integer, dimension(:), allocatable lsegcom
integer, dimension(:), allocatable iskwp_l
integer, dimension(:), allocatable inod_pxfem
integer, dimension(:), allocatable dd_r2r_elem
integer, dimension(:), allocatable kloadpinter
integer, dimension(:), allocatable ixr
integer, dimension(:,:), allocatable sh3tree
integer, dimension(:), allocatable lonfsph
integer, dimension(:), pointer madnod
integer, dimension(:), allocatable madidx
integer, dimension(:), allocatable iexlnk
integer, dimension(:), allocatable, target ixtg
integer, dimension(:), pointer lpbyl
integer, dimension(:), allocatable nnlink
integer, dimension(:), allocatable, target ibcl
integer, dimension(:), allocatable adsky_crkxfem
integer, dimension(:), pointer madprt
integer, dimension(:), allocatable fr_rbym
integer, dimension(:), allocatable monvol
integer, dimension(:), allocatable ifill
integer, dimension(:), allocatable iskwp
integer, dimension(:), allocatable isensp
integer, dimension(:), allocatable fr_rbe2
integer, dimension(:), allocatable irbe2
integer, dimension(:), allocatable inod_crkxfem
integer, dimension(:), allocatable nporgeo
integer, dimension(:), allocatable procne_crkxfem
integer, dimension(:), allocatable fr_rbm2
integer, dimension(:), allocatable kxsp
integer, dimension(:), allocatable neth
integer, dimension(:), allocatable nodlevxf
integer, dimension(:), allocatable fr_wall
integer, dimension(:), allocatable loadpinter
integer, dimension(:), allocatable fr_ll
integer, dimension(:), allocatable iad_sec
integer, dimension(:), allocatable nsensp
integer, dimension(:), allocatable dd_iad
integer, dimension(:), allocatable gjbufi
integer, dimension(:), pointer madsh3
integer, dimension(:), allocatable icut
integer, dimension(:), allocatable fr_cj
integer, dimension(:), allocatable, target iskwn
integer, dimension(:), allocatable nesdvois
integer, dimension(:), allocatable cne_crkxfem
integer, dimension(:), allocatable, target iloadp
integer, dimension(:), allocatable iadcj
integer, dimension(:), allocatable nprw
integer, dimension(:), allocatable ngaup
integer, dimension(:), allocatable lnrbym
integer, dimension(:), allocatable nod2sp
integer, dimension(:), allocatable adsky_pxfem
integer, dimension(:), allocatable nodglobxfe
integer, dimension(:), allocatable weight_rm
integer, dimension(:), allocatable ixp
integer, dimension(:), allocatable laccelm
integer, dimension(:), allocatable, target nom_opt
integer, dimension(:), allocatable iad_rbe2
double precision, dimension(:), allocatable bufgeo
integer, dimension(:), pointer madsol
integer, dimension(:), allocatable fasolfr
integer, dimension(:), allocatable iadi2
integer, dimension(:), allocatable, target npc
integer, dimension(:), allocatable igeo
integer, dimension(:), allocatable, target ibmpc
integer, dimension(:), allocatable ixtg1
integer, dimension(:), allocatable fr_mv
integer, dimension(:), allocatable ims
integer, dimension(:), allocatable fr_edge
integer, dimension(:), allocatable lercvois
integer, dimension(:), allocatable iadrl
integer, dimension(:), allocatable addcni2
integer, dimension(:), allocatable lbcscyc
integer, dimension(:), allocatable fr_rby2
integer, dimension(:), allocatable iad_frnor
integer, dimension(:), allocatable iadc_pxfem
integer, dimension(:), allocatable ne_lesdvois
integer, dimension(:), allocatable ibvel
integer, dimension(:), allocatable iadrbm
integer, dimension(:), allocatable lrivet
integer, dimension(:), pointer npbyl
integer, dimension(:), allocatable iad_edge
integer, dimension(:), allocatable, target icfield
integer, dimension(:), allocatable kinet
integer, dimension(:), allocatable lgauge
integer, dimension(:), allocatable nstrf
integer, dimension(:), allocatable ibcscyc
integer, dimension(:), allocatable procnor
integer, dimension(:), allocatable tag_skins6
integer, dimension(:), allocatable fr_rby
integer, dimension(:), allocatable iad_rbm2
integer, dimension(:), allocatable irbym
integer, dimension(:,:), allocatable ixsp
integer, dimension(:), pointer madsh4
integer, dimension(:), allocatable iparg
integer, dimension(:), allocatable ixq
integer, dimension(:), allocatable iedge
integer, dimension(:), allocatable ibfflux
integer, dimension(:), allocatable nodedge
integer, dimension(:), allocatable ilas
integer, dimension(:), allocatable iad_rby2
integer, dimension(:), allocatable icode_ply
integer, dimension(:), allocatable lloadp
integer, dimension(:), allocatable fr_cut
integer, dimension(:), allocatable segquadfr
integer, dimension(:), allocatable procni2
integer, dimension(:), allocatable lcfield
integer, dimension(:), allocatable kxx
integer, dimension(:), allocatable nskwp
integer, dimension(:), allocatable ne_nesdvois
integer, dimension(:), allocatable iad_rbym
integer, dimension(:), allocatable nom_sect
integer, dimension(:), allocatable lprw
integer, dimension(:), allocatable npsegcom
type(nlocal_str_) nloc_dmg
integer, dimension(:), allocatable rg_cut
integer, dimension(:), allocatable iel_pxfem
integer, dimension(:), allocatable lrbe2
integer, dimension(:), allocatable fr_rbm
integer, dimension(:), allocatable llagf
integer, dimension(:), allocatable nbrcvois
integer, dimension(:), allocatable lnsdvois
integer, dimension(:,:), allocatable tab_ump
integer, dimension(:), allocatable naccp
integer, dimension(:), allocatable procne_pxfem
integer, dimension(:), allocatable ithvar
integer, dimension(:), allocatable dd_r2r
integer, dimension(:), allocatable iadll
integer, dimension(:), allocatable icontact
integer, dimension(:), allocatable ipart_state
integer nseatbelt_th_proc
type(retractor_struct), dimension(:), allocatable retractor
type(seatbelt_remote_nodes_struct) anchor_remote_send
type(seatbelt_remote_nodes_struct) anchor_remote
type(seatbelt_th_exch_struct), dimension(:), allocatable seatbelt_th_exch
type(slipring_struct), dimension(:), allocatable slipring
integer, dimension(:), allocatable sph2sol
integer, dimension(:), allocatable irst
integer, dimension(:), allocatable sol2sph_typ
integer, dimension(:), allocatable sol2sph
integer, dimension(:,:), allocatable ply_info
type(ttable), dimension(:), allocatable table
type(time_type) global_comp_time
type(xfem_sky_), dimension(:), allocatable crksky
integer, dimension(:,:), allocatable xedge4n
integer, dimension(:), allocatable indx_crk
type(xfem_edge_), dimension(:), allocatable crkedge
integer, dimension(:,:), allocatable xedge3n
subroutine spmd_glob_dmin9(v, len)
subroutine spmd_glob_dsum9(v, len)
subroutine write_joint(ljoint, cep, cel, proc, nodlocal, ljoint_l, len_ia, numnod_l)
subroutine w_bufbric_22()
subroutine write_pcyl(load_cyl, nload_cyl, nodlocal)
subroutine write_matparam(mat_elem, len)
subroutine w_cluster(cluster, iparg, nodlocal, ncluster_l, cep, proc, numlocgroup, len_ia, len_am)
subroutine w_elbuf_str(proc, iparg, elbuf_tab, len_am, flag_xfem)
subroutine w_failwave(failwave, nodglob, numnod, numnod_l, len_am, itab)
subroutine w_group_str(len_ia, igrnod, igrbric, igrquad, igrsh4n, igrsh3n, igrtruss, igrbeam, igrspring, igrpart, cep, cel, nodlocal, proc, frontb_r2r, numnod_l)
subroutine w_subset_str(subset, len_ia)
subroutine wrcomr(lmxvrea, lvarrea, tabvrea, ms_nd, p, inter_parameters, unitab, glob_therm, output)
subroutine write_elgroup_param(group_param_tab, iparg, proc, ngroup_l, len)
subroutine write_nloc_struct(nloc_dmg, numnod_l, nodglob, nodloc, cel, cep, proc, ixs, ixc, ixtg, numels_l, numelc_l, numeltg_l)
subroutine nfwrest(iflow, rflow)
subroutine plyxfem_wrest(ms_ply, zi_ply, iel, inod, icode, iskew)
subroutine thcwrest(mcp, temp)
subroutine convwrest(ibcv, fconv, numconv, niconv, lfacther)
subroutine eigwrest(eigipm, eigibuf, eigrpm)
subroutine rigmatwrest(rbym, irbym, lcrbym, weight)
subroutine userwi_write(user_windows, ispmd, nspmd, numnod)
subroutine w_line_str(igrslin)
subroutine w_surf_str(igrsurf)
subroutine write_db(a, n)
subroutine write_dpdb(a, n)
subroutine write_intbuf(intbuf_tab)
void write_i_c(int *w, int *len)
void file_size(int *filesize)
void write_c_c(int *w, int *len)
void open_c(int *ifil, int *len, int *mod)
subroutine write_th_restart(th)
subroutine write_units(unitab)