OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
czstra3.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!|| czstra3 ../engine/source/elements/shell/coquez/czstra3.f
25!||--- called by ------------------------------------------------------
26!|| czforc3 ../engine/source/elements/shell/coquez/czforc3.F
27!|| czforc3_crk ../engine/source/elements/xfem/czforc3_crk.F
28!||====================================================================
29 SUBROUTINE czstra3(JFT ,JLT ,NFT ,VDEF ,GSTR ,
30 2 EXX ,EYY ,EXY ,EXZ ,EYZ ,
31 3 KXX ,KYY ,KXY ,DT1C ,EPSDOT,
32 4 IEPSDOT,ISTRAIN,UX1 ,UX2 ,UX3 ,
33 5 UX4 ,UY1 ,UY2 ,UY3 ,UY4 ,
34 6 PX1 ,PX2 ,PY1 ,PY2 ,AREA ,
35 7 ISMSTR ,MTN ,WXY ,F_DEF ,GSTRW ,
36 8 NEL )
37C-----------------------------------------------
38C I m p l i c i t T y p e s
39C-----------------------------------------------
40#include "implicit_f.inc"
41C-----------------------------------------------
42C G l o b a l P a r a m e t e r s
43C-----------------------------------------------
44#include "mvsiz_p.inc"
45C-----------------------------------------------
46C D u m m y A r g u m e n t s
47C-----------------------------------------------
48 INTEGER JFT, JLT, NFT, IEPSDOT, ISTRAIN, ISMSTR, MTN,NEL
49 my_real
50 . VDEF(MVSIZ,8), GSTR(NEL,8),
51 . EXX(MVSIZ),EYY(MVSIZ),EXY(MVSIZ),EXZ(MVSIZ),EYZ(MVSIZ),
52 . KXX(MVSIZ),KYY(MVSIZ),KXY(MVSIZ),DT1C(MVSIZ),EPSDOT(6,*),
53 . UX1(*),UX2(*),UX3(*),UX4(*),UY1(*),UY2(*),UY3(*),UY4(*),
54 . PX1(*),PX2(*),PY1(*),PY2(*),AREA(*),F_DEF(MVSIZ,8),WXY(*),GSTRW(*)
55C-----------------------------------------------
56C L o c a l V a r i a b l e s
57C-----------------------------------------------
58 INTEGER I, J
59 my_real
60 . FAC1(MVSIZ),UX13,UX24,UY13,UY24,
61 . EXXT,EYYT,EXYT
62C---+----1----+----2----+----3----+----4----+----5----+----6----+----7--
63C
64 IF(IEPSDOT/=0)then
65 DO i=jft,jlt
66 j = i + nft
67 epsdot(1,j) = vdef(i,1)
68 epsdot(2,j) = vdef(i,2)
69 epsdot(3,j) = vdef(i,3)
70 epsdot(4,j) = vdef(i,6)
71 epsdot(5,j) = vdef(i,7)
72 epsdot(6,j) = vdef(i,8)
73 ENDDO
74 ENDIF
75C
76 DO i=jft,jlt
77 exx(i) = vdef(i,1) * dt1c(i)
78 eyy(i) = vdef(i,2) * dt1c(i)
79 exy(i) = vdef(i,3) * dt1c(i)
80 eyz(i) = vdef(i,5) * dt1c(i)
81 exz(i) = vdef(i,4) * dt1c(i)
82 kxx(i) = vdef(i,6) * dt1c(i)
83 kyy(i) = vdef(i,7) * dt1c(i)
84 kxy(i) = vdef(i,8) * dt1c(i)
85 ENDDO
86C
87 IF (istrain /= 0.OR.ismstr == 10) THEN
88 IF(ismstr == 10)THEN
89 DO i=jft,jlt
90 gstr(i,1)=gstr(i,1)+exx(i)
91 gstr(i,2)=gstr(i,2)+eyy(i)
92 gstr(i,3)=gstr(i,3)+exy(i)
93 gstr(i,4)=gstr(i,4)+eyz(i)
94 gstr(i,5)=gstr(i,5)+exz(i)
95 gstr(i,6)=gstr(i,6)+kxx(i)
96 gstr(i,7)=gstr(i,7)+kyy(i)
97 gstr(i,8)=gstr(i,8)+kxy(i)
98C-------- WXY
99 gstrw(i)=gstrw(i)+wxy(i)*dt1c(i)
100 ENDDO
101C-----
102 DO i=jft,jlt
103 f_def(i,6) = gstr(i,6)
104 f_def(i,7) = gstr(i,7)
105 f_def(i,8) = (gstr(i,8)+gstrw(i))*half
106 f_def(i,5) = (gstr(i,8)-gstrw(i))*half
107 ENDDO
108 ELSEIF(ismstr /= 11)THEN
109 DO i=jft,jlt
110 gstr(i,1)=gstr(i,1)+exx(i)
111 gstr(i,2)=gstr(i,2)+eyy(i)
112 gstr(i,3)=gstr(i,3)+exy(i)
113 gstr(i,4)=gstr(i,4)+eyz(i)
114 gstr(i,5)=gstr(i,5)+exz(i)
115 gstr(i,6)=gstr(i,6)+kxx(i)
116 gstr(i,7)=gstr(i,7)+kyy(i)
117 gstr(i,8)=gstr(i,8)+kxy(i)
118 ENDDO
119 ELSE
120 DO i=jft,jlt
121 fac1(i) =one/area(i)
122 ux13=ux1(i)-ux3(i)
123 ux24=ux2(i)-ux4(i)
124 uy13=uy1(i)-uy3(i)
125 uy24=uy2(i)-uy4(i)
126 exxt=(px1(i)*ux13+px2(i)*ux24)*fac1(i)
127 eyyt=(py1(i)*uy13+py2(i)*uy24)*fac1(i)
128 exyt=(py1(i)*ux13+py2(i)*ux24
129 . +px1(i)*uy13+px2(i)*uy24)*fac1(i)
130 gstr(i,1)=exxt
131 gstr(i,2)=eyyt
132 gstr(i,3)=exyt
133 gstr(i,4)=gstr(i,4)+eyz(i)
134 gstr(i,5)=gstr(i,5)+exz(i)
135 gstr(i,6)=gstr(i,6)+kxx(i)
136 gstr(i,7)=gstr(i,7)+kyy(i)
137 gstr(i,8)=gstr(i,8)+kxy(i)
138 ENDDO
139 ENDIF
140 ENDIF
141C
142 RETURN
143 END
subroutine czstra3(jft, jlt, nft, vdef, gstr, exx, eyy, exy, exz, eyz, kxx, kyy, kxy, dt1c, epsdot, iepsdot, istrain, ux1, ux2, ux3, ux4, uy1, uy2, uy3, uy4, px1, px2, py1, py2, area, ismstr, mtn, wxy, f_def, gstrw, nel)
Definition czstra3.F:37