55!|| intstamp_rresti ../engine/share/modules/
intstamp_mod.f
151 SUBROUTINE rdresb( AF ,IAF ,LVARREA ,IRUNN ,
152 . MULTI_FVM ,H3D_DATA ,PINCH_DATA ,ALE_CONNECTIVITY ,T_MONVOL ,
153 . SENSORS ,EBCS_TAB ,DYNAIN_DATA ,USER_WINDOWS ,OUTPUT ,
154 . INTERFACES ,LOADS ,MAT_ELEM ,PYTHON ,IFLOW ,
155 . SKEWS ,RFLOW ,LIFLOW ,LRFLOW ,IMPL_S0 ,
157 . STACK ,DRAPE_SH4N ,DRAPE_SH3N ,DRAPEG ,NDRAPE ,
158 . GLOB_THERM ,PBLAST ,ELEMENT ,NODES ,RBE3)
194 USE bcs_mod ,
ONLY : bcs
201 use read_inivel_mod,
only : read_inivel
203 use read_ale_grid_mod,
only : read_ale_grid
204 use read_bcs_wall_mod,
only : read_bcs_wall
206 use restart_rbe3pen_mod,
only : get_nrbe3pen_l,read_rrbe3pen
207 use checksum_output_option_mod
211#include "implicit_f.inc"
215#include "mvsiz_p.inc"
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"
241#include "tabsiz_c.inc"
246 INTEGER IAF(*),LVARREA,LEN_G,LEN_M, IRUNN
248 TYPE(MULTI_FVM_STRUCT) :: MULTI_FVM
249 TYPE(H3D_DATABASE) :: H3D_DATA
251TYPE(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
256TYPE(output_) ,
INTENT(INOUT) :: OUTPUT
257 TYPE(interfaces_) ,
INTENT(INOUT) :: INTERFACES
258 TYPE(sensors_) ,
INTENT(INOUT)
259TYPE() ,
INTENT(INOUT) :: LOADS
260 TYPE(mat_elem_) ,
INTENT(INOUT) :: MAT_ELEM
261 TYPE(python_) ,
INTENT(INOUT) :: PYTHON
262 TYPE(skew_) ,
INTENT(INOUT) :: SKEWS
264 TYPE (STACK_PLY) ,
INTENT(INOUT) :: STACK
265 TYPE(
drape_) ,
INTENT(INOUT) :: DRAPE_SH3N(NUMELTG_DRAPE),DRAPE_SH4N(NUMELC_DRAPE)
266 TYPE(
drapeg_) ,
INTENT(INOUT) :: DRAPEG
267 TYPE(glob_therm_) ,
INTENT(INOUT) :: GLOB_THERM
268 TYPE(pblast_) ,
INTENT(INOUT) :: PBLAST
269 TYPE(connectivity_) ,
INTENT(INOUT) ::
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
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
293 INTEGER :: PYTHON_LEN
294 INTEGER,
DIMENSION(:),
ALLOCATABLE :: BUFFER
296 LOGICAL :: IS_EBCS_PARALLEL
297 INTEGER :: NPT,NRBE3PEN_L
304 IF(lvarrea>lmxvrea)
THEN
305 CALL ancmsg(msgid=33,anmode=aninfo,i1=lvarrea,i2=lmxvrea)
312 len_g = npropgi*numgeo
313 len_m = npropmi*nummat
317 CALL checksum_restart_read(output%CHECKSUM)
319 CALL read_i_c(nodes%NODGLOB,snodglob)
321 CALL read_i_c(nodes%MAIN_PROC,sweight)
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)
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)
367 CALL init_global_shell_id(element%SHELL)
376 ! create
the map from global to local ids
377 CALL init_global_node_id(nodes,numnod)
383 CALL read_i_c(ale_connectivity%NALE,
ale%GLOBAL%SNALE)
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)
391 ALLOCATE(ale_connectivity%ee_connect%connected(itmp))
392 CALL read_i_c(ale_connectivity%ee_connect%connected, itmp)
395 ALLOCATE(ale_connectivity%ee_connect%type(itmp))
396 CALL read_i_c(ale_connectivity%ee_connect%type, itmp)
399 ALLOCATE(ale_connectivity%ee_connect%iface2(itmp))
400 CALL read_i_c(ale_connectivity%ee_connect%iface2, itmp)
407 IF(ale_connectivity%has_ne_connect)
THEN
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))
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))
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))
441 IF (.NOT.
ALLOCATED(ale_connectivity%IDGLOB%UID))
THEN
442 ALLOCATE(ale_connectivity%IDGLOB%UID(numels + nsvois + numelq + nqvois + numeltg + ntgvois))
444 IF (.NOT.
ALLOCATED(multi_fvm%ELEM_DATA%CENTROID))
THEN
445 ALLOCATE(multi_fvm%ELEM_DATA%CENTROID(3, numels + nsvois + numelq + nqvois + numeltg + ntgvois))
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))
450 IF (.NOT.
ALLOCATED(multi_fvm%VOL))
THEN
451 ALLOCATE(multi_fvm%VOL(numels + nsvois + numelq + nqvois + numeltg + ntgvois))
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)
504 IF (nintloadp>0)
THEN
522 ebcs_tab%nebcs = int0
523 ebcs_tab%nebcs_fvm = int1
524 ebcs_tab%nebcs_parallel = int2
525 ebcs_tab%nebcs_loc = int3
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))
533 ebcs_tab%my_typ(1:int0) = integer_data(1:int0)
539 ebcs_tab%need_to_compute(ii) = .false.
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.
545 ebcs_tab%need_to_compute(ii) = .true.
550 CALL ebcs_tab%create_from_types(int1 + int2 + int3 , integer_data(1:int1 + int2 + int3 ))
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()
560 ALLOCATE( ebcs_parithon(ebcs_tab%nebcs) )
591 CALL read_i_c(rbe3%IRBE3,rbe3%nrbe3*irbe3_variables)
593 CALL get_nrbe3pen_l(rbe3%nrbe3,irbe3_variables,rbe3%IRBE3,nrbe3pen_l)
595 CALL read_i_c(rbe3%LRBE3,rbe3%lrbe3_sz)
660 t_monvol(ii)%NB_FILL_TRI = ntri(ii)
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))
674 CALL thsurf_read_restart(output%TH%TH_SURF)
678 CALL read_i_c(nodes%BOUNDARY_ADD,siad_elem)
694 CALL read_i_c(rbe3%mpi%IAD_RBE3,nspmd+1)
704 CALL read_i_c(nodes%BOUNDARY,sfr_elem)
724 CALL read_i_c(rbe3%mpi%FR_RBE3,rbe3%mpi%fr_rbe3_sz)
726 CALL read_i_c(rbe3%mpi%FR_RBE3MP,rbe3%mpi%fr_rbe3_sz)
754 CALL read_i_c(interfaces%SPMD_ARRAYS%FR_EDG,2*nbddedgt)
756 CALL read_i_c(interfaces%SPMD_ARRAYS%IAD_FREDG,(nspmd+1)*ninter25)
807 nodes%WEIGHT_MD = nodes%WEIGHT
823 CALL read_i_c(element%PON%ADSKY,numnod+1)
825 CALL read_i_c(element%PON%PROCNE,lcne0)
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))
878 IF(iplyxfem > 0)
THEN
887 IF (icrack3d > 0)
THEN
895 ELSEIF(ipari0==1)
THEN
897 len = numnod+1+lcne0+(numnod+1)*
min(1,i2nsnt)+lcni2
898 + + nisky0+nskyrw0+nskyrbk0+niskyi2+nskymv0+nskymvc0
899 + + nskyll0+nskyrbm0+nskyi18+nskyrbe30+nskyrbmk0
901 IF(ns10e>0) len = len
902 IF(iplyxfem > 0)len = len + lcnepxfem + 4*eplyxfe+ nplyxfe+1
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)
945 . glob_therm%IDT_THERM,glob_therm%INTHEAT)
952 IF(nintstamp /= 0)
THEN
958 IF(ninterfric /= 0)
THEN
959 CALL intfric_rresti(interfaces%INTBUF_FRIC_TAB,ninterfric)
978 IF (pblast%NLOADP_B>0)
THEN
979 CALL pblast_load(pblast)
980 CALL pblast_init_tables(pblast%PBLAST_DATA)
983 IF (loads%NLOAD_CYL > 0)
THEN
1011 IF(bcs%NUM_WALL > 0)
THEN
1012 CALL read_bcs_wall()
1026 CALL rdcomr(lmxvrea,tabvrea,dynain_data,interfaces%PARAMETERS,
1027 . output,glob_therm)
1059 skew_len = skews%N_SKEW_VAR*skews%TOTAL_SKEW_NUMBER
1082 IF (multi_fvm%IS_USED)
THEN
1083 CALL read_db(multi_fvm%PRES_SHIFT, 1)
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)
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)
1111 CALL read_db(sphveln,ssphveln)
1125 CALL read_db(tab_mat,stab_mat)
1133 CALL read_db(gauge,llgauge*nbgauge)
1139 CALL read_db(rbe3%FRBE3,rbe3%frbe3_sz)
1141 CALL read_rrbe3pen(rbe3%PEN,nrbe3pen_l)
1143 CALL read_db(factiv,lractiv*nactiv)
1147 CALL read_db(fr_wave,sfr_wave)
1179 CALL read_db(rcontact ,srcontact)
1180 CALL read_db(acontact ,srcontact)
1181 CALL read_db(pcontact ,srcontact)
1184 IF(irunn>1.OR.mcheck/=0)
CALL spmd_initfi(
ipari,2,h3d_data,interfaces%PARAMETERS,
1185 . glob_therm%IDT_THERM,glob_therm%INTHEAT)
1193 IF (iresmd==0.AND.npsav>=25)
THEN
1194 CALL read_db(partsav,npsav*npart)
1197 IF(nnoise>0.AND. (irunn>1 .OR. mcheck/=0))
THEN
1200 CALL read_db(af(mf01),sfnoise)
1203 IF (iresp == 1)
THEN
1204 IF (irxdp == 1)
THEN
1208 CALL fillxdp(nodes%X,nodes%XDP,nodes%D,nodes%DDP)
1216 ALLOCATE(xdpdum(3*numnod))
1231 IF(mod(irform,5)>=2.AND.mod(irform,5)<=4)
THEN
1246 ALLOCATE(ibid(my_ilen),stat=istat)
1248 CALL ancmsg(msgid=20,anmode=aninfo)
1251 ALLOCATE(rbid(my_rlen),stat=istat)
1253 CALL ancmsg(msgid=20,anmode=aninfo)
1260 IF(nadmesh /= 0 .OR. irest_mselt /= 0)
THEN
1268 IF(irest_mselt /= 0)
THEN
1275 IF(nadmesh /= 0)
THEN
1276 CALL read_db(padmesh,kpadmesh*npart)
1277 IF(glob_therm%ITHERM_FE > 0)
THEN
1290 IF(istatcnd /= 0)
THEN
1295 IF(nintstamp /= 0)
THEN
1298 IF(nintskidold > 0)
THEN
1299 IF(nintstamp/=0)
THEN
1300 CALL read_db(pskids, nintskidold*numnodg)
1302 CALL read_db(pskids, nintskidold*numnod)
1306 IF(nintstamp/=0.AND.nspmd > 1 )
THEN
1307 IF(ispmd == 0)
CALL read_db(fcont_max, 3*numnodg)
1309 CALL read_db(fcont_max, 3*numnod)
1317 CALL read_db(fcont2_max, 3*numnod)
1320 CALL read_db(fncont2_max, 3*numnod)
1321 CALL read_db(ftcont2_max, 3*numnod)
1322 CALL read_db(npcont2_max, 3*numnod)
1325 CALL read_db(fcont2_min, 3*numnod)
1328 CALL read_db(fncont2_min, 3*numnod)
1329 CALL read_db(ftcont2_min, 3*numnod)
1330 CALL read_db(npcont2_min, 3*numnod)
1339 IF(nintstamp/=0)
CALL read_db(efricg_stamp, numnodg)
1344 IF(ninterfric /= 0)
THEN
1345 CALL intfric_rrestr(interfaces%INTBUF_FRIC_TAB,ninterfric)
1349 CALL read_db(nodes%MS0,numnod)
1351 IF(idtmins_old==1)
THEN
1353 ELSEIF(idtmins_old==2)
THEN
1361 IF(idtmins_old/=0.OR.idtmins_int_old/=0)
THEN
1362 CALL read_db(res_sms,3*numnod)
1364 IF(idtmins_old==2.OR.idtmins_int_old/=0)
THEN
1366 CALL read_db(diag_sms ,numnod)
1368 CALL read_db(dmint2 ,4*i2nsn25)
1370 IF (isms_selec /= 0)
THEN
1393 CALL read_ale_grid()
1458 DO i = 1, nretractor
1500 ALLOCATE (
retractor(i)%TABLE(j)%X(1)%VALUES(npt))
1502 ALLOCATE (
retractor(i)%TABLE(j)%Y%VALUES(npt))
1509 IF (n_anchor_remote > 0)
THEN
1514 IF (n_anchor_remote_send > 0)
THEN
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))
1545 IF (nconld > 0)
THEN
1546 CALL read_db(dpl0cld,6*nconld)
1547 CALL read_db(vel0cld,6*nconld)
1572 IF (impl_s0>0)
CALL imprrest(impl_s0)
1575 IF(glob_therm%ITHERM_FE > 0 )
THEN
1576 CALL thcrrest(nodes%MCP,nodes%TEMP)
1580 IF(nitsche > 0 )
THEN
1591 IF (glob_therm%NUMCONV > 0)
CALL convrrest(
ibcv, fconv ,glob_therm)
1592 IF (glob_therm%NUMRADIA > 0)
CALL radiarrest(
ibcr, fradia,glob_therm)
1597 IF (iplyxfem > 0)
THEN
1609 IF (nintloadp>0)
THEN
1610 CALL read_db(dgaploadint, ninter*nloadp_hyd )
1614 IF (loads%NINIVELT>0)
THEN
1615 ALLOCATE(loads%INIVELT(loads%NINIVELT))
1616 CALL read_inivel(loads%NINIVELT,loads%INIVELT)
1628 IF(srthbuf > 0)
CALL rthbufrest(rthbuf,srthbuf)
1633 IF(numelig3d > 0)
CALL wigerest(wige)
1635 IF(ipart_stack >0)
THEN
1639 IF (ndrape > 0)
THEN
1678#include "implicit_f.inc"
1682#include "com04_c.inc"
1683#include "scr05_c.inc"
1684#include "units_c.inc"
1685#include "fxbcom.inc"
1686#include "chara_c.inc"
1687#include "task_c.inc"
1691 INTEGER LEN_IPM,LEN_MOD, NRECM, NRECS, IRCM, , IRCM1,
1692 . IRCS, IRCS0, IRCS1, LREC, I, J, RCLEN,TLEN
1696 CHARACTER(LEN=10) ::
1697 CHARACTER(LEN=6) :: CISPMD
1698 CHARACTER(LEN=4096) :: TMPDIR
1702 len_ipm=nbipm*nfxbody
1703 IF (irform/5<=1)
THEN
1718 IF (irform/5<=1)
THEN
1719 IF (len_mod>0)
CALL redsqr (fxbmod,len_mod,irform)
1720 IF (lenglm>0)
CALL redsqr (fxbglm,lenglm,irform)
1721 IF (lencp>0)
CALL redsqr (fxbcpm,lencp ,irform)
1722 IF (lencp>0)
CALL redsqr (fxbcps,lencp ,irform)
1723 IF (lenlm>0)
CALL redsqr (fxblm
1724 IF (lenfls>0)
CALL redsqr (fxbfls,lenfls,irform)
1725 IF (lendls>0)
CALL redsqr (fxbdls,lendls,irform)
1726 CALL redsqr (fxbdep,lenvar,irform)
1728 CALL redsqr (fxbacc,lenvar,irform)
1729 CALL redsqr (fxbrpm,lenrpm,irform)
1730 IF (lensig>0)
CALL redsqr (fxbsig,lensig,irform)
1731 IF (lengrvr>0)
CALL redsqr (fxbgrvr,lengrvr,irform)
1733 IF (len_mod>0)
CALL read_db(fxbmod,len_mod)
1734 IF (lenglm>0)
CALL read_db(fxbglm,lenglm)
1735 IF (lencp>0)
CALL read_db(fxbcpm,lencp )
1736 IF (lencp>0)
CALL read_db(fxbcps,lencp )
1737 IF (lenlm>0)
CALL read_db(fxblm, lenlm )
1738 IF (lenfls>0)
CALL read_db(fxbfls,lenfls)
1739 IF (lendls>0)
CALL read_db(fxbdls,lendls)
1744 IF (lensig>0)
CALL read_db(fxbsig,lensig)
1745 IF (lengrvr>0)
CALL read_db(fxbgrvr,lengrvr)
1748 INQUIRE(iolength=rclen) vv
1753 WRITE(cpid,
'(I10.10)') my_pid
1754 WRITE(cispmd,
'(I6.6)') ispmd
1755 ifxm_fn=tmpdir(1:tlen)//
'/'//'25_
'//ROOTN(1:LENROOTN)//'_
'//CPID//'_
'//CISPMD//'.tmp
'
1756 IFXS_FN=TMPDIR(1:TLEN)//'/
'//'26_
'//ROOTN(1:LENROOTN)//'_
'//CPID//'_
'//CISPMD//'.tmp'
1760 OPEN(unit=ifxm,file=trim(
ifxm_fn),access=
'DIRECT',recl=rclen)
1761 OPEN(unit=ifxs,file=trim(
ifxs_fn),access=
'DIRECT',recl=rclen)
1773 nrecm=nrecm+ircm1-ircm0
1774 nrecs=nrecs+ircs1-ircs0
1782 WRITE(ifxm,rec=ircm) (vv(j),j=1,lrec)
1787 WRITE(ifxs,rec=ircs) (vv(j),j=1,lrec)
1798!||
read_db ../common_source/tools/input_output
1803!||--- uses -----------------------------------------------------
1816#include "implicit_f.inc"
1820#include "units_c.inc"
1821#include "com04_c.inc"
1822#include "scr05_c.inc"
1823#include "eigcom.inc"
1824#include "chara_c.inc"
1825#include "task_c.inc"
1829 INTEGER NRECM, IRCM, NBN, NBM, LREC, I, J, RCLEN,TLEN
1832 CHARACTER(LEN=10) :: CPID
1833 CHARACTER(LEN=6) :: CISPMD
1834 CHARACTER(LEN=4096) :: TMPDIR
1839 IF (irform/5<=1)
THEN
1849 IF (irform/5<=1)
THEN
1850 CALL redsqr (eigrpm,neig*nerpm,irform)
1852 CALL read_db(eigrpm,neig*nerpm)
1855 INQUIRE(iolength=rclen) vv
1858 WRITE(cpid,
'(I10.10)') my_pid
1859 WRITE(cispmd,
'(I6.6)') ispmd
1862 ieigm_fn=tmpdir(1:tlen)//
'/'//
'27_'//rootn(1:lenrootn)//
'_'//cpid//
'_'//cispmd//
'.tmp'
1864 OPEN(unit=ieigm,file=trim(
ieigm_fn),access=
'DIRECT',recl=rclen)
1879 WRITE(ieigm,rec=ircm) (vv(j),j=1,lrec)
1903#include "implicit_f.inc"
1907#include "com01_c.inc"
1908#include "scr05_c.inc"
1916 INTEGER I, , TN(7), N, NDDL, DSNDDL, DSLEN, K, L, NSDEC
1925 IF (irform/5<=1)
THEN
1926 CALL redsqi(tn, n, irform)
1933 graphe(i)%NDDL=dsnddl
1935 graphe(i)%NSLEVEL=tn(3)
1936 graphe(i)%NSDEC=nsdec
1937 graphe(i)%NSVMAX=tn(5)
1938 graphe(i)%IPRI=tn(6)
1939 graphe(i)%NDDL_GLOB=tn(7)
1944 IF (irform/5<=1)
THEN
1945 CALL redsqr(cutfreq, n, irform)
1949 graphe(i)%CUTFREQ=cutfreq
1953 ALLOCATE(graphe(i)%LSDDL(2,dsnddl),
1954 . graphe(i)%LSDDL_INI(2,dsnddl),
1955 . graphe(i)%LSDDL_GLOB(dsnddl),
1956 . graphe(i)%LSDDL_GLOB_INI(dsnddl))
1958 IF (irform/5<=1)
THEN
1959 CALL redsqi(graphe(i)%LSDDL(j,1:dsnddl), dsnddl, irform)
1961 CALL read_i_c(graphe(i)%LSDDL(j,1:dsnddl), dsnddl)
1964 IF (irform/5<=1)
THEN
1965 CALL redsqi(graphe(i)%LSDDL_GLOB, dsnddl, irform)
1967 CALL read_i_c(graphe(i)%LSDDL_GLOB, dsnddl)
1969 graphe(i)%NDDL_INI=graphe(i)%NDDL
1972 graphe(i)%LSDDL_INI(j,k)=graphe(i)%LSDDL(j,k)
1976 graphe(i)%LSDDL_GLOB_INI(j)=graphe(i)%LSDDL_GLOB(j)
1981 ALLOCATE(graphe(i)%DGRAPH(dslen))
1984 IF (irform/5<=1)
THEN
1985 CALL redsqi(tn, n, irform)
1989 graphe(i)%DGRAPH(j)%NDDL_I=tn(1)
1990 graphe(i)%DGRAPH(j)%NDDL_F=tn(2)
1991 graphe(i)%DGRAPH(j)%NSDMAX=tn(3)
1993 ALLOCATE(graphe(i)%DGRAPH(j)%CHILD(nsdec))
1994 ALLOCATE(graphe(i)%DGRAPH(j)%DDLS(nddl),
1995 . graphe(i)%DGRAPH(j)%DDLS_INI(nddl))
1996 ALLOCATE(graphe(i)%DGRAPH(j)%IFAC(tn(3)+1,tn(2)),
1997 . graphe(i)%DGRAPH(j)%IFACM(tn(2)))
1998 ALLOCATE(graphe(i)%DGRAPH(j)%IFAC_INI(tn(3)+1,tn(2)),
1999 . graphe(i)%DGRAPH(j)%IFACM_INI(tn(2)))
2001 IF (irform/5<=1)
THEN
2002 CALL redsqi(graphe(i)%DGRAPH(j)%CHILD, nsdec, irform)
2003 CALL redsqi(graphe(i)%DGRAPH(j)%DDLS, nddl, irform)
2005 CALL redsqi(graphe(i)%DGRAPH(j)
2006 . %IFAC(1:n,k), n, irform)
2008 CALL redsqi(graphe(i)%DGRAPH(j)%IFACM, tn(2), irform)
2010 CALL read_i_c(graphe(i)%DGRAPH(j)%CHILD, nsdec)
2011 CALL read_i_c(graphe(i)%DGRAPH(j)%DDLS, nddl)
2016 CALL read_i_c(graphe(i)%DGRAPH(j)%IFACM, tn(2))
2018 graphe(i)%DGRAPH(j)%NDDL_I_INI=graphe(i)%DGRAPH(j)%NDDL_I
2019 graphe(i)%DGRAPH(j)%NDDL_F_INI=graphe(i)%DGRAPH(j)%NDDL_F
2021 graphe(i)%DGRAPH(j)%DDLS_INI(k)=
2022 . graphe(i)%DGRAPH(j)%DDLS(k)
2026 graphe(i)%DGRAPH(j)%IFAC_INI(l,k)=
2027 . graphe(i)%DGRAPH(j)%IFAC(l,k)
2029 graphe(i)%DGRAPH(j)%IFACM_INI(k)=
2030 . graphe(i)%DGRAPH(j)%IFACM(k)
2053#include
"implicit_f.inc"
2057#include "scr05_c.inc"
2058#include "flowcom.inc"
2072 IF (irform/5<=1)
THEN
2073 CALL redsqi (iflow,liflow,irform)
2080 IF (irform/5<=1)
THEN
2081 CALL redsqr (rflow,lrflow,irform)
2109#include "implicit_f.inc"
2113#include "com01_c.inc"
2114#include "com04_c.inc"
2115#include "impl1_c.inc"
2125 . A(3*NUMNOD),AR(3*)
2127 IF(
ALLOCATED(imp_rr))
DEALLOCATE(imp_rr)
2128 ALLOCATE(imp_rr(nimpr))
2139 IF (iroddl/=0)
CALL read_db(ar,nd)
2143 IF ((idyna+idyna0)>0)
THEN
2144 ALLOCATE(dy_a(3,numnod))
2145 IF (iroddl/=0)
ALLOCATE(dy_ar(3,numnod))
2147 IF (iroddl/=0)
CALL cp_real(nd,ar,dy_ar)
2161!||
read_i_c ../common_source/tools/input_output/write_routtines.c
2179#include "implicit_f.inc"
2183#include "com01_c.inc"
2184#include "com04_c.inc"
2185#include "task_c.inc"
2186#include "param_c.inc"
2187#include "tabsiz_c.inc"
2188#include
"units_c.inc"
2192 INTEGER,
INTENT(IN) :: MONVOL(SMONVOL)
2196 INTEGER LEN, I, II, KK, TABI(11), NNS, NNTR, LENP, NPOLY, LENH, NPOLH,
2197 . LENP_ANIM, NPOLH_ANIM, LENH_ANIM, NNS_ANIM, NN_L, NNA_L,
2198 . NNSA_L, NSA, NELSA, NNI_L, IFV, ID_DT_OPTION, K1, ITYP,
2199 . id_bag, id_bag_input, n
2200 INTEGER COLOR,KEY, IH3D_FLAG
2253 NULLIFY(
fvspmd(i)%IBUF_L)
2254 NULLIFY(
fvspmd(i)%IBUFA_L)
2255 NULLIFY(
fvspmd(i)%IBUFSA_L)
2257 NULLIFY(
fvspmd(i)%ELEMSA)
2288 fvspmd(i)%NNA_L_GLOB = nna_l
2290 color =
min(1,nn_l+nni_l+nna_l+nnsa_l)
2291 IF(ispmd ==
fvspmd(i)%PMAIN - 1)
THEN
2309 ALLOCATE(
fvspmd(i)%ITAB(4,nspmd-1))
2314 ALLOCATE(
fvspmd(i)%IBUF_L(2,nn_l+nni_l))
2319 ALLOCATE(
fvspmd(i)%IBUFA_L(2,nna_l))
2324 ALLOCATE(
fvspmd(i)%IBUFSA_L(2,nnsa_l))
2331 IF (ispmd/=
fvspmd(i)%PMAIN-1) cycle
2333 ALLOCATE(
fvspmd(i)%IXSA(8,nsa))
2338 ALLOCATE(
fvspmd(i)%ELEMSA(3,nelsa))
2396 .
ALLOCATE(
fvdata_old(i)%IFVPOLY_ANIM(lenp_anim),
2418 IF (npolh_anim>0)
THEN
2453 IF (npolh_anim>0)
THEN
2464 ifv = monvol(k1-1 + 45)
2466 ih3d_flag = monvol(k1-1 + 75)
2467 IF(ih3d_flag==1)
THEN
2489 IF(id_dt_option==1)
THEN
2493 id_bag=monvol(k1-1+1)
2496 ifv = monvol(k1 -1 +45)
2519 IF(id_dt_option == 2)
THEN
2523 IF(id_bag_input > 0)
THEN
2526 id_bag=monvol(k1-1+1)
2528 IF(id_bag == id_bag_input)
THEN
2529 ifv = monvol(k1 -1 +45)
2530 IF (ityp == 8 .OR. ityp == 11)
THEN
2543 CALL ancmsg(msgid=299,anmode=aninfo,i1=id_bag_input)
2560 id_bag=monvol(k1-1+1)
2562 IF (ityp == 6 .OR. ityp == 8 .OR. ityp == 11)
THEN
2563 ifv = monvol(k1 -1 +45)
2591 CALL ancmsg(msgid=302,anmode=aninfo,i1=id_bag)
2599 CALL ancmsg(msgid=303,anmode=aninfo,i1=id_bag)
2624#include "implicit_f.inc"
2628#include "com04_c.inc"
2629#include "scr05_c.inc"
2646 IF (irform/5<=1)
THEN
2647 CALL redsqr (mcp,numnod,irform)
2648 CALL redsqr (temp,numnod,irform)
2669#include "implicit_f.inc"
2673#include "com04_c.inc"
2674#include "scr05_c.inc"
2691 IF (irform/5<=1)
THEN
2692 CALL redsqr (forneqs,3*numnod,irform)
2694 CALL read_db(forneqs,3*numnod)
2719#include "implicit_f.inc"
2723#include "com04_c.inc"
2724#include "scr05_c.inc"
2725#include "param_c.inc"
2731 type (glob_therm_) :: GLOB_THERM
2743 IF (irform/5<=1)
THEN
2744 CALL redsqr (fconv,glob_therm%LFACTHER*glob_therm%NUMCONV,irform)
2745 CALL redsqi (ibcv,glob_therm%NICONV*glob_therm%NUMCONV,irform)
2747 CALL read_db(fconv,glob_therm%LFACTHER*glob_therm%NUMCONV)
2748 CALL read_i_c(ibcv,glob_therm%NICONV*glob_therm%NUMCONV)
2772#include "implicit_f.inc"
2776#include "com04_c.inc"
2777#include "scr05_c.inc"
2778#include "param_c.inc"
2783 my_real :: FRADIA(*)
2784 type (glob_therm_) ,
intent(inout) :: GLOB_THERM
2796 IF (irform/5<=1)
THEN
2797 CALL redsqr (fradia,glob_therm%LFACTHER*glob_therm%NUMRADIA,irform)
2798 CALL redsqi (ibcr,glob_therm%NIRADIA*glob_therm%NUMRADIA,irform)
2800 CALL read_db(fradia,glob_therm%LFACTHER*glob_therm%NUMRADIA)
2801 CALL read_i_c(ibcr,glob_therm%NIRADIA*glob_therm%NUMRADIA)
2825#include "implicit_f.inc"
2829#include "com04_c.inc"
2830#include "scr05_c.inc"
2831#include "param_c.inc"
2836 my_real :: FBFTEMP(*)
2837 type (glob_therm_) ,
intent(inout) :: GLOB_THERM
2849 IF (irform/5<=1)
THEN
2850 CALL redsqr (fbftemp,glob_therm%LFACTHER*glob_therm%NFXTEMP,irform)
2851 CALL redsqi (ibftemp,glob_therm%NIFT*glob_therm%NFXTEMP,irform)
2853 CALL read_db(fbftemp,glob_therm%LFACTHER*glob_therm%NFXTEMP)
2854 CALL read_i_c(ibftemp,glob_therm%NIFT*glob_therm%NFXTEMP)
2874#include "implicit_f.inc"
2878#include "com04_c.inc"
2879#include "scr05_c.inc"
2883 INTEGER IRBYM(*), LNRBYM(*),WEIGHT(*)
2897 IF (irform/5<=1)
THEN
2898 CALL redsqr (rbym,nrbym*nfrbym,irform)
2899 CALL redsqi(irbym,nrbym*nirbym ,irform)
2900 CALL redsqi(lnrbym,ngslnrbym,irform)
2901 CALL redsqi(weight,nrbym,irform)
2903 CALL read_db(rbym,nrbym*nfrbym)
2925#include "implicit_f.inc"
2929#include "com01_c.inc"
2930#include "com04_c.inc"
2931#include "param_c.inc"
2936 . ms_layer(*),zi_layer(*),msz2(*)
2938 . icode(*),iskew(*),inod(*),iel(*)
2950 CALL read_db(ms_layer,nplyxfe*nplymax)
2951 CALL read_db(zi_layer,nplyxfe*nplymax)
2957 IF(iplybcs > 0)
THEN
2970!||--- uses -----------------------------------------------------
2979#include "implicit_f.inc"
2983#include "com01_c.inc"
2984#include "param_c.inc"
2990 IF(IPLYXFEM == 0) then
3002 ALLOCATE(
plynod(nplymax))
3008 ALLOCATE(
plyshell(k)%SHELLIPT(elsz))
3009 ALLOCATE(
plyshell(k)%SHELLID(elsz))
3017 plynod(k)%PLYNUMNODS=ndsz
3018 ALLOCATE(
plynod(k)%NODES(ndsz))
3019 ALLOCATE(
plynod(k)%PLYNODID(ndsz))
3036!||--- called by ------------------------------------------------------
3051#include "implicit_f.inc"
3055#include "com04_c.inc"
3056#include "param_c.inc"
3073 CALL read_db(cfield,lfacload*nloadc)
3085!||====================================================================
3094#include "implicit_f.inc"
3098#include "com04_c.inc"
3099#include "param_c.inc"
3115 CALL read_db(loadp,lfacload*nloadp)
3125!||
read_i_c ../common_source/tools/input_output/write_routtines.c
3131#include "implicit_f.inc"
3135#include "com04_c.inc"
3136#include "com_xfem1.inc"
3140 INTEGER INOD_CRKXFEM(*),IEL_CRKXFEM(*),NODLEVXF(*)
3145 CALL READ_I_C(INOD_CRKXFEM
3151!||====================================================================
3157!||
read_i_c ../common_source/tools/input_output/write_routtines.c
3159!||
restmod ../engine/share/modules/restart_mod.f
3169#include "implicit_f.inc"
3173#include "com01_c.inc"
3174#include "com04_c.inc"
3175#include "com_xfem1.inc"
3179 INTEGER K,LEN,ELSZ,NENR,ELSZC,ELSZTG,NCRKXFE_G,
3182 IF(ICRACK3D == 0) then
3184 ALLOCATE(crkshell(0))
3186 ALLOCATE(crklvset(0))
3189 ALLOCATE(xfem_phantom(0))
3199 ALLOCATE(crkshell(nlevmax))
3200 ALLOCATE(crknod(nlevmax))
3201 ALLOCATE(crklvset(nlevmax))
3202 ALLOCATE(crkavx(nlevmax))
3203 ALLOCATE(
crksky(nlevmax))
3211 crkshell(k)%CRKNUMSHELL = elsz
3212 crkshell(k)%CRKNUMSH4 = elszc
3213 crkshell(k)%CRKNUMSH3 = elsztg
3215 ALLOCATE(crkshell(k)%CRKSHELLID(elsz))
3216 ALLOCATE(crkshell(k)%ELTYPE(elsz))
3217 CALL read_i_c(crkshell(k)%CRKSHELLID ,elsz)
3218 CALL read_i_c(crkshell(k)%ELTYPE ,elsz)
3221 ALLOCATE(crknod(k)%XFECRKNODID(len))
3222 ALLOCATE(crknod(k)%XFENODES(len))
3223 CALL read_i_c(crknod(k)%XFECRKNODID ,len)
3224 CALL read_i_c(crknod(k)%XFENODES ,len)
3227 ALLOCATE(crkshell(k)%XNODEL(4 ,elsz))
3228 CALL read_i_c(crkshell(k)%XNODEL, len)
3231 ALLOCATE(crklvset(k)%ENR0(2,len))
3232 ALLOCATE(crklvset(k)%AREA(elsz))
3233 CALL read_i_c(crklvset(k)%ENR0(1,1:len) ,len)
3234 CALL read_i_c(crklvset(k)%ENR0(2,1:len) ,len)
3235 CALL read_db (crklvset(k)%AREA ,elsz)
3238 ALLOCATE(crkavx(k)%A(3,len))
3239 ALLOCATE(crkavx(k)%AR(3,len))
3240 ALLOCATE(crkavx(k)%V(3,len))
3241 ALLOCATE(crkavx(k)%VR(3,len))
3242 ALLOCATE(crkavx(k)%X(3,len))
3243 ALLOCATE(crkavx(k)%U(3,len))
3245 CALL read_db(crkavx(k)%A ,len)
3246 CALL read_db(crkavx(k)%AR ,len)
3247 CALL read_db(crkavx(k)%V ,len)
3248 CALL read_db(crkavx(k)%VR ,len)
3249 CALL read_db(crkavx(k)%X ,len)
3250 CALL read_db(crkavx(k)%U ,len)
3252 ALLOCATE(crkavx(k)%XX(3,len))
3253 CALL read_db(crkavx(k)%XX, 3*len)
3255 ALLOCATE(
crksky(k)%FSKY(8,lcnecrkxfem))
3259 ALLOCATE(crknod(k)%NOD2IAD(len))
3260 CALL read_i_c(crknod(k)%NOD2IAD, len)
3262 crknod(k)%CRKNUMNODS = crknumnods
3269 nenr = int(ienrnod/nlevmax)
3270 ALLOCATE(xfem_phantom(nxlaymax))
3272 ALLOCATE(xfem_phantom(k)%ELCUT(elsz))
3273 ALLOCATE(xfem_phantom(k)%IFI(lcnecrkxfem))
3274 ALLOCATE(xfem_phantom(k)%TAGXP(5,ncrkxfe,ienrnod))
3275 ALLOCATE(xfem_phantom(k)%ITRI(2,elsz))
3277 CALL read_i_c(xfem_phantom(k)%ELCUT ,elsz)
3278 CALL read_i_c(xfem_phantom(k)%IFI ,lcnecrkxfem)
3279 CALL read_i_c(xfem_phantom(k)%TAGXP ,ncrkxfe*ienrnod*5)
3280 CALL read_i_c(xfem_phantom(k)%ITRI ,elsz*2)
3288 ALLOCATE(
crkedge(k)%LAYCUT(elsz))
3289 ALLOCATE(
crkedge(k)%IEDGEC(4,elszc))
3290 ALLOCATE(
crkedge(k)%IEDGETG(3,elsztg))
3291 ALLOCATE(
crkedge(k)%EDGEICRK(numedges))
3292 ALLOCATE(
crkedge(k)%EDGEIFI(2,numedges))
3293 ALLOCATE(
crkedge(k)%EDGEENR(2,numedges))
3294 ALLOCATE(
crkedge(k)%EDGETIP(2,numedges))
3295 ALLOCATE(
crkedge(k)%IBORDEDGE(numedges))
3296 ALLOCATE(
crkedge(k)%ICUTEDGE(numedges))
3297 ALLOCATE(
crkedge(k)%RATIO(numedges))
3316 len = 2*(numelc+numeltg)
3322 len = numnod*ienrnod
3345#include "implicit_f.inc"
3349#include "param_c.inc"
3355 ALLOCATE(PLY(NPLYMAX))
3357 NULLIFY(ply(k)%V,ply(k)%U )
3358 ALLOCATE(ply(k)%V(3,nplyxfe), ply(k)%U(3,nplyxfe))
3369!||--- called by ------------------------------------------------------
3382#include "implicit_f.inc"
3386#include "com04_c.inc"
3392 ALLOCATE (VFLOW(3*NUMNOD), DFLOW(3*NUMNOD),(3*NUMNOD))
3408!||====================================================================
3417#include "implicit_f.inc"
3458#include "implicit_f.inc"
3462#include "tabsiz_c.inc"
3499#include "implicit_f.inc"
3503#include "tabsiz_c.inc"
3519 CALL read_db(knotlocpc,sknotlocpc)
3523!||====================================================================
3540#include "implicit_f.inc"
3544#include "tabsiz_c.inc"
3559 CALL read_db(knotlocel,sknotlocel)
3580#include "implicit_f.inc"
3584#include "com04_c.inc"
3615#include "implicit_f.inc"
3619#include "param_c.inc"
3624 my_real GEO(*),PM(*)
3631 lsiz =(4*npt_stack +2)*ns_stack
3633 lsiz =(6*npt_stack + 1)*ns_stack
3643!||--- calls -----------------------------------------------------
3655#include "implicit_f.inc"
3659#include "com04_c.inc"
3663 TYPE(
drape_),
DIMENSION(*) :: DRAPE_SH4N,DRAPE_SH3N
3664 TYPE(DRAPEG_) :: DRAPEG
3668 INTEGER LEN,OFF,II,J,,NSLICE,NPT,NDIM_INDX_PLY,NDIM,NDIM_SLICE,
3670 my_real,
DIMENSION(:,:),
ALLOCATABLE ::
3671 my_real,
DIMENSION(:) ,
ALLOCATABLE :: thk
3672 INTEGER,
DIMENSION(:,:),
ALLOCATABLE :: ITMP
3673 INTEGER,
DIMENSION(:) ,
ALLOCATABLE :: NPTDRP_ELT,ISLICE,INDX_PLY,
3685 drapeg%NDIM_SH4N = ndim
3686 drapeg%NDIM_SLICE_SH4N = ndim_slice
3687 drapeg%NDIM_INDX_PLY_SH4N = ndim_indx_ply
3689 ALLOCATE(npt_elt(
numelc_drape),itmp(ndim,2),rtmp(ndim,2),
3690 . nptdrp_elt(
numelc_drape),islice(ndim_slice),indx_ply(ndim_indx_ply),
3693 CALL read_i_c(drapeg%INDX_SH4N,numelc)
3697 CALL read_i_c(indx_ply,ndim_indx_ply)
3705 drape_sh4n(ii)%NPLY_DRAPE = nptdrp_elt(ii)
3706 drape_sh4n(ii)%NPLY = npt_elt(ii)
3707 drape_sh4n(ii)%THICK = thk(ii)
3708 npt = drape_sh4n(ii)%NPLY
3709 ALLOCATE(drape_sh4n(ii)%INDX_PLY(npt))
3710 drape_sh4n(ii)%INDX_PLY = 0
3712 drape_sh4n(ii)%INDX_PLY(j)=indx_ply(ndim_indx_ply + j)
3714 ndim_indx_ply = ndim_indx_ply + npt
3715 npt_drape = drape_sh4n(ii)%NPLY_DRAPE
3716 ALLOCATE(drape_sh4n(ii)%DRAPE_PLY(npt_drape))
3718 nslice = islice(ndim_slice + j)
3719 drape_sh4n(ii)%DRAPE_PLY(j)%NSLICE = nslice
3720 ALLOCATE(drape_sh4n(ii)%DRAPE_PLY(j)%IDRAPE(nslice,2),drape_sh4n(ii)%DRAPE_PLY(j)%RDRAPE(nslice,2))
3721 drape_sh4n(ii)%DRAPE_PLY(j)%IDRAPE = 0
3722 drape_sh4n(ii)%DRAPE_PLY(j)%RDRAPE = zero
3724 drape_sh4n(ii)%DRAPE_PLY(j)%IDRAPE(is,1) = itmp(ndim + is,1)
3725 drape_sh4n(ii)%DRAPE_PLY(j)%IDRAPE(is,2) = itmp(ndim + is,2)
3726 drape_sh4n(ii)%DRAPE_PLY(j)%RDRAPE(is,1) = rtmp(ndim + is,1)
3727 drape_sh4n(ii)%DRAPE_PLY(j)%RDRAPE(is,2) = rtmp(ndim + is,2)
3729 ndim = ndim + nslice
3731 ndim_slice = ndim_slice + npt_drape
3733 DEALLOCATE(npt_elt,itmp,rtmp,nptdrp_elt,islice,indx_ply, thk)
3742 drapeg%NDIM_SH3N = ndim
3743 drapeg%NDIM_SLICE_SH3N = ndim_slice
3744 drapeg%NDIM_INDX_PLY_SH3N = ndim_indx_ply
3746 . nptdrp_elt(
numeltg_drape),islice(ndim_slice),indx_ply(ndim_indx_ply),
3749 CALL read_i_c(drapeg%INDX_SH3N,numeltg)
3753 CALL read_i_c(indx_ply,ndim_indx_ply)
3761 drape_sh3n(ii)%NPLY_DRAPE = nptdrp_elt(ii)
3762 drape_sh3n(ii)%NPLY = npt_elt(ii)
3763 drape_sh3n(ii)%THICK = thk(ii)
3764 npt = drape_sh3n(ii)%NPLY
3765 ALLOCATE(drape_sh3n(ii)%INDX_PLY(npt))
3766 drape_sh3n(ii)%INDX_PLY = 0
3768 drape_sh3n(ii)%INDX_PLY(j)=indx_ply(ndim_indx_ply + j)
3770 ndim_indx_ply = ndim_indx_ply + npt
3771 npt_drape = drape_sh3n(ii)%NPLY_DRAPE
3772 ALLOCATE(drape_sh3n(ii)%DRAPE_PLY(npt_drape))
3774 nslice = islice(ndim_slice + j)
3775 drape_sh3n(ii)%DRAPE_PLY(j)%NSLICE = nslice
3776 ALLOCATE(drape_sh3n(ii)%DRAPE_PLY(j)%IDRAPE(nslice,2),drape_sh3n
3777 drape_sh3n(ii)%DRAPE_PLY(j)%IDRAPE = 0
3778 drape_sh3n(ii)%DRAPE_PLY(j)%RDRAPE = zero
3780 drape_sh3n(ii)%DRAPE_PLY(j)%IDRAPE(is,1) = itmp(ndim + is,1)
3781 drape_sh3n(ii)%DRAPE_PLY(j)%IDRAPE(is,2) = itmp(ndim + is,2)
3782 drape_sh3n(ii)%DRAPE_PLY(j)%RDRAPE(is,1) = rtmp(ndim + is,1)
3783 drape_sh3n(ii)%DRAPE_PLY(j)%RDRAPE(is,2) = rtmp(ndim
3785 ndim = ndim + nslice
3787 ndim_slice = ndim_slice + npt_drape
3789 DEALLOCATE( npt_elt,itmp,rtmp,nptdrp_elt,islice,indx_ply,thk)
3797!||--- called by ------------------------------------------------------
3812#include "implicit_f.inc"
3816#include "com04_c.inc"
subroutine decompress_i_nnz(array, len)
subroutine decompress_r_nnz(array, len)
end diagonal values have been computed in the(sparse) matrix id.SOL
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
integer, dimension(:), allocatable eigibuf
integer, dimension(:,:), allocatable eigipm
type(fvbag_data), dimension(:), allocatable fvdata_old
integer num_opt_dt_fvmbag_2
type(fvbag_spmd), dimension(:), allocatable fvspmd
integer airbags_total_fvm_in_h3d
type(fvmbag_input_options_), dimension(:), allocatable fvmbag_input_options
integer num_opt_dt_fvmbag_1
integer num_opt_dt_fvmbag
integer num_opt_dt_fvmbag_0
integer, dimension(:), allocatable kmesh
integer, dimension(:,:), allocatable fxbipm
integer, dimension(:), allocatable fxbnod
integer, dimension(:), allocatable fxbelm
integer, dimension(:), allocatable fxbgrvi
type(intstamp_data), dimension(:), allocatable intstamp
type(plynods), dimension(:), allocatable plynod
integer, dimension(:), allocatable indx_ply
integer, dimension(:), allocatable idpid_ply
integer, dimension(:), allocatable plysizg
type(plyshells), dimension(:), allocatable plyshell
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 nodenr
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 kxfenod2elc
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 enrtag
integer, dimension(:), allocatable nodlevxf
integer, dimension(:), allocatable fr_wall
integer, dimension(:), allocatable loadpinter
integer, dimension(:), allocatable elcutc
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
character(len=10192) ifxm_fn
character(len=10192) ieigm_fn
character(len=10192) ifxs_fn
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 cp_real(n, x, xc)
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 rdresb(af, iaf, lvarrea, irunn, multi_fvm, h3d_data, pinch_data, ale_connectivity, t_monvol, sensors, ebcs_tab, dynain_data, user_windows, output, interfaces, loads, mat_elem, python, iflow, skews, rflow, liflow, lrflow, impl_s0, forneqs, unitab, stack, drape_sh4n, drape_sh3n, drapeg, ndrape, glob_therm, pblast, element, nodes, rbe3)
subroutine cfieldrest(cfield)
subroutine knotlocelrest(knotlocel)
subroutine stack_rrest(igeo, geo, pm)
subroutine fvrrest(monvol)
subroutine loadprest(loadp)
subroutine dsrrest(graphe)
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 redsqi(ia, l, iform)
subroutine redsqr(a, l, iform)
subroutine spmd_comm_split(color, key, subcomm, rank, size_l)
subroutine spmd_fvb_comm_pattern(ifv)
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 ancmsg(msgid, msgtype, anmode, i1, i2, i3, i4, i5, i6, i7, i8, i9, i10, i11, i12, i13, i14, i15, i16, i17, i18, i19, i20, r1, r2, r3, r4, r5, r6, r7, r8, r9, c1, c2, c3, c4, c5, c6, c7, c8, c9, prmode)
void tmpenvf(char *tmpdir, int *tmplen)
subroutine userwi_read(user_windows, ispmd, nspmd, numnod)
void read_i_c(int *w, int *len)
subroutine read_units(unitab)