OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
s10defo3.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!|| s10defo3 ../engine/source/elements/solid/solide10/s10defo3.F
25!||--- called by ------------------------------------------------------
26!|| s10forc3 ../engine/source/elements/solid/solide10/s10forc3.F
27!||====================================================================
28 SUBROUTINE s10defo3(
29 1 PX, PY, PZ, VX,
30 2 VY, VZ, DXX, DXY,
31 3 DXZ, DYX, DYY, DYZ,
32 4 DZX, DZY, DZZ, D4,
33 5 D5, D6, WXX, WYY,
34 6 WZZ, VOLP, VOLN, RHO,
35 7 RHOO, NEL, JHBE, ISROT)
36C-----------------------------------------------
37C I m p l i c i t T y p e s
38C-----------------------------------------------
39#include "implicit_f.inc"
40C-----------------------------------------------
41C G l o b a l P a r a m e t e r s
42C-----------------------------------------------
43#include "mvsiz_p.inc"
44C-----------------------------------------------
45C D u m m y A r g u m e n t s
46C-----------------------------------------------
47 INTEGER, INTENT(IN) :: NEL
48 INTEGER, INTENT(IN) :: JHBE
49 INTEGER, INTENT(IN) :: ISROT
50C REAL
51 my_real
52 . VX(MVSIZ,10),VY(MVSIZ,10),VZ(MVSIZ,10),
53 . PX(MVSIZ,10),PY(MVSIZ,10),PZ(MVSIZ,10),
54 . dxx(*), dxy(*), dxz(*),
55 . dyx(*), dyy(*), dyz(*),
56 . dzx(*), dzy(*), dzz(*), d4(*), d5(*), d6(*),
57 . wxx(*), wyy(*), wzz(*),volp(*),voln(*),rho(*),
58 . rhoo(*)
59C-----------------------------------------------
60C C o m m o n B l o c k s
61C-----------------------------------------------
62#include "com08_c.inc"
63C-----------------------------------------------
64C L o c a l V a r i a b l e s
65C-----------------------------------------------
66 INTEGER I,N
67C REAL
68 my_real
69 . DT1D2
70 my_real
71 . PXX2,PYY2,PZZ2,PXX2P,PYY2P,PZZ2P,AAA,BBB
72C-----------------------------------------------
73C
74 IF(isrot /= 1)THEN
75 DO i=1,nel
76 voln(i)=volp(i)
77 rhoo(i)=rho(i)
78 ENDDO
79 ELSE
80 DO i=1,nel
81c VOLN(I)=VOLP(I)
82 rhoo(i)=rho(i)
83 ENDDO
84 ENDIF
85 DO i=1,nel
86 dxx(i)=px(i,1)*vx(i,1)+px(i,2)*vx(i,2)+px(i,3)*vx(i,3)+px(i,4)*vx(i,4)+px(i,5)*vx(i,5)
87 . +px(i,6)*vx(i,6)+px(i,7)*vx(i,7)+px(i,8)*vx(i,8)+px(i,9)*vx(i,9)+px(i,10)*vx(i,10)
88 dyy(i)=py(i,1)*vy(i,1)+py(i,2)*vy(i,2)+py(i,3)*vy(i,3)+py(i,4)*vy(i,4)+py(i,5)*vy(i,5)
89 . +py(i,6)*vy(i,6)+py(i,7)*vy(i,7)+py(i,8)*vy(i,8)+py(i,9)*vy(i,9)+py(i,10)*vy(i,10)
90 dzz(i)=pz(i,1)*vz(i,1)+pz(i,2)*vz(i,2)+pz(i,3)*vz(i,3)+pz(i,4)*vz(i,4)+pz(i,5)*vz(i,5)
91 . +pz(i,6)*vz(i,6)+pz(i,7)*vz(i,7)+pz(i,8)*vz(i,8)+pz(i,9)*vz(i,9)+pz(i,10)*vz(i,10)
92 dxy(i)=py(i,1)*vx(i,1)+py(i,2)*vx(i,2)+py(i,3)*vx(i,3)+py(i,4)*vx(i,4)+py(i,5)*vx(i,5)
93 . +py(i,6)*vx(i,6)+py(i,7)*vx(i,7)+py(i,8)*vx(i,8)+py(i,9)*vx(i,9)+py(i,10)*vx(i,10)
94 dxz(i)=pz(i,1)*vx(i,1)+pz(i,2)*vx(i,2)+pz(i,3)*vx(i,3)+pz(i,4)*vx(i,4)+pz(i,5)*vx(i,5)
95 . +pz(i,6)*vx(i,6)+pz(i,7)*vx(i,7)+pz(i,8)*vx(i,8)+pz(i,9)*vx(i,9)+pz(i,10)*vx(i,10)
96 dyx(i)=px(i,1)*vy(i,1)+px(i,2)*vy(i,2)+px(i,3)*vy(i,3)+px(i,4)*vy(i,4)+px(i,5)*vy(i,5)
97 . +px(i,6)*vy(i,6)+px(i,7)*vy(i,7)+px(i,8)*vy(i,8)+px(i,9)*vy(i,9)+px(i,10)*vy(i,10)
98 dyz(i)=pz(i,1)*vy(i,1)+pz(i,2)*vy(i,2)+pz(i,3)*vy(i,3)+pz(i,4)*vy(i,4)+pz(i,5)*vy(i,5)
99 . +pz(i,6)*vy(i,6)+pz(i,7)*vy(i,7)+pz(i,8)*vy(i,8)+pz(i,9)*vy(i,9)+pz(i,10)*vy(i,10)
100 dzx(i)=px(i,1)*vz(i,1)+px(i,2)*vz(i,2)+px(i,3)*vz(i,3)+px(i,4)*vz(i,4)+px(i,5)*vz(i,5)
101 . +px(i,6)*vz(i,6)+px(i,7)*vz(i,7)+px(i,8)*vz(i,8)+px(i,9)*vz(i,9)+px(i,10)*vz(i,10)
102 dzy(i)=py(i,1)*vz(i,1)+py(i,2)*vz(i,2)+py(i,3)*vz(i,3)+py(i,4)*vz(i,4)+py(i,5)*vz(i,5)
103 . +py(i,6)*vz(i,6)+py(i,7)*vz(i,7)+py(i,8)*vz(i,8)+py(i,9)*vz(i,9)+py(i,10)*vz(i,10)
104 ENDDO
105C
106 dt1d2=half*dt1
107C
108 IF(jhbe>=2)THEN
109 DO i=1,nel
110 dxx(i) = dxx(i)
111 . -dt1d2*(dxx(i)*dxx(i)+dyx(i)*dyx(i)+dzx(i)*dzx(i))
112 dyy(i) = dyy(i)
113 . -dt1d2*(dyy(i)*dyy(i)+dzy(i)*dzy(i)+dxy(i)*dxy(i))
114 dzz(i) = dzz(i)
115 . -dt1d2*(dzz(i)*dzz(i)+dxz(i)*dxz(i)+dyz(i)*dyz(i))
116 aaa = dt1d2*(dxx(i)*dxy(i)+dyx(i)*dyy(i)+dzx(i)*dzy(i))
117 dxy(i) = dxy(i) - aaa
118 dyx(i) = dyx(i) - aaa
119 d4(i) = dxy(i)+dyx(i)
120 aaa = dt1d2*(dyy(i)*dyz(i)+dzy(i)*dzz(i)+dxy(i)*dxz(i))
121 dyz(i) = dyz(i) - aaa
122 dzy(i) = dzy(i) - aaa
123 d5(i) = dyz(i)+dzy(i)
124 aaa = dt1d2*(dzz(i)*dzx(i)+dxz(i)*dxx(i)+dyz(i)*dyx(i))
125 dxz(i) = dxz(i) - aaa
126 dzx(i) = dzx(i) - aaa
127 d6(i) = dxz(i)+dzx(i)
128!
129 n = 1
130 pxx2 = px(i,n)*px(i,n)
131 pyy2 = py(i,n)*py(i,n)
132 pzz2 = pz(i,n)*pz(i,n)
133 DO n=2,10
134 pxx2 = pxx2+px(i,n)*px(i,n)
135 pyy2 = pyy2+py(i,n)*py(i,n)
136 pzz2 = pzz2+pz(i,n)*pz(i,n)
137 END DO
138 wzz(i)=dt1*(pyy2*dyx(i)-pxx2*dxy(i))/(pxx2+pyy2)
139 wxx(i)=dt1*(pzz2*dzy(i)-pyy2*dyz(i))/(pyy2+pzz2)
140 wyy(i)=dt1*(pxx2*dxz(i)-pzz2*dzx(i))/(pzz2+pxx2)
141 ENDDO
142 ELSE !IF(JHBE>=2)
143 DO i=1,nel
144 d4(i) =dxy(i)+dyx(i)
145 d5(i) =dyz(i)+dzy(i)
146 d6(i) =dxz(i)+dzx(i)
147 wzz(i)=dt1d2*(dyx(i)-dxy(i))
148 wyy(i)=dt1d2*(dxz(i)-dzx(i))
149 wxx(i)=dt1d2*(dzy(i)-dyz(i))
150 ENDDO
151 END IF
152C
153 RETURN
154C
155 END
subroutine s10defo3(px, py, pz, vx, vy, vz, dxx, dxy, dxz, dyx, dyy, dyz, dzx, dzy, dzz, d4, d5, d6, wxx, wyy, wzz, volp, voln, rho, rhoo, nel, jhbe, isrot)
Definition s10defo3.F:36