OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
c3fint3.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!|| c3fint3 ../engine/source/elements/sh3n/coque3n/c3fint3.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 c3fint3(JFT ,JLT ,FOR ,MOM ,THK,
30 2 PX1 ,PY1 ,PY2 ,FX1 ,FX2,
31 3 FX3 ,FY1 ,FY2 ,FY3 ,FZ1,
32 4 FZ2 ,FZ3 ,MX1 ,MX2 ,MX3,
33 5 MY1 ,MY2 ,MY3 ,NEL )
34C-----------------------------------------------
35C I m p l i c i t T y p e s
36C-----------------------------------------------
37#include "implicit_f.inc"
38C-----------------------------------------------
39C G l o b a l P a r a m e t e r s
40C-----------------------------------------------
41#include "mvsiz_p.inc"
42C-----------------------------------------------
43C D u m m y A r g u m e n t s
44C-----------------------------------------------
45 INTEGER JFT, JLT, NEL
46C REAL
47 my_real
48 . FOR(NEL,5), MOM(NEL,3), THK(*),
49 . px1(*), py1(*), py2(*),
50 . fx1(mvsiz), fx2(mvsiz), fx3(mvsiz),
51 . fy1(mvsiz), fy2(mvsiz), fy3(mvsiz),
52 . fz1(mvsiz), fz2(mvsiz), fz3(mvsiz),
53 . mx1(mvsiz), mx2(mvsiz), mx3(mvsiz),
54 . my1(mvsiz), my2(mvsiz), my3(mvsiz)
55C-----------------------------------------------
56C L o c a l V a r i a b l e s
57C-----------------------------------------------
58 INTEGER I, J
59C REAL
60 my_real
61 . F1, F2, F3, F4, F5, M1, M2, M3, M4, M5, TH2
62C-----------------------------------------------
63C
64 DO i=jft,jlt
65C
66 f1 = for(i,1)*thk(i)
67 f3 = for(i,3)*thk(i)
68 fx1(i) = f1 * px1(i) + f3 * py1(i)
69 fx2(i) = -f1 * px1(i) + f3 * py2(i)
70 fx3(i) = -fx1(i) - fx2(i)
71C
72 f2 = for(i,2)*thk(i)
73 fy1(i) = f2 * py1(i) + f3 * px1(i)
74 fy2(i) = f2 * py2(i) - f3 * px1(i)
75 fy3(i) = -fy1(i) - fy2(i)
76C
77 f4 = for(i,4)*thk(i)
78 f5 = for(i,5)*thk(i)
79 fz1(i) = f5 * px1(i) + f4 * py1(i)
80 fz2(i) = -f5 * px1(i) + f4 * py2(i)
81 fz3(i) = -fz1(i) - fz2(i)
82C
83 th2 = thk(i)*thk(i)
84 m2 = mom(i,2)*th2
85 m3 = mom(i,3)*th2
86C
87 mx1(i) = -m2 * py1(i) - m3 * px1(i)
88 mx2(i) = -m2 * py2(i) + m3 * px1(i)
89 mx3(i) = -mx1(i) - mx2(i)
90C
91 m1 = mom(i,1)*th2
92 my1(i) = m1 * px1(i) + m3 * py1(i)
93 my2(i) = -m1 * px1(i) + m3 * py2(i)
94 my3(i) = -my1(i) - my2(i)
95C
96 m4 = f4 * third
97 m5 = f5 * third
98 m5 = m5 * px1(i)
99C
100 my1(i) = my1(i) + m5 * (two*py1(i)+three*py2(i))
101 . + m4 * py1(i) * (py1(i)+two*py2(i))
102 my2(i) = my2(i) + m5 * (three*py1(i)+two*py2(i))
103 . - m4 * py2(i) * (two*py1(i)+py2(i))
104 my3(i) = my3(i) + m5 * (py1(i)+py2(i))
105 . + m4 * (py2(i)**2 - py1(i)**2)
106C
107 m5 = m5 * px1(i)
108 m4 = m4 * px1(i)
109C
110 mx1(i) = mx1(i) - m5 - m4 * (two*py1(i)+py2(i))
111 mx2(i) = mx2(i) + m5 - m4 * (py1(i)+two*py2(i))
112 mx3(i) = mx3(i) - m4 * three*(py1(i)+py2(i))
113 ENDDO
114C
115 RETURN
116 END
117!||====================================================================
118!|| c3fintrz ../engine/source/elements/sh3n/coque3n/c3fint3.F
119!||--- called by ------------------------------------------------------
120!|| c3forc3 ../engine/source/elements/sh3n/coque3n/c3forc3.F
121!|| c3forc3_crk ../engine/source/elements/xfem/c3forc3_crk.F
122!||====================================================================
123 SUBROUTINE c3fintrz(JFT ,JLT ,THK ,AREA ,PX1 ,
124 2 PY1 ,PY2 ,F11 ,F12 ,F13 ,
125 3 F21 ,F22 ,F23 ,WXY ,VSTRE,
126 4 VSRZ ,VMZ ,BM0RZ,B0RZ ,BKRZ ,
127 5 BERZ ,KRZ ,RLZ ,DT1C ,EINT ,
128 6 OFF ,VOL ,NEL )
129C-----------------------------------------------
130C I M P L I C I T T Y P E S
131C-----------------------------------------------
132#include "implicit_f.inc"
133#include "mvsiz_p.inc"
134C-----------------------------------------------
135C D U M M Y A R G U M E N T S
136C-----------------------------------------------
137 INTEGER JFT ,JLT,NEL
138 my_real
139 . THK(*) ,AREA(*) ,PX1(*) ,PY1(*) ,
140 . PY2(*) ,F11(*) ,F12(*) ,F13(*) ,
141 . F21(*) ,F22(*) ,F23(*) ,WXY(*) ,
142 . VSTRE(NEL,5),VSRZ(NEL,5) ,VMZ(MVSIZ,3),
143 . BM0RZ(MVSIZ,3,2),B0RZ(MVSIZ,3),BKRZ(MVSIZ,2),BERZ(MVSIZ,2),KRZ(*),
144 . RLZ(MVSIZ,3),DT1C,EINT(NEL,2),OFF(*),VOL(*)
145C-----------------------------------------------
146c FUNCTION: strains relative to the drilling dof for Tria
147c
148c Note:
149c ARGUMENTS: (I: input, O: output, IO: input * output, W: workspace)
150c
151c TYPE NAME FUNCTION
152c I JFT,JLT - element id limit
153c I AREA,THK(NEL) - element area A, thickness
154c IO FIJ(NEL) - internal force in local system (J=1-3 node)
155c I VSTRE(NEL,5) - stress Sxx,Syy,Sxy,Syz,Sxz
156C I PX1,PY1,PX2=-PX1,PY2(NEL): standard [B] of Tria
157c O VSRZ(NEL,NG) asymmetrical stress Srz using 3of 5 places
158c O VMZ(J,NEL) -internal moment Mz(nodal) due to drilling dof
159c O BM0RZ(NEL,I,J) - constant terms of derivations for membrane
160C I=1:A*Nx,x;I=2:A*Ny,y;I=3:A*(Nx,y+Ny,x); J=1,2(node)
161C only store J=1,2 as f(j=3)=-f(j=1)-f(j=2)
162C O B0RZ(NEL,J) A*(-Nx,y+Ny,x -2Ni) for asymmetric rotation
163c O BKRZ(NEL,J) - Ksi terms of derivation : A*(-Nx,y+Ny,x -2Ni)
164c O BERZ(NEL,J) - Eta terms of derivation : A*(-Nx,y+Ny,x -2Ni)
165c I WXY(NEL) - asymmetric strain : 0.5*(-NxJ,y*VxJ+NyJ,x*VyJ)
166c I KRZ(NEL) -drilling dof modulus
167c I RLZ(NEL,J) - nodal Rz rotation velocity (J=1-3)
168c I DT1C,EINT(NEL,2) - time step and internal energy (1:membrane 2:moment)
169c I VOL,OFF(NEL) - element volume and activation flag value
170C-----------------------------------------------
171C L O C A L V A R I A B L E S
172C-----------------------------------------------
173 INTEGER I ,J ,NG,NPG
174 PARAMETER (NPG = 3)
175 my_real
176 . s1, c2, erz,off05(mvsiz),brz(mvsiz,3),vrlz(mvsiz),
177 . fx1,fx2,fy1,srzm(mvsiz),a_hammer(npg,2),a05(mvsiz),
178 . thk_6(mvsiz),bn1rz,bn2rz,bn3rz
179 DATA a_hammer /
180 1 0.166666666666667,0.666666666666667,0.166666666666667,
181 2 0.166666666666667,0.166666666666667,0.666666666666667/
182C--------------------------------c
183 DO i=jft,jlt
184 vmz(i,1)=(bm0rz(i,1,1)*vstre(i,1)+bm0rz(i,2,1)*vstre(i,2)
185 . +bm0rz(i,3,1)*vstre(i,3))*thk(i)
186 vmz(i,2)=(bm0rz(i,1,2)*vstre(i,1)+bm0rz(i,2,2)*vstre(i,2)
187 . +bm0rz(i,3,2)*vstre(i,3))*thk(i)
188 vmz(i,3)=-vmz(i,1)-vmz(i,2)
189 ENDDO
190c
191 DO i=jft,jlt
192 srzm(i)=zero
193 off05(i)=one_over_6*off(i)*vol(i)
194 a05(i)=half/area(i)
195 thk_6(i)=one_over_6*thk(i)
196 ENDDO
197C--------NxI,x *A------pay attention Bi*A--- RLZ: VRZ--
198 DO ng =1,npg
199 DO i=jft,jlt
200 bn1rz=bkrz(i,1)*a_hammer(ng,1)+berz(i,1)*a_hammer(ng,2)
201 bn2rz=bkrz(i,2)*a_hammer(ng,1)+berz(i,2)*a_hammer(ng,2)
202 bn3rz=-bn1rz-bn2rz
203 brz(i,1)=b0rz(i,1)+bn1rz
204 brz(i,2)=b0rz(i,2)+bn2rz
205 brz(i,3)=b0rz(i,3)+bn3rz
206 vrlz(i)= wxy(i)+(brz(i,1)*rlz(i,1)+
207 1 brz(i,2)*rlz(i,2)+brz(i,3)*rlz(i,3))*a05(i)
208 ENDDO
209 DO i=jft,jlt
210 erz= vrlz(i)*dt1c
211 eint(i,1) = eint(i,1)+ vsrz(i,ng)*erz*off05(i)
212 vsrz(i,ng)= vsrz(i,ng)+krz(i)*erz*off(i)
213 eint(i,1) = eint(i,1)+ vsrz(i,ng)*erz*off05(i)
214 srzm(i)=srzm(i)+vsrz(i,ng)
215 ENDDO
216C
217 DO j=1,3
218 DO i=jft,jlt
219 c2=thk_6(i)*vsrz(i,ng)
220 vmz(i,j)= vmz(i,j)+brz(i,j)*c2
221 ENDDO
222 ENDDO
223 END DO !NG =1,NPG
224C-------------------------------------------------
225C constant part PX2=-PX1
226C-------------------------------------------------
227 DO i=jft,jlt
228 c2=thk(i)*srzm(i)*one_over_6
229 fx1=-c2*py1(i)
230 fx2=-c2*py2(i)
231C
232 f11(i) = f11(i) + fx1
233 f12(i) = f12(i) + fx2
234 f13(i) = f13(i) - fx1 - fx2
235C
236 fy1=c2*px1(i)
237 f21(i) = f21(i) + fy1
238 f22(i) = f22(i) - fy1
239C F23(I) = F23(I) - FY1
240 ENDDO
241C
242 RETURN
243 END
subroutine c3fint3(jft, jlt, for, mom, thk, px1, py1, py2, fx1, fx2, fx3, fy1, fy2, fy3, fz1, fz2, fz3, mx1, mx2, mx3, my1, my2, my3, nel)
Definition c3fint3.F:34
subroutine c3fintrz(jft, jlt, thk, area, px1, py1, py2, f11, f12, f13, f21, f22, f23, wxy, vstre, vsrz, vmz, bm0rz, b0rz, bkrz, berz, krz, rlz, dt1c, eint, off, vol, nel)
Definition c3fint3.F:129