159
160
161
162 USE connectivity_mod
163 USE nodal_arrays_mod
164 USE python_funct_mod
172 USE multi_fvm_mod
175 USE mat_elem_mod
179 USE sensor_mod
180 USE ebcs_mod
182 USE pblast_mod
189 USE output_mod
190 USE interfaces_mod
191 USE sensor_mod
192 USE loads_mod
194 USE bcs_mod , ONLY : bcs
195 USE skew_mod
201 use read_inivel_mod, only : read_inivel
202 use glob_therm_mod
203 use read_ale_grid_mod, only : read_ale_grid
204 use read_bcs_wall_mod, only : read_bcs_wall
205 use rbe3_mod
206 use restart_rbe3pen_mod, only : get_nrbe3pen_l,read_rrbe3pen
207 use checksum_output_option_mod
208
209
210
211#include "implicit_f.inc"
212
213
214
215#include "mvsiz_p.inc"
216
217
218
219#include "com01_c.inc"
220#include "com04_c.inc"
221#include "com_xfem1.inc"
222#include "couple_c.inc"
223#include "intstamp_c.inc"
224#include "param_c.inc"
225#include "parit_c.inc"
226#include "remesh_c.inc"
227#include "scr06_c.inc"
228#include "scr03_c.inc"
229#include "scr05_c.inc"
230#include "scr07_c.inc"
231#include "scr14_c.inc"
232#include "scr16_c.inc"
233#include "scr19_c.inc"
234#include "scrcut_c.inc"
235#include "scrfs_c.inc"
236#include "scrnoi_c.inc"
237#include "scr_fac_c.inc"
238#include "sms_c.inc"
239#include "sphcom.inc"
240#include "spmd_c.inc"
241#include "tabsiz_c.inc"
242#include "task_c.inc"
243
244
245
246 INTEGER IAF(*),LVARREA,LEN_G,LEN_M, IRUNN
248 TYPE(MULTI_FVM_STRUCT) :: MULTI_FVM
249 TYPE(H3D_DATABASE) :: H3D_DATA
250 TYPE(PINCH) :: PINCH_DATA
251 TYPE(t_ale_connectivity), INTENT(INOUT) :: ALE_CONNECTIVITY
252 TYPE(MONVOL_STRUCT_),DIMENSION(NVOLU), INTENT(INOUT) :: T_MONVOL
253 TYPE(t_ebcs_tab), INTENT(INOUT) :: EBCS_TAB
254 TYPE(DYNAIN_DATABASE) ,INTENT(INOUT) :: DYNAIN_DATA
255 TYPE(USER_WINDOWS_) ,INTENT(INOUT) :: USER_WINDOWS
256 TYPE(OUTPUT_) ,INTENT(INOUT) :: OUTPUT
257 TYPE(INTERFACES_) ,INTENT(INOUT) ::
258 TYPE(SENSORS_) ,INTENT(INOUT) :: SENSORS
259 TYPE(LOADS_) ,INTENT(INOUT) :: LOADS
260 TYPE(MAT_ELEM_) ,INTENT(INOUT) :: MAT_ELEM
261 TYPE(PYTHON_) ,INTENT(INOUT) :: PYTHON
262 TYPE() ,INTENT(INOUT) :: SKEWS
263 TYPE(UNIT_TYPE_) ,INTENT(INOUT) :: UNITAB
264 TYPE (STACK_PLY) ,INTENT(INOUT) :: STACK
265 TYPE(DRAPE_) ,INTENT(INOUT) :: DRAPE_SH3N(NUMELTG_DRAPE)
266TYPE(DRAPEG_) ,INTENT(INOUT) :: DRAPEG
267 TYPE(GLOB_THERM_) ,INTENT(INOUT) :: GLOB_THERM
268 TYPE(PBLAST_) ,INTENT(INOUT) :: PBLAST
269 TYPE(connectivity_) ,INTENT(INOUT) :: ELEMENT
270 TYPE(nodal_arrays_) ,INTENT(INOUT) :: NODES
271 TYPE(RBE3_) ,INTENT(INOUT) :: RBE3
272 INTEGER, INTENT(IN) :: LIFLOW
273 INTEGER, INTENT(IN) :: LRFLOW
274 my_real,
INTENT(INOUT) :: forneqs(3,numnod)
275 INTEGER, INTENT(INOUT) :: IFLOW(LIFLOW)
276 my_real,
INTENT(INOUT) :: rflow(lrflow)
277 INTEGER, INTENT(IN) :: IMPL_S0
278 INTEGER, INTENT(IN) :: NDRAPE
279
280
281
282 INTEGER IDUMM(MVSIZ)
283 INTEGER I,J,LMXVREA, LEN,MY_ILEN,MY_RLEN,ISTAT,II,NS_DIFF
284 parameter(lmxvrea=1000+30*maxlaw+30)
286 INTEGER, DIMENSION(:), ALLOCATABLE::IBID
287 my_real,
DIMENSION(:),
ALLOCATABLE::rbid
288 DOUBLE PRECISION, DIMENSION(:),ALLOCATABLE :: XDPDUM
289 INTEGER, DIMENSION(NVOLU) :: NTRI
290 INTEGER, DIMENSION(:), ALLOCATABLE :: INTEGER_DATA
291 INTEGER :: INT1, INT2, INT3, INT0, ITMP
292 INTEGER :: MY_SIZE
293 INTEGER :: PYTHON_LEN
294 INTEGER, DIMENSION(:), ALLOCATABLE :: BUFFER
295 INTEGER :: SKEW_LEN
296 LOGICAL ::
297 INTEGER :: NPT,NRBE3PEN_L
298
299
300
301 DO i=1,lmxvrea
302 tabvrea(i)=zero
303 ENDDO
304 IF(lvarrea>lmxvrea)THEN
305 CALL ancmsg(msgid=33,anmode=aninfo,i1=lvarrea,i2=lmxvrea)
307 ENDIF
308
309
310
311
312 len_g = npropgi*numgeo
313 len_m = npropmi*nummat
314
316
317 CALL checksum_restart_read(output%CHECKSUM)
318
319 CALL read_i_c(nodes%NODGLOB,snodglob)
320
321 CALL read_i_c(nodes%MAIN_PROC,sweight)
322
324
326
328
330
332
334
336
338
340
342
343
344 ALLOCATE(buffer(python_len))
345 buffer(1) = python_len
346 CALL read_i_c(buffer(2:python_len), python_len-1)
347 CALL python_deserialize(python, buffer)
348 DEALLOCATE(buffer)
349
351
353
355
357
359
360 CALL read_i_c(element%shell%ixc,sixc)
361 DO i = 1, sixc / nixc
362 element%shell%nodes(1:4,i) = element%shell%ixc(2:5, i)
363 element%shell%pid(i) = element%shell%ixc(6, i)
364 element%shell%matid(i) = element%shell%ixc(1, i)
365 element%shell%user_id(i) = element%shell%ixc(7, i)
366 ENDDO
367 CALL init_global_shell_id(element%SHELL)
368
370
372
374
376
377 CALL init_global_node_id(nodes,numnod)
378
380
382
383 CALL read_i_c(ale_connectivity%NALE,
ale%GLOBAL%SNALE)
384
385 IF (iale + ieuler + ialelag + glob_therm%ITHERM /= 0) THEN
387 ALLOCATE(ale_connectivity%ee_connect%iad_connect(itmp))
388 CALL read_i_c(ale_connectivity%ee_connect%iad_connect, itmp)
389
391 ALLOCATE(ale_connectivity%ee_connect%connected(itmp))
392 CALL read_i_c(ale_connectivity%ee_connect%connected, itmp)
393
395 ALLOCATE(ale_connectivity%ee_connect%type(itmp))
396 CALL read_i_c(ale_connectivity%ee_connect%type, itmp)
397
399 ALLOCATE(ale_connectivity%ee_connect%iface2(itmp))
400 CALL read_i_c(ale_connectivity%ee_connect%iface2, itmp)
401 ENDIF
402
404
406
407 IF(ale_connectivity%has_ne_connect) THEN
414 ELSE
417 ENDIF
418 IF (iale > 0 .AND.
ale%GRID%NWALE_RST >= 0)
THEN
419 IF(ale_connectivity%has_nn_connect)THEN
420 ALLOCATE(ale_connectivity%NN_CONNECT%IAD_CONNECT(numnod + 1))
421 CALL read_i_c(ale_connectivity%NN_CONNECT%IAD_CONNECT, numnod + 1)
422 ALLOCATE(ale_connectivity%NN_CONNECT%CONNECTED(ale_connectivity%NN_CONNECT%IAD_CONNECT(numnod + 1)))
423 CALL read_i_c(ale_connectivity%NN_CONNECT%CONNECTED, ale_connectivity%NN_CONNECT%IAD_CONNECT(numnod + 1))
424 ENDIF
425 ENDIF
426 IF(ale_connectivity%has_ne_connect)THEN
427 ALLOCATE(ale_connectivity%NE_CONNECT%IAD_CONNECT(numnod + 1))
428 CALL read_i_c(ale_connectivity%NE_CONNECT%IAD_CONNECT, numnod + 1)
429 ALLOCATE(ale_connectivity%NE_CONNECT%CONNECTED(ale_connectivity%NE_CONNECT%IAD_CONNECT(numnod + 1)))
430 CALL read_i_c(ale_connectivity%NE_CONNECT%CONNECTED, ale_connectivity%NE_CONNECT%IAD_CONNECT(numnod + 1))
431 ENDIF
432
434 multi_fvm%NS_DIFF = .false.
435 IF (ns_diff == 1) THEN
436 multi_fvm%NS_DIFF = .true.
437 ale_connectivity%HAS_IDGLOB = .true.
438 IF (.NOT. ALLOCATED(ale_connectivity%IDGLOB%ID)) THEN
439 ALLOCATE(ale_connectivity%IDGLOB%ID(numels + nsvois + numelq + nqvois + numeltg + ntgvois))
440 ENDIF
441 IF (.NOT. ALLOCATED(ale_connectivity%IDGLOB%UID)) THEN
442 ALLOCATE(ale_connectivity%IDGLOB%UID(numels + nsvois + numelq + nqvois + numeltg + ntgvois))
443 ENDIF
444 IF (.NOT. ALLOCATED(multi_fvm%ELEM_DATA%CENTROID)) THEN
445 ALLOCATE(multi_fvm%ELEM_DATA%CENTROID(3, numels + nsvois + numelq + nqvois + numeltg + ntgvois))
446 ENDIF
447 IF (.NOT. ALLOCATED(multi_fvm%FACE_DATA%CENTROID)) THEN
448 ALLOCATE(multi_fvm%FACE_DATA%CENTROID(3, 6, numels + nsvois + numelq + nqvois + numeltg + ntgvois))
449 ENDIF
450 IF (.NOT. ALLOCATED(multi_fvm%VOL)THEN
451 ALLOCATE(multi_fvm%VOL(numels + nsvois + numelq + nqvois + numeltg + ntgvois))
452 ENDIF
453 CALL read_i_c(ale_connectivity%IDGLOB%ID, numels + nsvois + numelq + nqvois + numeltg + ntgvois)
454 CALL read_i_c(ale_connectivity%IDGLOB%UID, numels + nsvois + numelq + nqvois + numeltg + ntgvois)
455 ENDIF
456
458
460
462
464
466
468
470
472
474
476
478
480
482
484
486
488
490
491 IF(nsphsol/=0)THEN
492
494
496
498
500 END IF
501
503
504 IF (nintloadp>0) THEN
507 ENDIF
508
510
512
514
515
516 ! ebcs option
521
522 ebcs_tab%nebcs = int0
523 ebcs_tab%nebcs_fvm = int1
524 ebcs_tab%nebcs_parallel = int2
525 ebcs_tab%nebcs_loc = int3
526
527 IF (int0 > 0) THEN
528 ALLOCATE(integer_data(int0))
529 CALL ebcs_tab%read_type_data(int0, integer_data)
530 ALLOCATE(ebcs_tab%my_typ(int0))
531 ALLOCATE(ebcs_tab%need_to_compute(int0))
532
533 ebcs_tab%my_typ(1:int0) = integer_data(1:int0)
534
535
536
537
538 DO ii=1,int0
539 ebcs_tab%need_to_compute(ii) = .false.
540 IF(ispmd /= 0) THEN
541 is_ebcs_parallel = .false.
542 IF(ebcs_tab%my_typ(ii) == 10 .or. ebcs_tab%my_typ(ii) == 11)is_ebcs_parallel = .true.
543 IF(is_ebcs_parallel) ebcs_tab%need_to_compute(ii) = .true.
544 ELSE
545 ebcs_tab%need_to_compute(ii) = .true.
546 ENDIF
547 ENDDO
548
549
550 CALL ebcs_tab%create_from_types(int1 + int2 + int3 , integer_data(1:int1 + int2 + int3 ))
551 ENDIF
552
553 IF (int1 + int2 + int3 > 0) THEN
554 DO ii = 1, int1 + int2 + int3
555 CALL ebcs_tab%tab(ii)%poly%read_common_data()
556 CALL ebcs_tab%tab(ii)%poly%read_data()
557 ENDDO
558 ENDIF
559
560 ALLOCATE( ebcs_parithon(ebcs_tab%nebcs) )
561
562
564
566
568
570
572
574
576
578
580
582
584
586
588
590
591 CALL read_i_c(rbe3%IRBE3,rbe3%nrbe3*irbe3_variables)
592
593 CALL get_nrbe3pen_l(rbe3%nrbe3,irbe3_variables,rbe3%IRBE3,nrbe3pen_l)
594
595 CALL read_i_c(rbe3%LRBE3,rbe3%lrbe3_sz)
596
598
600
602
604
606
608
609
610
612
613
615
617
619
621
623
625
627
629
631
633
635
637
639
641
643
645
647
649
651
653
655
657
659 DO ii = 1, nvolu
660 t_monvol(ii)%NB_FILL_TRI = ntri
661 IF (ntri(ii) > 0) THEN
662 ALLOCATE(t_monvol(ii)%FILL_TRI(3 * ntri(ii)))
663 CALL read_i_c(t_monvol(ii)%FILL_TRI(1:3 * ntri(ii)), 3 * ntri(ii))
664 ENDIF
665 ENDDO
666
668
670
671
673
674 CALL thsurf_read_restart(output%TH%TH_SURF)
675
677
678 CALL read_i_c(nodes%BOUNDARY_ADD,siad_elem)
679
681
683
685
687
689
691
693
694 CALL read_i_c(rbe3%mpi%IAD_RBE3,nspmd+1)
695
697
699
701
703
704 CALL read_i_c(nodes%BOUNDARY,sfr_elem)
705
707
709
711
713
715
717
719
721
723
724 CALL read_i_c(rbe3%mpi%FR_RBE3,rbe3%mpi%fr_rbe3_sz)
725
726 CALL read_i_c(rbe3%mpi%FR_RBE3MP,rbe3%mpi%fr_rbe3_sz)
727
729
731
733
735
737
739
741
743
745
747
749
751
753
754 CALL read_i_c(interfaces%SPMD_ARRAYS%FR_EDG,2*nbddedgt)
755
756 CALL read_i_c(interfaces%SPMD_ARRAYS%IAD_FREDG,(nspmd+1)*ninter25)
757
758
760
762
764
766
768
770
772
774
776
778
780
782
784
786
788
790
792
794
796
798
800
802
804
806
807 nodes%WEIGHT_MD = nodes%WEIGHT
808
809
810 IF(icrack3d > 0)THEN
814 ENDIF
815
818
819
820
821
822 IF(iparit==1) THEN
823 CALL read_i_c(element%PON%ADSKY,numnod+1)
824
825 CALL read_i_c(element%PON%PROCNE,lcne0)
826
827 IF (i2nsnt > 0) THEN
829 ENDIF
831
832 IF(ns10e>0) THEN
834 ENDIF
836
837
838 CALL read_i_c(element%PON%IADS ,
SIZE(element%PON%IADS))
839 CALL read_i_c(element%PON%IADS10 ,
SIZE(element%PON%IADS10 ))
840 CALL read_i_c(element%PON%IADS20 ,
SIZE(element%PON%IADS20 ))
841 CALL read_i_c(element%PON%IADS16 ,
SIZE(element%PON%IADS16 ))
842 CALL read_i_c(element%PON%IADQ ,
SIZE(element%PON%IADQ ))
843 CALL read_i_c(element%PON%IADC ,
SIZE(element%PON%IADC ))
844 CALL read_i_c(element%PON%IAD_TRUSS ,
SIZE(element%PON%IAD_TRUSS))
845 CALL read_i_c(element%PON%IAD_BEAM ,
SIZE(element%PON%IAD_BEAM ))
846 CALL read_i_c(element%PON%IAD_SPRING ,
SIZE(element%PON%IAD_SPRING ))
847 CALL read_i_c(element%PON%IAD_TG ,
SIZE(element%PON%IAD_TG ))
848 CALL read_i_c(element%PON%IAD_TG6 ,
SIZE(element%PON%IAD_TG6 ))
849 CALL read_i_c(element%PON%IAD_MV ,
SIZE(element%PON%IAD_MV ))
850 CALL read_i_c(element%PON%IAD_CONLD ,
SIZE(element%PON%IAD_CONLD))
851 CALL read_i_c(element%PON%IAD_CONV ,
SIZE(element%PON%IAD_CONV))
852 CALL read_i_c(element%PON%IAD_RADIA ,
SIZE(element%PON%IAD_RADIA))
853 CALL read_i_c(element%PON%IAD_LOADP ,
SIZE(element%PON%IAD_LOADP))
854 CALL read_i_c(element%PON%IAD_FXFLUX ,
SIZE(element%PON%IAD_FXFLUX))
855
857
859
861
863
865
867
869
871
873
875
876
877
878 IF(iplyxfem > 0) THEN
880
883 ENDIF
884
885
886
887 IF (icrack3d > 0) THEN
893 ENDIF
894
895 ELSEIF(ipari0==1)THEN
896
897 len = numnod+1+lcne0+(numnod+1)*
min(1,i2nsnt)+lcni2
898 + + nisky0+nskyrw0+nskyrbk0+niskyi2+nskymv0+nskymvc0
899 + + nskyll0+nskyrbm0+nskyi18+nskyrbe30+nskyrbmk0
900
901 IF(ns10e>0) len = len +saddcncnd+sprocncnd+siadcnd
902 IF(iplyxfem > 0)len = len + lcnepxfem + 4*eplyxfe+ nplyxfe+1
903 DO i = 1,len,mvsiz
905 ENDDO
906 ENDIF
907
908
909
910
911 IF(ebcs_tab%nebcs_parallel > 0) THEN
912 DO i=1,ebcs_tab%nebcs
913 is_ebcs_parallel = .false.
914 IF(ebcs_tab%my_typ(i)==10 .OR. ebcs_tab%my_typ(i)==11)is_ebcs_parallel = .true.
915 IF(is_ebcs_parallel) THEN
916 my_size = ebcs_tab%tab(i)%poly%nb_elem
917 ALLOCATE(ebcs_parithon(i)%ELEM_ADRESS(4,my_size))
918 CALL read_i_c(ebcs_parithon(i)%ELEM_ADRESS,4*my_size)
919 ENDIF
920 ENDDO
921 ENDIF
922
923
925
927
929
931
932 IF(nadmesh /= 0)THEN
936 len=abs(lsh4trim)
938 len=abs(lsh3trim)
940 END IF
941
942
943
945 . glob_therm%IDT_THERM,glob_therm%INTHEAT
946
947
948
949
951
952 IF(nintstamp /= 0)THEN
954 END IF
955
956
957
958 IF(ninterfric /= 0)THEN
959 CALL intfric_rresti(interfaces%INTBUF_FRIC_TAB,ninterfric)
960 END IF
961
962
963
964 IF(ntable /= 0)THEN
966 END IF
967
969
970 IF (nloadc>0)THEN
973 ENDIF
974 IF (nloadp>0)THEN
977 ENDIF
978 IF (pblast%NLOADP_B>0)THEN
979 CALL pblast_load(pblast)
980 CALL pblast_init_tables(pblast%PBLAST_DATA)
981 ENDIF
982
983 IF (loads%NLOAD_CYL > 0) THEN
985 ENDIF
986
987 IF(icrack3d > 0)THEN
993 END IF
994
997
999
1000
1001
1002 IF(nbcscyc > 0)THEN
1005 END IF
1006
1007
1008
1010 bcs%NUM_WALL = itmp
1011 IF(bcs%NUM_WALL > 0)THEN
1012 CALL read_bcs_wall()
1013 ENDIF
1014
1015
1016
1017
1018
1019
1020
1021
1022
1024
1025
1026 CALL rdcomr(lmxvrea,tabvrea,dynain_data,interfaces%PARAMETERS,
1027 . output,glob_therm)
1028
1029
1030
1036
1038
1040
1042
1044
1045 IF (n2d >0) THEN
1047 ENDIF
1048
1050
1052
1054
1056
1058
1059 skew_len = skews%N_SKEW_VAR*skews%TOTAL_SKEW_NUMBER
1060 CALL read_db(skews%SKEW,skew_len)
1061
1063
1065
1067
1069
1071
1073
1075
1077
1079
1081
1082 IF (multi_fvm%IS_USED) THEN
1083 CALL read_db(multi_fvm%PRES_SHIFT, 1)
1084 IF (n2d == 0) THEN
1085 CALL read_db(multi_fvm%VEL(1, :), numels)
1086 CALL read_db(multi_fvm%VEL(2, :), numels)
1087 CALL read_db(multi_fvm%VEL(3, :), numels)
1088 ELSE
1089 CALL read_db(multi_fvm%VEL(1, :), numelq + numeltg)
1090 CALL read_db(multi_fvm%VEL(2, :), numelq + numeltg)
1091 CALL read_db(multi_fvm%VEL(3, :), numelq + numeltg)
1092 ENDIF
1093 ENDIF
1094
1096
1098
1100
1102
1104
1106
1108
1110
1111 CALL read_db(sphveln,ssphveln)
1112
1114
1116
1118
1120
1122
1124
1125 CALL read_db(tab_mat,stab_mat)
1126
1128
1130
1132
1133 CALL read_db(gauge,llgauge*nbgauge)
1134
1136
1138
1139 CALL read_db(rbe3%FRBE3,rbe3%frbe3_sz)
1140
1141 CALL read_rrbe3pen(rbe3%PEN,nrbe3pen_l)
1142
1143 CALL read_db(factiv,lractiv*nactiv)
1144
1146
1147 CALL read_db(fr_wave,sfr_wave)
1148
1150
1152
1154
1156
1158
1160
1162
1164
1166
1168
1170
1172
1174
1176
1178
1179 CALL read_db(rcontact ,srcontact)
1180 CALL read_db(acontact ,srcontact)
1181 CALL read_db(pcontact ,srcontact)
1182
1183
1184 IF(irunn>1.OR.mcheck/=0)
CALL spmd_initfi(
ipari,2,h3d_data,interfaces%PARAMETERS,
1185 . glob_therm%IDT_THERM,glob_therm%INTHEAT)
1186
1187
1188
1190
1191
1192
1193 IF (iresmd==0.AND.npsav>=25) THEN
1194 CALL read_db(partsav,npsav*npart)
1195 ENDIF
1196
1197 IF(nnoise>0.AND. (irunn>1 .OR. mcheck/=0))THEN
1198
1200 CALL read_db(af(mf01),sfnoise)
1201 ENDIF
1202
1203 IF (iresp == 1) THEN
1204 IF (irxdp == 1) THEN
1207 ELSE
1208 CALL fillxdp(nodes%X,nodes%XDP,nodes%D,nodes%DDP)
1209
1210 irxdp=1
1211 ENDIF
1212
1213 ELSE
1214 IF (irxdp ==1)THEN
1215
1216 ALLOCATE(xdpdum(3*numnod))
1217
1219
1221 DEALLOCATE(xdpdum)
1222 irxdp=0
1223 ENDIF
1224 ENDIF
1225 npsav = 29
1226
1227
1228 IF(mcheck/=0)THEN
1231 IF(mod(irform,5)>=2.AND.mod(irform,5)<=4) THEN
1236
1242 ENDIF
1243 ELSE
1246 ALLOCATE(ibid(my_ilen),stat=istat)
1247 IF(istat/=0)THEN
1248 CALL ancmsg(msgid=20,anmode=aninfo)
1250 END IF
1251 ALLOCATE(rbid(my_rlen),stat=istat)
1252 IF(istat/=0)THEN
1253 CALL ancmsg(msgid=20,anmode=aninfo)
1255 END IF
1258 ENDIF
1259
1260 IF(nadmesh /= 0 .OR. irest_mselt /= 0)THEN
1266 END IF
1267
1268 IF(irest_mselt /= 0)THEN
1273 END IF
1274
1275 IF(nadmesh /= 0)THEN
1276 CALL read_db(padmesh,kpadmesh*npart)
1277 IF(glob_therm%ITHERM_FE > 0)THEN
1280 END IF
1281 END IF
1282
1288 ENDIF
1289
1290 IF(istatcnd /= 0)THEN
1293 ENDIF
1294
1295 IF(nintstamp /= 0)THEN
1297 END IF
1298 IF(nintskidold > 0) THEN
1299 IF(nintstamp/=0) THEN
1300 CALL read_db(pskids, nintskidold*numnodg)
1301 ELSE
1302 CALL read_db(pskids, nintskidold*numnod)
1303 ENDIF
1304 ENDIF
1306 IF(nintstamp/=0.AND.nspmd > 1 ) THEN
1307 IF(ispmd == 0)
CALL read_db(fcont_max, 3*numnodg)
1308 ELSE
1309 CALL read_db(fcont_max, 3*numnod)
1310 ENDIF
1311 ENDIF
1315 ENDIF
1317 CALL read_db(fcont2_max, 3*numnod)
1318 ENDIF
1320 CALL read_db(fncont2_max, 3*numnod)
1321 CALL read_db(ftcont2_max, 3*numnod)
1322 CALL read_db(npcont2_max, 3*numnod)
1323 ENDIF
1325 CALL read_db(fcont2_min, 3*numnod)
1326 ENDIF
1328 CALL read_db(fncont2_min, 3*numnod)
1329 CALL read_db(ftcont2_min, 3*numnod)
1330 CALL read_db(npcont2_min, 3*numnod)
1331 ENDIF
1332
1336 ENDIF
1339 IF(nintstamp/=0)
CALL read_db(efricg_stamp, numnodg)
1340 ENDIF
1341
1342
1343
1344 IF(ninterfric /= 0)THEN
1345 CALL intfric_rrestr(interfaces%INTBUF_FRIC_TAB,ninterfric)
1346 END IF
1347
1348
1349 CALL read_db(nodes%MS0,numnod)
1351 IF(idtmins_old==1) THEN
1353 ELSEIF(idtmins_old==2) THEN
1360 END IF
1361 IF(idtmins_old/=0.OR.idtmins_int_old/=0)THEN
1362 CALL read_db(res_sms,3*numnod)
1363 END IF
1364 IF(idtmins_old==2.OR.idtmins_int_old/=0) THEN
1365
1366 CALL read_db(diag_sms ,numnod)
1367
1368 CALL read_db(dmint2 ,4*i2nsn25)
1369 END IF
1370 IF (isms_selec /= 0) THEN
1372 ENDIF
1373
1374
1375
1376 IF(ntable /= 0)THEN
1378 END IF
1379
1380
1381
1382#ifdef DNC
1383 CALL eng_read_mds()
1384#endif
1385
1386
1387
1388
1390
1391
1392
1393 CALL read_ale_grid()
1394
1395
1396
1397 IF (nfxbody>0) THEN
1399 ENDIF
1400
1401
1402
1403 IF (neig>0) THEN
1405 ENDIF
1406
1407
1408
1409 DO i = 1, nslipring
1410
1418
1425
1427
1429
1439
1453
1454 ENDDO
1455
1456 ENDDO
1457
1458 DO i = 1, nretractor
1495 DO j=1,2
1500 ALLOCATE (
retractor(i)%TABLE(j)%X(1)%VALUES(npt))
1502 ALLOCATE (
retractor(i)%TABLE(j)%Y%VALUES(npt))
1505 ENDIF
1506 ENDDO
1507 ENDDO
1508
1509 IF (n_anchor_remote > 0) THEN
1512 ENDIF
1513
1514 IF (n_anchor_remote_send > 0) THEN
1517 ENDIF
1518
1519 IF ((nslipring_g + nretractor_g >0).AND.(ispmd == 0)) THEN
1520 ALLOCATE(th_slipring(nslipring_g,6))
1521 ALLOCATE(th_retractor(nretractor_g,3))
1522 th_slipring = 0
1523 th_retractor = 0
1532 ENDDO
1533 ENDIF
1534 ENDIF
1535
1536
1537
1544
1545 IF (nconld > 0) THEN
1546 CALL read_db(dpl0cld,6*nconld)
1547 CALL read_db(vel0cld,6*nconld)
1548 ENDIF
1549
1550
1551
1556 ENDIF
1557 IF (ndamp > 0) THEN
1558 DO i=1,ndamp
1560 ENDDO
1561 ENDIF
1562
1563
1564 IF (nflow>0) THEN
1566 ENDIF
1567
1568 ! fvmbag structures
1570
1571
1572 IF (impl_s0>0)
CALL imprrest(impl_s0)
1573
1574
1575 IF(glob_therm%ITHERM_FE > 0 ) THEN
1576 CALL thcrrest(nodes%MCP,nodes%TEMP)
1577 ENDIF
1578
1579
1580 IF(nitsche > 0 ) THEN
1582 ENDIF
1583
1584
1586
1587
1589
1590
1591 IF (glob_therm%NUMCONV > 0)
CALL convrrest(
ibcv, fconv ,glob_therm)
1592 IF (glob_therm%NUMRADIA > 0)
CALL radiarrest(
ibcr, fradia,glob_therm)
1595
1596
1597 IF (iplyxfem > 0) THEN
1600 ENDIF
1603
1604
1607
1608
1609 IF (nintloadp>0) THEN
1610 CALL read_db(dgaploadint, ninter*nloadp_hyd )
1611 ENDIF
1612
1613
1614 IF (loads%NINIVELT>0) THEN
1615 ALLOCATE(loads%INIVELT(loads%NINIVELT))
1616 CALL read_inivel(loads%NINIVELT,loads%INIVELT)
1617 ENDIF
1618
1621
1622
1624
1625
1627
1628 IF(srthbuf > 0)
CALL rthbufrest(rthbuf,srthbuf)
1629
1633 IF(numelig3d > 0)
CALL wigerest(wige)
1634
1635 IF(ipart_stack >0) THEN
1637 ENDIF
1638
1639 IF (ndrape > 0) THEN
1641 ENDIF
1642
1644
1645
1647
1650 ENDIF
1651
1652 RETURN
subroutine decompress_i_nnz(array, len)
subroutine decompress_r_nnz(array, len)
subroutine fillxdp(x, xdp, d, ddp)
subroutine fxfluxrrest(ibfflux, fbfflux, glob_therm)
subroutine intbuf_ini(intbuf_tab)
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(intstamp_data), dimension(:), allocatable intstamp
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
subroutine r_bufbric_22()
subroutine rdcomr(lmxvrea, tabvrea, dynain_data, inter_parameters, output, glob_therm)
subroutine alelag_rrest()
subroutine plyxfem_ravuply()
subroutine thcrrest(mcp, temp)
subroutine imprrest(nimpr)
subroutine drape_rrest(drape_sh4n, drape_sh3n, drapeg)
subroutine rthbufrest(rthbuf, srthbuf)
subroutine knotlocpcrest(knotlocpc)
subroutine cfieldrest(cfield)
subroutine knotlocelrest(knotlocel)
subroutine stack_rrest(igeo, geo, pm)
subroutine fvrrest(monvol)
subroutine loadprest(loadp)
subroutine knotrest(knot)
subroutine nitscherrest(forneqs)
subroutine wigerest(wige)
subroutine fxtemprrest(ibftemp, fbftemp, glob_therm)
subroutine ply_info_rest(ply_info)
subroutine rmatrrest(rbym, irbym, lnrbym, weight)
subroutine convrrest(ibcv, fconv, glob_therm)
subroutine plyxfem_rrestanim()
subroutine plyxfem_rrest(ms_layer, zi_layer, inod, iel, icode, iskew, msz2)
subroutine nfrrest(iflow, rflow)
subroutine crkxfem_rrest(inod_crkxfem, iel_crkxfem, nodlevxf)
subroutine crkxfem_rrestanim()
subroutine radiarrest(ibcr, fradia, glob_therm)
subroutine read_cluster(cluster)
subroutine read_dpdb(a, n)
subroutine read_elgroup_param(mat_elem)
subroutine read_failwave(failwave)
subroutine read_matparam(mat_elem)
subroutine read_nloc_struct(nloc_dmg)
subroutine read_pcyl(loads)
subroutine read_sensors(sensors, python)
subroutine read_th_restart(th)
subroutine elbuf_ini(elbuf_tab, mat_param, mlaw_tag, prop_tag, fail_tag, igeo, ipm, pm, iparg, ipart, ipartsp, ixs, ixq, ixc, ixtg, flag_xfem, ipartig3d, stack, igeo_stack, ixt, ixp, ixr, kxx, geo, eos_tag, istr_24, print_flag, defaults)
subroutine group_ini(igrnod, igrbric, igrquad, igrsh4n, igrsh3n, igrtruss, igrbeam, igrspring, igrpart)
subroutine subset_ini(subset)
subroutine userwi_read(user_windows, ispmd, nspmd, numnod)
subroutine read_units(unitab)