OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
s4rcoor12.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!|| s4rcoor12 ../engine/source/elements/solid/solide4/s4rcoor12.f
25!||--- called by ------------------------------------------------------
26!|| s4forc3 ../engine/source/elements/solid/solide4/s4forc3.F
27!||--- calls -----------------------------------------------------
28!|| smortho3 ../engine/source/elements/solid/solide4/smortho3.F
29!||====================================================================
30 SUBROUTINE s4rcoor12(
31 1 OFF, NC1, NC2, NC3,
32 2 NC4, X, XDP, D,
33 3 R11, R12, R13, R21,
34 4 R22, R23, R31, R32,
35 5 R33, NEL, JCVT)
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 C o m m o n B l o c k s
46C-----------------------------------------------
47#include "scr05_c.inc"
48C-----------------------------------------------
49C D u m m y A r g u m e n t s
50C-----------------------------------------------
51 INTEGER, INTENT(IN) :: NEL
52 INTEGER, INTENT(IN) :: JCVT
53 INTEGER NC1(*), NC2(*), NC3(*), NC4(*)
54C REAL
55 my_real
56 . off(*),x(3,*),d(3,*),
57 . r11(mvsiz),r12(mvsiz),r13(mvsiz),
58 . r21(mvsiz),r22(mvsiz),r23(mvsiz),
59 . r31(mvsiz),r32(mvsiz),r33(mvsiz)
60 DOUBLE PRECISION
61 . XDP(3,*)
62C-----------------------------------------------
63C L o c a l V a r i a b l e s
64C-----------------------------------------------
65 INTEGER I
66
67 DOUBLE PRECISION
68 . X1(MVSIZ), X2(MVSIZ), X3(MVSIZ), X4(MVSIZ),
69 . Y1(MVSIZ), Y2(MVSIZ), Y3(MVSIZ), Y4(MVSIZ),
70 . z1(mvsiz), z2(mvsiz), z3(mvsiz), z4(mvsiz)
71
72C REAL
73 my_real
74 . rx(mvsiz) , ry(mvsiz) , rz(mvsiz) ,
75 . sx(mvsiz) , sy(mvsiz) , sz(mvsiz) ,
76 . tx(mvsiz) , ty(mvsiz) , tz(mvsiz)
77 my_real
78 . x41, y41, z41, x42, y42, z42, x43, y43, z43
79C=======================================================================
80C---for case of Ismstr=10-> Ismstr11 :
81C----1) config is fixed at t= t_dtmin but will not be updated like Ismstr11
82C----2) [H] = [B](t=0)*{u}, [B](t=0)<-JAC_I, {u}={d};
83C----3) in case of JCVT=0, [H] and [D] are transformed to local system and
84C- return to global system for stress
85C ---------local system compute----------
86 IF(iresp==1)THEN
87 DO i=1,nel
88 IF (off(i) <= one ) cycle
89 x1(i)=xdp(1,nc1(i))
90 y1(i)=xdp(2,nc1(i))
91 z1(i)=xdp(3,nc1(i))
92 x2(i)=xdp(1,nc2(i))
93 y2(i)=xdp(2,nc2(i))
94 z2(i)=xdp(3,nc2(i))
95 x3(i)=xdp(1,nc3(i))
96 y3(i)=xdp(2,nc3(i))
97 z3(i)=xdp(3,nc3(i))
98 x4(i)=xdp(1,nc4(i))
99 y4(i)=xdp(2,nc4(i))
100 z4(i)=xdp(3,nc4(i))
101 ENDDO
102 ELSE
103 DO i=1,nel
104 IF (off(i) <= one ) cycle
105 x1(i)=x(1,nc1(i))
106 y1(i)=x(2,nc1(i))
107 z1(i)=x(3,nc1(i))
108 x2(i)=x(1,nc2(i))
109 y2(i)=x(2,nc2(i))
110 z2(i)=x(3,nc2(i))
111 x3(i)=x(1,nc3(i))
112 y3(i)=x(2,nc3(i))
113 z3(i)=x(3,nc3(i))
114 x4(i)=x(1,nc4(i))
115 y4(i)=x(2,nc4(i))
116 z4(i)=x(3,nc4(i))
117 ENDDO
118 ENDIF
119C-----------
120C REPERE CONVECTE (ITERATIONS).
121C-----------
122 DO i=1,nel
123 IF (off(i) <= one ) cycle
124 x43 = x4(i) - x3(i)
125 y43 = y4(i) - y3(i)
126 z43 = z4(i) - z3(i)
127 x41 = x4(i) - x1(i)
128 y41 = y4(i) - y1(i)
129 z41 = z4(i) - z1(i)
130 x42 = x4(i) - x2(i)
131 y42 = y4(i) - y2(i)
132 z42 = z4(i) - z2(i)
133C
134 rx(i) = -x41
135 ry(i) = -y41
136 rz(i) = -z41
137 sx(i) = -x42
138 sy(i) = -y42
139 sz(i) = -z42
140C
141 tx(i) = -x43
142 ty(i) = -y43
143 tz(i) = -z43
144 END DO
145 CALL smortho3(
146 1 off, rx, ry, rz,
147 2 sx, sy, sz, tx,
148 3 ty, tz, r11, r12,
149 4 r13, r21, r22, r23,
150 5 r31, r32, r33, nel)
151
152C-----------
153C PASSAGE AU REPERE CONVECTE.
154C-----------
155C CALL S4RROTA3(OFF,
156C . R11, R12, R13, R21, R22, R23, R31, R32, R33,
157C . X0(I,1), X0(I,2), X0(I,3), X0(I,4),
158C . Y0(I,1), Y0(I,2), Y0(I,3), Y0(I,4),
159C . Z0(I,1), Z0(I,2), Z0(I,3), Z0(I,4))
160C CALL S4RROTA3(OFF,
161C . R11, R12, R13, R21, R22, R23, R31, R32, R33,
162C . VX0(I,1), VX0(I,2), VX0(I,3), VX0(I,4),
163C . VY0(I,1), VY0(I,2), VY0(I,3), VY0(I,4),
164C . VZ0(I,1), VZ0(I,2), VZ0(I,3), VZ0(I,4))
165C
166C-----------
167 RETURN
168 END
subroutine s4rcoor12(off, nc1, nc2, nc3, nc4, x, xdp, d, r11, r12, r13, r21, r22, r23, r31, r32, r33, nel, jcvt)
Definition s4rcoor12.F:36
subroutine smortho3(off, rx, ry, rz, sx, sy, sz, tx, ty, tz, e1x, e2x, e3x, e1y, e2y, e3y, e1z, e2z, e3z, nel)
Definition smortho3.F:35