OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
c3stra3.F
Go to the documentation of this file.
1Copyright> OpenRadioss
2Copyright> Copyright (C) 1986-2025 Altair Engineering Inc.
3Copyright>
4Copyright> This program is free software: you can redistribute it and/or modify
5Copyright> it under the terms of the GNU Affero General Public License as published by
6Copyright> the Free Software Foundation, either version 3 of the License, or
7Copyright> (at your option) any later version.
8Copyright>
9Copyright> This program is distributed in the hope that it will be useful,
10Copyright> but WITHOUT ANY WARRANTY; without even the implied warranty of
11Copyright> MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12Copyright> GNU Affero General Public License for more details.
13Copyright>
14Copyright> You should have received a copy of the GNU Affero General Public License
15Copyright> along with this program. If not, see <https://www.gnu.org/licenses/>.
16Copyright>
17Copyright>
18Copyright> Commercial Alternative: Altair Radioss Software
19Copyright>
20Copyright> As an alternative to this open-source version, Altair also offers Altair Radioss
21Copyright> software under a commercial license. Contact Altair to discuss further if the
22Copyright> commercial version may interest you: https://www.altair.com/radioss/.
23!||====================================================================
24!|| c3stra3 ../engine/source/elements/sh3n/coque3n/c3stra3.F
25!||--- called by ------------------------------------------------------
26!|| c3forc3 ../engine/source/elements/sh3n/coque3n/c3forc3.F
27!|| c3forc3_crk ../engine/source/elements/xfem/c3forc3_crk.F
28!||====================================================================
29 SUBROUTINE c3stra3(JFT ,JLT ,PM ,
30 2 MAT ,AREA ,EXX ,EYY ,EXY ,
31 3 EXZ ,EYZ ,KXX ,KYY ,KXY ,
32 4 GEO ,PID ,NU ,SHF ,GSTR ,
33 5 SSP ,RHO ,EPSDOT ,
34 6 NFT ,ISTRAIN ,ISMSTR ,
35 7 UX1 ,UX2 ,UX3 ,UY1 ,UY2 ,
36 8 UY3 ,PX1 ,PY1 ,PY2 ,MTN ,
37 9 F_DEF ,WXY ,GSTRW ,NEL )
38C-----------------------------------------------
39C I m p l i c i t T y p e s
40C-----------------------------------------------
41#include "implicit_f.inc"
42C-----------------------------------------------
43C G l o b a l P a r a m e t e r s
44C-----------------------------------------------
45#include "mvsiz_p.inc"
46C-----------------------------------------------
47C C o m m o n B l o c k s
48C-----------------------------------------------
49#include "scr14_c.inc"
50#include "param_c.inc"
51#include "com08_c.inc"
52C-----------------------------------------------
53C D u m m y A r g u m e n t s
54C-----------------------------------------------
55 INTEGER JFT, JLT,NFT,ISTRAIN,ISMSTR,NEL
56 INTEGER MAT(MVSIZ),PID(MVSIZ),MTN
57C REAL
58 my_real
59 . GSTR(NEL,8), PM(NPROPM,*),GEO(NPROPG,*),
60 . AREA(MVSIZ),SHF(MVSIZ),
61 . EXX(MVSIZ), EYY(MVSIZ), EXY(MVSIZ), EXZ(MVSIZ), EYZ(MVSIZ),
62 . KXX(MVSIZ), KYY(MVSIZ), KXY(MVSIZ),NU(MVSIZ),SSP(*),RHO(*),
63 . epsdot(6,*),
64 . ux1(*),ux2(*),ux3(*),uy1(*),uy2(*),uy3(*),
65 . px1(*),py1(*),py2(*),wxy(*),f_def(mvsiz,*),gstrw(*)
66 my_real
67 . ux12,ux13,ux23,uy13,uy23,exxt,eyyt,exyt
68C-----------------------------------------------
69C L o c a l V a r i a b l e s
70C-----------------------------------------------
71 INTEGER ISH(MVSIZ),
72 . I, MX, J
73C REAL
74 my_real
75 . fsh(mvsiz),
76 . thk2 ,fac1, fac2, fc1p
77C---+----1----+----2----+----3----+----4----+----5----+----6----+----7--
78C
79 IF(iepsdot/=0)THEN
80 DO i=jft,jlt
81 fac1 =one/area(i)
82 j = i + nft
83 epsdot(1,j)=exx(i)*fac1
84 epsdot(2,j)=eyy(i)*fac1
85 epsdot(3,j)=exy(i)*fac1
86 epsdot(4,j)=kxx(i)*fac1
87 epsdot(5,j)=kyy(i)*fac1
88 epsdot(6,j)=kxy(i)*fac1
89 ENDDO
90 ENDIF
91C
92 DO i=jft,jlt
93 fac1 =dt1/area(i)
94 exx(i)=exx(i)*fac1
95 eyy(i)=eyy(i)*fac1
96 exy(i)=exy(i)*fac1
97 eyz(i)=eyz(i)*fac1
98 exz(i)=exz(i)*fac1
99 kxx(i)=kxx(i)*fac1
100 kyy(i)=kyy(i)*fac1
101 kxy(i)=kxy(i)*fac1
102 ENDDO
103C
104 IF (istrain /= 0.OR.ismstr == 10) THEN
105 IF(ismstr == 10)THEN
106 DO i=jft,jlt
107 gstr(i,1)=gstr(i,1)+exx(i)
108 gstr(i,2)=gstr(i,2)+eyy(i)
109 gstr(i,3)=gstr(i,3)+exy(i)
110 gstr(i,4)=gstr(i,4)+eyz(i)
111 gstr(i,5)=gstr(i,5)+exz(i)
112 gstr(i,6)=gstr(i,6)+kxx(i)
113 gstr(i,7)=gstr(i,7)+kyy(i)
114 gstr(i,8)=gstr(i,8)+kxy(i)
115C-------- WXY
116 gstrw(i)=gstrw(i)+wxy(i)*dt1/area(i)
117 ENDDO
118C-----
119 DO i=jft,jlt
120 f_def(i,6) = gstr(i,6)
121 f_def(i,7) = gstr(i,7)
122 f_def(i,8) = (gstr(i,8)+gstrw(i))*half
123 f_def(i,5) = (gstr(i,8)-gstrw(i))*half
124 ENDDO
125 ELSEIF (ismstr /= 11 ) THEN
126 DO i=jft,jlt
127 gstr(i,1)=gstr(i,1)+exx(i)
128 gstr(i,2)=gstr(i,2)+eyy(i)
129 gstr(i,3)=gstr(i,3)+exy(i)
130 gstr(i,4)=gstr(i,4)+eyz(i)
131 gstr(i,5)=gstr(i,5)+exz(i)
132 gstr(i,6)=gstr(i,6)+kxx(i)
133 gstr(i,7)=gstr(i,7)+kyy(i)
134 gstr(i,8)=gstr(i,8)+kxy(i)
135 ENDDO
136 ELSE
137 DO i=jft,jlt
138 fac1 =one/area(i)
139 ux12=ux1(i)-ux2(i)
140 ux13=ux1(i)-ux3(i)
141 ux23=ux2(i)-ux3(i)
142 uy13=uy1(i)-uy3(i)
143 uy23=uy2(i)-uy3(i)
144 exxt= px1(i)*ux12*fac1
145 eyyt=(py1(i)*uy13+py2(i)*uy23)*fac1
146 exyt=(py1(i)*ux13+py2(i)*ux23)*fac1
147 gstr(i,1)=exxt
148 gstr(i,2)=eyyt
149 gstr(i,3)=exyt
150 gstr(i,4)=gstr(i,4)+eyz(i)
151 gstr(i,5)=gstr(i,5)+exz(i)
152 gstr(i,6)=gstr(i,6)+kxx(i)
153 gstr(i,7)=gstr(i,7)+kyy(i)
154 gstr(i,8)=gstr(i,8)+kxy(i)
155 ENDDO
156 ENDIF
157 ENDIF
158C-----------
159 RETURN
160 END
subroutine c3stra3(jft, jlt, pm, mat, area, exx, eyy, exy, exz, eyz, kxx, kyy, kxy, geo, pid, nu, shf, gstr, ssp, rho, epsdot, nft, istrain, ismstr, ux1, ux2, ux3, uy1, uy2, uy3, px1, py1, py2, mtn, f_def, wxy, gstrw, nel)
Definition c3stra3.F:38