OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
spstres.F File Reference
#include "implicit_f.inc"
#include "mvsiz_p.inc"
#include "vect01_c.inc"
#include "com01_c.inc"
#include "com04_c.inc"
#include "com06_c.inc"
#include "com08_c.inc"
#include "sphcom.inc"
#include "param_c.inc"
#include "scr07_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine spstres (timers, elbuf_tab, ng, pm, geo, x, v, ms, w, spbuf, wa, nloc_dmg, itab, pld, bufmat, bufgeo, partsav, fsav, dt2t, iparg, npc, kxsp, ixsp, nod2sp, neltst, ityptst, ipart, ipartsp, fv, nel, ipm, gresav, grth, igrth, table, istrain, voln, igeo, iexpan, temp, itask, sph2sol, mat_elem, h3d_strain, output, snpc, stf, sbufmat, svis, nsvois, idtmins, iresp, idel7ng, idel7nok, idtmin, maxfunc, lipart1, imon_mat, userl_avail, impl_s, idyna, dt, glob_therm, sensors)

Function/Subroutine Documentation

◆ spstres()

subroutine spstres ( type(timer_), intent(inout) timers,
type (elbuf_struct_), dimension(ngroup), target elbuf_tab,
integer ng,
pm,
geo,
x,
v,
ms,
w,
spbuf,
wa,
type (nlocal_str_), target nloc_dmg,
integer, dimension(*) itab,
pld,
bufmat,
bufgeo,
partsav,
fsav,
dt2t,
integer, dimension(nparg,*) iparg,
integer, dimension(*) npc,
integer, dimension(nisp,*) kxsp,
integer, dimension(kvoisph,*) ixsp,
integer, dimension(*) nod2sp,
integer neltst,
integer ityptst,
integer, dimension(lipart1,*) ipart,
integer, dimension(*) ipartsp,
fv,
integer nel,
integer, dimension(npropmi,*) ipm,
gresav,
integer, dimension(*) grth,
integer, dimension(*) igrth,
type(ttable), dimension(*) table,
integer istrain,
voln,
integer, dimension(*) igeo,
integer iexpan,
temp,
integer itask,
integer, dimension(*) sph2sol,
type (mat_elem_), intent(inout) mat_elem,
integer h3d_strain,
type(output_), intent(inout) output,
integer, intent(in) snpc,
integer, intent(in) stf,
integer, intent(in) sbufmat,
intent(inout) svis,
integer, intent(in) nsvois,
integer, intent(in) idtmins,
integer, intent(in) iresp,
integer, intent(in) idel7ng,
integer, intent(inout) idel7nok,
integer, dimension(102) idtmin,
integer, intent(in) maxfunc,
integer, intent(in) lipart1,
integer, intent(in) imon_mat,
integer, intent(in) userl_avail,
integer, intent(in) impl_s,
integer, intent(in) idyna,
type (dt_), intent(in) dt,
type (glob_therm_), intent(inout) glob_therm,
type (sensors_), intent(in) sensors )
Parameters
[in,out]outputoutput structure
[in]sensorssensor structure

Definition at line 53 of file spstres.F.

67C-----------------------------------------------
68C M o d u l e s
69C-----------------------------------------------
70 USE timer_mod
71 USE mmain_mod
72 USE table_mod
73 USE mat_elem_mod
76 USE output_mod
77 USE elbufdef_mod
78 USE dt_mod
79 use glob_therm_mod
80 use sensor_mod
81C----6---------------------------------------------------------------7---------8
82C I m p l i c i t T y p e s
83C-----------------------------------------------
84#include "implicit_f.inc"
85C-----------------------------------------------
86C G l o b a l P a r a m e t e r s
87C-----------------------------------------------
88#include "mvsiz_p.inc"
89C-----------------------------------------------
90C C o m m o n B l o c k s
91C-----------------------------------------------
92#include "vect01_c.inc"
93#include "com01_c.inc"
94#include "com04_c.inc"
95#include "com06_c.inc"
96#include "com08_c.inc"
97#include "sphcom.inc"
98#include "param_c.inc"
99#include "scr07_c.inc"
100C-----------------------------------------------------------------
101C D u m m y A r g u m e n t s
102C-----------------------------------------------
103 TYPE(TIMER_) ,INTENT(INOUT) :: TIMERS
104 INTEGER, INTENT(IN) :: SNPC
105 INTEGER, INTENT(IN) :: STF
106 INTEGER, INTENT(IN) :: SBUFMAT
107 INTEGER, INTENT(IN) :: NSVOIS
108 INTEGER, INTENT(IN) :: IDTMINS
109 INTEGER ,INTENT(IN) :: IRESP
110 INTEGER ,INTENT(IN) :: IDEL7NG
111 INTEGER ,INTENT(INOUT) :: IDEL7NOK
112 integer,dimension(102) :: IDTMIN
113 INTEGER ,INTENT(IN) :: MAXFUNC
114 INTEGER ,INTENT(IN) :: LIPART1
115 INTEGER, INTENT(IN) :: IMPL_S
116 INTEGER, INTENT(IN) :: IDYNA
117 INTEGER, INTENT(IN) :: USERL_AVAIL
118 INTEGER, INTENT(IN) :: IMON_MAT
119 INTEGER KXSP(NISP,*),IXSP(KVOISPH,*),NOD2SP(*),ITAB(*),
120 . IPART(LIPART1,*) ,IPARTSP(*), NPC(*), IPARG(NPARG,*),NG,
121 . NELTST,ITYPTST,NEL,GRTH(*),IGRTH(*) , ISTRAIN,
122 . IPM(NPROPMI,*),IGEO(*),IEXPAN,ITASK,SPH2SOL(*),H3D_STRAIN
123 my_real
124 . x(3,*) ,v(3,*) ,ms(*) ,
125 . pm(npropm,*),geo(npropg,*),bufmat(*) ,bufgeo(*) ,w(3,*) ,
126 . pld(*) ,fsav(nthvki,*) ,spbuf(nspbuf,*) ,
127 . wa(*) , partsav(*) ,dt2t, fv(*),
128 . gresav(*),voln(mvsiz),temp(*)
129 my_real, DIMENSION(MVSIZ,6), INTENT(INOUT) :: svis
130 TYPE (ELBUF_STRUCT_), TARGET, DIMENSION(NGROUP) :: ELBUF_TAB
131 TYPE (NLOCAL_STR_) , TARGET :: NLOC_DMG
132 TYPE(OUTPUT_), INTENT(INOUT) :: OUTPUT !< output structure
133 TYPE (MAT_ELEM_) ,INTENT(INOUT) :: MAT_ELEM
134 TYPE (DT_) ,INTENT(IN) :: DT
135 type (glob_therm_) ,intent(inout) :: glob_therm
136 type (sensors_) ,intent(in) :: sensors !< sensor structure
137C-----------------------------------------------
138C L o c a l V a r i a b l e s
139C-----------------------------------------------
140 INTEGER NF1, IFLAG, NB3S, I, OFFSET, IPRT,ILAY
141C-----
142 INTEGER MXT(MVSIZ),NGL(MVSIZ), IBIDON(1),IBID
143 my_real
144 . vd2(mvsiz) , dvol(mvsiz),deltax(mvsiz),
145 . vis(mvsiz) , qvis(mvsiz), cxx(mvsiz) ,
146 . s1(mvsiz) , s2(mvsiz) , s3(mvsiz) ,
147 . s4(mvsiz) , s5(mvsiz) , s6(mvsiz) ,
148 . dxx(mvsiz) , dyy(mvsiz) , dzz(mvsiz) ,
149 . d4(mvsiz) , d5(mvsiz) , d6(mvsiz) ,
150 . rx(mvsiz) , ry(mvsiz) , rz(mvsiz) ,
151 . sx(mvsiz) , sy(mvsiz) , sz(mvsiz) ,gama(mvsiz,6),
152 . vdx(mvsiz), vdy(mvsiz), vdz(mvsiz) ,ssp_eq(mvsiz),aire(mvsiz),
153 . tempel(mvsiz)
154C-----
155C Variables utilisees en argument par les materiaux.
156 my_real
157 . sti(mvsiz),
158 . wxx(mvsiz) , wyy(mvsiz) , wzz(mvsiz), bid(mvsiz)
159C Variables utilisees en argument par les materiaux si SPH uniquement.
160 my_real
161 . mumax(mvsiz)
162C-----
163C Variables utilisees (en arguments) dans les routines solides (uniquement).
164 INTEGER NC1(MVSIZ),NGEO(MVSIZ)
165 my_real
166 . off(mvsiz) , rhoo(mvsiz),
167 . vx1(mvsiz), vy1(mvsiz), vz1(mvsiz),
168 . dxy(mvsiz),dyx(mvsiz),
169 . dyz(mvsiz),dzy(mvsiz),
170 . dzx(mvsiz),dxz(mvsiz),die(mvsiz)
171C Variables void MMAIN
172 my_real
173 . sigy(mvsiz),et(mvsiz),
174 . r1_free(mvsiz),r3_free(mvsiz),r4_free(mvsiz)
175 INTEGER SZ_R1_FREE
176 my_real,
177 . DIMENSION(:), POINTER :: eint
178 my_real varnl(nel)
179 TYPE(TTABLE) TABLE(*)
180 TYPE(G_BUFEL_) ,POINTER :: GBUF
181 TYPE(L_BUFEL_) ,POINTER :: LBUF
182 TYPE(t_ale_connectivity) :: ALE_CONNECT
183 INTEGER SZ_IX
184C-----------------------------------------------
185C S o u r c e L i n e s
186C-----------------------------------------------
187 sz_ix=numelq+numels+nsvois
188 ilay=1
189 sz_r1_free = mvsiz
190 ibid = 0
191 gbuf => elbuf_tab(ng)%GBUF
192 lbuf => elbuf_tab(ng)%BUFLY(1)%LBUF(1,1,1)
193 tempel(:) = zero
194C-----------
195 nf1=nft+1
196C-----------
197C GATHER PARTICLE VARIABLES
198 CALL spoff3(
199 1 kxsp(1,nf1), vd2, vis, gbuf%OFF,
200 2 off, nc1, ngl, mxt,
201 3 ngeo, ipart, ipartsp(nf1),nel)
202C-----------
203C DOWNLOAD RHOO, RHON, DELTAX and D FROM WA.
204 CALL spload3(
205 1 spbuf, wa, rhoo, gbuf%RHO,
206 2 deltax, gbuf%OFF,dxx, dxy,
207 3 dxz, dyx, dyy, dyz,
208 4 dzx, dzy, dzz, mumax,
209 5 lft, llt, nft)
210C-----------
211C LAGRANGIAN ONLY.
212C do not enter spvol3 case thermal only material.
213C (actually only Lagrangian case is available , not Ale neither Euler)
214 IF(jlag+jale+jeul/=0)THEN
215 CALL spvol3(
216 1 off, pm, gbuf%VOL, gbuf%EINT,
217 2 rhoo, gbuf%RHO, voln, dvol,
218 3 ngl, mxt, lft, llt,
219 4 jlag)
220 END IF
221C-----------
222 CALL spdefo3(
223 1 dxx, dxy, dxz, dyx,
224 2 dyy, dyz, dzx, dzy,
225 3 dzz, d4, d5, d6,
226 4 wxx, wyy, wzz, nel)
227C-----------
228C when particle is sleeping, stresses (global system) do not rotate.
229 CALL srota3(
230 1 gbuf%SIG,s1, s2, s3,
231 2 s4, s5, s6, wxx,
232 3 wyy, wzz, nel, mtn,
233 4 ismstr)
234 CALL spreploc(
235 1 gbuf%GAMA,wxx, wyy, wzz,
236 2 gama, nel, lft, llt,
237 3 isorth)
238C-----------
239Cbm compute temperature in element
240 IF (jthe < 0) CALL sptempel(
241 1 kxsp, temp, tempel, lft,
242 2 llt, nft)
243 die(1:mvsiz)=zero
244C------------------------------------------------------
245C CALCUL DES CONTRAINTES SUIVANT LOIS CONSTITUTIVES
246C------------------------------------------------------
247C LAW 11 uses IELVS=IBIDON and IXS=IBIDON should not be used.
248 ibidon(1)=0
249 offset=0
250 CALL mmain(timers, output,
251 1 elbuf_tab, ng, pm, geo,
252 2 ale_connect, ibidon, iparg,
253 3 v, pld, npc, bufmat,
254 4 sti, x, dt2t, neltst,
255 5 ityptst, offset, nel, w,
256 6 off, ngeo, mxt, ngl,
257 7 voln, vd2, dvol, deltax,
258 8 vis, qvis, cxx, s1,
259 9 s2, s3, s4, s5,
260 a s6, dxx, dyy, dzz,
261 b d4, d5, d6, wxx,
262 c wyy, wzz, rx, ry,
263 d rz, sx, sy, sz,
264 e vdx, vdy, vdz, mumax,
265 f ssp_eq, aire, sigy, et,
266 g r1_free, lbuf%PLA, r3_free, r4_free,
267 h dxx, dxy, dxz, dyx,
268 i dyy, dyz, dzx, dzy,
269 j dzz, ipm, gama, bid,
270 k bid, bid, bid, bid,
271 l bid, bid, istrain, tempel,
272 m die, iexpan, ilay, bid,
273 n bid, 1, 1, 1,
274 o table, bid, bid, bid,
275 p bid, iparg(1,ng), igeo, bid,
276 q itask, nloc_dmg, varnl, mat_elem,
277 r h3d_strain, jplasol, jsph, sz_r1_free,
278 s snpc, stf, sbufmat, glob_therm,
279 * svis, sz_ix, iresp,
280 t n2d, th_strain, ngroup, tt,
281 . dt1, ntable, numelq, nummat,
282 . numgeo, numnod, numels,
283 . idel7nok, idtmin, maxfunc,
284 . imon_mat, userl_avail, impl_s,
285 . idyna, dt , bid ,sensors)
286C-----------------------------
287 IF(istrain==1)THEN
288 CALL sstra3(dxx,dyy ,dzz ,d4 ,d5 ,
289 . d6 ,lbuf%STRA,wxx ,wyy ,wzz ,
290 . off,nel, iparg(37,ng))
291 ENDIF
292C-----------------------------
293C SMALL STRAIN
294C-----------------------------
295 CALL spmallb3(
296 1 gbuf%OFF, off, kxsp(1,nf1), sph2sol(nf1),
297 2 lft, llt, ismstr)
298C--------------------------
299C SUBMATERIALS SYNTHESIS
300C--------------------------
301 iflag=mod(ncycle,ncpri)
302 IF(iflag==0.OR.tt>=output%TH%THIS.OR.mdess/=0 .OR.tt>=tabfis(1).
303 . or.tt>=tabfis(2).OR.tt>=tabfis(3).OR.tt>=tabfis(4).
304 . or.tt>=tabfis(5).OR.tt>=tabfis(6).OR.tt>=tabfis(7).
305 . or.tt>=tabfis(8).OR.tt>=tabfis(9).OR.tt>=tabfis(10))THEN
306 IF (mtn == 11) THEN
307 eint => elbuf_tab(ng)%GBUF%EINS(1:nel)
308 ELSE
309 eint => elbuf_tab(ng)%GBUF%EINT(1:nel)
310 ENDIF
311 CALL spbilan(
312 1 v, partsav, nc1, eint,
313 2 gbuf%RHO, gbuf%RK, gbuf%VOL, voln,
314 3 ipartsp(nf1),gbuf%OFF, gresav, grth,
315 4 igrth(nf1), gbuf%EINTTH, iexpan, x,
316 5 lft, llt, jtur, igre)
317 ENDIF
318C----------------------------
319C RETURN TENSORS BACK FOR INTEGRATION.
320C----------------------------
321 CALL spback3(
322 1 gbuf%SIG,qvis, sti, cxx,
323 2 wa, ssp_eq, die, nel,
324 3 lft, llt, nft)
325C----------------------------
326 RETURN
#define my_real
Definition cppsort.cpp:32
subroutine mmain(pm, elbuf_str, ix, nix, x, geo, iparg, nel, skew, bufmat, ipart, ipartel, nummat, matparam, imat, ipm, ngl, pid, npf, tf, mfxx, mfxy, mfxz, mfyx, mfyy, mfyz, mfzx, mfzy, mfzz, rx, ry, rz, sx, sy, sz, gama, voln, dvol, s1, s2, s3, s4, s5, s6, dxx, dyy, dzz, d4, d5, d6, wxx, wyy, wzz)
Definition mmain.F:43
subroutine spback3(sig, qvis, sti, ssp, wa, ssp_eq, die, nel, lft, llt, nft)
Definition spback3.F:32
subroutine spbilan(v, partsav, nc1, eint, rho, rk, vol, vnew, ipartsp, offg, gresav, grth, igrth, eintth, iexpan, x, lft, llt, jtur, igre)
Definition spbilan.F:36
subroutine spdefo3(dxx, dxy, dxz, dyx, dyy, dyz, dzx, dzy, dzz, d4, d5, d6, wxx, wyy, wzz, nel)
Definition spdefo3.F:33
subroutine spload3(spbuf, wa, rhoa, rhon, deltax, offg, dxx, dxy, dxz, dyx, dyy, dyz, dzx, dzy, dzz, mumax, lft, llt, nft)
Definition spload3.F:34
subroutine spmallb3(offg, off, kxsp, sph2sol, lft, llt, ismstr)
Definition spmall3.F:31
subroutine spoff3(kxsp, vd2, vis, offg, off, nc1, ngl, mxt, ngeo, ipart, ipartsp, nel)
Definition spoff3.F:32
subroutine spreploc(reploc, wxx, wyy, wzz, gama, nel, lft, llt, isorth)
Definition spreploc.F:32
subroutine sptempel(kxsp, temp, tempel, lft, llt, nft)
Definition sptemp.F:793
subroutine spvol3(off, pm, volo, eint, rhoa, rhon, voln, dvol, ngl, mat, lft, llt, jlag)
Definition spvol3.F:33
subroutine srota3(sig, s1, s2, s3, s4, s5, s6, wxx, wyy, wzz, nel, mtn, ismstr)
Definition srota3.F:43
subroutine sstra3(dxx, dyy, dzz, d4, d5, d6, strain, wxx, wyy, wzz, off, nel, jcvt)
Definition sstra3.F:46