OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
read_monvol.F File Reference
#include "implicit_f.inc"
#include "com04_c.inc"
#include "scr17_c.inc"
#include "r2r_c.inc"
#include "param_c.inc"
#include "units_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine read_monvol (t_monvol, t_monvol_metadata, itab, itabm1, ipm, igeo, x, pm, geo, ixc, ixtg, sensors, unitab, npc, npt, pld, igrsurf, igrbric, nom_opt, iframe, xframe, lsubmodel)

Function/Subroutine Documentation

◆ read_monvol()

subroutine read_monvol ( type(monvol_struct_), dimension(nvolu + nmonvol), intent(inout) t_monvol,
type(monvol_metadata_), intent(inout) t_monvol_metadata,
integer, dimension(*), intent(in) itab,
integer, dimension(*), intent(in) itabm1,
integer, dimension(npropmi, nummat), intent(in) ipm,
integer, dimension(npropgi, numgeo), intent(in) igeo,
dimension(3, numnod), intent(in) x,
dimension(npropm, nummat), intent(in) pm,
dimension(npropg, numgeo), intent(in) geo,
integer, dimension(nixc, numelc), intent(in) ixc,
integer, dimension(nixtg, numeltg), intent(in) ixtg,
type (sensors_), intent(in) sensors,
type(unit_type_), intent(in) unitab,
integer, dimension(*), intent(in) npc,
integer, dimension(*), intent(in) npt,
dimension(2, *), intent(in) pld,
type (surf_), dimension(nsurf), intent(inout) igrsurf,
type (group_), dimension(ngrbric), intent(in) igrbric,
integer, dimension(lnopt1, *), intent(inout) nom_opt,
integer, dimension(liskn,*), intent(in) iframe,
dimension(nxframe,*), intent(in) xframe,
type (submodel_data), dimension(nsubmod), intent(in) lsubmodel )

Definition at line 62 of file read_monvol.F.

66C-----------------------------------------------
67C M o d u l e s
68C-----------------------------------------------
69 USE unitab_mod
70 USE r2r_mod
71 USE message_mod
72 USE groupdef_mod , only:group_,surf_
74 USE submodel_mod
76 USE sensor_mod
89C-----------------------------------------------
90C I m p l i c i t T y p e s
91C-----------------------------------------------
92#include "implicit_f.inc"
93C-----------------------------------------------
94C C o m m o n B l o c k s
95C-----------------------------------------------
96C NVOLU
97#include "com04_c.inc"
98C KMONVO, IREC
99#include "scr17_c.inc"
100C NSUBDOM
101#include "r2r_c.inc"
102C NIMV, NRVOLU
103#include "param_c.inc"
104C LUNIT, NUNITS
105C IOUT
106#include "units_c.inc"
107C-----------------------------------------------
108C D u m m y A r g u m e n t s
109C-----------------------------------------------
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
123C-----------------------------------------------
124C L o c a l V a r i a b l e s
125C-----------------------------------------------
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
131C-----------------------------------------------
132C B e g i n n i n g o f s o u r c e
133C-----------------------------------------------
134C Beginning of MONVOL cards in the IIN file
135 WRITE(iout, 1000)
136 t_monvol_metadata%LCA = 0
137 nvb = 0
138C
139! ************************** !
140! MONVOL read with hm reader !
141! ************************** !
142 CALL hm_option_start('/MONVOL')
143 DO ii = 1, nmonvol
144 nvb = nvb + 1
145C Multidomain -> skip untagged monvols
146 IF (nsubdom > 0) THEN
147 IF( tagmon(nvb) == 0) THEN
148 CALL hm_sz_r2r(tagmon, nvb, lsubmodel)
149 ENDIF
150 ENDIF
151 CALL hm_option_read_key(lsubmodel, option_id = id, unit_id = uid, option_titr = titr,
152 . keyword2 = key)
153 nom_opt(1, ii) = id
154 CALL fretitl(titr,nom_opt(lnopt1-ltitr+1,ii),ltitr)
155C Check units
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 itype = 10
190 ELSE
191 itype = 0
192 CALL ancmsg(msgid=7,anmode=aninfo,msgtype=msgerror,
193 . i1=id,c1=titr)
194 ENDIF
195
196 t_monvol(ii)%ID = id
197 t_monvol(ii)%IVOLU(1) = id
198 t_monvol(ii)%IVOLU(27) = -1 !ID_DT_OPTION ( /DT/FVMBAG/[id_dt_option] )
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! /MONVOL/AREA !
209! ************ !
210 CALL hm_read_monvol_type1(t_monvol(ii),
211 . unitab, local_uid, igrsurf,
212 . itab, x, pm, geo, ixc, ixtg,lsubmodel)
213 CASE(2)
214! ************ !
215! /MONVOL/PRES !
216! ************ !
217 CALL hm_read_monvol_type2(t_monvol(ii),
218 . unitab, local_uid, npc, igrsurf,
219 . itab, x, pm, geo, ixc, ixtg,lsubmodel)
220 CASE(3)
221! *********** !
222! /MONVOL/GAS !
223! *********** !
224 CALL hm_read_monvol_type3(t_monvol(ii),
225 . unitab, local_uid, npc, igrsurf,
226 . itab, x, pm, geo, ixc, ixtg, lsubmodel)
227 CASE(4)
228! ************** !
229! /MONVOL/AIRBAG !
230! ************** !
231 CALL hm_read_monvol_type4(t_monvol(ii), itabm1,
232 . sensors, npt, pld, unitab, local_uid, npc, igrsurf,
233 . itab, x, pm, geo, ixc, ixtg, lsubmodel)
234 CASE(5)
235! ************* !
236! /MONVOL/COMMU !
237! ************* !
238 CALL hm_read_monvol_type5(t_monvol(ii), t_monvol_metadata, itabm1,
239 . sensors, npt, pld,
240 . unitab, local_uid, npc, igrsurf, itab, x, pm, geo, ixc, ixtg,
241 . lsubmodel)
242 CASE(6)
243! ************** !
244! /MONVOL/FVMBAG !
245! ************** !
246 CALL hm_read_monvol_type6(t_monvol(ii),
247 . sensors, npt, pld, igrbric,
248 . unitab, npc, igrsurf, itab, x, pm, geo, ixc, ixtg,
249 . lsubmodel)
250 CASE(7)
251! *************** !
252! /MONVOL/AIRBAG1 !
253! *************** !
254 CALL hm_read_monvol_type7(t_monvol(ii), ipm, igeo, itabm1,
255 . sensors,
256 . unitab, local_uid, npc, igrsurf, itab, x, pm, geo, ixc, ixtg,
257 . lsubmodel)
258 CASE(8)
259! *************** !
260! /MONVOL/FVMBAG1 !
261! *************** !
262 CALL hm_read_monvol_type8(t_monvol(ii), ipm, igeo, itabm1,
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! /MONVOL/COMMU1 !
270! ************** !
271 CALL hm_read_monvol_type9(t_monvol(ii), t_monvol_metadata, ipm, igeo, itabm1,
272 . sensors,
273 . unitab, local_uid, npc, igrsurf, itab, x, pm, geo, ixc, ixtg,
274 . lsubmodel)
275 CASE(10)
276! ************** !
277! /MONVOL/LFLUID !
278! ************** !
279 CALL hm_read_monvol_type10(t_monvol(ii),
280 . unitab, npc, igrsurf, itab, x, pm, geo, ixc, ixtg,lsubmodel)
281 CASE(11)
282! *************** !
283! /MONVOL/FVMBAG2 !
284! *************** !
285 CALL hm_read_monvol_type11(t_monvol(ii), ipm, igeo, itabm1,
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)
#define my_real
Definition cppsort.cpp:32
subroutine hm_option_start(entity_type)
initmumps id
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
Definition r2r_mod.F:132
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)
Definition message.F:889
subroutine fretitl(titr, iasc, l)
Definition freform.F:620