48
49
50
58 USE format_mod , ONLY : fmw_10i
59
60
61
62#include "implicit_f.inc"
63
64
65
66#include "com04_c.inc"
67#include "units_c.inc"
68#include "param_c.inc"
69#include "tabsiz_c.inc"
70
71
72
73 TYPE (UNIT_TYPE_),INTENT(IN) :: UNITAB
74 INTEGER,INTENT(IN) :: ITABM1(SITABM1),ITAB(NUMNOD)
75 INTEGER,INTENT(IN) :: IPM(NPROPMI,NUMMAT)
76 my_real,
INTENT(IN) :: x(3,numnod)
77 TYPE(SUBMODEL_DATA),INTENT(IN) :: LSUBMODEL(NSUBMOD)
78 TYPE(DETONATORS_STRUCT_),INTENT(INOUT) :: DETONATORS
79 TYPE (GROUP_),DIMENSION(NGRNOD),INTENT(IN) :: IGRNOD
80
81
82
83 INTEGER :: I, MAT, J, NPEM, K,IGU,IGS,JJ,MDET,DET_ID,IDET
84 INTEGER :: IBID, NODE_ID1, NODE_ID2,uID1,uID2, IOPT, IUNIT, UID
85 INTEGER :: FLAG_FMT,IMAT,IFLAGUNIT,UNUSED,NNOD
86 INTEGER :: STAT,NPE,NPE2
87 my_real :: xc, yc, zc, alt, xc1, yc1, zc1, xc2, yc2, zc2, nx, ny, nz, bid, vcj
88 CHARACTER*40 :: MESS
89 CHARACTER*64 :: chain1,chain2
90 CHARACTER(LEN=NCHARKEY) :: KEY, KEY2
91 CHARACTER(LEN=NCHARTITLE) :: TITR
92 LOGICAL :: IS_ENCRYPTED, IS_AVAILABLE
93 INTEGER :: NDETPS,,NECRAN,NDETPL,NDETCORD
94
95
96
97 INTEGER,EXTERNAL :: NODGRNR5, USR2SYS, NINTRI
98 INTEGER :: UNUSED_MAT_DETONATOR
99 DATA mess/'DETONATORS DEFINITION '/
100
101
102
104
105 DO idet=1,detonators%N_DET_CORD
106
107 CALL hm_option_read_key(lsubmodel,option_id=det_id, unit_id=uid,keyword2=key,keyword3=key2)
108 IF (len_trim(key) > 0) key = key(1:7)
109 IF (len_trim(key2) > 0) key2 = key2(1:4)
110
111 is_encrypted= .false.
112 is_available = .false.
114
115
116
117 CALL hm_get_floatv(
'magnitude', vcj, is_available, lsubmodel, unitab)
118 CALL hm_get_floatv(
'rad_det_time', alt, is_available, lsubmodel, unitab)
119 CALL hm_get_intv(
'rad_det_iopt', iopt, is_available, lsubmodel)
120 CALL hm_get_intv(
'rad_det_materialid', mat, is_available, lsubmodel)
121 CALL hm_get_intv(
'entityid', igu, is_available, lsubmodel)
122
123
124
125
126
127 mdet=mat
128 IF (alt > infinity) alt=infinity
129 IF (alt < -infinity)alt=-infinity
130 nnod =
nodgrnr5(igu ,igs,detonators%CORD(idet)%NODES,igrnod,itabm1,mess)
131 IF(igrnod(igs)%SORTED /= 1)THEN
132 CALL ancmsg(msgid = 104,msgtype = msgerror,anmode = aninfo,
133 . c1 = '/DFS/DETCORD',
134 . i1 = det_id,
135 . c2 = 'ORDERED GROUP OF NODES IS REQUIRED')
136 ENDIF
137 unused = 0
139 IF (mat < 0) THEN
140 CALL ancmsg(msgid=102,msgtype=msgerror,anmode=aninfo,
141 . i1=det_id,
142 . c1='DETONATOR IS REFERRING TO A NEGATIVE MATERIAL ID',
143 . c2='/DFS/DETCORD',
144 . i2=mdet)
145 ELSEIF (unused==1) THEN
147 . msgtype=msgerror,
148 . anmode=aninfo,
149 . i1=det_id,
150 . c1='DETONATOR IS REFERRING TO AN UNKNOWN MATERIAL ID',
151 . c2='/DFS/DETCORD',
152 . i2=mdet)
153 ELSEIF (unused==2) THEN
154 CALL ancmsg(msgid=102,msgtype=msgerror,anmode=aninfo,
155 . i1=det_id,
156 . c1='DETONATOR MUST REFER TO A JWL MATERIAL LAW (LAWS 5, 51, 97, 151)',
157 . c2='/DFS/DETCORD',
158 . i2=mdet)
159 ELSEIF (nnod == 0) THEN
160
161 ELSE
162 detonators%CORD(idet)%IS_MAT_VALID = .true.
163
164
165
166
167
168
169
170 IF(is_encrypted) WRITE(iout,1001)
171 IF(iopt == 0)iopt=3
172 IF(iopt == 2)THEN
173 IF(.NOT.is_encrypted)WRITE(iout,1700) det_id,igu,nnod,alt,mdet
174 ELSEIF(iopt == 1)THEN
175 IF(.NOT.is_encrypted)WRITE(iout,1701) det_id,igu,nnod,alt,vcj,mdet
176 ELSEIF(iopt==3)THEN
177 IF(.NOT.is_encrypted)WRITE(iout,1700) det_id,igu,nnod,alt,mdet
178 ENDIF
179
180 IF(.NOT.is_encrypted)WRITE(iout,fmt=fmw_10i) (itab(detonators%CORD(idet)%NODES(i)),i=1,nnod)
181 DO i=1,nnod
182 CALL ifrontplus(detonators%CORD(idet)%NODES(i),1)
183 END DO
184 IF(iopt == 1 .AND. vcj <= zero)iopt=2
185
186 CALL detcord0(detonators%CORD(idet),alt,x,vcj,iopt)
187
188
189 detonators%CORD(idet)%TDET= alt
190 detonators%CORD(idet)%MAT = mat
191 detonators%CORD(idet)%VDET = vcj
192 detonators%CORD(idet)%IOPT = iopt
193 END IF
194
195 END do
196
197
198
199
200 1001 FORMAT(///5x,
201 & 'DETONATING CORD ',i10,/5x,
202 & '--------------- ',/5x,
203 & 'CONFIDENTIAL DATA')
204 1700 FORMAT(///5x,
205 & 'DETONATING CORD ',i10,/5x,
206 & '---------------- ',/5x,
207 & 'NODE GROUP IDENTIFIER =',i10 ,/5x,
208 & 'NUMBER OF POINTS(CORD) =',i10 ,/5x,
209 & 'LIGHTING TIME =',1pg20.13,/5x,
210 & 'EXPLOSIVE MATERIAL NUMBER =',i10 ,/5x,
211 & 'CORD DEFINITION : ')
212 1701 FORMAT(///5x,
213 & 'DETONATING CORD ',i10,/5x,
214 & '---------------- ',/5x,
215 & 'NODE GROUP IDENTIFIER =',i10 ,/5x,
216 & 'NUMBER OF POINTS(CORD) =',i10 ,/5x,
217 & 'LIGHTING TIME =',1pg20.13,/5x,
218 & 'DETONATION VELOCITY =',1pg20.13,/5x,
219 & 'EXPLOSIVE MATERIAL NUMBER =',i10 ,/5x,
220 & 'CORD DEFINITION : ')
221
222
subroutine detcord0(detonator_cord, alt, x, vdet2, iopt)
subroutine ifrontplus(n, p)
subroutine hm_get_floatv(name, rval, is_available, lsubmodel, unitab)
subroutine hm_get_intv(name, ival, is_available, lsubmodel)
subroutine hm_option_is_encrypted(is_encrypted)
subroutine hm_option_start(entity_type)
integer, parameter nchartitle
integer, parameter ncharkey
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)
integer function unused_mat_detonator(mdet, nummat, listmat)