OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
i8dis3.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!|| i8dis3 ../engine/source/interfaces/inter3d/i8dis3.F
25!||--- called by ------------------------------------------------------
26!|| intvo8 ../engine/source/interfaces/inter3d/intvo8.F
27!||====================================================================
28 SUBROUTINE i8dis3(
29 1 IGIMP, NTY, DIST, X1,
30 2 Y1, Z1, X2, Y2,
31 3 Z2, X3, Y3, Z3,
32 4 X4, Y4, Z4, XI,
33 5 YI, ZI, XP, YP,
34 6 ZP, N1, N2, N3,
35 7 ANS, SSC, TTC, H1,
36 8 H2, H3, H4, XFACE,
37 9 ALP, LFT, LLT)
38
39C-----------------------------------------------
40C I m p l i c i t T y p e s
41C-----------------------------------------------
42#include "implicit_f.inc"
43C-----------------------------------------------
44C D u m m y A r g u m e n t s
45C-----------------------------------------------
46 INTEGER, INTENT(INOUT) :: LFT
47 INTEGER, INTENT(INOUT) :: LLT
48 INTEGER IGIMP,NTY
49 my_real DIST(*)
50 my_real
51 . X1(*), X2(*), X3(*), X4(*), Y1(*), Y2(*), Y3(*), Y4(*),
52 . Z1(*), Z2(*), Z3(*), Z4(*), XI(*), YI(*), ZI(*), XP(*), YP(*),
53 . ZP(*), ANS(*), ALP(*), N1(*), N2(*), N3(*), SSC(*), TTC(*),
54 . XFACE(*), H1(*), H2(*), H3(*), H4(*)
55
56C-----------------------------------------------
57C C o m m o n B l o c k s
58C-----------------------------------------------
59C-----------------------------------------------
60C L o c a l V a r i a b l e s
61C-----------------------------------------------
62 INTEGER I
63C REAL
64C-----------------------------------------------
65C=======================================================================
66 DO I=lft,llt
67 h1(i) = zero
68 h2(i) = zero
69 h3(i) = zero
70 h4(i) = zero
71 xp(i) = zero
72 yp(i) = zero
73 zp(i) = zero
74 ans(i) = zero
75 dist(i) = zero
76
77
78 IF (xface(i) == zero) cycle
79 IF (abs(ssc(i))>one+alp(i) .OR. abs(ttc(i))>one+alp(i)) THEN
80 xface(i)=zero
81 ELSE
82 IF(abs(ssc(i)) > one) ssc(i)=ssc(i)/abs(ssc(i))
83 IF(abs(ttc(i)) > one) ttc(i)=ttc(i)/abs(ttc(i))
84 ENDIF
85 END DO
86C
87 DO i=lft,llt
88 h1(i) = fourth*(one-ttc(i))*(one-ssc(i))
89 h2(i) = fourth*(one-ttc(i))*(one+ssc(i))
90 h3(i) = fourth*(one+ttc(i))*(one+ssc(i))
91 h4(i) = fourth*(one+ttc(i))*(one-ssc(i))
92 END DO
93C
94 DO i=lft,llt
95 xp(i)=h1(i)*x1(i)+h2(i)*x2(i)+h3(i)*x3(i)+h4(i)*x4(i)
96 yp(i)=h1(i)*y1(i)+h2(i)*y2(i)+h3(i)*y3(i)+h4(i)*y4(i)
97 zp(i)=h1(i)*z1(i)+h2(i)*z2(i)+h3(i)*z3(i)+h4(i)*z4(i)
98 END DO
99C
100 DO i=lft,llt
101 ans(i)= n1(i)*(xi(i)-xp(i))
102 . +n2(i)*(yi(i)-yp(i))
103 . +n3(i)*(zi(i)-zp(i))
104 END DO
105 IF (nty == 8) THEN
106 DO i=lft,llt
107 dist(i) = ans(i)
108 ENDDO
109 ENDIF
110C-----------
111 RETURN
112 END
subroutine i8dis3(igimp, nty, dist, x1, y1, z1, x2, y2, z2, x3, y3, z3, x4, y4, z4, xi, yi, zi, xp, yp, zp, n1, n2, n3, ans, ssc, ttc, h1, h2, h3, h4, xface, alp, lft, llt)
Definition i8dis3.F:38