OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
r5def3.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!|| r5def3 ../engine/source/elements/spring/r5def3.F
25!||--- called by ------------------------------------------------------
26!|| rforc3 ../engine/source/elements/spring/rforc3.F
27!||====================================================================
28 SUBROUTINE r5def3(
29 1 XL, VX2L, RY1L, RZ1L,
30 2 RX2L, RY2L, RZ2L, FR_WAVE,
31 3 FR_W_E, EINT, FX, XMOM,
32 4 YMOM, ZMOM, FY, FZ,
33 5 PARTSAV, IPARTR, EXX, EYX,
34 6 EZX, EXY, EYY, EZY,
35 7 EXZ, EYZ, EZZ, RX1,
36 8 RY1, RZ1, RX2, RY2,
37 9 RZ2, VX1, VX2, VY1,
38 A VY2, VZ1, VZ2, NC1,
39 B NC2, NEL)
40C-----------------------------------------------
41C I m p l i c i t T y p e s
42C-----------------------------------------------
43#include "implicit_f.inc"
44C-----------------------------------------------
45C G l o b a l P a r a m e t e r s
46C-----------------------------------------------
47#include "mvsiz_p.inc"
48C-----------------------------------------------
49C C o m m o n B l o c k s
50C-----------------------------------------------
51#include "com01_c.inc"
52#include "com08_c.inc"
53#include "param_c.inc"
54C-----------------------------------------------
55C D u m m y A r g u m e n t s
56C-----------------------------------------------
57 INTEGER, INTENT(IN) :: NEL
58 INTEGER IPARTR(*),NC1(*),NC2(*)
59C REAL
60 my_real
61 . XL(*), VX2L(*),RY1L(*), RZ1L(*), RX2L(*), RY2L(*), RZ2L(*),
62 . FR_WAVE(*) ,FR_W_E(*),EINT(*) ,
63 . FX(*), FY(*), FZ(*), XMOM(*), YMOM(*),ZMOM(*),PARTSAV(NPSAV,*),
64 . EXX(MVSIZ), EYX(MVSIZ), EZX(MVSIZ),
65 . EXY(MVSIZ), EYY(MVSIZ), EZY(MVSIZ),
66 . EXZ(MVSIZ), EYZ(MVSIZ), EZZ(MVSIZ), RX1(MVSIZ), RX2(MVSIZ),
67 . RY1(MVSIZ), RY2(MVSIZ), RZ1(MVSIZ), RZ2(MVSIZ), VX1(MVSIZ),
68 . vx2(mvsiz), vy1(mvsiz), vy2(mvsiz), vz1(mvsiz), vz2(mvsiz)
69C-----------------------------------------------
70C L o c a l V a r i a b l e s
71C-----------------------------------------------
72 INTEGER I,MX
73C REAL
74 my_real
75 . VX1L, VY1L, VY2L, VZ1L, VZ2L,THETA , XLDEMI,XSIGN
76C-----------------------------------------------
77C--------------------------------------------
78C VITESSES REPERE CONVECTEE
79C--------------------------------------------
80 DO I=1,nel
81 rx2l(i) = exx(i)*(rx2(i)-rx1(i))
82 . + eyx(i)*(ry2(i)-ry1(i))
83 . + ezx(i)*(rz2(i)-rz1(i))
84 ry1l(i) = exy(i)*rx1(i)+eyy(i)*ry1(i)+ezy(i)*rz1(i)
85 ry2l(i) = exy(i)*rx2(i)+eyy(i)*ry2(i)+ezy(i)*rz2(i)
86 rz1l(i) = exz(i)*rx1(i)+eyz(i)*ry1(i)+ezz(i)*rz1(i)
87 rz2l(i) = exz(i)*rx2(i)+eyz(i)*ry2(i)+ezz(i)*rz2(i)
88 vx2l(i) = exx(i)*(vx2(i)-vx1(i))
89 . + eyx(i)*(vy2(i)-vy1(i))
90 . + ezx(i)*(vz2(i)-vz1(i))
91 vy2l = exy(i)*(vx2(i)-vx1(i))
92 . + eyy(i)*(vy2(i)-vy1(i))
93 . + ezy(i)*(vz2(i)-vz1(i))
94 xsign = sign(one, xl(i) - half*vx2l(i)*dt1)
95 xldemi = xsign/max(em15,abs(xl(i) - half*vx2l(i)*dt1))
96 theta = vy2l * xldemi
97 rz1l(i) = rz1l(i) - theta
98 rz2l(i) = rz2l(i) - theta
99 vz2l = exz(i)*(vx2(i)-vx1(i))
100 . + eyz(i)*(vy2(i)-vy1(i))
101 . + ezz(i)*(vz2(i)-vz1(i))
102 theta = vz2l * xldemi
103 ry1l(i) = ry1l(i) + theta
104 ry2l(i) = ry2l(i) + theta
105 vx2l(i) = vx2l(i)
106 . - half*dt1*xldemi*(vy2l*vy2l+vz2l*vz2l)
107 ENDDO
108C--------------------------------------------
109C Energy
110C--------------------------------------------
111 DO i=1,nel
112 eint(i) = eint(i)
113 .+ half*dt1 * (vx2l(i) * fx(i) + rx2l(i) * xmom(i)
114 . + (ry2l(i) - ry1l(i)) * ymom(i)
115 . + (rz2l(i) - rz1l(i)) * zmom(i)
116 . + half * (ry2l(i) + ry1l(i)) * fz(i) * xl(i)
117 . - half * (rz2l(i) + rz1l(i)) * fy(i) * xl(i) )
118 ENDDO
119C
120 IF (npsav >= 21) THEN
121 DO i=1,nel
122 mx = ipartr(i)
123 partsav(23,mx)=partsav(23,mx)
124 . + half*dt1 * (rx2l(i) * xmom(i)
125 . + (ry2l(i) - ry1l(i)) * ymom(i)
126 . + (rz2l(i) - rz1l(i)) * zmom(i)
127 . + half * (ry2l(i) + ry1l(i)) * fz(i) * xl(i)
128 . - half * (rz2l(i) + rz1l(i)) * fy(i) * xl(i) )
129 ENDDO
130 ENDIF
131C--------------------------------------------
132C Front wave
133C--------------------------------------------
134 IF (ifrwv /= 0) THEN
135 DO i=1,nel
136 fr_w_e(i)=max(fr_wave(nc1(i)),fr_wave(nc2(i)),zero)
137 ENDDO
138 ENDIF
139C---
140 RETURN
141 END
#define max(a, b)
Definition macros.h:21
subroutine r5def3(xl, vx2l, ry1l, rz1l, rx2l, ry2l, rz2l, fr_wave, fr_w_e, eint, fx, xmom, ymom, zmom, fy, fz, partsav, ipartr, exx, eyx, ezx, exy, eyy, ezy, exz, eyz, ezz, rx1, ry1, rz1, rx2, ry2, rz2, vx1, vx2, vy1, vy2, vz1, vz2, nc1, nc2, nel)
Definition r5def3.F:40