46
47
48
51 USE matparam_def_mod
57 USE hm_read_visc_plas_mod
58
59
60
61#include "implicit_f.inc"
62
63
64
65#include "com04_c.inc"
66#include "param_c.inc"
67#include "units_c.inc"
68#include "tablen_c.inc"
69
70
71
72 TYPE (UNIT_TYPE_),INTENT(IN) ::UNITAB
73 INTEGER ,DIMENSION(NPROPMI,NUMMAT) ,INTENT(INOUT) :: IPM
74 my_real ,
DIMENSION(*) ,
INTENT(INOUT) :: bufmat
75 TYPE(SUBMODEL_DATA) ,DIMENSION(*) ,INTENT(IN) :: LSUBMODEL
76 TYPE(TTABLE) TABLE(NTABLE)
77 TYPE(MATPARAM_STRUCT_) ,DIMENSION(NUMMAT) ,INTENT(INOUT) :: MAT_PARAM
78
79
80
81 INTEGER I,NV,IMAT,MAT_ID,IMID,ILAW,IVISC,UID,IUNIT,FLAGUNIT,
82 . N_NET,IADD,HM_NVISC,FLAGMAT,IMATVIS
83 CHARACTER(LEN=NCHARKEY)::KEY
84
85
86
87
89
90
91
92
93
95
96
97
98 DO nv = 1,hm_nvisc
99
101 . option_id = mat_id ,
102 . unit_id = uid ,
103 . keyword2 = key )
104
105
106
107
108 flagmat = 0
109 DO imat=1,nummat-1
110 imid = ipm(1,imat)
111 IF (imid == mat_id) THEN
112 flagmat = 1
113 EXIT
114 ENDIF
115 ENDDO
116 IF (mat_id > 0 .AND. flagmat == 0) THEN
117 CALL ancmsg(msgid=1663,anmode=aninfo,msgtype=msgerror,
118 . i1= mat_id,
119 . c1='VISCOSITY',
120 . c2= key,
121 . c3='')
122 ENDIF
123
124
125
126 flagunit = 0
127 DO iunit=1,unitab%NUNITS
128 IF (unitab%UNIT_ID(iunit) == uid) THEN
129 flagunit = 1
130 EXIT
131 ENDIF
132 ENDDO
133 IF (uid > 0 .AND. flagunit == 0) THEN
134 CALL ancmsg(msgid=659,anmode=aninfo,msgtype=msgerror,
135 . i1= mat_id,
136 . i2= uid,
137 . c1='MATERIAL',
138 . c2='VISCOSITY MODEL',
139 . c3='')
140 ENDIF
141
142
143
144 DO i=1,nummat-1
145 imid = ipm(1,i)
146 ilaw = ipm(2,i)
147 IF (imid == mat_id) THEN
148 WRITE(iout,1000) trim(key),mat_id
149
150 imatvis = ipm(216,i)
152
153 IF (key(1:5) == 'PRONY')THEN
154
155 ivisc = 1
157 . mat_param(imat)%VISC,ivisc ,
158 . ntable ,table ,mat_id ,unitab ,lsubmodel)
159
160 IF (imatvis > 0) THEN
161 imatvis = 3
162 ELSE
163 imatvis = 1
164 END IF
165
166 ELSE IF (key(1:6) == 'LPRONY') THEN
167
168 ivisc = 2
170 . mat_param(imat)%VISC,ivisc ,mat_id ,unitab ,lsubmodel)
171
172 ELSE IF (key(1:6) == 'PLAS') THEN
173
174 ivisc = 3
175 CALL hm_read_visc_plas(
176 . mat_param(imat)%VISC,ivisc ,iout, unitab ,lsubmodel)
177 END IF
178
179 mat_param(imat)%IVISC = ivisc
180
181 IF (ivisc == 1 .AND. ilaw == 100) THEN
182 iadd = ipm(7,i)
183 n_net = nint(bufmat(iadd) )
184 IF (n_net /= 0)
CALL ancmsg(msgid=1568 ,msgtype=msgerror,
185 . anmode
186 ENDIF
187
188
189
190 ipm(216 ,i) = imatvis
191
192
193
194 ENDIF
195
196 END DO
197
198
199 ENDDO
200
201 RETURN
202
203 1000 FORMAT(//
204 & 5x,'VISCOSITY MODEL: ',5x,a,/,
205 & 5x,'MATERIAL ID . . . . . . . . . . . .=',i10/)
206
subroutine hm_option_count(entity_type, hm_option_number)
subroutine hm_option_start(entity_type)
subroutine hm_read_visc_lprony(visc, ivisc, mat_id, unitab, lsubmodel)
subroutine hm_read_visc_prony(visc, ivisc, ntable, table, mat_id, unitab, lsubmodel)
subroutine init_mat_keyword(matparam, keyword)
integer, parameter ncharkey
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)