OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
i12cor3.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!|| i12cor3 ../engine/source/interfaces/inter3d/i12cor3.F
25!||--- called by ------------------------------------------------------
26!|| intti12a ../engine/source/interfaces/interf/intti12.F
27!||====================================================================
28 SUBROUTINE i12cor3(
29 1 XS, XM, IRECT, MSR,
30 2 IRTL, ILEV, X, TETS,
31 3 IX1, IX2, IX3, IX4,
32 4 X1, X2, X3, X4,
33 5 XI, Y1, Y2, Y3,
34 6 Y4, YI, Z1, Z2,
35 7 Z3, Z4, ZI, XFACE,
36 8 LFT, LLT, NFT)
37C-----------------------------------------------
38C I m p l i c i t T y p e s
39C-----------------------------------------------
40#include "implicit_f.inc"
41C-----------------------------------------------
42C G l o b a l P a r a m e t e r s
43C-----------------------------------------------
44#include "mvsiz_p.inc"
45C-----------------------------------------------
46C D u m m y A r g u m e n t s
47C-----------------------------------------------
48 INTEGER, INTENT(INOUT) :: LFT
49 INTEGER, INTENT(INOUT) :: LLT
50 INTEGER, INTENT(INOUT) :: NFT
51 INTEGER IRECT(4,*), MSR(*), IRTL(*),ILEV
52 my_real
53 . XS(3,*),XM(3,*),X(3,*),TETS(*)
54 INTEGER, DIMENSION(MVSIZ), INTENT(OUT) :: IX1,IX2,IX3,IX4
55 my_real, DIMENSION(MVSIZ), INTENT(OUT) :: X1,X2,X3,X4,XI
56 my_real, DIMENSION(MVSIZ), INTENT(OUT) :: y1,y2,y3,y4,yi
57 my_real, DIMENSION(MVSIZ), INTENT(OUT) :: z1,z2,z3,z4,zi
58 my_real, DIMENSION(MVSIZ), INTENT(OUT) :: xface
59C-----------------------------------------------
60C C o m m o n B l o c k s
61C-----------------------------------------------
62C-----------------------------------------------
63C L o c a l V a r i a b l e s
64C-----------------------------------------------
65 INTEGER I, IL, IG, L, NN
66 my_real
67 . deupi,tetmin,tetmax,rmin
68C-----------------------------------------------
69
70 deupi=two*pi
71
72 DO i=lft,llt
73 xface(i)=one
74 il=i+nft
75 l=irtl(il)
76
77 xi(i)=xs(1,il)
78 yi(i)=xs(2,il)
79 zi(i)=xs(3,il)
80
81 nn=irect(1,l)
82 ix1(i)=msr(nn)
83 x1(i)=xm(1,nn)
84 y1(i)=xm(2,nn)
85 z1(i)=xm(3,nn)
86
87 nn=irect(2,l)
88 ix2(i)=msr(nn)
89 x2(i)=xm(1,nn)
90 y2(i)=xm(2,nn)
91 z2(i)=xm(3,nn)
92
93 nn=irect(3,l)
94 ix3(i)=msr(nn)
95 x3(i)=xm(1,nn)
96 y3(i)=xm(2,nn)
97 z3(i)=xm(3,nn)
98
99 nn=irect(4,l)
100 ix4(i)=msr(nn)
101 x4(i)=xm(1,nn)
102 y4(i)=xm(2,nn)
103 z4(i)=xm(3,nn)
104 ENDDO
105
106 IF(ilev==1)THEN
107 !--------------------------------------------------!
108 ! CORRECTION DES TET SI A CHEVAL AXE Y NEGATIF !
109 !--------------------------------------------------!
110 DO i=lft,llt
111 tetmin=min(z1(i),z2(i),z3(i),z4(i),zi(i))
112 tetmax=max(z1(i),z2(i),z3(i),z4(i),zi(i))
113 IF(tetmax-tetmin >= pi)THEN
114 IF(z1(i)<zero)z1(i)=z1(i)+deupi
115 IF(z2(i)<zero)z2(i)=z2(i)+deupi
116 IF(z3(i)<zero)z3(i)=z3(i)+deupi
117 IF(z4(i)<zero)z4(i)=z4(i)+deupi
118 IF(zi(i)<zero)zi(i)=zi(i)+deupi
119 ENDIF
120 ENDDO
121
122 !--------------------------------------------------!
123 ! CAS D'UNE FACETTE CENTRALE !
124 !--------------------------------------------------!
125 DO i=lft,llt
126 rmin=min(y1(i),y2(i),y3(i),y4(i))
127 IF(yi(i)<rmin)THEN
128 tetmin=min(z1(i),z2(i),z3(i),z4(i))
129 tetmax=max(z1(i),z2(i),z3(i),z4(i))
130 IF(tetmax-tetmin >= pi)THEN
131 il=i+nft
132 l=irtl(il)
133 nn=msr(irect(1,l))
134 ix1(i)=nn
135 x1(i)=x(1,nn)
136 y1(i)=x(2,nn)
137 z1(i)=x(3,nn)
138
139 nn=msr(irect(2,l))
140 ix2(i)=nn
141 x2(i)=x(1,nn)
142 y2(i)=x(2,nn)
143 z2(i)=x(3,nn)
144
145 nn=msr(irect(3,l))
146 ix3(i)=nn
147 x3(i)=x(1,nn)
148 y3(i)=x(2,nn)
149 z3(i)=x(3,nn)
150
151 nn=msr(irect(4,l))
152 ix4(i)=nn
153 x4(i)=x(1,nn)
154 y4(i)=x(2,nn)
155 z4(i)=x(3,nn)
156 tets(i)=10001.
157 ENDIF
158 ENDIF
159 ENDDO !I=LFT,LLT
160 ENDIF !(ILEV==1)
161
162 RETURN
163 END
subroutine i12cor3(xs, xm, irect, msr, irtl, ilev, x, tets, ix1, ix2, ix3, ix4, x1, x2, x3, x4, xi, y1, y2, y3, y4, yi, z1, z2, z3, z4, zi, xface, lft, llt, nft)
Definition i12cor3.F:37
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21