OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
qnorm2.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!|| qnorm2 ../engine/source/multifluid/qnorm2.F
25!||--- called by ------------------------------------------------------
26!|| multi_face_elem_data ../engine/source/multifluid/multi_face_data_elem.F
27!||====================================================================
28 SUBROUTINE qnorm2 (NEL, NFT, JALE, SYM, IXQ, XGRID, WGRID,
29 . NORM, WFAC, SURF)
30C-----------------------------------------------
31C D e s c r i p t i o n
32C-----------------------------------------------
33C Computes normal vector to the faces of each element in a group
34C for a 3d solid element (hence Snorm3)
35C-----------------------------------------------
36C I m p l i c i t T y p e s
37C-----------------------------------------------
38#include "implicit_f.inc"
39C-----------------------------------------------
40C C o m m o n B l o c k s
41C-----------------------------------------------
42! NIXQ
43C-----------------------------------------------
44C D u m m y A r g u m e n t s
45C-----------------------------------------------
46 INTEGER, INTENT(IN) :: NEL, NFT, JALE, SYM, IXQ(NIXQ, *)
47 my_real, INTENT(IN) ::
48 . xgrid(3, *), wgrid(*)
49 my_real, INTENT(OUT) :: wfac(3, 4, nel), surf(4, nel)
50 my_real, INTENT(OUT), TARGET :: norm(3, 4, nel)
51C-----------------------------------------------
52C L o c a l V a r i a b l e s
53C-----------------------------------------------
54 INTEGER :: II, NODE1, NODE2, NODE3, NODE4, KFACE
55 my_real ::
56 . x1(3), x2(3), x3(3), x4(3),
57 . w1(3), w2(3), w3(3), w4(3)
58 my_real, POINTER :: ny, nz
59
60
61 DO ii = 1, nel
62 node1 = ixq(2, ii + nft)
63 node2 = ixq(3, ii + nft)
64 node3 = ixq(4, ii + nft)
65 node4 = ixq(5, ii + nft)
66 x1(1:3) = xgrid(1:3, node1)
67 x2(1:3) = xgrid(1:3, node2)
68 x3(1:3) = xgrid(1:3, node3)
69 x4(1:3) = xgrid(1:3, node4)
70 IF (jale /= 0) THEN
71C Node grid velocities
72 w1(1:3) = wgrid(3 * (node1 - 1) + 1 : 3 * (node1 - 1) + 3)
73 w2(1:3) = wgrid(3 * (node2 - 1) + 1 : 3 * (node2 - 1) + 3)
74 w3(1:3) = wgrid(3 * (node3 - 1) + 1 : 3 * (node3 - 1) + 3)
75 w4(1:3) = wgrid(3 * (node4 - 1) + 1 : 3 * (node4 - 1) + 3)
76 ELSE ! Euler
77 w1(1:3) = zero
78 w2(1:3) = zero
79 w3(1:3) = zero
80 w4(1:3) = zero
81 ENDIF
82C Face normal
83C Face 1
84 kface = 1
85 norm(1, kface, ii) = zero
86 norm(2, kface, ii) = x2(3) - x1(3)
87 norm(3, kface, ii) = -(x2(2) - x1(2))
88 ny => norm(2, kface, ii)
89 nz => norm(3, kface, ii)
90 surf(kface, ii) = sqrt(ny * ny + nz * nz)
91 ny = ny / surf(kface, ii)
92 nz = nz / surf(kface, ii)
93 IF (sym == 1) THEN
94 surf(kface, ii) = surf(kface, ii) * half * (x1(2) + x2(2))
95 ENDIF
96C Face 2
97 kface = 2
98 norm(1, kface, ii) = zero
99 norm(2, kface, ii) = x3(3) - x2(3)
100 norm(3, kface, ii) = -(x3(2) - x2(2))
101 ny => norm(2, kface, ii)
102 nz => norm(3, kface, ii)
103 surf(kface, ii) = sqrt(ny * ny + nz * nz)
104 ny = ny / surf(kface, ii)
105 nz = nz / surf(kface, ii)
106 IF (sym == 1) THEN
107 surf(kface, ii) = surf(kface, ii) * half * (x2(2) + x3(2))
108 ENDIF
109C Face 3
110 kface = 3
111 norm(1, kface, ii) = zero
112 norm(2, kface, ii) = x4(3) - x3(3)
113 norm(3, kface, ii) = -(x4(2) - x3(2))
114 ny => norm(2, kface, ii)
115 nz => norm(3, kface, ii)
116 surf(kface, ii) = sqrt(ny * ny + nz * nz)
117 ny = ny / surf(kface, ii)
118 nz = nz / surf(kface, ii)
119 IF (sym == 1) THEN
120 surf(kface, ii) = surf(kface, ii) * half * (x3(2) + x4(2))
121 ENDIF
122C Face 4
123 kface = 4
124 norm(1, kface, ii) = zero
125 norm(2, kface, ii) = x1(3) - x4(3)
126 norm(3, kface, ii) = -(x1(2) - x4(2))
127 ny => norm(2, kface, ii)
128 nz => norm(3, kface, ii)
129 surf(kface, ii) = sqrt(ny * ny + nz * nz)
130 ny = ny / surf(kface, ii)
131 nz = nz / surf(kface, ii)
132 IF (sym == 1) THEN
133 surf(kface, ii) = surf(kface, ii) * half * (x4(2) + x1(2))
134 ENDIF
135C Face grid velocity 1
136 wfac(1:3, 1, ii) = half * (w1(1:3) + w2(1:3))
137C Face grid velocity 2
138 wfac(1:3, 2, ii) = half * (w2(1:3) + w3(1:3))
139C Face grid velocity 3
140 wfac(1:3, 3, ii) = half * (w3(1:3) + w4(1:3))
141C Face grid velocity 4
142 wfac(1:3, 4, ii) = half * (w4(1:3) + w1(1:3))
143 ENDDO
144 END SUBROUTINE qnorm2
#define my_real
Definition cppsort.cpp:32
norm(diag(diag(diag(inv(mat))) -id.SOL), 2) % destroy mumps instance id.JOB
subroutine qnorm2(nel, nft, jale, sym, ixq, xgrid, wgrid, norm, wfac, surf)
Definition qnorm2.F:30