OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
multi_unplug_neighbors.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!|| multi_unplug_neighbors ../starter/source/multifluid/multi_unplug_neighbors.F
25!||--- called by ------------------------------------------------------
26!|| lectur ../starter/source/starter/lectur.F
27!||--- calls -----------------------------------------------------
28!|| iface2 ../starter/source/ale/ale3d/iface.F
29!||--- uses -----------------------------------------------------
30!||====================================================================
31 SUBROUTINE multi_unplug_neighbors(ALE_CONNECTIVITY, IXS, IXQ, IXTG)
32C-----------------------------------------------
33C D e s c r i p t i o n
34C-----------------------------------------------
35C In the case where two elements are connected through
36C a Lagrangian face (or edge), that is to say that all nodes of
37C the shared edge are Lagrangian, there is no exchange in terms
38C of convection between this two elements : the face, or edge, has to
39C be considered as a (moving) sliding wall.
40C Hence, the neighbors in IVOIS are set to zero for corresponding faces, or edges.
41C-----------------------------------------------
42C M o d u l e s
43C-----------------------------------------------
45C-----------------------------------------------
46C I m p l i c i t T y p e s
47C-----------------------------------------------
48#include "implicit_f.inc"
49C-----------------------------------------------
50C C o m m o n B l o c k s
51C-----------------------------------------------
52C NIXS, NIXQ, NIXTG
53C NUMELS, NUMELQ, NUMELTG
54#include "com04_c.inc"
55C N2D
56#include "com01_c.inc"
57C-----------------------------------------------
58C D u m m y A r g u m e n t s
59C-----------------------------------------------
60 TYPE(t_ale_connectivity), INTENT(INOUT) :: ALE_CONNECTIVITY
61 INTEGER, INTENT(IN) :: IXS(NIXS, *), IXQ(NIXQ, *), IXTG(NIXTG, *)
62C-----------------------------------------------
63C L o c a l V a r i a b l e s
64C-----------------------------------------------
65 INTEGER :: IELEM, JELEM, KFACE, ELEM_TYPE, KFACE2, IAD, IAD2, LGTH, LGTH2
66 INTEGER :: NODELIST(8), FLAGNODE(8), INODE
67 INTEGER, DIMENSION(6, 4), TARGET :: HEXA_FACE
68 INTEGER, DIMENSION(4, 3), TARGET :: TETRA_FACE
69 INTEGER, DIMENSION(:, :), POINTER :: ELEM_FACE
70 INTEGER :: NFACE, NFACE_NODE
71 ! HEXA
72 hexa_face(1, 1) = 1
73 hexa_face(1, 2) = 2
74 hexa_face(1, 3) = 3
75 hexa_face(1, 4) = 4
76 hexa_face(2, 1) = 3
77 hexa_face(2, 2) = 4
78 hexa_face(2, 3) = 8
79 hexa_face(2, 4) = 7
80 hexa_face(3, 1) = 5
81 hexa_face(3, 2) = 6
82 hexa_face(3, 3) = 7
83 hexa_face(3, 4) = 8
84 hexa_face(4, 1) = 1
85 hexa_face(4, 2) = 2
86 hexa_face(4, 3) = 6
87 hexa_face(4, 4) = 5
88 hexa_face(5, 1) = 2
89 hexa_face(5, 2) = 3
90 hexa_face(5, 3) = 7
91 hexa_face(5, 4) = 6
92 hexa_face(6, 1) = 1
93 hexa_face(6, 2) = 4
94 hexa_face(6, 3) = 8
95 hexa_face(6, 4) = 5
96! TETRA
97 tetra_face(1, 1) = 2
98 tetra_face(1, 2) = 3
99 tetra_face(1, 3) = 7
100 tetra_face(2, 1) = 2
101 tetra_face(2, 2) = 6
102 tetra_face(2, 3) = 4
103 tetra_face(3, 1) = 4
104 tetra_face(3, 2) = 6
105 tetra_face(3, 3) = 7
106 tetra_face(4, 1) = 2
107 tetra_face(4, 2) = 7
108 tetra_face(4, 3) = 6
109 IF (n2d == 0) THEN
110C 3D case
111 DO ielem = 1, numels
112 iad = ale_connectivity%ee_connect%iad_connect(ielem)
113 lgth = ale_connectivity%ee_connect%iad_connect(ielem+1) - iad
114 nodelist(1) = ixs(2, ielem)
115 nodelist(2) = ixs(3, ielem)
116 nodelist(3) = ixs(4, ielem)
117 nodelist(4) = ixs(5, ielem)
118 nodelist(5) = ixs(6, ielem)
119 nodelist(6) = ixs(7, ielem)
120 nodelist(7) = ixs(8, ielem)
121 nodelist(8) = ixs(9, ielem)
122 flagnode(1:8) = 1
123C DEFAULT ELEM_TYPE = 1 : HEXA
124 elem_type = 1
125 nface = 6
126 nface_node = 4
127 elem_face => hexa_face
128C Test if TETRA
129 IF ((nodelist(1) == nodelist(2)) .AND.
130 . (nodelist(3) == nodelist(4)) .AND.
131 . (nodelist(6) == nodelist(7))) THEN
132 elem_type = 2
133 nface = 4
134 nface_node = 3
135 elem_face => tetra_face
136 ENDIF
137
138 DO inode = 1, 8
139 IF (ale_connectivity%NALE(nodelist(inode)) == 0) THEN
140 flagnode(inode) = 0
141 ENDIF
142 ENDDO
143
144 DO kface = 1, lgth
145 jelem = ale_connectivity%ee_connect%connected(iad + kface - 1)
146 IF (jelem > 0) THEN
147 kface2 = ale_connectivity%ee_connect%iface2(iad + kface - 1)
148 iad2 = ale_connectivity%ee_connect%iad_connect(jelem)
149 ale_connectivity%ee_connect%connected(iad2 + kface - 1) = 0
150 ale_connectivity%ee_connect%iface2(iad2 + kface - 1) = 0
151 ale_connectivity%ee_connect%connected(iad2 + kface2 - 1) = 0
152 ale_connectivity%ee_connect%iface2(iad2 + kface2 - 1) = 0
153 ENDIF
154 ENDDO
155 ENDDO
156 ELSE
157C 2D case
158 ENDIF
159 END SUBROUTINE multi_unplug_neighbors
subroutine multi_unplug_neighbors(ale_connectivity, ixs, ixq, ixtg)