86
87
88
89 USE connectivity_mod
90 use nodal_arrays_mod
98 USE multi_fvm_mod
100 USE intbuf_fric_mod
102 USE mat_elem_mod
109 USE sensor_mod
110 USE ebcs_mod
113 USE loads_mod
116 USE output_mod
117 USE interfaces_mod
119 USE python_funct_mod
123 USE skew_mod
124 use glob_therm_mod
125 use pblast_mod
126 use timer_mod
127 use rbe3_mod
128 use coupling_adapter_mod
129
130
131
132#include "implicit_f.inc"
133
134#include "com01_c.inc"
135#include "com04_c.inc"
136#include "scr_fac_c.inc"
137#include "scr01_c.inc"
138#include "task_c.inc"
139#include "com_xfem1.inc"
140
141
142
143 type(connectivity_), intent(inout) :: ELEMENT
144 type(nodal_arrays_), intent(inout) :: NODES
145 type(timer_), intent(inout) :: TIMERS
146 type(coupling_type), intent(inout) :: coupling
147 INTEGER, INTENT(IN) :: LIFLOW
148 INTEGER, INTENT(IN) :: LRFLOW
149
150 INTEGER,INTENT(INOUT) :: IFLOW(LIFLOW)
151 INTEGER,INTENT(INOUT) :: RFLOW(LRFLOW)
152
153 INTEGER ITASK,IAF(*),IDATA(*),IRUNN_BIS
154
156 . af(*),rdata(*),
157 . forneqs(*)
158 TYPE(PRGRAPH) :: GRAPHE(*)
159 TYPE (STACK_PLY) :: STACK
160 TYPE(MULTI_FVM_STRUCT) :: MULTI_FVM
161 TYPE(H3D_DATABASE) :: H3D_DATA
162 TYPE(UNIT_TYPE_) :: UNITAB
163
164 TYPE(SUBSET_) ,DIMENSION(NSUBS) :: SUBSETS
165 TYPE(GROUP_) ,DIMENSION(NGRNOD) :: IGRNOD
166 TYPE(GROUP_) ,DIMENSION(NGRBRIC) :: IGRBRIC
167 TYPE(GROUP_) ,DIMENSION(NGRQUAD) :: IGRQUAD
168 TYPE(GROUP_) ,DIMENSION(NGRSHEL) :: IGRSH4N
169 TYPE(GROUP_) ,DIMENSION(NGRSH3N) :: IGRSH3N
170 TYPE(GROUP_) ,DIMENSION(NGRTRUS) :: IGRTRUSS
171 TYPE(GROUP_) ,DIMENSION(NGRBEAM) :: IGRBEAM
172 TYPE(GROUP_) ,DIMENSION(NGRSPRI) :: IGRSPRING
173 TYPE(GROUP_) ,DIMENSION(NGRPART) :: IGRPART
174 TYPE(SURF_) ,DIMENSION(NSURF) :: IGRSURF
175 TYPE(SURF_) ,DIMENSION(NSURF) :: IGRSLIN
176 TYPE(PINCH) :: PINCH_DATA
177 TYPE(t_ale_connectivity), INTENT(INOUT) :: ALE_CONNECTIVITY
178 TYPE(MONVOL_STRUCT_), DIMENSION(NVOLU), INTENT(INOUT) :: T_MONVOL
179 TYPE(DRAPE_) :: DRAPE_SH3N(NUMELTG_DRAPE),DRAPE_SH4N(NUMELC_DRAPE)
180 TYPE(DRAPEG_) :: DRAPEG
181 TYPE(SENSORS_) ,INTENT(INOUT) :: SENSORS
182 TYPE(t_ebcs_tab), INTENT(INOUT) :: EBCS_TAB
183 TYPE(T_DIFFUSION) ,INTENT(INOUT) :: DIFFUSION
184 TYPE(t_segvar) :: SEGVAR
185 TYPE(DYNAIN_DATABASE), INTENT(INOUT) :: DYNAIN_DATA
186 TYPE(USER_WINDOWS_),INTENT(INOUT) :: USER_WINDOWS
187 TYPE(OUTPUT_),INTENT(INOUT) :: OUTPUT
188 TYPE(INTERFACES_),INTENT(INOUT) :: INTERFACES
189 TYPE(DT_),INTENT(INOUT) :: DT
190 TYPE(LOADS_) ,INTENT(INOUT) :: LOADS
191 TYPE(MAT_ELEM_) ,INTENT(INOUT) :: MAT_ELEM
192 TYPE(PYTHON_) , INTENT(INOUT) :: PYTHON
193 TYPE(NAMES_AND_TITLES_),INTENT(INOUT) :: NAMES_AND_TITLES
194 TYPE(SKEW_), INTENT(INOUT) :: SKEWS
195 type (glob_therm_) ,intent(inout) :: glob_therm
196 type (pblast_) ,intent(inout) :: PBLAST
197 type (rbe3_) ,intent(inout) :: RBE3
198
199
200
201 INTEGER IUN,IFUN,IUNUSED,IPV,MFUN,I
202 INTEGER ITRACE(10)
203 DATA iun/1/,iunused/1/
205 . fsavd(1)
206
207
208
209
210
211
212 itaskp1 = 1
213 itaskp1_def = 1
214 itrace(1)=0
215 itrace(2)=nthread
217
218 CALL resol(timers, element,nodes,coupling,
219 . af ,iaf ,
230 b itask ,iaf(if01) ,
231 c thke ,damp ,
232 d pm ,skews ,geo ,eani ,bufmat ,
bufgeo ,bufsf ,
233 e w ,veul ,fill ,dfill ,alph ,wb ,dsave ,asave ,
234 . msnf ,
235 f tf ,forc ,vel ,fsav ,fzero ,xlas ,accelm ,
236 g grav ,fr_wave ,
failwave ,parts0 ,elbuf ,rwbuf ,sensors,
237 h rwsav ,rby ,rivet ,secbuf ,volmon ,lambda ,
238 i wa ,fv ,partsav ,
239 j uwa ,val2 ,phi ,segvar ,r ,crflsw ,
240 k flsw ,fani ,xcut ,anin ,tani ,secfcum ,af(mf01),
241 l idata ,rdata ,
256 c
fxbipm ,fxbrpm ,
fxbnod ,fxbmod ,fxbglm ,fxbcpm ,fxbcps ,
257 d fxblm ,fxbfls ,fxbdls ,fxbdep ,fxbvit ,fxbacc ,
fxbelm ,
260 g
fr_i18 ,graphe ,iflow ,rflow,
263 k
ipadmesh ,padmesh ,msc ,mstg ,inc ,intg ,ptg
265 m acontact ,pcontact ,factiv ,
272 w dmels ,mstr ,dmeltr ,msp ,dmelp ,msrt ,dmelrt ,
290 f interfaces%SPMD_ARRAYS%IAD_FREDG,interfaces%SPMD_ARRAYS%FR_EDG ,drape_sh4n ,drape_sh3n ,tab_mat ,
292 h h3d_data ,subsets ,igrnod ,igrbric ,
293 i igrquad ,igrsh4n ,igrsh3n ,igrtruss ,igrbeam ,
294 j igrspring ,igrpart ,igrsurf ,forneqs ,
299 o dt ,loads ,python ,dpl0cld ,vel0cld ,
301 r glob_therm ,pblast ,rbe3)
302
304
305 RETURN
integer, dimension(:), allocatable id_damp_vrel
integer, dimension(:), allocatable fr_damp_vrel
integer, dimension(:), allocatable eigibuf
integer, dimension(:,:), allocatable eigipm
integer, dimension(:,:), allocatable fxbipm
integer, dimension(:), allocatable fxbnod
integer, dimension(:), allocatable fxbelm
integer, dimension(:), allocatable fxbgrvi
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 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_i2m
integer, dimension(:), allocatable iad_cut
integer, dimension(:), allocatable lgrav
integer, dimension(:), allocatable, target npby
integer, dimension(:), allocatable kxig3d
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 iadrcp_pxfem
integer, dimension(:), allocatable ibc_ply
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 icodt_ply
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 fr_nor
integer, dimension(:), allocatable isphio
integer, dimension(:), allocatable fr_i18
integer, dimension(:), allocatable, target ipari
type(spsym_struct) xspsym
integer, dimension(:), allocatable igaup
integer, dimension(:), allocatable icodrbym
type(spsym_struct) wsmcomp
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 iecran
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 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 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 iadsdp_pxfem
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 iadsdp_crkxfem
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 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 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 irbym
integer, dimension(:,:), allocatable ixsp
integer, dimension(:), allocatable iadrcp_crkxfem
integer, dimension(:), pointer madsh4
integer, dimension(:), allocatable iparg
integer, dimension(:), allocatable ixq
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 llagf
integer, dimension(:), allocatable nbrcvois
integer, dimension(:), allocatable ljoint
integer, dimension(:), allocatable lnsdvois
integer, dimension(:,:), allocatable tab_ump
integer, dimension(:), allocatable naccp
type(spsym_struct) vspsym
integer, dimension(:), allocatable procne_pxfem
integer, dimension(:), allocatable dd_r2r
integer, dimension(:), allocatable icontact
integer, dimension(:), allocatable ipart_state
integer, dimension(:), allocatable sph2sol
integer, dimension(:), allocatable irst
integer, dimension(:), allocatable sol2sph_typ
integer, dimension(:), allocatable sol2sph
type(ttable), dimension(:), allocatable table
subroutine resol(timers, element, nodes, coupling, af, iaf, iskwn, neth, ipart, nom_opt, kxx, ixx, ixtg, ixs, ixq, ixt, ixp, ixr, ifill, mat_elem, ims, npc, ibcl, ibfv, idum, las, laccelm, nnlink, lnlink, iparg, dd_iad, igrv, iexlnk, kinet, ipari, nprw, iconx, npby, lpby, lrivet, nstrf, ljoint, nodpor, monvol, ilink, llink, linale, neflsw, nnflsw, icut, cluster, itask, inoise, thke, damp, pm, skews, geo, eani, bufmat, bufgeo, bufsf, w, veul, fill, dfill, alph, wb, dsave, asave, msnf, tf, forc, vel, fsav, fzero, xlas, accelm, agrv, fr_wave, failwave, parts0, elbuf, rwbuf, sensors, rwsav, rby, rivet, secbuf, volmon, lambda, wa, fv, partsav, uwa, val2, phi, segvar, r, crflsw, flsw, fani, xcut, anin, tani, secfcum, bufnois, idata, rdata, iframe, kxsp, ixsp, nod2sp, ispsym, ispcond, xframe, spbuf, xspsym, vspsym, pv, fsavd, ibvel, lbvel, wasph, w16, isphio, lprtsph, lonfsph, vsphio, fbvel, lagbuf, ibcslag, iactiv, dampr, gjbufi, gjbufr, rbmpc, ibmpc, sphveln, nbrcvois, nbsdvois, lnrcvois, lnsdvois, nercvois, nesdvois, lercvois, lesdvois, npsegcom, lsegcom, nporgeo, ixtg1, npbyl, lpbyl, rbyl, igeo, ipm, madprt, madsh4, madsh3, madsol, madnod, madfail, iad_rby, fr_rby, fr_wall, iad_rby2, fr_rby2, iad_i2m, fr_i2m, addcni2, procni2, iadi2, fr_mv, iadmv2, fr_ll, fr_rl, iadcj, fr_cj, fr_sec, iad_sec, iad_cut, fr_cut, rg_cut, newfront, fr_mad, fxbipm, fxbrpm, fxbnod, fxbmod, fxbglm, fxbcpm, fxbcps, fxblm, fxbfls, fxbdls, fxbdep, fxbvit, fxbacc, fxbelm, fxbsig, fxbgrvi, fxbgrvr, eigipm, eigibuf, eigrpm, lnodpor, fr_i18, graphe, iflow, rflow, lgrav, dd_r2r, fasolfr, fr_lagf, llagf, lprw, icontact, rcontact, sh4tree, sh3tree, ipadmesh, padmesh, msc, mstg, inc, intg, ptg, iskwp, nskwp, isensp, nsensp, iaccp, naccp, ipart_state, acontact, pcontact, factiv, sh4trim, sh3trim, mscnd, incnd, ibfflux, fbfflux, rbym, irbym, lnrbym, icodrbym, ibcv, fconv, ibftemp, fbftemp, iad_rbym, fr_rbym, weight_rm, ms_ply, zi_ply, inod_pxfem, iel_pxfem, iadc_pxfem, adsky_pxfem, icode_ply, icodt_ply, iskew_ply, admsms, madclnod, nom_sect, mcpc, mcptg, dmelc, dmeltg, mssa, dmels, mstr, dmeltr, msp, dmelp, msrt, dmelrt, ibcr, fradia, res_sms, table, irbe2, lrbe2, iad_rbe2, fr_rbe2, phie, msf, procne_pxfem, iadsdp_pxfem, iadrcp_pxfem, icfield, lcfield, cfield, msz2, diag_sms, iloadp, lloadp, loadp, inod_crk, iel_crk, iadc_crk, adsky_crk, cne_crk, procne_crk, iadsdp_crk, iadrcp_crk, ibufssg_io, ibc_ply, dmint2, ibordnode, elbuf_tab, por, nodedge, iad_edge, fr_edge, fr_nbedge, crknodiad, lgauge, gauge, igaup, ngaup, nodlevxf, dd_r2r_elem, nodglobxfe, sph2sol, sol2sph, irst, dmsph, wagap, xfem_tab, elcutc, nodenr, kxfenod2elc, enrtag, rthbu f, kxig3d, ixig3d, knot, wige, wsmcomp, stack, cputime_mp_glob, cputime_mp, tab_ump, poin_ump, sol2sph_typ, irunn_bis, addcsrect, iad_frnor, fr_nor, procnor, iad_fredg, fr_edg, drape_sh4n, drape_sh3n, tab_mat, nativ0_sms, multi_fvm, segquadfr, ms_2d, h3d_data, subsets, igrnod, igrbric, igrquad, igrsh4n, igrsh3n, igrtruss, igrbeam, igrspring, igrpart, igrsurf, forneqs, nloc_dmg, iskwp_l, knotlocpc, knotlocel, pinch_data, tag_skins6, ale_connectivity, xcell, xface, ne_nercvois, ne_nesdvois, ne_lercvois, ne_lesdvois, ibcscyc, lbcscyc, t_monvol, id_global_vois, face_vois, dynain_data, fcont_max, ebcs_tab, diffusion, kloadpinter, loadpinter, dgaploadint, drapeg, user_windows, output, interfaces, dt, loads, python, dpl0cld, vel0cld, ndamp_vrel, id_damp_vrel, fr_damp_vrel, ndamp_vrel_rbyg, names_and_titles, unitab, liflow, lrflow, glob_therm, pblast, rbe3)
subroutine trace_out(nsub)
subroutine trace_in(nsub, itab, atab)