OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
in_out_side.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!|| in_out_side ../starter/source/initial_conditions/inivol/in_out_side.F
25!||--- called by ------------------------------------------------------
26!|| phase_detection ../starter/source/initial_conditions/inivol/phase_detection.F
27!|| ratio_fill ../starter/source/initial_conditions/inivol/ratio_fill.F
28!||--- calls -----------------------------------------------------
29!|| nfacette ../starter/source/initial_conditions/inivol/nfacette.F
30!||====================================================================
31 SUBROUTINE in_out_side(
32 . INOD ,INOD2SURF ,KNOD2SURF ,NNOD2SURF ,X ,
33 . XN ,DIST ,NSEG ,SURF_ELTYP,NOD_NORMAL,
34 . SURF_NODES,SWIFTSURF ,IDSURF ,SEGTOSURF )
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#include "com04_c.inc"
43C-----------------------------------------------
44C D u m m y A r g u m e n t s
45C-----------------------------------------------
46 INTEGER INOD,KNOD2SURF(*),NNOD2SURF,
47 . INOD2SURF(NNOD2SURF,*),NSEG,SURF_ELTYP(NSEG),
48 . SURF_NODES(NSEG,4),SWIFTSURF(NSURF),IDSURF,SEGTOSURF(*)
50 . x(3,*),xn(3),dist,
51 . nod_normal(3,*),xfas(3,4)
52C-----------------------------------------------
53C L o c a l V a r i a b l e s
54C-----------------------------------------------
55 INTEGER I,K,OK,FAC,FAC1,FAC2,NULL_DIST,
56 . IPL,IXPL(4),
57 . p,r,p1,p2,dd1(4),dd2(4),ddd1(3),ddd2(3),ITYP,SH_ELEM,ISURF
59 . dist_pl(3),vx_nod_inod,vy_nod_inod,vz_nod_inod,xsign(3),
60 . v1x,v1y,v1z,v2x,v2y,v2z,v3x,v3y,v3z,v12x,v12y,v12z,dot,
61 . nx,ny,nz
62 DATA dd1/4,1,2,3/,dd2/2,3,4,1/,ddd1/3,1,2/,ddd2/2,3,1/
63C-----------------------------------------------
64 ok = 0
65 null_dist = 0
66 DO 60 k=1,knod2surf(inod)
67 ipl = inod2surf(k,inod)
68 isurf = segtosurf(ipl)
69 IF (isurf /= idsurf) GOTO 60
70 ipl = ipl - swiftsurf(isurf)
71 IF (ipl <= 0 .OR. ipl > nseg .OR. inod > numnod) GOTO 60
72 ityp = surf_eltyp(ipl)
73!
74 IF(ityp==3)THEN
75 ixpl(1) = surf_nodes(ipl,1)
76 ixpl(2) = surf_nodes(ipl,2)
77 ixpl(3) = surf_nodes(ipl,3)
78 ixpl(4) = surf_nodes(ipl,4)
79 ELSEIF(ityp==7)THEN
80 ixpl(1) = surf_nodes(ipl,1)
81 ixpl(2) = surf_nodes(ipl,2)
82 ixpl(3) = surf_nodes(ipl,3)
83 ixpl(4) = surf_nodes(ipl,3)
84 ENDIF
85C---
86 p = 0
87C---
88 IF(ityp==3)THEN
89 DO r=1,4
90 IF(inod == ixpl(r))THEN
91 p = r
92 EXIT
93 ENDIF
94 ENDDO
95 ELSEIF(ityp==7)THEN
96 DO r=1,3
97 IF(inod == ixpl(r))THEN
98 p = r
99 EXIT
100 ENDIF
101 ENDDO
102 ENDIF
103C
104 IF(p == 0)GOTO 60
105C
106 IF(ityp==3)THEN
107 p1 = dd1(p)
108 p2 = dd2(p)
109 ELSEIF(ityp==7)THEN
110 p1 = ddd1(p)
111 p2 = ddd2(p)
112 ENDIF
113C
114 xfas(1,1) = x(1,ixpl(1))
115 xfas(2,1) = x(2,ixpl(1))
116 xfas(3,1) = x(3,ixpl(1))
117 xfas(1,2) = x(1,ixpl(2))
118 xfas(2,2) = x(2,ixpl(2))
119 xfas(3,2) = x(3,ixpl(2))
120 xfas(1,3) = x(1,ixpl(3))
121 xfas(2,3) = x(2,ixpl(3))
122 xfas(3,3) = x(3,ixpl(3))
123 xfas(1,4) = x(1,ixpl(4))
124 xfas(2,4) = x(2,ixpl(4))
125 xfas(3,4) = x(3,ixpl(4))
126C
127 CALL nfacette(xfas,nx,ny,nz)
128C
129 dist_pl(1:3) = zero
130C vect NOD --> INOD
131 vx_nod_inod = xn(1) - x(1,inod)
132 vy_nod_inod = xn(2) - x(2,inod)
133 vz_nod_inod = xn(3) - x(3,inod)
134C PLANE 1
135C V1xV2
136 v12x = nx
137 v12y = ny
138 v12z = nz
139C dist of N to plane 1
140 dot = vx_nod_inod*v12x+vy_nod_inod*v12y+vz_nod_inod*v12z
141 dist_pl(1) = dot
142C PLANE 2
143C V_NOR x V1
144 v1x = nod_normal(1,inod)
145 v1y = nod_normal(2,inod)
146 v1z = nod_normal(3,inod)
147 v2x = xfas(1,p)-xfas(1,p1)
148 v2y = xfas(2,p)-xfas(2,p1)
149 v2z = xfas(3,p)-xfas(3,p1)
150 v12x = v1y*v2z-v1z*v2y
151 v12y = v1z*v2x-v1x*v2z
152 v12z = v1x*v2y-v1y*v2x
153C dist of N to plane 2
154 dot = vx_nod_inod*v12x+vy_nod_inod*v12y+vz_nod_inod*v12z
155 dist_pl(2) = dot
156C PLANE 3
157C V_NOR x V2
158 v1x = nod_normal(1,inod)
159 v1y = nod_normal(2,inod)
160 v1z = nod_normal(3,inod)
161 v2x = xfas(1,p2)-xfas(1,p)
162 v2y = xfas(2,p2)-xfas(2,p)
163 v2z = xfas(3,p2)-xfas(3,p)
164 v12x = v1y*v2z-v1z*v2y
165 v12y = v1z*v2x-v1x*v2z
166 v12z = v1x*v2y-v1y*v2x
167C dist of N to plane 3
168 dot = vx_nod_inod*v12x+vy_nod_inod*v12y+vz_nod_inod*v12z
169 dist_pl(3) = dot
170C---
171 DO r=1,3
172 xsign(r) = sign(one,dist_pl(r))
173 IF(dist_pl(r) == zero)xsign(r) = one !ZERO
174 ENDDO
175 fac1 = 0
176 fac2 = 0
177C
178 IF(null_dist == 1)EXIT
179C
180 DO r=1,3
181 IF(xsign(r) >= zero)THEN
182 fac1 = fac1 + 1
183 ENDIF
184 ENDDO
185 IF(fac1 == 3)THEN
186 dist = one
187 ok = ok + 1
188 ENDIF
189 IF(ok > 0)EXIT
190C---
191 60 CONTINUE
192C---
193c IF(NULL_DIST == 1) DIST = ZERO
194 IF(ok == 0) dist = -one ! external node
195 IF(null_dist == 1) dist = zero
196C-----------------------------------------------
197 RETURN
198 END
#define my_real
Definition cppsort.cpp:32
subroutine in_out_side(inod, inod2surf, knod2surf, nnod2surf, x, xn, dist, nseg, surf_eltyp, nod_normal, surf_nodes, swiftsurf, idsurf, segtosurf)
Definition in_out_side.F:35
subroutine nfacette(xfas, nx, ny, nz)
Definition nfacette.F:30