OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
cbastra3.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!|| cbastra3 ../engine/source/elements/shell/coqueba/cbastra3.F
25!||--- called by ------------------------------------------------------
26!|| cbaforc3 ../engine/source/elements/shell/coqueba/cbaforc3.F
27!||====================================================================
28 SUBROUTINE cbastra3(GSTR,GSTRPG,
29 1 JFT, JLT, NFT, NPG,VDEF,
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 X13, X24, Y13, Y24, BM ,
35 7 ISMSTR ,MTN ,NPLAT,IPLAT,ISROT,
36 8 WXY ,F_DEF,GSTRWPG,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, NPG,II,NEL
49 INTEGER ISMSTR ,MTN ,NPLAT,IPLAT(*),ISROT
50 my_real
51 . VDEF(MVSIZ,8),GSTR(NEL,8),GSTRPG(NEL,8),DT1C(*),EPSDOT(6,*),
52 . EXX(*),EYY(*),EXY(*),EXZ(*),EYZ(*),KXX(*),KYY(*),KXY(*),
53 . UX1(*),UX2(*),UX3(*),UX4(*),UY1(*),UY2(*),UY3(*),UY4(*),
54 . X13(*), X24(*), Y13(*), Y24(*), BM(MVSIZ,36),F_DEF(MVSIZ,8),
55 . WXY(*),GSTRWPG(*)
56C-----------------------------------------------
57C L o c a l V a r i a b l e s
58C-----------------------------------------------
59 INTEGER I, J,EP
60 my_real
61 . UX13,UX24,UY13,UY24,UXHI,UYHI,QUATRE1,
62 . EXXT(MVSIZ),EYYT(MVSIZ),EXYT(MVSIZ)
63C---+----1----+----2----+----3----+----4----+----5----+----6----+----7--
64C
65 QUATRE1 = one/npg
66 IF (iepsdot /= 0) THEN
67 DO i=jft,jlt
68 j = i + nft
69 epsdot(1,j) = vdef(i,1)
70 epsdot(2,j) = vdef(i,2)
71 epsdot(3,j) = vdef(i,3)
72 epsdot(4,j) = vdef(i,6)
73 epsdot(5,j) = vdef(i,7)
74 epsdot(6,j) = vdef(i,8)
75 ENDDO
76 ENDIF
77C
78 DO i=jft,jlt
79 exx(i) = vdef(i,1) * dt1c(i)
80 eyy(i) = vdef(i,2) * dt1c(i)
81 exy(i) = vdef(i,3) * dt1c(i)
82 eyz(i) = vdef(i,5) * dt1c(i)
83 exz(i) = vdef(i,4) * dt1c(i)
84 kxx(i) = vdef(i,6) * dt1c(i)
85 kyy(i) = vdef(i,7) * dt1c(i)
86 kxy(i) = vdef(i,8) * dt1c(i)
87 ENDDO
88C
89 IF (istrain /= 0.OR.ismstr == 10) THEN
90 IF(ismstr == 10)THEN
91 DO i=jft,jlt
92 gstr(i,1)=gstr(i,1)+exx(i)*quatre1
93 gstr(i,2)=gstr(i,2)+eyy(i)*quatre1
94 gstr(i,3)=gstr(i,3)+exy(i)*quatre1
95 gstr(i,4)=gstr(i,4)+eyz(i)*quatre1
96 gstr(i,5)=gstr(i,5)+exz(i)*quatre1
97 gstr(i,6)=gstr(i,6)+kxx(i)*quatre1
98 gstr(i,7)=gstr(i,7)+kyy(i)*quatre1
99 gstr(i,8)=gstr(i,8)+kxy(i)*quatre1
100C
101 gstrpg(i,1)=gstrpg(i,1)+exx(i)
102 gstrpg(i,2)=gstrpg(i,2)+eyy(i)
103 gstrpg(i,3)=gstrpg(i,3)+exy(i)
104 gstrpg(i,4)=gstrpg(i,4)+eyz(i)
105 gstrpg(i,5)=gstrpg(i,5)+exz(i)
106 gstrpg(i,6)=gstrpg(i,6)+kxx(i)
107 gstrpg(i,7)=gstrpg(i,7)+kyy(i)
108 gstrpg(i,8)=gstrpg(i,8)+kxy(i)
109C
110 gstrwpg(i)=gstrwpg(i)+wxy(i)* dt1c(i)
111 ENDDO
112C----- use ISTRAIN temporarily for KXX.. cumulated
113 DO i=jft,jlt
114 f_def(i,6) = gstrpg(i,6)
115 f_def(i,7) = gstrpg(i,7)
116 f_def(i,8) = (gstrpg(i,8)+gstrwpg(i))*half
117 f_def(i,5) = (gstrpg(i,8)-gstrwpg(i))*half
118 ENDDO
119 ELSEIF(ismstr /= 11)THEN
120 DO i=jft,jlt
121 gstr(i,1)=gstr(i,1)+exx(i)*quatre1
122 gstr(i,2)=gstr(i,2)+eyy(i)*quatre1
123 gstr(i,3)=gstr(i,3)+exy(i)*quatre1
124 gstr(i,4)=gstr(i,4)+eyz(i)*quatre1
125 gstr(i,5)=gstr(i,5)+exz(i)*quatre1
126 gstr(i,6)=gstr(i,6)+kxx(i)*quatre1
127 gstr(i,7)=gstr(i,7)+kyy(i)*quatre1
128 gstr(i,8)=gstr(i,8)+kxy(i)*quatre1
129C
130 gstrpg(i,1)=gstrpg(i,1)+exx(i)
131 gstrpg(i,2)=gstrpg(i,2)+eyy(i)
132 gstrpg(i,3)=gstrpg(i,3)+exy(i)
133 gstrpg(i,4)=gstrpg(i,4)+eyz(i)
134 gstrpg(i,5)=gstrpg(i,5)+exz(i)
135 gstrpg(i,6)=gstrpg(i,6)+kxx(i)
136 gstrpg(i,7)=gstrpg(i,7)+kyy(i)
137 gstrpg(i,8)=gstrpg(i,8)+kxy(i)
138 ENDDO
139 ELSE
140 IF (isrot > 0) THEN
141#include "vectorize.inc"
142 DO ep=jft,nplat
143 i=iplat(ep)
144 ux13=ux1(i)-ux3(i)
145 ux24=ux2(i)-ux4(i)
146 uy13=uy1(i)-uy3(i)
147 uy24=uy2(i)-uy4(i)
148 uxhi=ux1(i)-ux2(i)+ux3(i)-ux4(i)
149 uyhi=uy1(i)-uy2(i)+uy3(i)-uy4(i)
150 exxt(i)=bm(i,1)*ux13+bm(i,2)*ux24+bm(i,3)*uxhi
151 eyyt(i)=bm(i,5)*uy13+bm(i,6)*uy24+bm(i,7)*uyhi
152 exyt(i)=bm(i,1)*uy13+bm(i,2)*uy24+bm(i,3)*uyhi
153 . +bm(i,5)*ux13+bm(i,6)*ux24+bm(i,7)*uxhi
154 END DO
155#include "vectorize.inc"
156 DO ep=nplat+1,jlt
157 i=iplat(ep)
158 exxt(i)=bm(i,1)*ux1(i)+bm(i,4)*uy1(i)
159 . +bm(i,10)*ux2(i)+bm(i,13)*uy2(i)
160 . +bm(i,19)*ux3(i)+bm(i,22)*uy3(i)
161 . +bm(i,28)*ux4(i)+bm(i,31)*uy4(i)
162 eyyt(i)=bm(i,2)*ux1(i)+bm(i,5)*uy1(i)
163 . +bm(i,11)*ux2(i)+bm(i,14)*uy2(i)
164 . +bm(i,20)*ux3(i)+bm(i,23)*uy3(i)
165 . +bm(i,29)*ux4(i)+bm(i,32)*uy4(i)
166 exyt(i)=bm(i,3)*ux1(i)+bm(i,6)*uy1(i)
167 . +bm(i,12)*ux2(i)+bm(i,15)*uy2(i)
168 . +bm(i,21)*ux3(i)+bm(i,24)*uy3(i)
169 . +bm(i,30)*ux4(i)+bm(i,33)*uy4(i)
170 END DO
171 ELSE
172#include "vectorize.inc"
173 DO ep=jft,nplat
174 i=iplat(ep)
175 ux13=ux1(i)-ux3(i)
176 ux24=ux2(i)-ux4(i)
177 uy13=uy1(i)-uy3(i)
178 uy24=uy2(i)-uy4(i)
179 uxhi=ux1(i)-ux2(i)+ux3(i)-ux4(i)
180 uyhi=uy1(i)-uy2(i)+uy3(i)-uy4(i)
181 exxt(i)=bm(i,1)*ux13+bm(i,2)*ux24+bm(i,3)*uxhi
182 eyyt(i)=bm(i,5)*uy13+bm(i,6)*uy24+bm(i,7)*uyhi
183 exyt(i)=y24(i)*uy13-y13(i)*uy24
184 . -x24(i)*ux13+x13(i)*ux24
185 END DO
186#include "vectorize.inc"
187 DO ep=nplat+1,jlt
188 i=iplat(ep)
189 ux13=ux1(i)-ux3(i)
190 ux24=ux2(i)-ux4(i)
191 uy13=uy1(i)-uy3(i)
192 uy24=uy2(i)-uy4(i)
193 exxt(i)=bm(i,1)*ux1(i)+bm(i,4)*uy1(i)
194 . +bm(i,10)*ux2(i)+bm(i,13)*uy2(i)
195 . +bm(i,19)*ux3(i)+bm(i,22)*uy3(i)
196 . +bm(i,28)*ux4(i)+bm(i,31)*uy4(i)
197 eyyt(i)=bm(i,2)*ux1(i)+bm(i,5)*uy1(i)
198 . +bm(i,11)*ux2(i)+bm(i,14)*uy2(i)
199 . +bm(i,20)*ux3(i)+bm(i,23)*uy3(i)
200 . +bm(i,29)*ux4(i)+bm(i,32)*uy4(i)
201 exyt(i)=y24(i)*uy13-y13(i)*uy24
202 . -x24(i)*ux13+x13(i)*ux24
203 END DO
204 END IF !(ISROT > 0) THEN
205 DO i=jft,jlt
206 gstr(i,1)=gstr(i,1)+exxt(i)*quatre1
207 gstr(i,2)=gstr(i,2)+eyyt(i)*quatre1
208 gstr(i,3)=gstr(i,3)+exyt(i)*quatre1
209 gstr(i,4)=gstr(i,4)+eyz(i)*quatre1
210 gstr(i,5)=gstr(i,5)+exz(i)*quatre1
211 gstr(i,6)=gstr(i,6)+kxx(i)*quatre1
212 gstr(i,7)=gstr(i,7)+kyy(i)*quatre1
213 gstr(i,8)=gstr(i,8)+kxy(i)*quatre1
214C
215 gstrpg(i,1)=exxt(i)
216 gstrpg(i,2)=eyyt(i)
217 gstrpg(i,3)=exyt(i)
218 gstrpg(i,4)=gstrpg(i,4)+eyz(i)
219 gstrpg(i,5)=gstrpg(i,5)+exz(i)
220 gstrpg(i,6)=gstrpg(i,6)+kxx(i)
221 gstrpg(i,7)=gstrpg(i,7)+kyy(i)
222 gstrpg(i,8)=gstrpg(i,8)+kxy(i)
223 ENDDO
224 ENDIF !IF(ISMSTR /= 11)
225 ENDIF !IF(ISTRAIN /= 0)
226c-----------
227 RETURN
228 END
subroutine cbastra3(gstr, gstrpg, jft, jlt, nft, npg, vdef, exx, eyy, exy, exz, eyz, kxx, kyy, kxy, dt1c, epsdot, iepsdot, istrain, ux1, ux2, ux3, ux4, uy1, uy2, uy3, uy4, x13, x24, y13, y24, bm, ismstr, mtn, nplat, iplat, isrot, wxy, f_def, gstrwpg, nel)
Definition cbastra3.F:37