66
67
68
76 USE sensor_mod
89
90
91
92#include "implicit_f.inc"
93
94
95
96
97#include "com04_c.inc"
98
99#include "scr17_c.inc"
100
101#include "r2r_c.inc"
102
103#include "param_c.inc"
104
105
106#include "units_c.inc"
107
108
109
110 TYPE(MONVOL_STRUCT_), DIMENSION(NVOLU + NMONVOL), INTENT(INOUT) :: T_MONVOL
111 TYPE(MONVOL_METADATA_), INTENT(INOUT) :: T_MONVOL_METADATA
112 TYPE(UNIT_TYPE_), INTENT(IN) :: UNITAB
113 my_real,
INTENT(IN) :: x(3, numnod), geo(npropg, numgeo), pm(npropm, nummat), pld(2, *),
114 . xframe(nxframe,*)
115 INTEGER, INTENT(IN) :: NPC(*), NPT(*), ITAB(*), ITABM1(*),
116 . IXC(NIXC, NUMELC), IXTG(NIXTG, NUMELTG),IPM(NPROPMI, NUMMAT),
117 . IGEO(NPROPGI, NUMGEO),IFRAME(LISKN,*)
118 INTEGER, INTENT(INOUT) :: NOM_OPT(LNOPT1, *)
119 TYPE (SURF_), INTENT(INOUT), DIMENSION(NSURF) :: IGRSURF
120 TYPE (GROUP_), DIMENSION(NGRBRIC), INTENT(IN) :: IGRBRIC
121 TYPE (SUBMODEL_DATA), DIMENSION(NSUBMOD), INTENT(IN) :: LSUBMODEL
122 TYPE (SENSORS_) ,INTENT(IN) :: SENSORS
123
124
125
126 INTEGER :: II, JJ
127 INTEGER :: NVB, ITYPE, ID, UID, LOCAL_UID
128 CHARACTER(len=ncharkey) :: KEY
129 CHARACTER(len=nchartitle) :: TITR
130 LOGICAL :: FOUND
131
132
133
134
135 WRITE(iout, 1000)
136 t_monvol_metadata%LCA = 0
137 nvb = 0
138
139
140
141
143 DO ii = 1, nmonvol
144 nvb = nvb + 1
145
146 IF (nsubdom > 0) THEN
147 IF(
tagmon(nvb) == 0)
THEN
149 ENDIF
150 ENDIF
152 . keyword2 = key)
154 CALL fretitl(titr,nom_opt(lnopt1-ltitr+1,ii),ltitr)
155
156 found = .false.
157 DO jj = 1,unitab%NUNITS
158 IF (unitab%UNIT_ID(jj) == uid) THEN
159 found = .true.
160 local_uid = jj
161 EXIT
162 ENDIF
163 ENDDO
164 IF (.NOT. found) THEN
165 CALL ancmsg(msgid = 659, anmode = aninfo, msgtype = msgerror,
166 . i2 = uid, i1 =
id, c1 =
'MONITORED VOLUME', c2 =
'MONITORED VOLUME', c3=titr)
167 ENDIF
168 IF (key(1:4) == 'AREA') THEN
169 itype = 1
170 ELSEIF (key(1:4) == 'PRES') THEN
171 itype = 2
172 ELSEIF (key(1:3) == 'GAS') THEN
173 itype = 3
174 ELSEIF (key(1:7) == 'AIRBAG1') THEN
175 itype = 7
176 ELSEIF (key(1:6) == 'AIRBAG') THEN
177 itype = 4
178 ELSEIF (key(1:6) == 'COMMU1') THEN
179 itype = 9
180 ELSEIF (key(1:5) == 'COMMU') THEN
181 itype = 5
182 ELSEIF (key(1:7) == 'FVMBAG2') THEN
183 itype = 11
184 ELSEIF (key(1:7) == 'FVMBAG1') THEN
185 itype = 8
186 ELSEIF (key(1:6) == 'FVMBAG') THEN
187 itype = 6
188 ELSEIF (key(1:6) == 'LFLUID') THEN
189
190 ELSE
191 itype = 0
192 CALL ancmsg(msgid=7,anmode=aninfo,msgtype=msgerror,
194 ENDIF
195
197 t_monvol(ii)%IVOLU(1) =
id
198 t_monvol(ii)%IVOLU(27) = -1
199 t_monvol(ii)%TYPE = itype
200 t_monvol(ii)%IVOLU(2) = itype
201 t_monvol(ii)%TITLE = trim(titr)
202
203 WRITE(iout,1001)
id, t_monvol(ii)%TITLE, key(1:len_trim(key))
204
205 SELECT CASE(itype)
206 CASE(1)
207
208
209
211 . unitab, local_uid, igrsurf,
212 . itab, x, pm, geo, ixc, ixtg,lsubmodel)
213 CASE(2)
214
215
216
218 . unitab, local_uid, npc, igrsurf,
219 . itab, x, pm, geo, ixc, ixtg,lsubmodel)
220 CASE(3)
221
222
223
225 . unitab, local_uid, npc, igrsurf,
226 . itab, x, pm, geo, ixc, ixtg, lsubmodel)
227 CASE(4)
228
229
230
232 . sensors, npt, pld, unitab, local_uid, npc, igrsurf,
233 . itab, x, pm, geo, ixc, ixtg, lsubmodel)
234 CASE(5)
235
236
237
239 . sensors, npt, pld,
240 . unitab, local_uid, npc, igrsurf, itab, x, pm, geo, ixc, ixtg,
241 . lsubmodel)
242 CASE(6)
243
244
245
247 . sensors, npt, pld, igrbric,
248 . unitab, npc, igrsurf, itab, x, pm, geo, ixc, ixtg,
249 . lsubmodel)
250 CASE(7)
251
252
253
255 . sensors,
256 . unitab, local_uid, npc, igrsurf, itab, x, pm, geo, ixc, ixtg,
257 . lsubmodel)
258 CASE(8)
259
260
261
263 . sensors, iframe, xframe, igrbric,
264 . unitab, local_uid, npc, igrsurf, itab, x, pm, geo, ixc, ixtg,
265 . lsubmodel)
266
267 CASE(9)
268
269
270
272 . sensors,
273 . unitab, local_uid, npc, igrsurf, itab, x, pm, geo, ixc, ixtg,
274 . lsubmodel)
275 CASE(10)
276
277
278
280 . unitab, npc, igrsurf, itab, x, pm, geo, ixc, ixtg,lsubmodel)
281 CASE(11)
282
283
284
286 . sensors, xframe, igrbric,
287 . unitab, local_uid, npc, igrsurf, itab, x, pm, geo, ixc, ixtg,
288 . lsubmodel)
289 END SELECT
290 ENDDO
291
292 nvolu = nvolu + nmonvol
293
294 RETURN
295 1000 FORMAT(
296 . //,' MONITORED VOLUME DEFINITION '/
297 . ' ---------------------------- ')
298 1001 FORMAT(//5x,'VOLUME NUMBER ',i10,
299 . / 5x,'------------------------',
300 . / 5x,'TITLE: ',a,
301 . / 5x,'TYPE OF MONITORED VOLUME. . . . . . . .=',a10)
subroutine hm_option_start(entity_type)
subroutine hm_read_monvol_type10(t_monvoln, unitab, npc, igrsurf, itab, x, pm, geo, ixc, ixtg, lsubmodel)
subroutine hm_read_monvol_type11(t_monvoln, ipm, igeo, itabm1, sensors, xframe, igrbric, unitab, luid, npc, igrsurf, itab, x, pm, geo, ixc, ixtg, lsubmodel)
subroutine hm_read_monvol_type1(t_monvoln, unitab, luid, igrsurf, itab, x, pm, geo, ixc, ixtg, lsubmodel)
subroutine hm_read_monvol_type2(t_monvoln, unitab, luid, npc, igrsurf, itab, x, pm, geo, ixc, ixtg, lsubmodel)
subroutine hm_read_monvol_type3(t_monvoln, unitab, luid, npc, igrsurf, itab, x, pm, geo, ixc, ixtg, lsubmodel)
subroutine hm_read_monvol_type4(t_monvoln, itabm1, sensors, npt, pld, unitab, luid, npc, igrsurf, itab, x, pm, geo, ixc, ixtg, lsubmodel)
subroutine hm_read_monvol_type5(t_monvoln, t_monvol_metadata, itabm1, sensors, npt, pld, unitab, luid, npc, igrsurf, itab, x, pm, geo, ixc, ixtg, lsubmodel)
subroutine hm_read_monvol_type6(t_monvoln, sensors, npt, pld, igrbric, unitab, npc, igrsurf, itab, x, pm, geo, ixc, ixtg, lsubmodel)
subroutine hm_read_monvol_type7(t_monvoln, ipm, igeo, itabm1, sensors, unitab, luid, npc, igrsurf, itab, x, pm, geo, ixc, ixtg, lsubmodel)
subroutine hm_read_monvol_type8(t_monvoln, ipm, igeo, itabm1, sensors, iframe, xframe, igrbric, unitab, luid, npc, igrsurf, itab, x, pm, geo, ixc, ixtg, lsubmodel)
subroutine hm_read_monvol_type9(t_monvoln, t_monvol_metadata, ipm, igeo, itabm1, sensors, unitab, luid, npc, igrsurf, itab, x, pm, geo, ixc, ixtg, lsubmodel)
integer, parameter nchartitle
integer, parameter ncharkey
integer, dimension(:), allocatable tagmon
subroutine hm_sz_r2r(tag, val, lsubmodel)
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)