46 . LSUBMODEL ,DETONATORS)
61#include "implicit_f.inc"
68#include "tabsiz_c.inc"
72 TYPE (UNIT_TYPE_),
INTENT(IN) :: UNITAB
73 INTEGER,
INTENT(IN) :: ITABM1(SITABM1),ITAB(NUMNOD)
74 my_real,
INTENT(INOUT) :: pm(npropm,nummat)
75 INTEGER,
INTENT(IN) :: IPM(NPROPMI,NUMMAT)
76 my_real,
INTENT(IN) :: x(3,numnod)
79 TYPE (GROUP_),
DIMENSION(NGRNOD),
INTENT(IN) :: IGRNOD
86 INTEGER :: DET_ID,STAT
88 CHARACTER(LEN=NCHARKEY) :: KEY, KEY2
93 DATA mess/
'DETONATORS DEFINITION '/
97 ndet = detonators%N_DET
98 detonators%IS_SHADOWING_REQUIRED = .false.
109 CALL hm_option_read_key(lsubmodel,option_id=det_id, unit_id=uid,keyword2=key,keyword3=key2)
110 IF (len_trim(key) > 0) key = key(1:7)
111 IF (len_trim(key2) > 0) key2 = key2(1:4)
115 DO iunit=1,unitab%NUNITS
116 IF (unitab%UNIT_ID(iunit) == uid)
THEN
121 IF (iflagunit == 0)
THEN
122 CALL ancmsg(msgid=659,anmode=aninfo,msgtype=msgerror,
123 . i2=uid,i1=det_id,c1=
'DETONATORS',c2=
'DETONATORS',c3=
'/DFS')
129 CALL prelecdet(igrnod, lsubmodel, detonators)
142 1000
FORMAT(////
' DETONATORS' /
subroutine read_detonators(itabm1, itab, igrnod, pm, ipm, x, unitab, lsubmodel, detonators)
subroutine read_dfs_detcord(detonators, x, igrnod, ipm, itabm1, unitab, lsubmodel, itab)
subroutine read_dfs_detpoint(detonators, x, ipm, pm, itabm1, unitab, lsubmodel, igrnod)
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)