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