OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
i21cor3t.F File Reference
#include "implicit_f.inc"
#include "mvsiz_p.inc"

Go to the source code of this file.

Functions/Subroutines

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)

Function/Subroutine Documentation

◆ i21cor3t()

subroutine i21cor3t ( integer jlt,
xloc,
integer, dimension(4,*) irect,
integer, dimension(*) cand_e,
integer, dimension(*) cand_n,
integer igap,
gap,
x1,
x2,
x3,
x4,
y1,
y2,
y3,
y4,
z1,
z2,
z3,
z4,
xi,
yi,
zi,
integer, dimension(mvsiz) ix1,
integer, dimension(mvsiz) ix2,
integer, dimension(mvsiz) ix3,
integer, dimension(mvsiz) ix4,
integer nsn,
gap_s,
gapv,
gapmax,
gapmin,
curv_max,
depth,
xm0,
intent(in) drad,
intent(in) dgapload )

Definition at line 28 of file i21cor3t.F.

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
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
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
#define my_real
Definition cppsort.cpp:32
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21