OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
i25comp_1.F File Reference
#include "implicit_f.inc"
#include "comlock.inc"
#include "mvsiz_p.inc"
#include "com04_c.inc"
#include "com08_c.inc"
#include "param_c.inc"
#include "warn_c.inc"
#include "task_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine i25comp_1 (ipari, intbuf_tab, x, itab, nin, kinet, jtask, nb_dst1, v, nsensor, sensor_tab)

Function/Subroutine Documentation

◆ i25comp_1()

subroutine i25comp_1 ( integer, dimension(npari,ninter) ipari,
type(intbuf_struct_) intbuf_tab,
x,
integer, dimension(*) itab,
integer nin,
integer, dimension(*) kinet,
integer jtask,
integer nb_dst1,
v,
integer, intent(in) nsensor,
type (sensor_str_), dimension(nsensor) sensor_tab )

Definition at line 37 of file i25comp_1.F.

41C=======================================================================
42C M o d u l e s
43C-----------------------------------------------
44 USE intbufdef_mod
45 USE tri7box
46 USE sensor_mod
47C-----------------------------------------------
48C I m p l i c i t T y p e s
49C-----------------------------------------------
50#include "implicit_f.inc"
51#include "comlock.inc"
52C-----------------------------------------------
53C G l o b a l P a r a m e t e r s
54C-----------------------------------------------
55#include "mvsiz_p.inc"
56C-----------------------------------------------
57C C o m m o n B l o c k s
58C-----------------------------------------------
59#include "com04_c.inc"
60#include "com08_c.inc"
61#include "param_c.inc"
62#include "warn_c.inc"
63#include "task_c.inc"
64C-----------------------------------------------
65C D u m m y A r g u m e n t s
66C-----------------------------------------------
67 INTEGER ,INTENT(IN) :: NSENSOR
68 INTEGER NIN, NB_DST1, JTASK
69 INTEGER IPARI(NPARI,NINTER), ITAB(*), KINET(*)
70C REAL
71 my_real :: x(3,*), v(3,*)
72 TYPE(INTBUF_STRUCT_) INTBUF_TAB
73 TYPE (SENSOR_STR_) ,DIMENSION(NSENSOR) :: SENSOR_TAB
74C-----------------------------------------------
75C L o c a l V a r i a b l e s
76C-----------------------------------------------
77 INTEGER
78 . I, J, L, H, I_STOK_RTLM, I_STOK, JLT , NFT,
79 . INACTI, NADMSR, NB_LOC, DEBUT, IGAP,
80 . MG, N, NSN, NSNR, IVIS2, ISENS
81 INTEGER LENT, MAXCC
82 INTEGER IX1(MVSIZ), IX2(MVSIZ), IX3(MVSIZ), IX4(MVSIZ),
83 . NSVG(MVSIZ), FAR(MVSIZ,4), SUBTRIA(MVSIZ),
84 . MVOISN(MVSIZ,4), IBOUND(4,MVSIZ)
85C REAL
86C-----------------------------------------------
87C REAL
89 . nnx(mvsiz,5), nny(mvsiz,5), nnz(mvsiz,5),
90 . xx(mvsiz,5), yy(mvsiz,5), zz(mvsiz,5),
91 . xi(mvsiz), yi(mvsiz), zi(mvsiz), stif(mvsiz),
92 . gaps(mvsiz), gapm(mvsiz),
93 . pent(mvsiz,4), dist(mvsiz), lb(mvsiz,4), lc(mvsiz,4),
94 . lbh(mvsiz,4), lch(mvsiz,4), gap_nm(4,mvsiz), gapmxl(mvsiz),
95 . ts, startt, stopt, drad, dgapload
96C-----------------------------------------------
97 nsn =ipari(5,nin)
98 ivis2 =ipari(14,nin)
99 nsnr =ipari(24,nin)
100 inacti=ipari(22,nin)
101 nadmsr=ipari(67,nin)
102 igap =ipari(21,nin)
103 drad = zero
104 IF(ipari(47,nin) > 0) drad = intbuf_tab%VARIABLES(32)
105 dgapload = intbuf_tab%VARIABLES(46)
106C
107 startt=intbuf_tab%VARIABLES(3)
108 stopt =intbuf_tab%VARIABLES(11)
109 IF(startt>tt) RETURN ! dont look for sliding
110 IF(tt>stopt) RETURN
111C
112C Look if interface is activated
113 isens = ipari(64,nin)
114 IF (isens > 0) THEN ! Interface activated by sensor
115 ts = sensor_tab(isens)%TSTART
116 ELSE
117 ts = tt
118 ENDIF
119 IF(tt<ts) RETURN
120C
121 i_stok_rtlm=intbuf_tab%I_STOK(3) ! IRTLM/=0 was stored at the beginning of CAND_OPT
122 nb_loc = i_stok_rtlm / nthread
123 IF (jtask==nthread) THEN
124 i_stok = i_stok_rtlm-nb_loc*(nthread-1)
125 ELSE
126 i_stok = nb_loc
127 ENDIF
128C-----------------------------------------------------------------------
129 IF (debug(3)>=1) THEN
130 nb_dst1 = nb_dst1 + i_stok
131 ENDIF
132 DO nft = 0 , i_stok - 1 , nvsiz
133 debut = (jtask-1)*nb_loc + nft
134 jlt = min( nvsiz, i_stok - nft )
135 CALL i25cor3_1(
136 1 jlt ,x ,intbuf_tab%IRECTM,intbuf_tab%NSV ,intbuf_tab%CAND_OPT_E(debut+1),
137 2 intbuf_tab%CAND_OPT_N(debut+1),intbuf_tab%IRTLM ,intbuf_tab%STFM ,intbuf_tab%STFNS,stif ,
138 3 igap ,xi ,yi ,zi ,
139 4 ix1 ,ix2 ,ix3 ,ix4 ,
140 5 nsvg ,nsn ,
141 6 nin ,intbuf_tab%GAP_S,gaps ,intbuf_tab%ADMSR ,
142 . intbuf_tab%EDGE_BISECTOR,
143 7 xx ,yy ,zz ,
144 8 nnx ,nny ,nnz ,
145 9 intbuf_tab%GAP_M,gapm ,intbuf_tab%GAP_NM,gap_nm ,subtria,
146 a intbuf_tab%MVOISIN,mvoisn ,
147 b intbuf_tab%GAP_SL,intbuf_tab%GAP_ML, gapmxl,intbuf_tab%LBOUND,ibound)
148C
149 CALL i25dst3_1(
150 1 jlt ,intbuf_tab%CAND_OPT_N(debut+1),intbuf_tab%CAND_OPT_E(debut+1),
151 2 xx ,yy ,zz ,
152 3 xi ,yi ,zi ,
153 5 nin ,nsn ,ix1 ,
154 6 ix2 ,ix3 ,ix4 ,nsvg ,stif ,
155 7 inacti ,intbuf_tab%MSEGLO,gaps ,gapm ,gapmxl ,
156 8 intbuf_tab%IRECTM,intbuf_tab%IRTLM ,intbuf_tab%TIME_S,gap_nm ,itab ,
157 9 intbuf_tab%ICONT_I,nnx ,nny ,nnz ,
158 a far ,pent ,dist ,lb ,lc ,
159 b lbh ,lch ,subtria ,mvoisn ,ibound ,
160 c intbuf_tab%VTX_BISECTOR ,drad ,dgapload )
161C
162 CALL i25glob_1(
163 1 jlt ,intbuf_tab%CAND_OPT_N(debut+1),intbuf_tab%CAND_OPT_E(debut+1),
164 2 nin ,nsn ,ix1 ,ix2 ,ix3 ,
165 3 ix4 ,nsvg ,stif ,inacti ,intbuf_tab%MSEGLO ,
166 4 intbuf_tab%IRTLM ,intbuf_tab%TIME_S ,itab ,
167 5 far ,pent ,lbh ,lch ,
168C 5 FAR ,PENT ,LB ,LC ,
169 6 intbuf_tab%FARM(4*debut+1) ,intbuf_tab%PENM(4*debut+1) ,
170 . intbuf_tab%LBM(4*debut+1) ,intbuf_tab%LCM(4*debut+1) )
171C
172 CALL i25prep_slid_1(
173 1 jlt ,intbuf_tab%CAND_OPT_N(debut+1),intbuf_tab%CAND_OPT_E(debut+1),nin ,
174 2 nsn ,nsnr ,inacti ,intbuf_tab%MSEGLO ,
175 3 intbuf_tab%IRTLM ,intbuf_tab%TIME_S ,itab ,intbuf_tab%FARM(4*debut+1),
176 . intbuf_tab%PENM(4*debut+1) ,
177 4 intbuf_tab%IRECTM,nadmsr ,intbuf_tab%ADMSR,intbuf_tab%LBM(4*debut+1) ,
178 . intbuf_tab%LCM(4*debut+1) ,
179 5 intbuf_tab%ISLIDE ,intbuf_tab%NSV)
180
181 ENDDO
182C-----------------------------------------------------------------------
183 RETURN
#define my_real
Definition cppsort.cpp:32
subroutine i25cor3_1(jlt, x, irect, nsv, cand_e, cand_n, irtlm, stf, stfn, stif, igap, xi, yi, zi, ix1, ix2, ix3, ix4, nsvg, nsn, nin, gap_s, gaps, admsr, nod_normal, xx, yy, zz, nnx, nny, nnz, gap_m, gapm, gapn_m, gapnm, subtria, mvoisin, mvoisn, gap_s_l, gap_m_l, gapmxl, lbound, ibound)
Definition i25cor3.F:42
subroutine i25glob_1(jlt, cand_n, cand_e, nin, nsn, ix1, ix2, ix3, ix4, nsvg, stif, inacti, mseglo, irtlm, time_s, itab, far, pent, lb, lc, farm, penm, lbm, lcm)
Definition i25dst3_1.F:854
subroutine i25dst3_1(jlt, cand_n, cand_e, xx, yy, zz, xi, yi, zi, nin, nsn, ix1, ix2, ix3, ix4, nsvg, stif, inacti, mseglo, gaps, gapm, gapmxl, irect, irtlm, time_s, gap_nm, itab, icont_i, nnx, nny, nnz, far, pent, dist, lb, lc, lbp, lcp, subtria, mvoisn, ibound, vtx_bisector, drad, dgapload)
Definition i25dst3_1.F:42
subroutine i25prep_slid_1(jlt, cand_n, cand_e, nin, nsn, nsnr, inacti, mseglo, irtlm, time_s, itab, farm, penm, irect, nadmsr, admsr, lbm, lcm, islide, nsv)
Definition i25slid.F:155
#define min(a, b)
Definition macros.h:20