120
121
122
124 USE intbufdef_mod
128 USE intbuf_fric_mod
137 USE sensor_mod
139 USE multi_fvm_mod
140 USE ebcs_mod
144 USE output_mod
145 USE mat_elem_mod
146 USE defaults_mod
148 use glob_therm_mod
149 USE pblast_mod
150
151
152
153#include "implicit_f.inc"
154
155
156
157#include "com01_c.inc"
158#include "com04_c.inc"
159#include "lagmult.inc"
160#include "param_c.inc"
161#include "scr03_c.inc"
162#include "scr17_c.inc"
163#include "scr23_c.inc"
164#include "tabsiz_c.inc"
165#include "sphcom.inc"
166#include "com_xfem1.inc"
167#include "fxbcom.inc"
168
169
170
171 INTEGER, INTENT(IN) :: NOM_OPT(LNOPT1,SNOM_OPT1), INOM_OPT(SINOM_OPT)
172 INTEGER, INTENT(IN) :: ITAB(NUMNOD),IXR_KJ(5,*)
173 INTEGER, INTENT(IN) :: NNLINK(10,SNNLINK), LNLINK(SLNLINK)
174 TYPE (CLUSTER_) ,DIMENSION(NCLUSTER) :: CLUSTERS
175 INTEGER,INTENT(IN) :: NOM_SECT(SNOM_SECT),NSTRF(SNSTRF),IGEO_STACK(4* NPT_STACK+2,NS_STACK)
176 my_real,
INTENT(IN) :: secbuf(ssecbuf)
177 TYPE(MONVOL_STRUCT_), DIMENSION(NVOLU), INTENT(IN) :: T_MONVOL
178 TYPE(MONVOL_METADATA_), INTENT(IN) :: T_MONVOL_METADATA
179 TYPE(SUBSET_), DIMENSION(NSUBS), INTENT(IN) :: SUBSETS
180 TYPE(DETONATORS_STRUCT_) :: DETONATORS
182 INTEGER, INTENT(IN) :: LAS(*)
183 TYPE (DRAPE_) :: DRAPE(NUMELC_DRAPE + NUMELTG_DRAPE)
185 INTEGER, INTENT(IN) :: IACTIV(LACTIV,*)
186 my_real,
INTENT(IN) :: factiv(lractiv,*),geo_stack(6*npt_stack+1,ns_stack),pm_stack(20,ns_stack)
187 TYPE (UNIT_TYPE_) ::UNITAB
188 my_real,
INTENT(IN) :: xyzref(sx)
189 TYPE (SENSORS_) ,INTENT(IN) :: SENSORS
190 TYPE(FUNC2D_STRUCT), DIMENSION(NFUNC2D), INTENT(IN) :: FUNC2D
191 TYPE (INICRACK_) , DIMENSION(NINICRACK) :: INICRACK
192 INTEGER, INTENT(IN) :: LLINAL
193 INTEGER, DIMENSION(LLINAL), INTENT(IN) :: LINALE
194 my_real,
INTENT(IN) :: qp_rperturb(nperturb,4)
195 INTEGER, INTENT(IN) :: QP_IPERTURB(NPERTURB,6)
196 TYPE (FVM_INIVEL_STRUCT), DIMENSION(NINVEL), INTENT(IN) :: FVM_INIVEL
197 INTEGER, INTENT(IN) :: LGAUGE(3,NBGAUGE)
198 my_real,
INTENT(IN) :: gauge(llgauge,nbgauge)
199 INTEGER, INTENT(IN) :: KXX(NIXX,*)
200 INTEGER, INTENT(IN) :: IXX(*)
201 INTEGER, INTENT(IN) :: IXRI(4,*)
202 INTEGER, INTENT(IN) :: FXBIPM(NBIPM,),EIGIPM(*)
203 my_real,
INTENT(IN) :: eigrpm(*)
204 CHARACTER, DIMENSION(NFXBODY) :: FXBFILE_TAB*2148
205 INTEGER ISPHIO(NISPHIO,NSPHIO)
207 . vsphio(svsphio)
208 TYPE(t_ebcs_tab), INTENT(IN) :: EBCS_TAB
209 TYPE(INIMAP1D_STRUCT), DIMENSION(NINIMAP1D), INTENT(IN) :: INIMAP1D
210 TYPE(INIMAP2D_STRUCT), DIMENSION(NINIMAP2D), INTENT(IN) :: INIMAP2D
211 INTEGER, INTENT(IN) :: NSIGSH,NSIGI,NSIGS,NSIGBEAM,NSIGTRUSS,NSIGRS
212 my_real,
INTENT(IN) :: sigsh(
max(1,nsigsh),*),sigsp(nsigi,*),sigi(nsigs,*),
213 . sigbeam(nsigbeam,*),sigtruss(nsigtruss,*),
214 . sigrs(nsigrs,*)
215 INTEGER, INTENT(IN) :: IMERGE(*),MERGE_NODE_TAB(*),NMERGE_TOT
216 my_real,
INTENT(IN) :: merge_node_tol(*)
217 INTEGER,INTENT(IN) :: IPARG(NPARG,NGROUP)
218 INTEGER, INTENT(IN) :: IBEAM_VECTOR(NUMELP)
219 my_real,
INTENT(IN) :: rbeam_vector(3,numelp)
220 INTEGER ,INTENT(IN) :: DAMP_RANGE_PART(NPART)
221 TYPE(USER_WINDOWS_),INTENT(IN) :: USER_WINDOWS
222 TYPE(OUTPUT_) ,INTENT(IN) :: OUTPUT
223 TYPE(MAT_ELEM_) ,INTENT(IN) ::
224 TYPE(DEFAULTS_) ,INTENT(IN) :: DEFAULTS
225 TYPE(glob_therm_) ,intent(in) :: glob_therm
226 TYPE(PBLAST_) ,INTENT(IN) ::
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276 INTEGER, INTENT(IN) :: NIMPDISP,NIMPVEL,NIMPACC
277 INTEGER, INTENT(IN) :: IGEO(NPROPGI,NUMGEO),IPM(NPROPMI,NUMMAT)
278 INTEGER, INTENT(IN) :: NUMLOADP, ILOADP(SIZLOADP,NLOADP), (NUMLOADP)
279 INTEGER, INTENT(IN) :: ICFIELD(SIZFIELD,NLOADC), LCFIELD(SLCFIELD)
280 INTEGER, INTENT(IN) :: IBCL(NIBCLD,NCONLD-NPRELD), IPRES(NIBCLD)
281 INTEGER, INTENT(IN) :: IGRV(NIGRV,NGRAV), LGRV(*)
282 INTEGER, INTENT(IN) :: NPBY(NNPBY,NRBYKIN), NPBYL(NNPBY,NRBYLAG), LPBY(*), LPBYL(*)
283 INTEGER, INTENT(IN) :: IBCR(GLOB_THERM%NIRADIA,GLOB_THERM%)
284 INTEGER, INTENT(IN) :: IBCV(GLOB_THERM%NICONV,GLOB_THERM%NUMCONV)
285 INTEGER, INTENT(IN) :: IBFTEMP(GLOB_THERM%NIFT,GLOB_THERM%NFXTEMP)
286 INTEGER, INTENT(IN) :: IBFFLUX(GLOB_THERM%NITFLUX,GLOB_THERM%NFXFLUX)
287 INTEGER, INTENT(IN) :: IBFVEL(NIFV,NFXVEL)
288 INTEGER, INTENT(IN) :: ICODE(NUMNOD), ISKEW(NUMNOD)
289 INTEGER, INTENT(IN) :: IBCSLAG(5,NBCSLAG)
290 INTEGER, INTENT(IN) :: IPARI(NPARI,NINTER)
291 INTEGER, INTENT(IN) :: LACCELM(3, NACCELM)
292 INTEGER, INTENT(IN) :: ISKWN(LISKN,*)
293 INTEGER, INTENT(IN) :: NPFRICORTH , PFRICORTH(*) , IREPFORTH(*)
294 INTEGER, INTENT(IN) :: TAGXREF(NUMNOD),IXC(NIXC,*),IXTG(NIXTG,*),IXS(NIXS,*), IXS10(6,*),
295 . IXS16(8,*)
296 INTEGER, INTENT(IN) :: ISOLNOD(NUMELS),IXR(NIXR,*), R_SKEW(*),IXP(NIXP,*),IXT(NIXT,*),
297 . IXQ(NIXQ,*),KXSP(NISP,*),IPARTSP(*),IPARTX(*)
298 INTEGER, INTENT(IN) :: NPRW(NRWALL,NNPRW),LPRW(SLPRW)
299 INTEGER, INTENT(IN) :: ITHVAR(SITHVAR),
300 . IPART(LIPART1*(NPART+NTHPART)),
301 . IPARTTH(18*(NPART+NTHPART)),NTHGRPMX,IBCSCYC(*)
302 INTEGER, INTENT(IN) :: NPTS,NPC(*),IRBE3(*),LRBE3(*),IRBE2(*),LRBE2(*)
303 INTEGER, INTENT(IN) :: MGRBY(NMGRBY,SMGRBY)
304 INTEGER, INTENT(IN) :: ISPCOND(NISPCOND,*),LJOINT(*),GJBUFI(LKJNI,*)
305 INTEGERINTENT(IN)
306INTEGER, INTENT(IN) :: IPRELOAD(3,*), IFLAG_BPRELOAD(*)
307 INTEGER, INTENT(IN) :: IBMPC(NUMMPC),(LMPC),IBMPC3(LMPC),IBMPC4(LMPC)
308 INTEGER, INTENT(IN) :: IPADMESH(KIPADMESH,*)
309 INTEGER, INTENT(IN) :: SH4TREE(KSH4TREE,*), SH3TREE(KSH3TREE,*),
310 . SH4TRIM(*),SH3TRIM(*)
311 INTEGER, INTENT(IN) :: IEXMAD(*),IEXLNK(NR2R,*)
312
314 . geo(npropg,numgeo), bufgeo(*), pm(npropm,nummat), bufmat(*)
316 . loadp
317 . forc(lfaccld,nconld-npreld), pres(lfaccld,npreld),
318 . agrv(lfacgrv,ngrav),preload(6,*)
319 my_real,
INTENT(IN) :: rby(nrby,nrbykin),rbyl(nrby,nrbylag),frbe3(sfrbe3)
320 my_real,
INTENT(IN) :: gjbufr(lkjnr,*),ms(*),in(*)
321 my_real,
INTENT(IN) :: fradia(glob_therm%LFACTHER,glob_therm%NUMRADIA)
322 my_real,
INTENT(IN) :: fconv(glob_therm%LFACTHER,glob_therm%NUMCONV)
323 my_real,
INTENT(IN) :: fbftemp(glob_therm%LFACTHER,glob_therm%NFXTEMP)
324 my_real,
INTENT(IN) :: fbfflux(glob_therm%LFACTHER,glob_therm%NFXFLUX)
325 my_real,
INTENT(IN) :: fbfvel(lfxvelr,nfxvel)
326 my_real,
INTENT(IN) :: v(3,numnod), vr(svr) ,
327 . w(sw)
329 . dampr(nrdamp,*)
331 . temp(numnod)
333 . accelm(llaccelm, naccelm)
335 . skew(lskew,*)
337 . xframe(nxframe,*)
340 my_real,
INTENT(IN) :: phiforth(*), vforth(3,*)
342 . xrefc(4,3,numelc),xreftg(3,3,numeltg),xrefs(8,3,numels8)
344 . rwbuf(nrwlp,nrwall)
346 . pld(*)
348 . x(3,numnod),
349 . thke(*),thkec(*),sh4ang(*),sh3ang(*)
351 . rtrans(ntransf,*)
353 . alea(*),xseed(*)
355 . rbmpc(srbmpc)
356
357 my_real,
INTENT(IN) :: bufsf(sbufsf)
358 INTEGER,INTENT(IN) :: SBUFSF_
359
360 my_real,
INTENT(IN) :: padmesh(kpadmesh,*)
361
362 TYPE(INTBUF_STRUCT_) INTBUF_TAB(*)
363 TYPE (BOX_) ,DIMENSION(NBBOX) ,INTENT(IN) :: IBOX
364 TYPE (ADMAS_) ,DIMENSION(NODMAS) ,INTENT(IN) :: IPMAS
365 TYPE(INTBUF_FRIC_STRUCT_) INTBUF_FRIC_TAB(*)
366 TYPE(TTABLE) TABLE(*)
367
368 TYPE (SET_) , DIMENSION(NSETS) :: SET
369 TYPE(SUBMODEL_DATA),INTENT(IN)::LSUBMODEL(*)
370 TYPE (GROUP_) , INTENT(IN), DIMENSION(NGRNOD) :: IGRNOD
371 TYPE (GROUP_) , INTENT(IN), DIMENSION(NGRPART) :: IGRPART
372 TYPE (GROUP_) , INTENT(IN), DIMENSION(NGRBRIC) :: IGRBRIC
373 TYPE (GROUP_) , INTENT(IN), DIMENSION(NGRSHEL) :: IGRSH4N
374 TYPE (GROUP_) , INTENT(IN), DIMENSION(NGRSH3N) :: IGRSH3N
375 TYPE (GROUP_) , INTENT(IN), DIMENSION(NGRQUAD) :: IGRQUAD
376 TYPE (GROUP_) , INTENT(IN), DIMENSION(NGRBEAM) :: IGRBEAM
377 TYPE (GROUP_) , INTENT(IN), DIMENSION(NGRTRUS) :: IGRTRUSS
378 TYPE (GROUP_) , INTENT(IN), DIMENSION(NGRSPRI) :: IGRSPRING
379 TYPE (SURF_) , INTENT(IN), DIMENSION(NSURF) :: IGRSURF
380 TYPE (SURF_) , INTENT(IN), DIMENSION(NSLIN) :: IGRSLIN
381 INTEGER, INTENT(IN) :: LIFLOW, LRFLOW
382 INTEGER, DIMENSION(LIFLOW), INTENT(IN) :: IFLOW
383 my_real,
DIMENSION(LRFLOW),
INTENT(IN) :: rflow
384
385
386
387
388
389
390
391 IF (
doqa /= 1 )
RETURN
392
394
396 . pm_stack ,geo_stack ,igeo_stack)
397
399 1 nom_opt ,inom_opt ,itab ,v ,vr ,
400 2 w ,temp ,inicrack ,fvm_inivel,
401 3 inimap1d, inimap2d)
402
404 2 ibftemp ,fbftemp ,ibfflux ,fbfflux ,itab ,
405 3 icode ,iskew ,ibcslag ,ibfvel ,fbfvel ,
406 4 nimpdisp ,nimpvel ,nimpacc ,rwbuf ,nprw ,
407 5 lprw ,ibcscyc ,irbe3 ,lrbe3 ,frbe3 ,
408 6 mgrby ,ispcond ,irbe2 ,lrbe2 ,npbyl ,
409 7 lpbyl ,rbyl ,ibmpc ,ibmpc2 ,ibmpc3 ,
410 8 ibmpc4 ,rbmpc ,ljoint ,nnlink ,lnlink,
411 9 llinal ,linale ,gjbufi ,gjbufr ,ms ,
412 9 in ,fxbipm ,fxbfile_tab,glob_therm)
413
415 2 loadp ,ibcl ,forc ,ipres ,pres ,
416 3 ibcr ,fradia ,ibcv ,fconv ,igrv ,
417 4 lgrv ,agrv ,icfield ,lcfield ,cfield ,
418 5 ipreload ,preload ,iflag_bpreload,
419 6 liflow, lrflow, iflow,rflow ,isphio ,vsphio,
420 7 glob_therm ,pblast )
421
423 1 xseed ,unitab ,qp_iperturb ,
424 2 qp_rperturb,eigipm , eigrpm, defaults ,
425 3 damp_range_part)
427 1 areasl,glob_therm%INTHEAT)
431 . skew , iskwn , xframe, npc,pld,table,npts,
432 . iactiv , factiv ,sensors,func2d)
434 CALL st_qaprint_friction(nom_opt,inom_opt,intbuf_fric_tab,npfricorth,pfricorth ,irepforth,phiforth,vforth)
436 1 ixs ,ixc ,ixtg )
437
439 1 ipartth ,nthgrpmx )
440
442
444
445 CALL st_qaprint_nodes(itab ,x,imerge,merge_node_tol, merge_node_tab,nmerge_tot,ms)
446
448 1 isolnod,ixr,r_skew,iskwn,ixp,
449 2 ixt ,x ,ixc ,ixtg ,thke,
450 3 sh4ang ,thkec,sh3ang,kxsp,ipartsp,
451 4 ipart ,ixr_kj,kxx, ixx ,ipartx,
452 5 ixri ,ixs16 ,ixq, ibeam_vector,rbeam_vector)
453
454
456 . ipart ,igrbric ,igrsh4n ,igrsh3n,igrquad,
457 . igrbeam,igrtruss ,igrspring,igrsurf,igrslin,
458 . ixc ,ixtg ,ixq ,ixp ,ixt ,
459 . ixr ,ixs )
464 CALL st_qaprint_refsta(xrefc ,xreftg ,xrefs ,tagxref ,ixs ,ixc ,ixtg ,itab, xyzref)
467 . igrquad,igrbeam ,igrtruss ,igrspring)
470 . ixc ,ixtg ,sh4trim,sh3trim )
474 . nsigsh ,sigsh ,nsigi ,sigsp ,nsigs ,
475 . sigi ,nsigbeam ,sigbeam ,nsigtruss,sigtruss,
476 . nsigrs ,sigrs )
480
481
482 RETURN
subroutine i2rupt(x, v, a, ms, in, stifn, fsav, weight, irect, nsv, msr, irtl, irupt, crst, mmass, miner, smass, siner, area, uvar, xsm0, dsm, fsm, prop, ipari, nsn, nmn, nuvar, igtyp, pid, npf, tf, itab, fncont, pdama2, isym, inorm, h3d_data, fncontp, ftcontp)
integer, parameter nchartitle
subroutine st_qaprint_admesh(ipart, ipadmesh, padmesh, sh4tree, sh3tree, ixc, ixtg, sh4trim, sh3trim)
subroutine st_qaprint_ale_options_driver
subroutine st_qaprint_clusters(nom_opt, inom_opt, clusters)
subroutine st_qaprint_composite_options(drape, drapeg)
subroutine st_qaprint_constraints(nom_opt, inom_opt, npby, lpby, rby, ibftemp, fbftemp, ibfflux, fbfflux, itab, icode, iskew, ibcslag, ibfvel, fbfvel, nimpdisp, nimpvel, nimpacc, rwbuf, nprw, lprw, ibcscyc, irbe3, lrbe3, frbe3, mgrby, ispcond, irbe2, lrbe2, npbyl, lpbyl, rbyl, ibmpc, ibmpc2, ibmpc3, ibmpc4, rbmpc, ljoint, nnlink, lnlink, llinal, linale, gjbufi, gjbufr, ms, in, fxbipm, fxbfile_tab, glob_therm)
subroutine st_qaprint_dfs_detonators(detonators)
subroutine st_qaprint_dfs_lasers(xlas, ilas)
subroutine st_qaprint_ebcs(ebcs_tab)
subroutine st_qaprint_element(ixs, ixs10, ipm, igeo, itab, isolnod, ixr, r_skew, iskwn, ixp, ixt, x, ixc, ixtg, thke, sh4ang, thkec, sh3ang, kxsp, ipartsp, ipart, ixr_kj, kxx, ixx, ipartx, ixri, ixs16, ixq, ibeam_vector, rbeam_vector)
subroutine st_qaprint_friction(nom_opt, inom_opt, intbuf_fric_tab, npfricorth, pfricorth, irepforth, phiforth, vforth)
subroutine st_qaprint_general_controls(nom_opt, inom_opt, dampr, irand, alea, xseed, unitab, qp_iperturb, qp_rperturb, eigipm, eigrpm, defaults, damp_range_part)
subroutine st_qaprint_groups(igrnod, igrpart, igrbric, igrsh4n, igrsh3n, igrquad, igrbeam, igrtruss, igrspring)
subroutine st_qaprint_initial_conditions(nom_opt, inom_opt, itab, v, vr, w, temp, inicrack, fvm_inivel, inimap1d, inimap2d)
subroutine st_qaprint_initial_state(nsigsh, sigsh, nsigi, sigsp, nsigs, sigi, nsigbeam, sigbeam, nsigtruss, sigtruss, nsigrs, sigrs)
subroutine st_qaprint_inivol()
subroutine st_qaprint_interfaces(nom_opt, inom_opt, ipari, intbuf_tab, i2rupt, areasl, intheat)
subroutine st_qaprint_internal_groups(iparg)
subroutine st_qaprint_loads(nom_opt, inom_opt, numloadp, iloadp, lloadp, loadp, ibcl, forc, ipres, pres, ibcr, fradia, ibcv, fconv, igrv, lgrv, agrv, icfield, lcfield, cfield, ipreload, preload, iflag_bpreload, liflow, lrflow, iflow, rflow, isphio, vsphio, glob_therm, pblast)
subroutine st_qaprint_madymo(iexmad, itab, ipart, ixs, ixc, ixtg)
subroutine st_qaprint_materials(mat_elem, ipm, pm, bufmat)
subroutine st_qaprint_monvol(t_monvol, t_monvol_metadata)
subroutine st_qaprint_multidomains(ipart, iexlnk, igrnod)
subroutine st_qaprint_nodes(itab, x, imerge, merge_node_tol, merge_node_tab, nmerge_tot, ms)
subroutine st_qaprint_output_databases(nom_opt, inom_opt, laccelm, accelm, lgauge, gauge)
subroutine st_qaprint_properties(igeo, geo, bufgeo, pm_stack, geo_stack, igeo_stack)
subroutine st_qaprint_reference_state(xrefc, xreftg, xrefs, tagxref, ixs, ixc, ixtg)
subroutine st_qaprint_refsta(xrefc, xreftg, xrefs, tagxref, ixs, ixc, ixtg, itab, xyzref)
subroutine st_qaprint_seatbelts(itab)
subroutine st_qaprint_set(set, lsubmodel, itab, igrnod, igrpart, ipart, igrbric, igrsh4n, igrsh3n, igrquad, igrbeam, igrtruss, igrspring, igrsurf, igrslin, ixc, ixtg, ixq, ixp, ixt, ixr, ixs)
subroutine st_qaprint_surf(igrsurf, igrslin, bufsf, sbufsf)
subroutine st_qaprint_time_histories(th, ithvar, ipart, subsets, ipartth, nthgrpmx)
subroutine st_qaprint_userwi(user_windows)