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