75 SUBROUTINE updmat(BUFMAT ,PM ,IPM ,TABLE ,FUNC_ID ,
76 . NPC ,PLD ,SENSORS ,NLOC_DMG ,MLAW_TAG ,
87 USE law19_upd_mod ,
ONLY : law19_upd
88 USE law81_upd_mod ,
ONLY : law81_upd
89 USE law87_upd_mod ,
ONLY : law87_upd
90 USE law129_upd_mod ,
ONLY : law129_upd
91 USE law133_upd_mod ,
ONLY : law133_upd
92 USE law163_upd_mod ,
ONLY : law163_upd
93 USE law190_upd_mod ,
ONLY : law190_upd
96 USE eosfun_usr2sys_mod ,
ONLY : eosfun_usr2sys
100#include "implicit_f.inc"
104#include "units_c.inc"
105#include "param_c.inc"
106#include "scr17_c.inc"
107#include "scr19_c.inc"
108#include "com04_c.inc"
109#include "tabsiz_c.inc"
113 INTEGER NPC(SNPC), FUNC_ID(NFUNCT)
114 INTEGER,
DIMENSION(NPROPMI,NUMMAT) ,
INTENT(INOUT) :: IPM
115 my_real pm(npropm,nummat), pld(stf),bufmat(sbufmat)
117 TYPE(
mlaw_tag_),
TARGET,
DIMENSION(NUMMAT) :: MLAW_TAG
118 TYPE(
ttable),
DIMENSION(NTABLE) ,
INTENT(INOUT) :: TABLE
119 TYPE (NLOCAL_STR_) :: NLOC_DMG
120 TYPE (SENSORS_) ,
INTENT(IN) :: SENSORS
121 TYPE(matparam_struct_) ,
DIMENSION(NUMMAT),
INTENT(INOUT) ,
TARGET :: MAT_PARAM
125 INTEGER IMAT,ILAW,IRUP,MAT_ID,IADD,IFC,FLAG_HE,NFUNC,NFUNCL,NUMTABL,
126 . NPARAM,NUPARF,NFAIL,IR,FLAG_FIT,IFAILG,
127 . nprony,j,itype_visc,form
129 INTEGER,
DIMENSION(NUMMAT) :: ,GURSON
130 INTEGER,
DIMENSION(MAXTAB) :: TABLE_ID
131 INTEGER,
DIMENSION(:),
POINTER :: IFUNC,ITABLE
132 my_real,
DIMENSION(:),
POINTER :: uparam,uparf
134 CHARACTER(LEN=NCHARTITLE)::TITR, TITLE
135 TYPE() ,
POINTER :: MATPARAM
136 TYPE () ,
POINTER :: VISC
141 mullins(1:nummat) = 0
144 ilaw = mat_param(imat)%ILAW
145 nfail = mat_param(imat)%NFAIL
147 mtag => mlaw_tag(imat)
149 irup = mat_param(imat)%FAIL(ir)%IRUPT
150 IF (irup == 33 .AND. ilaw /=100 .AND. ilaw /=95 .AND. ilaw/=92)
THEN
151 CALL ancmsg(msgid=1769, msgtype=msgerror, anmode=aninfo_blind_1,
155 IF (irup == 33 .AND. (ilaw ==100 .OR. ilaw ==95 .OR. ilaw==92))
THEN
157 ELSEIF (irup == 35 .and. ilaw==104)
THEN
158 IF (gurson(imat) == 0)
THEN
162 CALL ancmsg(msgid=1650,msgtype=msgerror,
165 ELSE IF (irup == 14)
THEN
167 ELSE IF (irup == 28)
THEN
170 ELSE IF (irup == 10 .OR. irup == 11 .OR. irup == 13 .OR. irup == 30 .OR.
171 . irup == 41 .OR. irup == 42 .OR. irup == 44 .OR. irup == 45 .OR.
172 . irup == 46 .OR. irup == 47 .OR. irup == 50 .OR. irup == 51)
THEN
176 ELSE IF (irup == 48)
THEN
188 mat_id = mat_param(imat)%MAT_ID
189 ilaw = mat_param(imat)%ILAW
192 nfunc_eos = mat_param(imat)%EOS%NFUNC
193 IF(nfunc_eos > 0)
THEN
194 title = mat_param(imat)%EOS%title
195 CALL eosfun_usr2sys(title,mat_id,nfunc_eos,mat_param(imat)%EOS%FUNC,func_id, nfunct )
199 IF (ilaw < 29.and.ilaw/=19.or.ilaw==32.or.ilaw==43.or.ilaw==49.or.ilaw==52.or.
200 . ilaw==57.or.ilaw==59.or.ilaw==60.or.ilaw==65.or.ilaw==75.or.
203 CALL fretitl2(titr,ipm(npropmi-ltitr+1,imat),ltitr)
205 iadd =
max(1,ipm(7,imat))
206 nparam =
min(ipm(9,imat),sbufmat)
207 uparam => bufmat(iadd:iadd+nparam-1)
209 itype_visc = mat_param(imat)%IVISC
211 IF (itype_visc == 2)
THEN
212 visc => mat_param(imat)%VISC
213 nprony = visc%IPARAM(1)
214 form = visc%IPARAM(2)
218 gama_inf = gama_inf - visc%UPARAM(j)
220 gama_inf =
max(em20, gama_inf)
223 gama_inf =
min(gama_inf
229 nfunc = ipm(10 ,imat)
230 numtabl = ipm(226,imat)
231 ifunc => ipm(10+1:10+nfunc,imat)
232 itable => ipm(226+1:226+numtabl,imat)
238 IF (ilaw /= 73 .and. ilaw /= 74 .and. ilaw /= 80)
THEN
239 IF (numtabl > 0 )
THEN
240 table_id(1:numtabl) = ipm(226+1:226+numtabl,imat)
249 CALL law19_upd(mat_param(imat),sensors)
252 mtag => mlaw_tag(imat)
253 CALL law36_upd(iout ,titr ,mat_id ,nparam,uparam ,
254 . nfunc ,ifunc ,func_id,npc ,pld ,
258 CALL law42_upd(mat_param(imat),iout,titr,mat_id,pm(1,imat),gama_inf)
262 ifunc => ipm(10+1:10+nfunc+nfuncl,imat)
263 CALL law58_upd(mat_param(imat),titr,npc,pld,
264 . nfunc,nfuncl,ifunc,mat_id,func_id,
265 . pm(1,imat),sensors)
268 CALL law62_upd(iout,titr,mat_id,nparam,uparam, pm(1,imat),gama_inf)
271 CALL law69_upd(iout, titr , mat_id, uparam, nfunc,nfunct,
272 . ifunc, func_id , npc , pld ,
273 . pm(1,imat),ipm(1,imat),gama_inf)
278 CALL law70_upd(mat_param(imat) ,titr ,mat_id ,nparam ,uparam ,
279 . nfunc ,ifunc ,npc ,pld ,iout ,
280 . nfunct ,func_id ,npropm ,pm(1,imat))
283 CALL law76_upd(iout ,titr ,mat_id ,nparam ,mat_param(imat) ,
284 . uparam ,numtabl ,itable ,table ,nfunc ,
289 CALL law77_upd(titr ,mat_id ,nparam ,mat_param(imat) ,
290 . uparam ,nfunc ,ifunc ,npc ,pld )
294 CALL law81_upd(mat_param(imat) ,nfunc ,ifunc ,npc ,snpc ,
295 . pld ,stf ,pm(1,imat),npropm,iout ,
300 flag_fit = mat_param(imat)%IPARAM(3)
301 IF (flag_fit == 1)
THEN
302 CALL law87_upd(iout ,titr ,mat_id ,mat_param(imat) )
308 . nfunc,ifunc,mat_id,func_id,pm(1,imat),
314 . ipm(1,imat),func_id,npc,pld,pm(1,imat),
320 uparam(13) = mullins(imat)
323 CALL law92_upd(iout ,titr ,mat_id ,uparam ,nfunc ,nfunct,
324 . ifunc ,func_id ,npc ,pld ,pm(1,imat),ipm(1,imat))
328 uparam(21) = mullins(imat)
333 uparam(3) = mullins(imat)
334 IF (flag_he == 2 )
THEN
338 . ifunc, func_id , npc , pld , pm(1,imat))
340 ELSEIF(flag_he == 13 )
THEN
342 . ifunc, func_id , npc , pld , pm(1,imat))
350 nuparf = mat_param(imat)%FAIL(ir)%NUPARAM
351 uparf => mat_param(imat)%FAIL(ir)%UPARAM(1:nuparf)
353 CALL law104_upd(ifailg ,nparam,nuparf,uparam,uparf ,
354 . nloc_dmg,imat ,mlaw_tag(imat),ipm ,
360 . nfunc,ifunc,mat_id,func_id,
364 IF (mat_param(imat)%NLOC > 0)
THEN
365 mlaw_tag(imat)%NUVAR = 1
373 CALL law111_upd(iout ,titr ,mat_id ,uparam ,nfunc ,
374 . ifunc ,func_id ,npc ,pld ,pm(1,imat),ipm(1,imat))
379 . numtabl,itable,table,mat_id)
383 . nfunc,ifunc,mat_id,func_id,
387 CASE (114) ! spring material------------------
389 . nfunc,ifunc,mat_id,func_id,
393 CALL law119_upd(nparam ,numtabl ,itable ,table ,table_id,
394 . uparam,pm(1,imat),titr ,mat_id )
397 CALL law120_upd(nparam ,numtabl ,itable ,table ,uparam)
400 CALL law129_upd(mat_param(imat),sensors)
403 CALL law133_upd(mat_param(imat),pm(1,imat),npropm)
407 ifunc => ipm(10+1:10+nfunc+nfuncl,imat)
409 . nfunc,nfuncl,ifunc,mat_id,func_id,
410 . pm(1,imat),sensors)
413 CALL law163_upd(mat_param(imat),pm(1,imat),npropm)
416 CALL law190_upd(mat_param(imat) ,numtabl ,itable ,table ,pm