OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
snorm3.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!|| snorm3 ../engine/source/multifluid/snorm3.F
25!||--- called by ------------------------------------------------------
26!|| multi_face_elem_data ../engine/source/multifluid/multi_face_data_elem.F
27!|| multi_fvm2fem ../engine/source/multifluid/multi_fvm2fem.F
28!||====================================================================
29 SUBROUTINE snorm3 (NEL, NFT, JALE, IXS, XGRID, WGRID,
30 . NORM, WFAC, SURF)
31C-----------------------------------------------
32C D e s c r i p t i o n
33C-----------------------------------------------
34C Computes normal vector to the faces of each element in a group
35C for a 3d solid element (hence Snorm3)
36C-----------------------------------------------
37C I m p l i c i t T y p e s
38C-----------------------------------------------
39#include "implicit_f.inc"
40C-----------------------------------------------
41C C o m m o n B l o c k s
42C-----------------------------------------------
43! NIXS
44C-----------------------------------------------
45C D u m m y A r g u m e n t s
46C-----------------------------------------------
47 INTEGER, INTENT(IN) :: NEL, NFT, JALE, IXS(NIXS, *)
48 my_real, INTENT(IN) ::
49 . xgrid(3, *), wgrid(*)
50 my_real, INTENT(OUT) :: wfac(3, 6, nel), surf(6, nel)
51 my_real, INTENT(OUT), TARGET :: norm(3, 6, nel)
52C-----------------------------------------------
53C L o c a l V a r i a b l e s
54C-----------------------------------------------
55 INTEGER :: II, NODE1, NODE2, NODE3, NODE4, NODE5, NODE6, NODE7, NODE8, KFACE
57 . x1(3), x2(3), x3(3), x4(3), x5(3), x6(3), x7(3), x8(3),
58 . w1(3), w2(3), w3(3), w4(3), w5(3), w6(3), w7(3), w8(3)
59 my_real, POINTER :: nx, ny, nz
60
61 DO ii = 1, nel
62C Nodes of the element locally stored in NODE* for memory access
63 node1 = ixs(2, ii + nft)
64 node2 = ixs(3, ii + nft)
65 node3 = ixs(4, ii + nft)
66 node4 = ixs(5, ii + nft)
67 node5 = ixs(6, ii + nft)
68 node6 = ixs(7, ii + nft)
69 node7 = ixs(8, ii + nft)
70 node8 = ixs(9, ii + nft)
71C Node coordinates
72 x1(1:3) = xgrid(1:3, node1)
73 x2(1:3) = xgrid(1:3, node2)
74 x3(1:3) = xgrid(1:3, node3)
75 x4(1:3) = xgrid(1:3, node4)
76 x5(1:3) = xgrid(1:3, node5)
77 x6(1:3) = xgrid(1:3, node6)
78 x7(1:3) = xgrid(1:3, node7)
79 x8(1:3) = xgrid(1:3, node8)
80 IF (jale /= 0) THEN
81C Node grid velocities
82 w1(1:3) = wgrid(3 * (node1 - 1) + 1 : 3 * (node1 - 1) + 3)
83 w2(1:3) = wgrid(3 * (node2 - 1) + 1 : 3 * (node2 - 1) + 3)
84 w3(1:3) = wgrid(3 * (node3 - 1) + 1 : 3 * (node3 - 1) + 3)
85 w4(1:3) = wgrid(3 * (node4 - 1) + 1 : 3 * (node4 - 1) + 3)
86 w5(1:3) = wgrid(3 * (node5 - 1) + 1 : 3 * (node5 - 1) + 3)
87 w6(1:3) = wgrid(3 * (node6 - 1) + 1 : 3 * (node6 - 1) + 3)
88 w7(1:3) = wgrid(3 * (node7 - 1) + 1 : 3 * (node7 - 1) + 3)
89 w8(1:3) = wgrid(3 * (node8 - 1) + 1 : 3 * (node8 - 1) + 3)
90 ELSE
91! Euler
92 w1(1:3) = zero
93 w2(1:3) = zero
94 w3(1:3) = zero
95 w4(1:3) = zero
96 w5(1:3) = zero
97 w6(1:3) = zero
98 w7(1:3) = zero
99 w8(1:3) = zero
100 ENDIF
101C Face normal
102C Face 1
103 kface = 1
104 norm(1, kface, ii) = half * ((x3(2) - x1(2)) * (x2(3) - x4(3)) -
105 . (x3(3) - x1(3)) * (x2(2) - x4(2)))
106 norm(2, kface, ii) = half * ((x3(3) - x1(3)) * (x2(1) - x4(1)) -
107 . (x3(1) - x1(1)) * (x2(3) - x4(3)))
108 norm(3, kface, ii) = half * ((x3(1) - x1(1)) * (x2(2) - x4(2)) -
109 . (x3(2) - x1(2)) * (x2(1) - x4(1)))
110 nx => norm(1, kface, ii)
111 ny => norm(2, kface, ii)
112 nz => norm(3, kface, ii)
113 surf(kface, ii) = sqrt(nx * nx + ny * ny + nz * nz)
114 nx = nx / surf(kface, ii)
115 ny = ny / surf(kface, ii)
116 nz = nz / surf(kface, ii)
117C Face 2
118 kface = 2
119 norm(1, kface, ii) = half * ((x7(2) - x4(2)) * (x3(3) - x8(3)) -
120 . (x7(3) - x4(3)) * (x3(2) - x8(2)))
121 norm(2, kface, ii) = half * ((x7(3) - x4(3)) * (x3(1) - x8(1)) -
122 . (x7(1) - x4(1)) * (x3(3) - x8(3)))
123 norm(3, kface, ii) = half * ((x7(1) - x4(1)) * (x3(2) - x8(2)) -
124 . (x7(2) - x4(2)) * (x3(1) - x8(1)))
125 nx => norm(1, kface, ii)
126 ny => norm(2, kface, ii)
127 nz => norm(3, kface, ii)
128 surf(kface, ii) = sqrt(nx * nx + ny * ny + nz * nz)
129 nx = nx / surf(kface, ii)
130 ny = ny / surf(kface, ii)
131 nz = nz / surf(kface, ii)
132C Face 3
133 kface = 3
134 norm(1, kface, ii) = half * ((x6(2) - x8(2)) * (x7(3) - x5(3)) -
135 . (x6(3) - x8(3)) * (x7(2) - x5(2)))
136 norm(2, kface, ii) = half * ((x6(3) - x8(3)) * (x7(1) - x5(1)) -
137 . (x6(1) - x8(1)) * (x7(3) - x5(3)))
138 norm(3, kface, ii) = half * ((x6(1) - x8(1)) * (x7(2) - x5(2)) -
139 . (x6(2) - x8(2)) * (x7(1) - x5(1)))
140 nx => norm(1, kface, ii)
141 ny => norm(2, kface, ii)
142 nz => norm(3, kface, ii)
143 surf(kface, ii) = sqrt(nx * nx + ny * ny + nz * nz)
144 nx = nx / surf(kface, ii)
145 ny = ny / surf(kface, ii)
146 nz = nz / surf(kface, ii)
147C Face 4
148 kface = 4
149 norm(1, kface, ii) = half * ((x2(2) - x5(2)) * (x6(3) - x1(3)) -
150 . (x2(3) - x5(3)) * (x6(2) - x1(2)))
151 norm(2, kface, ii) = half * ((x2(3) - x5(3)) * (x6(1) - x1(1)) -
152 . (x2(1) - x5(1)) * (x6(3) - x1(3)))
153 norm(3, kface, ii) = half * ((x2(1) - x5(1)) * (x6(2) - x1(2)) -
154 . (x2(2) - x5(2)) * (x6(1) - x1(1)))
155 nx => norm(1, kface, ii)
156 ny => norm(2, kface, ii)
157 nz => norm(3, kface, ii)
158 surf(kface, ii) = sqrt(nx * nx + ny * ny + nz * nz)
159 nx = nx / surf(kface, ii)
160 ny = ny / surf(kface, ii)
161 nz = nz / surf(kface, ii)
162C Face 5
163 kface = 5
164 norm(1, kface, ii) = half * ((x7(2) - x2(2)) * (x6(3) - x3(3)) -
165 . (x7(3) - x2(3)) * (x6(2) - x3(2)))
166 norm(2, kface, ii) = half * ((x7(3) - x2(3)) * (x6(1) - x3(1)) -
167 . (x7(1) - x2(1)) * (x6(3) - x3(3)))
168 norm(3, kface, ii) = half * ((x7(1) - x2(1)) * (x6(2) - x3(2)) -
169 . (x7(2) - x2(2)) * (x6(1) - x3(1)))
170 nx => norm(1, kface, ii)
171 ny => norm(2, kface, ii)
172 nz => norm(3, kface, ii)
173 surf(kface, ii) = sqrt(nx * nx + ny * ny + nz * nz)
174 nx = nx / surf(kface, ii)
175 ny = ny / surf(kface, ii)
176 nz = nz / surf(kface, ii)
177C Face 6
178 kface = 6
179 norm(1, kface, ii) = half * ((x8(2) - x1(2)) * (x4(3) - x5(3)) -
180 . (x8(3) - x1(3)) * (x4(2) - x5(2)))
181 norm(2, kface, ii) = half * ((x8(3) - x1(3)) * (x4(1) - x5(1)) -
182 . (x8(1) - x1(1)) * (x4(3) - x5(3)))
183 norm(3, kface, ii) = half * ((x8(1) - x1(1)) * (x4(2) - x5(2)) -
184 . (x8(2) - x1(2)) * (x4(1) - x5(1)))
185 nx => norm(1, kface, ii)
186 ny => norm(2, kface, ii)
187 nz => norm(3, kface, ii)
188 surf(kface, ii) = sqrt(nx * nx + ny * ny + nz * nz)
189 nx = nx / surf(kface, ii)
190 ny = ny / surf(kface, ii)
191 nz = nz / surf(kface, ii)
192C Face grid velocity 1
193 wfac(1:3, 1, ii) = fourth * (w1(1:3) + w2(1:3) + w3(1:3) + w4(1:3))
194C Face grid velocity 2
195 wfac(1:3, 2, ii) = fourth * (w3(1:3) + w4(1:3) + w8(1:3) + w7(1:3))
196C Face grid velocity 3
197 wfac(1:3, 3, ii) = fourth * (w5(1:3) + w6(1:3) + w7(1:3) + w8(1:3))
198C Face grid velocity 4
199 wfac(1:3, 4, ii) = fourth * (w1(1:3) + w2(1:3) + w6(1:3) + w5(1:3))
200C Face grid velocity 5
201 wfac(1:3, 5, ii) = fourth * (w2(1:3) + w3(1:3) + w7(1:3) + w6(1:3))
202C Face grid velocity 6
203 wfac(1:3, 6, ii) = fourth * (w1(1:3) + w4(1:3) + w8(1:3) + w5(1:3))
204 ENDDO
205 END SUBROUTINE snorm3
#define my_real
Definition cppsort.cpp:32
norm(diag(diag(diag(inv(mat))) -id.SOL), 2) % destroy mumps instance id.JOB
subroutine snorm3(nel, nft, jale, ixs, xgrid, wgrid, norm, wfac, surf)
Definition snorm3.F:31