OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
r5evec3.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!|| r5evec3 ../engine/source/elements/spring/r5evec3.F
25!||--- called by ------------------------------------------------------
26!|| rforc3 ../engine/source/elements/spring/rforc3.f
27!||====================================================================
28 SUBROUTINE r5evec3(
29 1 RLOC, V, NGL, AL,
30 2 X1, Y1, Z1, X2,
31 3 Y2, Z2, EXX, EYX,
32 4 EZX, EXY, EYY, EZY,
33 5 EXZ, EYZ, EZZ, RX1,
34 6 RY1, RZ1, RX2, RY2,
35 7 RZ2, VX1, VX2, VY1,
36 8 VY2, VZ1, VZ2, NC1,
37 9 NC2, NEL)
38C-----------------------------------------------
39C I m p l i c i t T y p e s
40C-----------------------------------------------
41#include "implicit_f.inc"
42C-----------------------------------------------
43C G l o b a l P a r a m e t e r s
44C-----------------------------------------------
45#include "mvsiz_p.inc"
46C-----------------------------------------------
47C C o m m o n B l o c k s
48C-----------------------------------------------
49#include "com08_c.inc"
50C-----------------------------------------------
51C D u m m y A r g u m e n t s
52C-----------------------------------------------
53 INTEGER, INTENT(IN) :: NEL
54 INTEGER NGL(*),NC1(*),NC2(*)
55C REAL
56 my_real
57 . RLOC(6,*),V(3,*),X1(*),X2(*),Y1(*),Y2(*),
58 . Z1(*),Z2(*),
59 . EXX(MVSIZ), EYX(MVSIZ), EZX(MVSIZ),
60 . EXY(MVSIZ), EYY(MVSIZ), EZY(MVSIZ),
61 . EXZ(MVSIZ), EYZ(MVSIZ), EZZ(MVSIZ),
62 . rx1(mvsiz),rx2(mvsiz),ry1(mvsiz),
63 . ry2(mvsiz),rz1(mvsiz),rz2(mvsiz),al(mvsiz),
64 . vx1(mvsiz),vx2(mvsiz),vy1(mvsiz),vy2(mvsiz),
65 . vz1(mvsiz),vz2(mvsiz)
66C-----------------------------------------------
67C L o c a l V a r i a b l e s
68C-----------------------------------------------
69 INTEGER I,J
70C REAL
71 my_real
72 . RX(3),RXX1, RXX2, SINT(MVSIZ),
73 . SUM(MVSIZ) ,SUM2(MVSIZ), SUM3(MVSIZ) ,THETA(MVSIZ),
74 . COST(MVSIZ)
75C-----------------------------------------------
76 DO I=1,nel
77 exx(i)=(x2(i)-x1(i))
78 eyx(i)=(y2(i)-y1(i))
79 ezx(i)=(z2(i)-z1(i))
80 al(i) =sqrt(exx(i)**2+eyx(i)**2+ezx(i)**2)
81 ENDDO
82C
83 DO i=1,nel
84 IF (al(i) <= em15) THEN
85 exx(i)= one
86 eyx(i)= zero
87 ezx(i)= zero
88 exy(i)= zero
89 eyy(i)= one
90 ezy(i)= zero
91 ELSE
92 exx(i)=exx(i)/al(i)
93 eyx(i)=eyx(i)/al(i)
94 ezx(i)=ezx(i)/al(i)
95 ENDIF
96 ENDDO
97C
98 DO i=1,nel
99 exy(i)=rloc(4,i)
100 eyy(i)=rloc(5,i)
101 ezy(i)=rloc(6,i)
102 ENDDO
103C
104 DO i=1,nel
105 exz(i)=eyx(i)*ezy(i)-ezx(i)*eyy(i)
106 eyz(i)=ezx(i)*exy(i)-exx(i)*ezy(i)
107 ezz(i)=exx(i)*eyy(i)-eyx(i)*exy(i)
108 ENDDO
109C
110 DO i=1,nel
111 exy(i)=eyz(i)*ezx(i)-ezz(i)*eyx(i)
112 eyy(i)=ezz(i)*exx(i)-exz(i)*ezx(i)
113 ezy(i)=exz(i)*eyx(i)-eyz(i)*exx(i)
114 ENDDO
115C--------------------------------------------
116C TORSION MOYENNE EN COORDONNEES GLOBALES
117C--------------------------------------------
118 DO i=1,nel
119 rxx1 = exx(i)*rx1(i)+eyx(i)*ry1(i)+ezx(i)*rz1(i)
120 rxx2 = exx(i)*rx2(i)+eyx(i)*ry2(i)+ezx(i)*rz2(i)
121 theta(i) = (rxx1+rxx2)/two*dt1
122 sum2(i) = max(em15,sqrt(exy(i)**2+eyy(i)**2+ezy(i)**2))
123 sum3(i) = max(em15,sqrt(exz(i)**2+eyz(i)**2+ezz(i)**2))
124 cost(i) = cos(theta(i))/sum2(i)
125 sint(i) = sin(theta(i))/sum3(i)
126 ENDDO
127C ... it is modified.
128 DO i=1,nel
129 exy(i)= exy(i)*cost(i)+exz(i)*sint(i)
130 eyy(i)= eyy(i)*cost(i)+eyz(i)*sint(i)
131 ezy(i)= ezy(i)*cost(i)+ezz(i)*sint(i)
132 ENDDO
133C
134 DO i=1,nel
135 sum(i)=max(em15,sqrt(exy(i)**2+eyy(i)**2+ezy(i)**2))
136 exy(i)=exy(i)/sum(i)
137 eyy(i)=eyy(i)/sum(i)
138 ezy(i)=ezy(i)/sum(i)
139 ENDDO
140C
141 DO i=1,nel
142 exz(i)=eyx(i)*ezy(i)-ezx(i)*eyy(i)
143 eyz(i)=ezx(i)*exy(i)-exx(i)*ezy(i)
144 ezz(i)=exx(i)*eyy(i)-eyx(i)*exy(i)
145 ENDDO
146C
147 DO i=1,nel
148 sum(i)=max(em15,sqrt(exz(i)**2+eyz(i)**2+ezz(i)**2))
149 exz(i)=exz(i)/sum(i)
150 eyz(i)=eyz(i)/sum(i)
151 ezz(i)=ezz(i)/sum(i)
152 ENDDO
153C
154 DO i=1,nel
155 rloc(1,i) = exx(i)
156 rloc(2,i) = eyx(i)
157 rloc(3,i) = ezx(i)
158 rloc(4,i) = exy(i)
159 rloc(5,i) = eyy(i)
160 rloc(6,i) = ezy(i)
161 ENDDO
162C
163 DO i=1,nel
164 vx1(i)=v(1,nc1(i))
165 vy1(i)=v(2,nc1(i))
166 vz1(i)=v(3,nc1(i))
167 vx2(i)=v(1,nc2(i))
168 vy2(i)=v(2,nc2(i))
169 vz2(i)=v(3,nc2(i))
170 ENDDO
171C---
172 RETURN
173 END
#define max(a, b)
Definition macros.h:21
subroutine r5evec3(rloc, v, ngl, al, x1, y1, z1, x2, y2, z2, 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 r5evec3.F:38
subroutine rforc3(python, elbuf_str, jft, jlt, nel, mtn, igeo, geo, ixr, x, table, xdp, f, npf, tf, skew, flg_kj2, vr, ar, v, dt2t, neltst, ityptst, stifn, stifr, ms, in, fsky, iadr, sensors, offset, anim, partsav, ipartr, tani, fr_wave, bufmat, bufgeo, pm, rby, fx1, fx2, fy1, fy2, fz1, fz2, mx1, mx2, my1, my2, mz1, mz2, gresav, grth, igrth, msrt, dmelrt, itask, h3d_data, jsms, nft, iad, igre, preld1, stf_f, stf, sanin, iresp, impl_s, idyna, snpc)
Definition rforc3.F:104