OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
i20cor3t.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!|| i20cor3t ../engine/source/interfaces/int20/i20cor3t.F
25!||--- called by ------------------------------------------------------
26!|| i20sto ../engine/source/interfaces/intsort/i20sto.F
27!||--- uses -----------------------------------------------------
28!|| tri7box ../engine/share/modules/tri7box.F
29!||====================================================================
30 SUBROUTINE i20cor3t(JLT ,XA ,IRECT ,NSV ,CAND_E ,
31 1 CAND_N ,IGAP ,GAP ,X1 ,X2 ,
32 2 X3 ,X4 ,Y1 ,Y2 ,Y3 ,
33 3 Y4 ,Z1 ,Z2 ,Z3 ,Z4 ,
34 4 XI ,YI ,ZI ,STIF ,IX1 ,
35 5 IX2 ,IX3 ,IX4 ,NSN ,GAP_S ,
36 6 GAP_M ,GAPV ,GAPMAX,GAPMIN,CURV_MAX,
37 7 NIN ,GAP_SH)
38
39C============================================================================
40C-----------------------------------------------
41C M o d u l e s
42C-----------------------------------------------
43 USE tri7box
44C-----------------------------------------------
45C I m p l i c i t T y p e s
46C-----------------------------------------------
47#include "implicit_f.inc"
48C-----------------------------------------------
49C G l o b a l P a r a m e t e r s
50C-----------------------------------------------
51#include "mvsiz_p.inc"
52C-----------------------------------------------
53C D u m m y A r g u m e n t s
54C-----------------------------------------------
55 INTEGER IRECT(4,*), NSV(*), CAND_E(*), CAND_N(*),
56 . JLT,IDT, NOINT, NSN, IGAP, NIN
57 INTEGER IX1(MVSIZ), IX2(MVSIZ), IX3(MVSIZ), IX4(MVSIZ)
58C REAL
59 my_real
60 . XA(3,*), GAPV(*), GAP_S(*), GAP_M(*),CURV_MAX(*),
61 . GAP, GAPMAX, GAPMIN,GAP_SH(*)
62C REAL
63 my_real
64 . x1(mvsiz), x2(mvsiz), x3(mvsiz), x4(mvsiz),
65 . y1(mvsiz), y2(mvsiz), y3(mvsiz), y4(mvsiz),
66 . z1(mvsiz), z2(mvsiz), z3(mvsiz), z4(mvsiz),
67 . xi(mvsiz), yi(mvsiz), zi(mvsiz), stif(mvsiz)
68C-----------------------------------------------
69C L o c a l V a r i a b l e s
70C-----------------------------------------------
71 INTEGER I ,J ,IL, L, NN, IG,JFT
72C-----------------------------------------------
73C
74 IF(IGAP==0)then
75 DO i=1,jlt
76 gapv(i)=gap
77 END DO
78 ELSE
79 DO i=1,jlt
80 j = cand_n(i)
81 IF(j<=nsn) THEN
82 gapv(i)=gap_s(j)+gap_m(cand_e(i))
83 ELSE
84 ig = j-nsn
85 gapv(i)=xrem(12,ig)+gap_m(cand_e(i))
86C GAPV(I)=GAPFI(NIN)%P(CAND_N(I)-NSN)+GAP_M(CAND_E(I))
87 END IF
88 gapv(i)=min(gapv(i),gapmax)
89 gapv(i)=gapv(i)+two*gap_sh(cand_e(i))
90 gapv(i)=max(gapmin,gapv(i))
91 END DO
92 END IF
93 DO i=1,jlt
94 j = cand_n(i)
95 IF(j<=nsn) THEN
96 il = nsv(j)
97 xi(i) = xa(1,il)
98 yi(i) = xa(2,il)
99 zi(i) = xa(3,il)
100 ELSE
101 ig = j-nsn
102 xi(i) = xrem(1,ig)
103 yi(i) = xrem(2,ig)
104 zi(i) = xrem(3,ig)
105 ENDIF
106C
107 l = cand_e(i)
108C
109 ix1(i)=irect(1,l)
110 x1(i)=xa(1,ix1(i))
111 y1(i)=xa(2,ix1(i))
112 z1(i)=xa(3,ix1(i))
113C
114 ix2(i)=irect(2,l)
115 x2(i)=xa(1,ix2(i))
116 y2(i)=xa(2,ix2(i))
117 z2(i)=xa(3,ix2(i))
118C
119 ix3(i)=irect(3,l)
120 x3(i)=xa(1,ix3(i))
121 y3(i)=xa(2,ix3(i))
122 z3(i)=xa(3,ix3(i))
123C
124 ix4(i)=irect(4,l)
125 x4(i)=xa(1,ix4(i))
126 y4(i)=xa(2,ix4(i))
127 z4(i)=xa(3,ix4(i))
128 ENDDO
129C
130 RETURN
131 END
132
subroutine i20cor3t(jlt, xa, irect, nsv, cand_e, cand_n, igap, gap, x1, x2, x3, x4, y1, y2, y3, y4, z1, z2, z3, z4, xi, yi, zi, stif, ix1, ix2, ix3, ix4, nsn, gap_s, gap_m, gapv, gapmax, gapmin, curv_max, nin, gap_sh)
Definition i20cor3t.F:38
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21