78
79
80
85 USE matparam_def_mod
86 USE sensor_mod
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
94 USE visc_param_mod
96 USE eosfun_usr2sys_mod , ONLY : eosfun_usr2sys
97
98
99
100#include "implicit_f.inc"
101
102
103
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"
110
111
112
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)
116 TARGET ipm,bufmat
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
122
123
124
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) :: MULLINS,GURSON
130 INTEGER, DIMENSION(MAXTAB) :: TABLE_ID
131 INTEGER, DIMENSION(:), POINTER :: IFUNC,ITABLE
132 my_real,
DIMENSION(:),
POINTER :: uparam,uparf
133 TYPE(MLAW_TAG_), POINTER :: MTAG
134 CHARACTER(LEN=NCHARTITLE)::TITR, TITLE
135 TYPE(MATPARAM_STRUCT_) , POINTER :: MATPARAM
136 TYPE (VISC_PARAM_) , POINTER :: VISC
137 INTEGER :: NFUNC_EOS
138
139
140
141 mullins(1:nummat) = 0
142 gurson(1:nummat) = 0
143 DO imat=1,nummat
144 ilaw = mat_param(imat)%ILAW
145 nfail = mat_param(imat)%NFAIL
146 IF (nfail > 0) THEN
147 mtag => mlaw_tag(imat)
148 DO ir = 1,nfail
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,
152 . i1=imat,
153 . i2=ilaw)
154 ENDIF
155 IF (irup == 33 .AND. (ilaw ==100 .OR. ilaw ==95 .OR. ilaw==92)) THEN
156 mullins(imat) = ir
157 ELSEIF (irup == 35 .and. ilaw==104) THEN
158 IF (gurson(imat) == 0) THEN
159 gurson(imat) = ir
160 ELSE
161
162 CALL ancmsg(msgid=1650,msgtype=msgerror,
163 . anmode=aninfo_blind_1,i1=imat)
164 ENDIF
165 ELSE IF (irup == 14) THEN
166 mtag%G_DMG = 1
167 ELSE IF (irup == 28) THEN
168 mtag%G_DMG = 2
169
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
173 mtag%L_DMGSCL = 1
174 mtag%G_DMGSCL = 1
175
176 ELSE IF (irup == 48) THEN
177 mtag%G_DMGSCL = 6
178 mtag%L_DMGSCL = 6
179 ENDIF
180 ENDDO
181 ENDIF
182 ENDDO
183
184
185
186 DO imat=1,nummat
187
188 mat_id = mat_param(imat)%MAT_ID
189 ilaw = mat_param(imat)%ILAW
190
191
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 )
196 ENDIF
197
198
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.
201 . ilaw==78 ) cycle
202
203 CALL fretitl2(titr,ipm(npropmi-ltitr+1,imat),ltitr)
204
205 iadd =
max(1,ipm(7,imat))
206 nparam =
min(ipm(9,imat),sbufmat)
207 uparam => bufmat(iadd:iadd+nparam-1)
208
209 itype_visc = mat_param(imat)%IVISC
210 gama_inf = one
211 IF (itype_visc == 2) THEN
212 visc => mat_param(imat)%VISC
213 nprony = visc%IPARAM(1)
214 form = visc%IPARAM(2)
215 IF(form == 1) THEN
216 gama_inf = one
217 DO j=1,nprony
218 gama_inf = gama_inf - visc%UPARAM(j)
219 ENDDO
220 gama_inf =
max(em20, gama_inf)
221 ENDIF
222 ENDIF
223 gama_inf =
min(gama_inf, one)
224
225
226
227
228
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)
233
234 IF (nfunc > 0) THEN
236 ENDIF
237
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)
242 ENDIF
243 ENDIF
244
245
246 SELECT CASE (ilaw)
247
248 CASE (19)
249 CALL law19_upd(mat_param(imat),sensors)
250
251 CASE (36)
252 mtag => mlaw_tag(imat)
253 CALL law36_upd(iout ,titr ,mat_id ,nparam,uparam ,
254 . nfunc ,ifunc ,func_id,npc ,pld ,
255 . mtag ,nfunct )
256
257 CASE (42)
258 CALL law42_upd(mat_param(imat),iout,titr,mat_id,pm(1,imat),gama_inf)
259
260 CASE (58)
261 nfuncl = ipm(6,imat)
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)
266
267 CASE (62)
268 CALL law62_upd(iout,titr,mat_id,nparam,uparam, pm(1,imat),gama_inf)
269
270 CASE (69)
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)
274
275
276 CASE (70)
277
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))
281
282 CASE (76)
283 CALL law76_upd(iout ,titr ,mat_id ,nparam ,mat_param(imat) ,
284 . uparam ,numtabl ,itable ,table ,nfunc ,
285 . ifunc ,npc ,pld )
286
287
288 CASE (77)
289 CALL law77_upd(titr ,mat_id ,nparam ,mat_param(imat) ,
290 . uparam ,nfunc ,ifunc ,npc ,pld )
291
292
293 CASE (81)
294 CALL law81_upd(mat_param(imat) ,nfunc ,ifunc ,npc ,snpc ,
295 . pld ,stf ,pm(1,imat),npropm,iout ,
296 . mat_id ,titr )
297
298
299 CASE (87)
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) )
303 ENDIF
304
305 CASE (88)
306
308 . nfunc,ifunc,mat_id,func_id,pm(1,imat),
309 . nfunct )
310
311 CASE (90)
312
314 . ipm(1,imat),func_id,npc,pld,pm(1,imat),
315 . nfunct)
316
317 CASE (92)
318
319
320 uparam(13) = mullins(imat)
321 ifc = ipm(11,imat)
322 IF (ifc > 0) THEN
323 CALL law92_upd(iout ,titr ,mat_id ,uparam ,nfunc ,nfunct,
324 . ifunc ,func_id ,npc ,pld ,pm(1,imat),ipm(1,imat))
325 ENDIF
326
327 CASE (95)
328 uparam(21) = mullins(imat)
329
330 CASE (100)
331
332 flag_he = uparam(2)
333 uparam(3) = mullins(imat)
334 IF (flag_he == 2 )THEN
335 ifc = ipm(11,imat)
336 IF( ifc /=0 ) THEN
338 . ifunc, func_id , npc , pld , pm(1,imat))
339 ENDIF
340 ELSEIF(flag_he == 13 )THEN
342 . ifunc, func_id , npc , pld , pm(1,imat))
343 ENDIF
344
345 CASE (104)
346
347 ir = gurson(imat)
348 IF (ir > 0) THEN
349 ifailg = 1
350 nuparf = mat_param(imat)%FAIL(ir)%NUPARAM
351 uparf => mat_param(imat)%FAIL(ir)%UPARAM(1:nuparf)
352
353 CALL law104_upd(ifailg ,nparam,nuparf,uparam,uparf ,
354 . nloc_dmg,imat ,mlaw_tag(imat),ipm ,
355 . mat_param(imat))
356 ENDIF
357
358 CASE (108)
360 . nfunc,ifunc,mat_id,func_id,
361 . pm(1,imat))
362
363 CASE (109)
364 IF (mat_param(imat)%NLOC > 0) THEN
365 mlaw_tag(imat)%NUVAR = 1
366 ENDIF
367
368 CASE (111)
369
370
371 ifc = ipm(11,imat)
372 IF (ifc > 0) THEN
373 CALL law111_upd(iout ,titr ,mat_id ,uparam ,nfunc ,
374 . ifunc ,func_id ,npc ,pld ,pm(1,imat),ipm(1,imat))
375 ENDIF
376
377 CASE (112)
379 . numtabl,itable,table,mat_id)
380
381 CASE (113)
383 . nfunc,ifunc,mat_id,func_id,
384 . pm(1,imat))
385
386
387 CASE (114)
389 . nfunc,ifunc,mat_id,func_id,
390 . pm(1,imat))
391
392 CASE (119)
393 CALL law119_upd(nparam ,numtabl ,itable ,table ,table_id,
394 . uparam,pm(1,imat),titr ,mat_id )
395
396 CASE (120)
397 CALL law120_upd(nparam ,numtabl ,itable ,table ,uparam)
398
399 CASE (129)
400 CALL law129_upd(mat_param(imat),sensors)
401
402 CASE (133)
403 CALL law133_upd(mat_param(imat),pm(1,imat),npropm)
404
405 CASE (158)
406 nfuncl = ipm(6,imat)
407 ifunc => ipm(10+1:10+nfunc+nfuncl,imat)
409 . nfunc,nfuncl,ifunc,mat_id,func_id,
410 . pm(1,imat),sensors)
411
412 CASE (163)
413 CALL law163_upd(mat_param(imat),pm(1,imat),npropm)
414
415 CASE (190)
416 CALL law190_upd(mat_param(imat) ,numtabl ,itable ,table ,pm(1,imat),
417 . npropm, ntable)
418
419
420 END SELECT
421
422 ENDDO
423
424 RETURN
subroutine law100_upd_ab(iout, titr, mat_id, uparam, nfunc, ifunc, func_id, npc, pld, pm)
subroutine law100_upd_nht(iout, titr, mat_id, uparam, nfunc, ifunc, func_id, npc, pld, pm)
subroutine law104_upd(ifailg, nuparam, nuparf, uparam, uparf, nloc_dmg, imat, mlaw_tag, ipm, matparam)
subroutine law108_upd(iout, titr, uparam, npc, pld, nfunc, ifunc, mat_id, func_id, pm)
subroutine law111_upd(iout, titr, mat_id, uparam, nfunc, ifunc, func_id, npc, pld, pm, ipm)
subroutine law112_upd(titr, uparam, npc, pld, numtabl, itable, table, mat_id)
subroutine law113_upd(iout, titr, uparam, npc, pld, nfunc, ifunc, mat_id, func_id, pm)
subroutine law114_upd(iout, titr, uparam, npc, pld, nfunc, ifunc, mat_id, func_id, pm)
subroutine law119_upd(nuparam, numtabl, itable, table, table_id, uparam, pm, titr, mat_id)
subroutine law120_upd(nuparam, numtabl, itable, table, uparam)
subroutine law158_upd(mat_param, titr, npc, pld, nfunc, nfunl, ifunc, mat_id, func_id, pm, sensors)
subroutine law36_upd(iout, titr, mat_id, nuparam, uparam, nfunc, ifunc, func_id, npc, pld, mtag, nfunct)
subroutine law42_upd(mat_param, iout, titr, mat_id, pm, gama_inf)
subroutine law58_upd(mat_param, titr, npc, pld, nfunc, nfunl, ifunc, mat_id, func_id, pm, sensors)
subroutine law62_upd(iout, titr, mat_id, nuparam, uparam, pm, gama_inf)
subroutine law69_upd(iout, titr, mat_id, uparam, nfunc, nfunct, ifunc, func_id, npc, pld, pm, ipm, gama_inf)
subroutine law70_upd(mat_param, titr, mat_id, nuparam, uparam, nfunc, ifunc, npc, pld, iout, nfunct, func_id, npropm, pm)
subroutine law76_upd(iout, titr, mat_id, nuparam, matparam, uparam, numtabl, itable, table, nfunc, ifunc, npc, pld)
subroutine law77_upd(titr, mat_id, nuparam, mat_param, uparam, nfunc, ifunc, npc, pld)
subroutine law88_upd(iout, titr, uparam, npc, pld, nfunc, ifunc, mat_id, func_id, pm, nfunct)
subroutine law90_upd(iout, titr, mat_id, uparam, ipm, func_id, npc, pld, pm, nfunct)
subroutine law92_upd(iout, titr, mat_id, uparam, nfunc, nfunct, ifunc, func_id, npc, pld, pm, ipm)
subroutine matfun_usr2sys(titr, mat_id, nfunc, ifunc, func_id)
subroutine mattab_usr2sys(titr, mat_id, ntable, table, ntabl, itable)
integer, parameter nchartitle
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)