35 SUBROUTINE m5in2t(PM,MAT,M151_ID,DETONATORS,TB,X,IX,NIX)
45#include "implicit_f.inc"
55#include "vect01_c.inc"
62 INTEGER MAT(*),NIX,IX(NIX,*)
63 INTEGER,
INTENT(IN) :: M151_ID
69 INTEGER I, N, MTL, MT,IOPT,NPE
70 INTEGER NDETPS, NDETSG, NECRAN, NDETPL, NDETCORD,NDETPS_NO_SHADOW,NDETPS_SHADOW
71 INTEGER :: I_SHADOW_FLAG
72 LOGICAL HAS_DETONATOR(MVSIZ)
73 my_real y1(mvsiz), y2(mvsiz), y3(mvsiz),
74 . z1(mvsiz), z2(mvsiz), z3(mvsiz),
75 . xc(mvsiz), yc(mvsiz), zc(mvsiz), bt(mvsiz),
77 . ylp1, zlp1, xlp2, ylp2, zlp2, xl0, yl0, zl0, xl1, yl1, zl1,
78 . xl2, yl2, zl2, ps1, ps2, dl1, dl2, s1, s2, s3,
79 . nx, ny, nz , nn, vdet
80 INTEGER :: NODE1, NODE2, NODE3, II, GRNOD_ID, INOD, NNOD, NODE_ID
84 ndetps = detonators%N_DET_POINT
85 ndetsg = detonators%N_DET_LINE
86 necran = detonators%N_DET_WAVE_SHAPER
87 ndetpl = detonators%N_DET_PLANE
88 ndetcord = detonators%N_DET_CORD
93 DO i = 1, detonators%N_DET_POINT
94 i_shadow_flag = detonators%POINT(i)%SHADOW
95 IF(i_shadow_flag == 0)
THEN
96 ndetps_no_shadow = ndetps_no_shadow + 1
98 ndetps_shadow = ndetps_shadow + 1
104 IF(detonators%N_DET - ndetps_shadow > 0)
THEN
124 has_detonator(i)=.false.
126 yc(i)=third*(y1(i)+y2(i)+y3(i))
127 zc(i)=third*(z1(i)+z2(i)+z3(i))
136 i_shadow_flag = detonators%POINT(n)%SHADOW
137 IF(i_shadow_flag /= 0)cycle
138 mtl=detonators%POINT(n)%MAT
139 grnod_id=detonators%POINT(n)%GRNOD_ID
140 IF(mtl == 0 .OR. mtl == mat(i) .OR. mtl == m151_id)
THEN
142 IF(grnod_id == 0)
THEN
143 alt=detonators%POINT(n)%TDET
144 xlp=detonators%POINT(n)%XDET
145 ylp=detonators%POINT(n)%YDET
146 zlp=detonators%POINT(n)%ZDET
147 dl(i) =(xc(i)-xlp)**2+(yc(i)-ylp)**2+(zc(i)-zlp)**2
149 bt(i) =alt+dl(i)/pm(38,mat
150 IF(bt(i) < abs(tb(i))) tb(i)=-bt(i)
151 has_detonator(i)= .true.
154 nnod = detonators%POINT(n)%NNOD
155 alt=detonators%POINT(n)%TDET
156 has_detonator(i)=.true.
158 node_id=detonators%POINT(n)%NODLIST(inod)
162 dl(i) =(xc(i)-xlp)**2+(yc(i)-ylp)**2+(zc(i)-zlp)**2
164 bt(i) =alt+dl(i)/pm(38,mat(i))
165 IF(bt(i) < abs(tb(i))) tb(i)=-bt(i)
178 alt=detonators%LINE(n)%TDET
179 mtl=detonators%LINE(n)%MAT
180 xlp1=detonators%LINE(n)%XDET_1
181 ylp1=detonators%LINE(n)%YDET_1
182 zlp1=detonators%LINE(n)%ZDET_1
183 xlp2=detonators%LINE(n)%XDET_2
184 ylp2=detonators%LINE(n)%YDET_2
185 zlp2=detonators%LINE(n)%ZDET_2
187 IF(mtl == 0 .OR. mtl == mat(i) .OR. mtl == m151_id)
THEN
197 ps1 =xl1*xl0+yl1*yl0+zl1*zl0
198 ps2 =xl2*xl0+yl2*yl0+zl2*zl0
199 IF(ps1*ps2 > zero)
THEN
200 dl1 =sqrt(xl1**2+yl1**2+zl1**2)
201 dl2 =sqrt(xl2**2+yl2**2+zl2**2)
204 s1 =yl1*zl0 - zl1*yl0
205 s2 =zl1*xl0 - xl1*zl0
206 s3 =xl1*yl0 - yl1*xl0
207 dl(i)=sqrt((s1**2+s2**2+s3**2)/(xl0**2+yl0**2+zl0**2))
209 bt(i) =alt+dl(i)/pm(38,mat(i))
210 IF(bt(i) < abs(tb(i))) tb(i)=-bt(i)
211 has_detonator(i)=.true.
222 alt=detonators%WAVE_SHAPER(n)%TDET
223 mtl=detonators%WAVE_SHAPER(n)%MAT
224 vdet =detonators%WAVE_SHAPER(n)%VDET
225 yd =detonators%WAVE_SHAPER(n)%YDET
226 zd =detonators%WAVE_SHAPER(n)%ZDET
227 npe=detonators%WAVE_SHAPER(n)%NUMNOD
230 IF(vdet == zero)vdet=pm(38,mat(1))
232 CALL ecran1(detonators%WAVE_SHAPER(n),x,vdet)
235 IF(mtl /= mat(i) .AND. mtl /= 0 .AND. mtl
236 yd =detonators%WAVE_SHAPER(n)%YDET
237 zd =detonators%WAVE_SHAPER(n)%ZDET
241 CALL ecran2(detonators%WAVE_SHAPER(n),x,vdet)
243 IF(bt(i) < abs(tb(i))) tb(i)=-bt(i)
244 has_detonator(i)= .true.
254 alt=detonators%PLANE(n)%TDET
255 mtl=detonators%PLANE(n)%MAT
256 xlp=detonators%PLANE(n)%XDET
257 ylp=detonators%PLANE(n)%YDET
258 zlp=detonators%PLANE(n)%ZDET
259 nx=detonators%PLANE(n
261 nz=detonators%PLANE(n)%NZ
264 dl1=xlp*nx + ylp*ny + zlp*nz
267 IF(mtl == 0 .OR. mtl == mat(i) .OR. mtl == m151_id)
THEN
272 dl(i) = (xc(i)-xlp)*nx + (yc(i)-ylp)*ny + (zc(i)-zlp)*nz
275 bt(i) =alt+dl(i)/pm(38,mat(i))
276 IF(bt(i) < abs(tb(i))) tb(i)=-bt(i)
277 has_detonator(i)= .true.
286 IF(ndetcord > 0)
THEN
288 alt = detonators%CORD(n)%TDET
289 mtl = detonators%CORD(n)%MAT
290 vdet2 = detonators%CORD(n)%VDET
291 iopt = detonators%CORD(n)%IOPT
296 IF(mtl /= mat(1) .AND. mtl /= 0 .AND. mtl /= m151_id) cycle
298 CALL detcord(detonators%CORD(n),x,xc,yc,zc,vdto,vdet2,alt,bt,tb,has_detonator,iopt)