45 . UNITAB ,LSUBMODEL ,TABLE )
57 USE hm_read_visc_plas_mod
61#include "implicit_f.inc"
68#include "tablen_c.inc"
72 TYPE (UNIT_TYPE_),
INTENT(IN) ::UNITAB
73 INTEGER ,
DIMENSION(NPROPMI,NUMMAT)INTENT(INOUT) :: IPM
74 my_real ,
DIMENSION(*) ,
INTENT(INOUT) :: bufmat
77 TYPE(matparam_struct_) ,
DIMENSION(NUMMAT) ,
INTENT(INOUT) :: MAT_PARAM
81 INTEGER I,NV,IMAT,MAT_ID,IMID,ILAW,IVISC,UID,IUNIT,,
82 . n_net,iadd,hm_nvisc,flagmat,imatvis
83 CHARACTER(LEN=NCHARKEY)::KEY
101 . option_id = mat_id ,
111 IF (imid == mat_id)
THEN
116 IF (mat_id > 0 .AND. flagmat == 0)
THEN
117 CALL ancmsg(msgid=1663,anmode=aninfo,msgtype=msgerror,
127 DO iunit=1,unitab%NUNITS
128 IF (unitab%UNIT_ID(iunit) == uid)
THEN
133 IF (uid > 0 .AND. flagunit == 0)
THEN
134 CALL ancmsg(msgid=659,anmode=aninfo,msgtype=msgerror,
138 . c2=
'VISCOSITY MODEL',
147 IF (imid == mat_id)
THEN
148 WRITE(iout,1000) trim(key),mat_id
153 IF (key(1:5) ==
'PRONY')
THEN
157 . mat_param(imat)%VISC,ivisc ,
158 . ntable ,table ,mat_id ,unitab ,lsubmodel)
160 IF (imatvis > 0)
THEN
166 ELSE IF (key(1:6) ==
'LPRONY')
THEN
170 . mat_param(imat)%VISC,ivisc ,mat_id ,unitab ,lsubmodel)
172 ELSE IF (key(1:6) ==
'PLAS')
THEN
175 CALL hm_read_visc_plas(
176 . mat_param(imat)%VISC,ivisc ,iout, unitab ,lsubmodel)
179 mat_param(imat)%IVISC = ivisc
181 IF (ivisc == 1 .AND. ilaw == 100)
THEN
183 n_net = nint(bufmat(iadd) )
184 IF (n_net /= 0)
CALL ancmsg(msgid=1568 ,msgtype=msgerror,
185 . anmode=aninfo_blind_2, i1=imid )
190 ipm(216 ,i) = imatvis
192! ipm(225 ,i) = mat_param(imat)%VISC%NUVAR
204 & 5x,
'VISCOSITY MODEL: ',5x,a,/,
205 & 5x,
'MATERIAL ID . . . . . . . . . . . .=',i10/)
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)