40 1 NOM_OPT ,UNITAB ,IGRPART ,IPART ,TAGPRT_FRIC,
41 2 TABCOUPLEPARTS_FRIC_TMP,TABCOEF_FRIC_TMP,INTBUF_FRIC_TAB ,
43 3 IFLAG ,COEFSLEN ,IORTHFRICMAX ,IFRICORTH_TMP ,NGRPF ,
44 4 LENGRPF ,LENG ,NSETMAX ,LSUBMODEL )
56 USE reader_old_mod ,
ONLY : irec
60#include "implicit_f.inc"
70 TYPE (UNIT_TYPE_),
INTENT(IN) ::UNITAB
71 INTEGER NOM_OPT(LNOPT1,*)
72 INTEGER IFLAG ,NSETFRICTOT ,COEFSLEN ,IORTHFRICMAX ,NGRPF ,LENG ,NSETMAX
73 INTEGER IPART(LIPART1,*) ,TAGPRT_FRIC(*),
74 . TABCOUPLEPARTS_FRIC_TMP(NINTERFRIC,*),IFRICORTH_TMP(NINTERFRIC,*),
77 my_real tabcoef_fric_tmp(ninterfric,*)
79 TYPE(intbuf_fric_struct_) INTBUF_FRIC_TAB(*)
80 TYPE (SUBMODEL_DATA),
DIMENSION(*),
INTENT(IN) :: LSUBMODEL
82 TYPE (GROUP_) ,
DIMENSION(NGRPART) :: IGRPART
86 INTEGER NIF ,NIN , NSET ,NGRPF0 ,NOINTF ,SUB_ID ,UID ,IFLAGUNIT ,J
87 CHARACTER(LEN=NCHARTITLE) :: TITR
97 IF(iflag==1)
WRITE(iout,1000)
113 . option_id = nointf,
115 . submodel_id = sub_id,
116 . option_titr = titr)
122 IF (unitab%UNIT_ID(j) == uid)
THEN
127 IF (uid/=0.AND.iflagunit==0)
THEN
128 CALL ancmsg(msgid=659,anmode=aninfo,msgtype=msgerror,
129 . i2=uid,i1=nointf,c1=
'FRITION',
144 1 nif ,nom_opt ,titr ,unitab ,igrpart ,
145 2 ipart ,nset ,tagprt_fric ,tabcoupleparts_fric_tmp,tabcoef_fric_tmp,
146 3 intbuf_fric_tab(nif)%FRICMOD,intbuf_fric_tab(nif)%IFFILTER ,
147 . intbuf_fric_tab(nif)%XFILTR_FRIC,intbuf_fric_tab(nif)%FRICFORM ,
148 4 iflag ,intbuf_fric_tab(nif)%IORTHFRIC,ifricorth_tmp ,ngrpf ,
149 5 lengrpf ,leng ,nointf , lsubmodel )
152 nset = ngrpf - ngrpf0
154 nsetfrictot = nsetfrictot + nset
155 nsetmax =
max(nsetmax,nset)
156 intbuf_fric_tab(nif)%NSETPRTS = nset
157 iorthfricmax =
max(iorthfricmax,intbuf_fric_tab(nif)%IORTHFRIC)
159 nsetfrictot = nsetfrictot + nset
160 intbuf_fric_tab(nif)%NSETPRTS = nset
161 nsetmax =
max(nsetmax,nset)
162 iorthfricmax =
max(iorthfricmax,intbuf_fric_tab(nif)%IORTHFRIC)
171 1000
FORMAT( /1x,
' FRICTION INTERFACES ' /
172 . 1x,
' -------------------- '// )
subroutine hm_option_read_key(lsubmodel, option_id, unit_id, submodel_index, submodel_id, option_titr, keyword1, keyword2, keyword3, keyword4, opt_pos)
subroutine hm_read_friction(nif, nom_opt, titr, unitab, igrpart, ipart, nset, tagprt_fric, tabcoupleparts_fric_tmp, tabcoef_fric_tmp, mfrot, ifq, xfiltr, fricform, iflag, orthfric, ifricorth_tmp, ngrpf, lengrpf, leng, nointf, lsubmodel)
subroutine hm_read_friction_models(nom_opt, unitab, igrpart, ipart, tagprt_fric, tabcoupleparts_fric_tmp, tabcoef_fric_tmp, intbuf_fric_tab, nsetfrictot, iflag, coefslen, iorthfricmax, ifricorth_tmp, ngrpf, lengrpf, leng, nsetmax, 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)