38 1 NEL ,NUPARAM ,NUVAR ,NFUNC ,IFUNC ,
39 2 NPF ,TABLE ,TF ,TIME ,UPARAM ,
40 3 NGL ,ALDT ,DPLA ,EPSP ,UVAR ,
41 4 SIGNXX ,SIGNYY ,SIGNZZ ,SIGNXY ,SIGNYZ ,SIGNZX ,
42 5 TEMP ,OFF ,DFMAX ,TDELE ,DMG_SCALE,
43 6 UELR ,IPG ,NPG ,LOFF ,NTABLF ,ITABLF ,
51#include "implicit_f.inc"
59#include "tabsiz_c.inc"
63 INTEGER,
INTENT(IN) :: NEL,NUPARAM,NUVAR,NGL(NEL)
64INTEGER,
DIMENSION(NTABLF) ,
INTENT(IN) :
65INTEGER,
INTENT(INOUT) :: NOFF(NEL)
66 my_real,
INTENT(IN) ::
67 . TIME,UPARAM(NUPARAM),ALDT(NEL),
68 . DPLA(NEL),EPSP(),TEMP(),
69 . SIGNXX(NEL),SIGNYY(NEL),SIGNZZ(NEL),
70 . signxy(nel),signyz(nel),signzx(nel),
72 my_real,
INTENT(INOUT) ::
73 . uvar(nel,nuvar),dfmax(nel),tdele(nel),
74 . dmg_scale(nel),off(nel),uelr(nel),
76 TYPE (TTABLE),
INTENT(IN),
DIMENSION(NTABLE) :: TABLE
80 INTEGER,
INTENT(IN) :: (),NFUNC,IFUNC()
81 my_real,
INTENT(IN) :: TF(STF)
88 INTEGER I,J,INDX(NEL),NINDX,ITAB_EPSF,FAILIP,
89 . itab_inst,itab_size,ireg,ipos(nel,3),
90 . ndim,ipos2(nel),iad(nel),ilen(nel),
91 . log_scale1,log_scale2
93 . fcrit ,dn,dcrit,
ecrit,exp_ref,expo,el_ref,
94 . sr_ref1,fscale_el,shrf,biaxf ,sr_ref2,
95 . fscale_sr,cjc,fscale_dlim,temp_ref, fscale_temp, volfrac
97 . lambda,fac,df,inst(nel) ,dc(nel) ,l0(nel)
98 . triax(nel) ,xi(nel) ,epsf(nel) ,epsl(nel) ,
100 . cos3theta ,det,p,svm ,sxx,syy,szz ,sizefac(nel),
101 . ratefac(nel),dsize(nel
102 . tempfac(nel),tempfac2(nel),dft(nel) ,var(nel)
109 failip =
min(nint(uparam(2)),npg)
115 ireg = nint(uparam(9))
118 fscale_el = uparam(12)
122 fscale_sr = uparam(16)
124 fscale_dlim = uparam(18)
125 temp_ref = uparam(19)
126 fscale_temp = uparam(20)
127 log_scale1 = nint(uparam(21))
128 log_scale2 = nint(uparam(22))
131 itab_epsf = itablf(1)
132 itab_inst = itablf(2)
133 itab_size = itablf(3)
138 IF ((itab_inst > 0).OR.(
ecrit > zero))
THEN
142 IF (uvar(i,2) == zero) uvar(i,2) = one
153 p = third*(signxx(i) + signyy(i) + signzz(i))
157 svm = half*(sxx**2 + syy**2 + szz**2)
158 . + signxy(i)**2 + signzx(i)**2 + signyz(i)**2
160 triax(i) = p/
max(em20,svm)
161 IF (triax(i) < -one) triax(i) = -one
162 IF (triax(i) > one) triax(i) = one
165 det = sxx*syy*szz + two*signxy(i)*signzx(i)*signyz(i)
166 . - sxx*signyz(i)**2-szz*signxy(i)**2 - syy*signzx(i)**2
167 cos3theta = half*twenty7*det/
max(em20,svm**3)
168 IF (cos3theta < -one) cos3theta = -one
169 IF (cos3theta > one) cos3theta = one
170 xi(i) = one - two*acos(cos3theta)/pi
178 IF (uvar(1,3) == zero) uvar(1:nel,3) = aldt(1:nel)
179 l0(1:nel) = uvar(1:nel,3)
182 IF (ifunc(1) > 0)
THEN
184 lambda = l0(i)/exp_ref
185 softexp(i) = finter(ifunc(1),lambda,npf,tf,df)
186 softexp(i) = expo*softexp(i)
189 softexp(1:nel) = expo
193 IF (ifunc(4) > 0)
THEN
194 var(1:nel) = temp(1:nel)/temp_ref
196 iad(1:nel) = npf(ifunc(4)) / 2 + 1
197 ilen(1:nel) = npf(ifunc(4)+1) / 2 - iad(1:nel) - ipos2(1:nel)
198 CALL vinter2(tf,iad,ipos2,ilen,nel,var,dft,tempfac)
199 tempfac(1:nel) = fscale_temp*tempfac(1:nel)
200 tempfac2(1:nel) = tempfac(1:nel)
203 tempfac2(1:nel) = one
207 IF (itab_size > 0)
THEN
209 ndim = table(itab_size)%NDIM
214 xvec(1:nel,1) = l0(1:nel)/el_ref
215 xvec(1:nel,2:3) = zero
219 xvec(1:nel,1) = l0(1:nel)/el_ref
220 IF (log_scale1 > 0)
THEN
222 xvec(i,2) = log(
max(epsp(i),em20)/sr_ref1)
225 xvec(1:nel,2) = epsp(1:nel)/sr_ref1
230 ELSEIF (ireg == 2)
THEN
234 xvec(1:nel,1) = l0(1:nel)/el_ref
239 xvec(1:nel,1) = l0(1:nel)/el_ref
240 xvec(1:nel,2) = triax(1:nel)
245 xvec(1:nel,1) = l0(1:nel)/el_ref
246 xvec(1:nel,2) = triax(1:nel)
247 xvec(1:nel,3) = xi(1:nel)
251 CALL table_vinterp(table(itab_size),nel,nel,ipos,xvec,sizefac,dsize)
252 sizefac(1:nel) = sizefac(1:nel)*fscale_el
255 IF (triax(i) < shrf)
THEN
257 ELSEIF (triax(i) > biaxf)
THEN
267 IF (ifunc(2) > 0)
THEN
268 IF (log_scale2 > 0)
THEN
270 var(i) = log(
max(epsp(i),em20)/sr_ref2)
273 var(1:nel) = epsp(1:nel)/sr_ref2
276 iad(1:nel) = npf(ifunc(2)) / 2 + 1
277 ilen(1:nel) = npf(ifunc(2)+1) / 2 - iad(1:nel) - ipos2(1:nel)
279 ratefac(1:nel) = fscale_sr*ratefac(1:nel)
280 ELSEIF (cjc > zero)
THEN
282 IF (epsp(i) > sr_ref2)
THEN
283 ratefac(i) = one + cjc*log(epsp(i)/sr_ref2)
293 IF (ifunc(3) > 0)
THEN
296 dlim(i) = finter(ifunc(3),lambda,npf,tf,df)
297 dlim(i) = fscale_dlim*dlim(i
298 dlim(i) =
min(dlim(i),one)
299 dlim(i) =
max(dlim(i),zero)
307 !====================================================================
308 IF (itab_epsf > 0)
THEN
310 ndim = table(itab_epsf)%NDIM
314 xvec(1:nel,1) = triax(1:nel)
315 xvec(1:nel,2:3) = zero
319 xvec(1:nel,1) = triax(1:nel)
320 xvec(1:nel,2) = xi(1:nel)
325 xvec(1:nel,1) = triax(1:nel)
326 xvec(1:nel,2) = xi(1:nel)
327 xvec(1:nel,3) = temp(1:nel)/temp_ref
331 CALL table_vinterp(table(itab_epsf),nel,nel,ipos,xvec,epsf,depsf)
332 epsf(1:nel) = epsf(1:nel)*fcrit
340 IF (itab_inst > 0)
THEN
342 ndim = table(itab_inst)%NDIM
346 xvec(1:nel,1) = triax(1:nel)
347 xvec(1:nel,2:3) = zero
351 xvec(1:nel,1) = triax(1:nel)
352 xvec(1:nel,2) = xi(1:nel)
357 xvec(1:nel,1) = triax(1:nel)
358 xvec(1:nel,2) = xi(1:nel)
359 xvec(1:nel,3) = temp(1:nel)/temp_ref
361 tempfac2(1:nel) = one
363 CALL table_vinterp(table(itab_inst),nel,nel,ipos,xvec,epsl,depsl)
364 epsl(1:nel) = epsl(1:nel)*
ecrit
365 ELSEIF (
ecrit > zero)
THEN
380 IF (loff(i) == one .AND. off(i) == one .AND. dpla(i) > zero)
THEN
383 IF (dfmax(i) == zero) dfmax(i) = em20
384 IF (inst(i) == zero) inst(i) = em20
387 dpl_def = dpla(i)/
max(epsf(i)*ratefac(i)*sizefac(i)*tempfac(i),em20)
388 dfmax(i) = dfmax(i) + dpl_def*dn*(dfmax(i)**(one-(one/dn)))
389 dfmax(i) =
min(dfmax(i),dlim(i))
390 IF (dfmax(i) >= one)
THEN
393 noff(i) = noff(i) + 1
395 uelr(i) = uelr(i) + voln(i)
396 IF ((npg > 1).AND.(volfrac > zero))
THEN
397 IF (uelr(i)/(npg*voln(i)) >= volfrac)
THEN
402 IF (noff(i) >= failip)
THEN
410 IF ((itab_inst > 0).OR.(
ecrit > zero))
THEN
411 dpl_def = dpla(i)/
max(epsl(i)*ratefac(i)*sizefac(i)*tempfac2(i),em20)
412 inst(i) = inst(i) + dpl_def*dn*(inst(i)**(one-(one/dn)))
413 inst(i) =
min(inst(i),one)
414 IF ((inst(i) >= one).AND.(dc(i) == one))
THEN
426 IF ((itab_inst > 0).OR.(
ecrit > zero))
THEN
429 IF (dfmax(i) >= dc(i))
THEN
430 IF (dc(i) < one)
THEN
431 dmg_scale(i) = one - ((dfmax(i)-dc(i))/
max(one-dc(i),em20))**softexp(i)
439 IF (dfmax(i) >= dcrit)
THEN
440 IF (dcrit < one)
THEN
441 dmg_scale(i) = one - ((dfmax(i)-dcrit)/
max
458 WRITE(iout, 1000) ngl(i),ipg,time
459 WRITE(istdo,1000) ngl(i),ipg
460 IF (off(i) == zero)
THEN
461 WRITE(iout, 2000) ngl(i),time
462 WRITE(istdo,2000) ngl(i),time
464#include "lockoff.inc"
468 1000
FORMAT(1x,
'FOR SOLID ELEMENT NUMBER el#',i10,
469 .
' FAILURE (TAB2) AT GAUSS POINT ',i5,
470 .
' AT TIME :',1pe12.4)
471 2000
FORMAT(1x,
'-- RUPTURE OF SOLID ELEMENT :',i10,
472 .
' AT TIME :',1pe12.4)
subroutine usermat_solid(timers, lft, llt, nft, mtn, jcvt, pm, off, sig, eint, rho, qold, vol, strain, sigl, gama, uvar, bufmat, tf, npf, stifn, mat, ngl, nuvar, dt2t, neltst, ityptst, offg, geo, pid, epsd, el_temp, wxx, wyy, wzz, jsph, mumax, ssp, aire, voln, vd2, deltax, vis, d1, d2, d3, d4, d5, d6, pnew, psh, q, ssp_eq, dvol, sold1, sold2, sold3, sold4, sold5, sold6, rx, ry, rz, sx, sy, sz, tx, ty, tz, ipla, sigy, defp, ismstr, mfxx, mfxy, mfxz, mfyx, mfyy, mfyz, mfzx, mfzy, mfzz, ipm, isorth, fbuf, nfail, npg, sigdd, dxy, dyx, dyz, dzy, dzx, dxz, fr_wav, isrot, v, varnl, w, ix, x, jthe, et, mssa, dmels, iptr, ipts, iptt, table, fvd2, fdeltax, fssp, fqvis, iparg1, igeo, sigv, al_imp, signor, istrain, ng, elbuf_tab, vbuf, ilay, vk, iparg, bufvois, vdx, vdy, vdz, ihet, conde, itask, iexpan, vol_avg, amu, epsth3, epsth, svisc, nel, etotsh, iselect, tstar, muold, amu2, dpdm, rhoref, rhosp, nloc_dmg, ity, jtur, mat_elem, idel7nok, svis, dt, glob_therm, damp_buf, idamp_freq_range)