OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
hm_read_inter_struct.F File Reference
#include "implicit_f.inc"
#include "units_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine hm_read_inter_struct (ipari, stfac, frigap, xfiltr, fric_p, igrnod, igrsurf, igrslin, npc, ilagm, unitab, i2rupt, areasl, ni, nom_opt, titr, def_inter, npc1, sensors, nom_optfric, intbuf_fric_tab, igrbric, noint, key, lsubmodel, tf, interfaces, snpc, snpc1, npari, nparir, npts, lnopt1, ltitr, ninter25, ngrnod, ngrbric, nsurf, nslin, itherm_fe, intheat)

Function/Subroutine Documentation

◆ hm_read_inter_struct()

subroutine hm_read_inter_struct ( integer, dimension(npari) ipari,
stfac,
frigap,
xfiltr,
fric_p,
type (group_), dimension(ngrnod), target igrnod,
type (surf_), dimension(nsurf), target igrsurf,
type (surf_), dimension(nslin), target igrslin,
integer, dimension(snpc) npc,
integer ilagm,
type (unit_type_), intent(in) unitab,
i2rupt,
areasl,
integer ni,
integer, dimension(lnopt1,*) nom_opt,
character(len=nchartitle) titr,
integer, dimension(100) def_inter,
integer, dimension(snpc1) npc1,
type (sensors_), intent(in) sensors,
integer, dimension(lnopt1,*) nom_optfric,
type(intbuf_fric_struct_), dimension(*) intbuf_fric_tab,
type (group_), dimension(ngrbric), target igrbric,
integer noint,
character(len=ncharkey) key,
type (submodel_data), dimension(nsubmod), intent(in) lsubmodel,
tf,
type (interfaces_), intent(inout) interfaces,
integer, intent(in) snpc,
integer, intent(in) snpc1,
integer, intent(in) npari,
integer, intent(in) nparir,
integer, intent(in) npts,
integer, intent(in) lnopt1,
integer, intent(in) ltitr,
integer, intent(inout) ninter25,
integer, intent(in) ngrnod,
integer, intent(in) ngrbric,
integer, intent(in) nsurf,
integer, intent(in) nslin,
integer, intent(in) itherm_fe,
integer, intent(inout) intheat )
Parameters
[in]nslinarray size (elem data structure)
[in]ltitrarray size NOM_OPT
[in]nparirarray size IPARI and FRIGAP
[in]snpc1array size (NPC and NPC1)

Definition at line 51 of file hm_read_inter_struct.F.

63C-----------------------------------------------
64C D e s r i p t i o n
65C-----------------------------------------------
66C CONTACT INTERFACES : READER SUBROUTINES
67C-----------------------------------------------
68C M o d u l e s
69C-----------------------------------------------
70 USE unitab_mod
71 USE message_mod
72 USE intbuf_fric_mod
73 USE groupdef_mod
75 USE sensor_mod
76 USE interfaces_mod
78C-----------------------------------------------
79C I m p l i c i t T y p e s
80C-----------------------------------------------
81#include "implicit_f.inc"
82C-----------------------------------------------
83C D u m m y A r g u m e n t s
84C-----------------------------------------------
85 INTEGER,INTENT(IN) :: NPTS !array size TF
86 INTEGER,INTENT(IN) :: NGRNOD,NGRBRIC,NSURF,NSLIN !< array size (elem data structure)
87 INTEGER,INTENT(IN) :: LNOPT1,LTITR !< array size NOM_OPT
88 INTEGER,INTENT(IN) :: NPARI, NPARIR !< array size IPARI and FRIGAP
89 INTEGER,INTENT(IN) :: SNPC, SNPC1 !< array size (NPC and NPC1)
90 INTEGER,INTENT(IN) :: ITHERM_FE
91 INTEGER,INTENT(INOUT) :: INTHEAT
92 INTEGER,INTENT(INOUT) :: NINTER25
93 TYPE (SUBMODEL_DATA), DIMENSION(NSUBMOD),INTENT(IN) :: LSUBMODEL
94 TYPE (UNIT_TYPE_),INTENT(IN) ::UNITAB
95 INTEGER NOM_OPT(LNOPT1,*), NOM_OPTFRIC(LNOPT1,*)
96 INTEGER ILAGM,NI,NOINT
97 INTEGER IPARI(NPARI),NPC(SNPC),DEF_INTER(100),NPC1(SNPC1)
98 my_real stfac,xfiltr,areasl
99 my_real frigap(nparir),fric_p(10),i2rupt(6),tf(npts)
100 CHARACTER(LEN=NCHARTITLE) :: TITR
101 TYPE(INTBUF_FRIC_STRUCT_) INTBUF_FRIC_TAB(*)
102 TYPE (SENSORS_) ,INTENT(IN) :: SENSORS
103C-----------------------------------------------
104 TYPE (GROUP_) ,TARGET, DIMENSION(NGRNOD) :: IGRNOD
105 TYPE (GROUP_) ,TARGET, DIMENSION(NGRBRIC) :: IGRBRIC
106 TYPE (SURF_) ,TARGET , DIMENSION(NSURF) :: IGRSURF
107 TYPE (SURF_) ,TARGET , DIMENSION(NSLIN) :: IGRSLIN
108 TYPE (INTERFACES_) ,INTENT(INOUT):: INTERFACES
109C-----------------------------------------------
110C C o m m o n B l o c k s
111C-----------------------------------------------
112#include "units_c.inc"
113C-----------------------------------------------
114C L o c a l V a r i a b l e s
115C-----------------------------------------------
116 INTEGER NTYP,ID_TYPE19
117 CHARACTER(LEN=NCHARKEY) :: KEY
118 LOGICAL IS_AVAILABLE
119!
120
121C=======================================================================
122C INTERFACES FOR SOLID AND STRUCTURE READING ROUTINES
123C=======================================================================
124
125 ntyp = 0
126C
127 ilagm = 0
128C
129 is_available = .false.
130C
131c flag from TYPE19 convert
132 id_type19 = 0
133 CALL hm_get_intv('ID_TYPE19',id_type19,is_available,lsubmodel)
134C
135 IF (id_type19 > 0) THEN
136C-- No printout for interfaces generated from type19 - noint set to id of the type19
137 noint = id_type19
138 ELSE
139 WRITE(iout,1000) noint,trim(titr)
140 ENDIF
141C
142 nom_opt(1,ni)=noint
143C
144C---------------------------------
145 CALL fretitl(titr,nom_opt(lnopt1-ltitr+1,ni),ltitr)
146
147C---------------------------------------------------------------
148C INTERFACES TYPE : READING ROUTINES
149C---------------------------------------------------------------
150
151 SELECT CASE(key(1:len_trim(key)))
152
153 CASE ('TYPE25')
154 ntyp=25
155 ninter25 = ninter25 +1
157 1 ipari ,stfac ,frigap ,noint ,ni ,
158 2 igrnod ,igrsurf ,xfiltr ,fric_p ,def_inter ,
159 3 sensors ,nom_opt ,unitab ,lsubmodel ,titr ,
160 4 nom_optfric ,intbuf_fric_tab ,npc ,npc1 ,tf ,
161 5 interfaces%PARAMETERS,npari ,nparir ,snpc ,snpc1 ,
162 6 npts ,itherm_fe ,intheat )
163
164 CASE ('TYPE24')
165 ntyp=24
167 1 ipari ,stfac ,frigap ,noint ,ni ,
168 2 igrnod ,igrsurf ,xfiltr ,fric_p ,def_inter ,
169 3 sensors ,nom_opt ,unitab ,lsubmodel ,titr ,
170 4 nom_optfric,intbuf_fric_tab,interfaces%PARAMETERS ,npari ,nparir ,
171 5 itherm_fe ,intheat)
172
173 CASE ('TYPE23')
174 ntyp=23
176 1 ipari ,stfac ,frigap ,noint ,
177 2 igrsurf ,xfiltr ,fric_p ,npc1 ,titr ,
178 3 lsubmodel ,unitab ,npari ,nparir ,snpc1 )
179
180 CASE ('TYPE21')
181 ntyp=21
183 1 ipari ,stfac ,frigap ,noint ,ni ,
184 2 igrsurf ,xfiltr ,fric_p ,npc1 ,sensors ,
185 3 nom_opt ,unitab ,lsubmodel ,titr ,npc ,
186 4 tf ,npari ,nparir ,snpc ,snpc1 ,
187 5 lnopt1 ,itherm_fe ,intheat ,nom_optfric,intbuf_fric_tab)
188
189 CASE ('TYPE20')
190 ntyp=20
192 1 ipari ,stfac ,frigap ,noint ,
193 2 igrnod ,igrsurf ,igrslin ,xfiltr ,fric_p ,
194 3 unitab ,lsubmodel ,titr )
195
196 CASE ('HERTZ')
197 ntyp = 17
198 ilagm = -1
200 1 ipari ,frigap ,noint ,ntyp ,
201 2 igrbric ,unitab ,lsubmodel ,titr )
202
203 CASE ('TYPE16')
204 ntyp = 16
205 ilagm = 1
206
207 CASE ('TYPE15')
208 ntyp = 15
210 1 ipari ,stfac ,frigap ,noint ,
211 2 igrsurf ,titr ,lsubmodel ,unitab )
212
213 CASE ('TYPE14')
214 ntyp = 14
216 1 ipari ,stfac ,frigap ,noint ,
217 2 igrnod ,igrsurf ,npc ,titr ,lsubmodel,
218 3 unitab )
219
220 CASE ('TYPE11')
221 ntyp = 11
223 1 ipari ,stfac ,frigap ,noint ,ni ,
224 2 igrslin ,sensors ,def_inter ,titr ,
225 3 nom_opt ,unitab ,lsubmodel ,nom_optfric,intbuf_fric_tab,
226 4 id_type19 ,npari ,nparir ,lnopt1 ,itherm_fe ,intheat)
227
228 CASE ('TYPE10')
229 ntyp = 10
231 . ipari ,stfac ,frigap ,igrnod ,igrsurf ,
232 . lsubmodel,unitab ,titr ,noint )
233
234 CASE ('TYPE8')
235 ntyp = 8
237 1 ipari ,stfac ,frigap ,noint ,
238 2 igrnod ,igrsurf ,unitab ,lsubmodel ,titr )
239
240 CASE ('TYPE7')
241 ntyp = 7
243 1 ipari ,stfac ,frigap ,noint ,ni ,
244 2 igrnod ,igrsurf ,xfiltr ,fric_p ,nom_opt ,
245 3 def_inter ,npc1 ,sensors ,unitab ,lsubmodel ,
246 4 titr ,nom_optfric,intbuf_fric_tab,npc ,tf ,
247 5 id_type19 ,npari ,nparir ,snpc ,snpc1 ,
248 6 lnopt1 ,npts ,itherm_fe ,intheat )
249
250 CASE ('TYPE6')
251 ntyp = 6
253 1 ipari ,stfac ,frigap ,noint ,
254 2 igrsurf ,npc1 ,titr ,lsubmodel ,unitab )
255
256 CASE ('TYPE5')
257 ntyp = 5
259 1 ipari ,stfac ,frigap ,noint ,ni ,
260 2 igrnod ,igrsurf ,nom_opt ,xfiltr ,fric_p ,
261 3 sensors ,unitab ,lsubmodel ,titr ,npari ,
262 4 nparir)
263
264 CASE ('TYPE4')
265 CALL ancmsg(msgid=1615,msgtype=msgerror,anmode=aninfo,i1=noint,c1=titr)
266
267 CASE ('TYPE3')
268 ntyp = 3
270 1 ipari ,stfac ,frigap ,noint ,
271 2 igrsurf ,unitab ,lsubmodel ,npari ,
272 3 nparir)
273
274 CASE ('TYPE2')
275 ntyp = 2
277 1 ipari ,stfac ,frigap ,noint ,igrnod ,
278 2 igrsurf ,i2rupt ,areasl ,def_inter ,npc1 ,
279 3 titr ,unitab ,lsubmodel ,npari ,nparir ,
280 4 snpc1 ,intheat )
281
282 END SELECT ! SELECT CASE(NTYP)
283C
284 ipari(33) = max(0,ilagm)
285C
286
287C=======================================================================
288 1000 FORMAT(/1x,' INTERFACE NUMBER :',i10,1x,a)
289C------------
290 RETURN
291
292
#define my_real
Definition cppsort.cpp:32
subroutine hm_get_intv(name, ival, is_available, lsubmodel)
subroutine hm_read_inter_hertz_type17(ipari, frigap, noint, ntyp, igrbric, unitab, lsubmodel, titr)
subroutine hm_read_inter_type02(ipari, stfac, frigap, noint, igrnod, igrsurf, i2rupt, areasl, def_inter, npc1, titr, unitab, lsubmodel, npari, nparir, snpc1, intheat)
subroutine hm_read_inter_type03(ipari, stfac, frigap, noint, igrsurf, unitab, lsubmodel, npari, nparir)
subroutine hm_read_inter_type05(ipari, stfac, frigap, noint, ni, igrnod, igrsurf, nom_opt, xfiltr, fric_p, sensors, unitab, lsubmodel, titr, npari, nparir)
subroutine hm_read_inter_type06(ipari, stfac, frigap, noint, igrsurf, npc1, titr, lsubmodel, unitab)
subroutine hm_read_inter_type07(ipari, stfac, frigap, noint, ni, igrnod, igrsurf, xfiltr, fric_p, nom_opt, def_inter, npc1, sensors, unitab, lsubmodel, titr, nom_optfric, intbuf_fric_tab, npc, tf, id_type19, npari, nparir, snpc, snpc1, lnopt1, npts, itherm_fe, intheat)
subroutine hm_read_inter_type08(ipari, stfac, frigap, noint, igrnod, igrsurf, unitab, lsubmodel, titr)
subroutine hm_read_inter_type10(ipari, stfac, frigap, igrnod, igrsurf, lsubmodel, unitab, titr, noint)
subroutine hm_read_inter_type11(ipari, stfac, frigap, noint, ni, igrslin, sensors, def_inter, titr, nom_opt, unitab, lsubmodel, nom_optfric, intbuf_fric_tab, id_type19, npari, nparir, lnopt1, itherm_fe, intheat)
subroutine hm_read_inter_type14(ipari, stfac, frigap, noint, igrnod, igrsurf, npc, titr, lsubmodel, unitab)
subroutine hm_read_inter_type15(ipari, stfac, frigap, noint, igrsurf, titr, lsubmodel, unitab)
subroutine hm_read_inter_type20(ipari, stfac, frigap, noint, igrnod, igrsurf, igrslin, xfiltr, fric_p, unitab, lsubmodel, titr)
subroutine hm_read_inter_type21(ipari, stfac, frigap, noint, ni, igrsurf, xfiltr, fric_p, npc1, sensors, nom_opt, unitab, lsubmodel, titr, npc, tf, npari, nparir, snpc, snpc1, lnopt1, itherm_fe, intheat, nom_optfric, intbuf_fric_tab)
subroutine hm_read_inter_type23(ipari, stfac, frigap, noint, igrsurf, xfiltr, fric_p, npc1, titr, lsubmodel, unitab, npari, nparir, snpc1)
subroutine hm_read_inter_type24(ipari, stfac, frigap, noint, ni, igrnod, igrsurf, xfiltr, fric_p, def_inter, sensors, nom_opt, unitab, lsubmodel, titr, nom_optfric, intbuf_fric_tab, parameters, npari, nparir, itherm_fe, intheat)
subroutine hm_read_inter_type25(ipari, stfac, frigap, noint, ni, igrnod, igrsurf, xfiltr, fric_p, def_inter, sensors, nom_opt, unitab, lsubmodel, titr, nom_optfric, intbuf_fric_tab, npc, npc1, tf, parameters, npari, nparir, snpc, snpc1, npts, itherm_fe, intheat)
subroutine i2rupt(x, v, a, ms, in, stifn, fsav, weight, irect, nsv, msr, irtl, irupt, crst, mmass, miner, smass, siner, area, uvar, xsm0, dsm, fsm, prop, ipari, nsn, nmn, nuvar, igtyp, pid, npf, tf, itab, fncont, pdama2, isym, inorm, h3d_data, fncontp, ftcontp)
Definition int2rupt.F:122
#define max(a, b)
Definition macros.h:21
integer, parameter nchartitle
integer, parameter ncharkey
integer nsubmod
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