47
48
49
58
59
60
61#include "implicit_f.inc"
62
63
64
65#include "com04_c.inc"
66#include "units_c.inc"
67#include "param_c.inc"
68#include "tabsiz_c.inc"
69
70
71
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)
77 TYPE(SUBMODEL_DATA),INTENT(IN) :: LSUBMODEL(NSUBMOD)
78 TYPE(DETONATORS_STRUCT_),TARGET,INTENT(INOUT) :: DETONATORS
79 TYPE (GROUP_),DIMENSION(NGRNOD),INTENT(IN) :: IGRNOD
80
81
82
83 INTEGER :: ID,K
84 INTEGER :: IUNIT, UID
85 INTEGER :: IFLAGUNIT
86 INTEGER :: DET_ID,STAT
87 CHARACTER*40 :: MESS
88 CHARACTER(LEN=NCHARKEY) :: KEY, KEY2
89 INTEGER :: NDET,NDFS
90
91
92
93 DATA mess/'DETONATORS DEFINITION '/
94
95
96
97 ndet = detonators%N_DET
98 detonators%IS_SHADOWING_REQUIRED = .false.
99 IF (ndet <= 0) RETURN
100
101
102
103
104
107 WRITE(iout,1000)
108 DO k=1,ndfs
110 IF (len_trim(key) > 0) key = key(1:7)
111 IF (len_trim(key2) > 0) key2
112
113 IF(uid > 0)THEN
114 iflagunit=0
115 DO iunit=1,unitab%NUNITS
116 IF (unitab%UNIT_ID(iunit) == uid) THEN
117 iflagunit = 1
118 EXIT
119 ENDIF
120 ENDDO
121 IF (iflagunit == 0) THEN
122 CALL ancmsg(msgid=659,anmode=aninfo
123 . i2=uid,i1=det_id,c1='DETONATORS',c2='DETONATORS',c3='/DFS')
124 ENDIF
125 ENDIF
126 ENDDO
127
128
129 CALL prelecdet(igrnod, lsubmodel, detonators)
130
131
137 WRITE(iout,2000)
138
139
140
141
142 1000 FORMAT(////' DETONATORS' /
143 . ' ----------'/)
144 2000 FORMAT(//)
subroutine hm_option_count(entity_type, hm_option_number)
subroutine hm_option_start(entity_type)
integer, parameter ncharkey
subroutine prelecdet(igrnod, lsubmodel, detonators)
subroutine read_dfs_detcord(detonators, x, igrnod, ipm, itabm1, unitab, lsubmodel, itab)
subroutine read_dfs_detline(detonators, x, ipm, itabm1, unitab, lsubmodel)
subroutine read_dfs_detplan(detonators, x, ipm, itabm1, unitab, lsubmodel)
subroutine read_dfs_detpoint(detonators, x, ipm, pm, itabm1, unitab, lsubmodel, igrnod)
subroutine read_dfs_wave_shaper(detonators, igrnod, ipm, itabm1, unitab, lsubmodel, itab)
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)