58 USE format_mod ,
ONLY : fmw_10i
62#include "implicit_f.inc"
69#include "tabsiz_c.inc"
73 TYPE (UNIT_TYPE_),
INTENT(IN) :: UNITAB
74 INTEGER,
INTENT(IN) :: ITABM1(SITABM1),ITAB(NUMNOD)
75 INTEGER,
INTENT(IN) :: IPM(NPROPMI,NUMMAT)
78 TYPE (GROUP_),
DIMENSION(NGRNOD),
INTENT(IN) :: IGRNOD
82 INTEGER :: I, MAT, J, K,IGU,IGS,JJ,MDET,DET_ID,IDET
83 INTEGER :: IBID, NODE_ID1, NODE_ID2,uID1,uID2, IOPT, , UID
84 INTEGER :: FLAG_FMT,IMAT,IFLAGUNIT,UNUSED
86 my_real :: xc, yc, zc, alt, xc1, yc1, zc1, xc2, yc2, zc2, nx, ny, nz, bid, vcj, vdet
88 CHARACTER*64 :: chain1,chain2
89 CHARACTER(LEN=NCHARKEY) :: KEY, KEY2
90 CHARACTER(LEN=NCHARTITLE) :: TITR
91 LOGICAL :: IS_ENCRYPTED, IS_AVAILABLE
92 INTEGER,
POINTER,
DIMENSION(:) :: IECRAN
93 my_real,
POINTER,
DIMENSION(:) :: decran
94 INTEGER :: NDETPS,NDETSG,NECRAN,NDETPL,NDETCORD
98 INTEGER,
EXTERNAL :: NODGRNR5, USR2SYS
99INTEGER :: UNUSED_MAT_DETONATOR
100 DATA mess/
'DETONATORS DEFINITION '/
107 DO idet=1,detonators%N_DET_WAVE_SHAPER
110 IF (len_trim(key) > 0) key = key(1:7)
111 IF (len_trim(key2) > 0) key2 = key2(1:4)
113 iecran => detonators%WAVE_SHAPER(idet)%NODES(1:)
114 decran => detonators%WAVE_SHAPER(idet)%TIME(1:)
116 is_encrypted= .false.
117 is_available = .false.
122 CALL hm_get_floatv'rad_det_locationA_X', vdet, is_available, lsubmodel
124 CALL hm_get_floatv(
'rad_det_locationA_Z', zc1, is_available, lsubmodel, unitab)
127 CALL hm_get_intv(
'entityid', igu, is_available, lsubmodel)
133 IF (alt > infinity) alt=infinity
134 IF(mat > 0)unused=unused_mat_detonator
137 CALL ancmsg(msgid=102,msgtype=msgerror,anmode=aninfo,
139 . c1=
'DETONATOR IS REFERRING TO A NEGATIVE MATERIAL ID',
142 ELSEIF (unused==1)
THEN
143 CALL ancmsg(msgid=102,msgtype=msgerror,anmode=aninfo,
145 . c1=
'DETONATOR IS REFERRING TO AN UNKNOWN MATERIAL ID',
148 ELSEIF (unused==2)
THEN
149 CALL ancmsg(msgid=102,msgtype=msgerror
151 . c1=
'DETONATOR MUST REFER TO A JWL MATERIAL LAW (LAWS 5, 51, 97, 151)',
158 npe = nodgrnr5(igu ,igs,iecran(1),igrnod ,itabm1 ,mess)
160 IF(is_encrypted)
WRITE(iout,1001)
161 IF(.NOT.is_encrypted)
WRITE(iout,1550) det_id,vdet,yc1,zc1,alt,mdet,igu,npe
162 IF(.NOT.is_encrypted)
WRITE(iout,fmt=fmw_10i) (itab(iecran(i)),i=1,npe)
166 detonators%WAVE_SHAPER(idet)%TDET = alt
167 detonators%WAVE_SHAPER(idet)%MAT = mat
168 detonators%WAVE_SHAPER(idet)%VDET = vdet
169 detonators%WAVE_SHAPER(idet)%XDET = zero
170 detonators%WAVE_SHAPER(idet)%YDET = yc1
171 detonators%WAVE_SHAPER(idet)%ZDET = zc1
172 detonators%WAVE_SHAPER(idet)%NUMNOD = npe
180 &
'SHADOW LINE DETONATION ',i10,/5x,
181 &
'---------------------- ',/5x,
182 &
'CONFIDENTIAL DATA')
184 &
'SHADOW LINE DETONATION =',i10,/5x,
185 &
'---------------------- ',/5x,
186 &
'OPTIONAL VELOCITY =',1pg20.13,/5x
187 &
'Y-COORDINATE =',1pg20.13,/5x,
188 &
'Z-COORDINATE =',1pg20.13,/5x,
189 &
'LIGHTING TIME =',1pg20.13,/5x,
190 & 'explosive material number =
',I10,/5X,
191 & 'shadow line node group
id =
',I10,/5X,
192 & 'number of points(shadow) =
',I10,/5X,
193 & 'shadow line definition :
')
subroutine ancmsg(msgid, msgtype, anmode, i1, i2, i3, i4, i5, i6, i7, i8, i9, i10, i11, i12, i13, i14, i15, i16, i17, i18, i19, i20, r1, r2, r3, r4, r5, r6, r7, r8, r9, c1, c2, c3, c4, c5, c6, c7, c8, c9, prmode)