OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
sigeps120_tab_dp.F
Go to the documentation of this file.
1Copyright> OpenRadioss
2Copyright> Copyright (C) 1986-2025 Altair Engineering Inc.
3Copyright>
4Copyright> This program is free software: you can redistribute it and/or modify
5Copyright> it under the terms of the GNU Affero General Public License as published by
6Copyright> the Free Software Foundation, either version 3 of the License, or
7Copyright> (at your option) any later version.
8Copyright>
9Copyright> This program is distributed in the hope that it will be useful,
10Copyright> but WITHOUT ANY WARRANTY; without even the implied warranty of
11Copyright> MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12Copyright> GNU Affero General Public License for more details.
13Copyright>
14Copyright> You should have received a copy of the GNU Affero General Public License
15Copyright> along with this program. If not, see <https://www.gnu.org/licenses/>.
16Copyright>
17Copyright>
18Copyright> Commercial Alternative: Altair Radioss Software
19Copyright>
20Copyright> As an alternative to this open-source version, Altair also offers Altair Radioss
21Copyright> software under a commercial license. Contact Altair to discuss further if the
22Copyright> commercial version may interest you: https://www.altair.com/radioss/.
23!||====================================================================
24!|| sigeps120_tab_dp ../engine/source/materials/mat/mat120/sigeps120_tab_dp.F
25!||--- called by ------------------------------------------------------
26!|| sigeps120 ../engine/source/materials/mat/mat120/sigeps120.F
27!||--- calls -----------------------------------------------------
28!|| table_vinterp ../engine/source/tools/curve/table_tools.F
29!||--- uses -----------------------------------------------------
30!|| interface_table_mod ../engine/share/modules/table_mod.F
31!|| table_mod ../engine/share/modules/table_mod.F
32!||====================================================================
33 SUBROUTINE sigeps120_tab_dp(
34 1 NEL ,NGL ,NUPARAM ,NUVAR ,TIME ,TIMESTEP,
35 2 UPARAM ,UVAR ,OFF ,PLA ,EPSD ,SOUNDSP ,
36 3 EPSPXX ,EPSPYY ,EPSPZZ ,EPSPXY ,EPSPYZ ,EPSPZX ,
37 4 DEPSXX ,DEPSYY ,DEPSZZ ,DEPSXY ,DEPSYZ ,DEPSZX ,
38 5 SIGOXX ,SIGOYY ,SIGOZZ ,SIGOXY ,SIGOYZ ,SIGOZX ,
39 6 SIGNXX ,SIGNYY ,SIGNZZ ,SIGNXY ,SIGNYZ ,SIGNZX ,
40 7 NUMTABL ,ITABLE ,TABLE ,NVARTMP ,VARTMP ,TEMP ,
41 8 INLOC ,DPLANL ,DMG ,DMG_SCALE)
42C-----------------------------------------------
43C M o d u l e s
44C-----------------------------------------------
45 USE table_mod
47C-----------------------------------------------
48C I m p l i c i t T y p e s
49C-----------------------------------------------
50#include "implicit_f.inc"
51C-----------------------------------------------
52C C o m m o n B l o c k s
53C-----------------------------------------------
54#include "com04_c.inc"
55#include "units_c.inc"
56#include "comlock.inc"
57C----------------------------------------------------------------
58C D u m m y A R G U M E N T S
59C----------------------------------------------------------------
60 INTEGER :: NEL,NUPARAM,NUVAR,NVARTMP,NUMTABL,INLOC
61 my_real :: TIME,TIMESTEP
62 INTEGER ,DIMENSION(NEL) ,INTENT(IN) :: NGL
63 INTEGER ,DIMENSION(NTABLE) ,INTENT(IN) :: ITABLE
64 my_real ,DIMENSION(NUPARAM),INTENT(IN) :: UPARAM
65 my_real ,DIMENSION(NEL) ,INTENT(IN) :: TEMP,
66 . EPSPXX,EPSPYY,EPSPZZ,EPSPXY,EPSPYZ,EPSPZX,
67 . DEPSXX,DEPSYY,DEPSZZ,DEPSXY,DEPSYZ,DEPSZX,
68 . sigoxx,sigoyy,sigozz,sigoxy,sigoyz,sigozx
69c
70 my_real ,DIMENSION(NEL) ,INTENT(OUT) :: epsd,soundsp
71 my_real ,DIMENSION(NEL) ,INTENT(OUT) ::
72 . signxx,signyy,signzz,signxy,signyz,signzx
73 INTEGER,DIMENSION(NEL,NVARTMP) ,INTENT(INOUT) :: VARTMP
74 my_real ,DIMENSION(NEL,NUVAR) ,INTENT(INOUT) :: UVAR
75 my_real ,DIMENSION(NEL) ,INTENT(INOUT) :: OFF,PLA,DPLANL,DMG,DMG_SCALE
76 TYPE(TTABLE), DIMENSION(NTABLE) :: TABLE
77C----------------------------------------------------------------
78C L O C A L V A R I B L E S
79C----------------------------------------------------------------
80 INTEGER :: I,II,ITER,NITER,NINDX,NINDF,ITRX,IDAM
81 my_real :: xscale,yscale
82 INTEGER :: IPOS1(NEL,1), IPOS2(NEL,2), IPOS3(NEL,3)
83 INTEGER :: NDIM_YLD,FUNC_YLD
84 my_real :: xvec1(nel,1), xvec2(nel,2), xvec3(nel,3)
85 INTEGER ,DIMENSION(NEL) :: INDX,INDF
86c material parameters
87 my_real :: YOUNG,NU,SSP,G,G2,BULK,YLD0,C11,C12,
88 . a1f,a2f,a1h,a2h,as,d1c,d2c,d1f,d2f,d_trx,d_jc,dm,expn
89c Johnson & Cook rate-dependency
90 my_real cc,epsdref,epsdmax,frate,fcut,alpha,alphai
91c Local variables
92 my_real facr,triax,i1p,ip,jp,tp,fact,facd,dfac,dtinv,
93 . dlam,ddep,dfdlam,dfdpla,dpla_dlam,dphi_dlam,
94 . gamc,gamf,np_xx,np_yy,np_zz,np_xy,np_yz,np_zx,
95 . nf_xx,nf_yy,nf_zz,nf_xy,nf_yz,nf_zx,dpxx,dpyy,dpzz,dpxy,dpyz,dpzx
96 my_real ,DIMENSION(NEL) :: i1,j2,a1,a2,yld,phi,dam,jcrate,
97 . sxx,syy,szz,sxy,syz,szx,dpla,jcr_log,gamma,dgamm,hardp,fdp,
98 . yld_i,hardp_i,pla_nl,dpdt_nl
99c--------------------------------
100c Material parameters
101c--------------------------------
102c UPARAM(1) = Young modulus E
103c UPARAM(2) = Poisson's ratio nu
104c UPARAM(3) = shear modulus G
105c UPARAM(4) = bulk modulus K
106c UPARAM(5) = Yld0: instant yield stress
107c UPARAM(6) = Q : expontial term coefficient in the hardening law
108c UPARAM(7) = BETA : exponent of the exponential term
109c UPARAM(8) = P : multiplier of the linear term in the hardening law
110c UPARAM(9) = A1F : parameter of the yield function
111c UPARAM(10) = A2F : parameter of the yield function
112c UPARAM(11) = A1H : distortionnal yield hardening coefficiant
113c UPARAM(12) = A2H : distortionnal yield hardening coefficiant
114c UPARAM(13) = AS : parameter of the potential function
115c UPARAM(14) = D1C: first damage strain parameter in initial damage threshold
116c UPARAM(15) = D2C: second damage strain parameter in initial damage threshold
117c UPARAM(16) = D1F: first damage strain parameter in final damage threshold
118c UPARAM(17) = D2F: second damage strain parameter in final damage threshold
119c UPARAM(18) = D_TRX : triaxiality factor in damage formula
120c UPARAM(19) = D_JC: JC strain rate coefficient in damage formula
121c UPARAM(20) = EXPN exponent in damage evolution
122c UPARAM(21) = CC : Johnson-Cook strain rate-dependency coefficient
123c UPARAM(22) = EPSDREF quasi-static reference strain rate
124c UPARAM(23) = EPSDMAX maximal reference strain rate
125c UPARAM(24) = FCUT : cut frequency for strain rate filtering
126c UPARAM(25) = IFORM = 1: Yield formulation flag => Drucker-Prager in tension
127c IFORM = 2: Yield formulation flag => Von Mises in tension
128c UPARAM(26) = ITRX = 1 : pressure dependent for all T values
129c ITRX = 2 : no pressure dependency when T < 0
130c UPARAM(27) = IDAM = 1 : damage model without turning point
131c IDAM = 2 : damage model with turning point
132c UPARAM(28) = SSP : sound speed
133c UPARAM(29) = Table Id
134c UPARAM(30) = Xscale for yld function
135c UPARAM(31) = Yscale for yld function
136c UPARAM(32) = Elastic modulus C11
137c UPARAM(33) = Elastic modulus C12
138c--------------------------------
139c UVAR(1) : ARCL = PLA / (1-DAM) or non local plastic strain
140c UVAR(2) : DAM
141c UVAR(3) : TOTAL STRAIN RATE
142c UVAR(4) : plastic function residual (for output/convergence check)
143c UVAR(5) : non local plastic strain
144C=======================================================================
145 young = uparam(1)
146 nu = uparam(2)
147 g = uparam(3)
148 bulk = uparam(4)
149c Parameters of yield function/hardening law and flow potential
150 yld0 = uparam(5)
151 a1f = uparam(9)
152 a2f = uparam(10)
153 a1h = uparam(11)
154 a2h = uparam(12)
155 as = uparam(13)
156c Johnson-Cook failure parameters
157 d1c = uparam(14)
158 d2c = uparam(15)
159 d1f = uparam(16)
160 d2f = uparam(17)
161 d_trx = uparam(18)
162 d_jc = uparam(19)
163 expn = uparam(20)
164c Johnson-Cook strain rate-dependency and distortional hardening
165 cc = uparam(21)
166 epsdref = uparam(22)
167 epsdmax = uparam(23)
168 fcut = uparam(24)
169c
170 itrx = nint(uparam(26))
171 idam = nint(uparam(27))
172 ssp = uparam(28)
173 xscale = uparam(30)
174 yscale = uparam(31)
175 c11 = uparam(32)
176 c12 = uparam(33)
177c
178 func_yld = itable(1)
179 ndim_yld = table(func_yld)%NDIM
180c
181 g2 = g * two
182 alpha = 0.005
183 alphai = one - alpha
184c
185 IF (inloc > 0) THEN
186 dtinv = one / max(timestep, em20)
187 DO i = 1,nel
188 pla_nl(i) = uvar(i,5) + max(dplanl(i),zero)
189 uvar(i,5) = pla_nl(i)
190 dpdt_nl(i) = min(max(dplanl(i),zero)*dtinv ,epsdmax)
191 ENDDO
192 ENDIF
193c------------------------------------------------------------------
194c Computation of the nominal trial stress tensor (non damaged)
195c------------------------------------------------------------------
196 dam(1:nel) = dmg(1:nel)
197 dpla(1:nel) = zero
198c
199 DO i = 1,nel
200 IF (off(i) < 0.001) off(i) = zero
201 IF (off(i) < one) off(i) = off(i)*four_over_5
202 IF (off(i) == one) THEN
203 signxx(i) = sigoxx(i) + c11*depsxx(i) + c12*(depsyy(i) + depszz(i))
204 signyy(i) = sigoyy(i) + c11*depsyy(i) + c12*(depsxx(i) + depszz(i))
205 signzz(i) = sigozz(i) + c11*depszz(i) + c12*(depsxx(i) + depsyy(i))
206 signxy(i) = sigoxy(i) + depsxy(i)*g
207 signyz(i) = sigoyz(i) + depsyz(i)*g
208 signzx(i) = sigozx(i) + depszx(i)*g
209 i1(i) = signxx(i) + signyy(i) + signzz(i)
210c
211 sxx(i) = signxx(i) - i1(i) * third
212 syy(i) = signyy(i) - i1(i) * third
213 szz(i) = signzz(i) - i1(i) * third
214 sxy(i) = signxy(i)
215 syz(i) = signyz(i)
216 szx(i) = signzx(i)
217 j2(i) = (sxx(i)**2 + syy(i)**2 + szz(i)**2)*half
218 . + sxy(i)**2 + syz(i)**2 + szx(i)**2
219 END IF
220 ENDDO
221c Johnson & Cook rate dependency (total strain rate)
222 jcr_log(1:nel) = zero
223 jcrate(1:nel) = one
224 IF (epsdref > zero) THEN
225 IF (inloc == 1) THEN ! non local plastic strain rate
226 jcr_log(1:nel) = log(dpdt_nl(1:nel) / epsdref)
227 jcrate(1:nel) = one + cc * jcr_log(1:nel)
228 ELSE ! total strain rate
229 DO i = 1,nel
230 IF (off(i) == one) THEN
231 epsd(i) = (epspxx(i)**2 + epspyy(i)**2 + epspzz(i)**2 )*two
232 . + epspxy(i)**2 + epspyz(i)**2 + epspzx(i)**2
233 epsd(i) = min(sqrt(epsd(i)) ,epsdmax)
234 epsd(i) = alpha*epsd(i) + alphai*uvar(i,3)
235 uvar(i,3) = epsd(i)
236 IF (epsd(i) > epsdref) THEN
237 jcr_log(i) = log(epsd(i) / epsdref)
238 jcrate(i) = one + cc * jcr_log(i)
239 END IF
240 END IF
241 ENDDO
242 END IF
243 END IF
244c----------------------------------------------------
245c Computation of the initial yield stress
246c----------------------------------------------------
247 IF (ndim_yld == 1) THEN
248 xvec1(1:nel,1) = pla(1:nel)
249 ipos1(1:nel,1) = vartmp(1:nel,1)
250c
251 CALL table_vinterp(table(func_yld),nel,nel,ipos1,xvec1,yld,hardp)
252c
253 yld(1:nel) = yld(1:nel) * yscale * jcrate(1:nel)
254 hardp(1:nel) = hardp(1:nel) * yscale * jcrate(1:nel)
255 vartmp(1:nel,1) = ipos1(1:nel,1)
256
257 ELSE IF (ndim_yld == 2) THEN
258 xvec2(1:nel,1) = pla(1:nel)
259 xvec2(1:nel,2) = epsd(1:nel)
260 ipos2(1:nel,1) = vartmp(1:nel,1)
261 ipos2(1:nel,2) = 1
262c
263 CALL table_vinterp(table(func_yld),nel,nel,ipos2,xvec2,yld,hardp)
264c
265 yld(1:nel) = yld(1:nel) * yscale
266 hardp(1:nel) = hardp(1:nel) * yscale
267 vartmp(1:nel,1) = ipos2(1:nel,1)
268
269 ELSE
270 xvec3(1:nel,1) = pla(1:nel)
271 xvec3(1:nel,2) = epsd(1:nel)
272 xvec3(1:nel,3) = temp(1:nel)
273 ipos3(1:nel,1) = vartmp(1:nel,1)
274 ipos3(1:nel,2) = 1
275 ipos3(1:nel,3) = 1
276c
277 CALL table_vinterp(table(func_yld),nel,nel,ipos3,xvec3,yld,hardp)
278c
279 yld(1:nel) = yld(1:nel) * yscale
280 hardp(1:nel) = hardp(1:nel) * yscale
281 vartmp(1:nel,1) = ipos3(1:nel,1)
282
283 END IF
284c
285 DO i = 1,nel
286 a1(i) = a1f + a1h * pla(i)
287 a2(i) = max(zero, a2f + a2h * pla(i))
288 fdp(i) = third*(sqr3*yld0*a1(i)*i1(i) + a2(i)*max(zero,i1(i))**2)
289 phi(i) = j2(i) + fdp(i) - yld(i)**2
290 ENDDO
291c------------------------------------------------------------------
292c Check plasticity
293c------------------------------------------------------------------
294 nindx = 0
295 nindf = 0
296 DO i = 1,nel
297 IF (phi(i) > zero .and. off(i) == one) THEN
298 nindx = nindx + 1
299 indx(nindx) = i
300 END IF
301 ENDDO
302c
303 IF (nindx > 0) THEN
304
305 niter = 4
306 dpla(1:nel) = zero
307
308 DO iter = 1,niter
309c
310 DO ii = 1,nindx
311 i = indx(ii)
312
313 ! normal to non associated plastic flow surface = d_psi/d_sig
314 i1p = max(zero, i1(i))
315 jp = third * as * i1p
316 tp = two * jp
317c
318 np_xx = sxx(i) + tp
319 np_yy = syy(i) + tp
320 np_zz = szz(i) + tp
321 np_xy = sxy(i)
322 np_yz = syz(i)
323 np_zx = szx(i)
324c
325 ! normal to plastic yield surface = d_phi/d_sig
326 ip = third*(sqr3*yld0*a1(i) + two*a2(i)*i1p)
327 nf_xx = sxx(i) + ip
328 nf_yy = syy(i) + ip
329 nf_zz = szz(i) + ip
330 nf_xy = sxy(i)
331 nf_yz = syz(i)
332 nf_zx = szx(i)
333c
334 ! derivative of yld criterion : dphi/dlam = d_phi/d_sig * dsig/dlam
335 dfdlam =-nf_xx * (c11*np_xx + c12 * (np_yy + np_zz))
336 . - nf_yy * (c11*np_yy + c12 * (np_xx + np_zz))
337 . - nf_zz * (c11*np_zz + c12 * (np_xx + np_yy))
338 . -(nf_xy*np_xy + nf_yz*np_yz + nf_zx*np_zx)*two*g2
339c
340 dfdpla = third*(sqr3*a1h*yld0*i1(i) + a2h*i1p**2)
341
342 dpla_dlam = two*sqrt((j2(i) + tp*as*i1(i)))
343c
344 dphi_dlam = dfdlam + (dfdpla - two*yld(i)*hardp(i))*dpla_dlam
345c----------------------------------------------------------------
346 dlam = -phi(i) / dphi_dlam
347c----------------------------------------------------------------
348 ! Plastic strains tensor update
349 dpxx = dlam*np_xx
350 dpyy = dlam*np_yy
351 dpzz = dlam*np_zz
352 dpxy = dlam*np_xy
353 dpyz = dlam*np_yz
354 dpzx = dlam*np_zx
355 ! Elasto-plastic stresses update
356 signxx(i) = signxx(i) - (c11*dpxx + c12*(dpyy + dpzz))
357 signyy(i) = signyy(i) - (c11*dpyy + c12*(dpxx + dpzz))
358 signzz(i) = signzz(i) - (c11*dpzz + c12*(dpxx + dpyy))
359 signxy(i) = signxy(i) - g2*dpxy
360 signyz(i) = signyz(i) - g2*dpyz
361 signzx(i) = signzx(i) - g2*dpzx
362c
363 ! Plastic strain increments update
364 ddep = dlam * dpla_dlam
365 dpla(i)= max(zero, dpla(i) + ddep)
366 pla(i) = pla(i) + ddep
367 ENDDO ! II = 1,NINDX
368c-----------------------------------------
369c Update yield from tabulated data
370c-----------------------------------------
371c
372 IF (ndim_yld == 1) THEN
373 DO ii = 1, nindx
374 i = indx(ii)
375 xvec1(ii,1) = pla(i)
376 ipos1(ii,1) = vartmp(i,1)
377 ENDDO
378c
379 CALL table_vinterp(table(func_yld),nel,nel,ipos1,xvec1,yld_i,hardp_i)
380c
381 DO ii = 1, nindx
382 i = indx(ii)
383 yld(i) = yld_i(ii)*yscale
384 hardp(i) = hardp_i(ii)*yscale
385 vartmp(i,1) = ipos1(ii,1)
386 ENDDO
387
388 ELSE IF (ndim_yld == 2) THEN
389 DO ii = 1, nindx
390 i = indx(ii)
391 xvec2(ii,1) = pla(i)
392 xvec2(ii,2) = epsd(i)
393 ipos2(ii,1) = vartmp(i,1)
394 ENDDO
395c
396 CALL table_vinterp(table(func_yld),nel,nindx,ipos2,xvec2,yld_i,hardp_i)
397c
398 DO ii = 1, nindx
399 i = indx(ii)
400 yld(i) = yld_i(ii)*yscale
401 hardp(i) = hardp_i(ii)*yscale
402 vartmp(i,1) = ipos2(ii,1)
403 ENDDO
404
405 ELSE
406 DO ii = 1, nindx
407 i = indx(ii)
408 xvec3(ii,1) = pla(i)
409 xvec3(ii,2) = epsd(i)
410 xvec3(ii,3) = temp(i)
411 ipos3(ii,1) = vartmp(i,1)
412 ENDDO
413c
414 CALL table_vinterp(table(func_yld),nel,nel,ipos3,xvec3,yld_i,hardp_i)
415c
416 DO ii = 1, nindx
417 i = indx(ii)
418 yld(i) = yld_i(ii)*yscale
419 hardp(i) = hardp_i(ii)*yscale
420 vartmp(i,1) = ipos3(ii,1)
421 ENDDO
422 END IF
423c----------------------
424c Update stress invariants and criterion function value
425c----------------------
426 DO ii = 1,nindx
427 i = indx(ii)
428 i1(i) = signxx(i) + signyy(i) + signzz(i)
429 i1p = max(zero, i1(i))
430 sxx(i) = signxx(i) - i1(i)*third
431 syy(i) = signyy(i) - i1(i)*third
432 szz(i) = signzz(i) - i1(i)*third
433 sxy(i) = signxy(i)
434 syz(i) = signyz(i)
435 szx(i) = signzx(i)
436 j2(i) =(sxx(i)**2 + syy(i)**2 + szz(i)**2 ) * half
437 . + sxy(i)**2 + syz(i)**2 + szx(i)**2
438 a1(i) = a1f + a1h * pla(i)
439 a2(i) = max(zero, a2f + a2h * pla(i))
440 fdp(i) = third*(sqr3*yld0*a1(i)*i1(i) + a2(i)*i1p**2)
441 phi(i) = j2(i) + fdp(i) - yld(i)**2
442 uvar(i,4) = phi(i) / yld(i)**2
443 END DO
444c
445 END DO ! Newton iterations
446c
447 END IF ! NINDX > 0
448c---------------------------------------------------------------------
449c Update damage
450c---------------------------------------------------------------------
451 IF (idam > 0) THEN
452 IF (idam == 1) THEN
453 IF (inloc == 1) THEN
454 dgamm(1:nel) = dplanl(1:nel)
455 gamma(1:nel) = pla_nl(1:nel)
456 ELSE
457 dgamm(1:nel) = dpla(1:nel)
458 gamma(1:nel) = pla(1:nel)
459 END IF
460 ELSE
461 IF (inloc == 1) THEN
462 dgamm(1:nel) = dplanl(1:nel) * dmg_scale(1:nel)
463 uvar(1:nel,1) = uvar(1:nel,1) + dgamm(1:nel)
464 gamma(1:nel) = uvar(1:nel,1)
465 ELSE
466 dgamm(1:nel) = dpla(1:nel) * dmg_scale(1:nel)
467 uvar(1:nel,1) = uvar(1:nel,1) + dgamm(1:nel)
468 gamma(1:nel) = uvar(1:nel,1)
469 END IF
470 END IF
471c
472 DO i = 1,nel
473c
474 triax = zero
475 fact = one
476 facr = one + d_jc * jcr_log(i) ! total strain rate factor on damage
477 IF ( j2(i)/= zero)triax = third * i1(i) / sqrt(three*j2(i))
478 IF (itrx == 1 ) THEN
479 fact = exp(-d_trx*triax)
480 ELSE
481 IF (triax > zero )fact = exp(-d_trx*triax)
482 ENDIF
483 gamc = (d1c + d2c * fact) * facr
484 gamf = (d1f + d2f * fact) * facr
485 IF (gamma(i) > gamc) THEN
486 IF (dam(i) == zero) THEN
487 nindf = nindf + 1
488 indf(nindf) = i
489 END IF
490 IF (expn == one) THEN
491 dam(i) = dam(i) + dgamm(i) / (gamf - gamc)
492 ELSE
493 dfac = (gamma(i) - gamc) / (gamf - gamc)
494 dam(i) = dam(i) + expn * dfac**(expn-one) * dgamm(i) / (gamf - gamc)
495 END IF
496 IF (dam(i) >= one) THEN
497 dam(i) = one
498 off(i) = four_over_5
499 END IF
500 dmg(i) = dam(i)
501 END IF ! GAMMA > GAMC
502 ENDDO
503c Update damaged stress
504 DO i = 1, nel
505 dmg_scale(i) = one - dam(i)
506 END DO
507 END IF
508c-------------------------
509 soundsp(1:nel) = ssp
510c-------------------------
511 IF (nindf > 0) THEN
512 DO ii=1,nindf
513#include "lockon.inc"
514 WRITE(iout, 1000) ngl(indf(ii))
515 WRITE(istdo,1100) ngl(indf(ii)),time
516#include "lockoff.inc"
517 ENDDO
518 END IF
519c-----------------------------------------------------------------
520 1000 FORMAT(1x,'START DAMAGE IN SOLID ELEMENT NUMBER ',i10)
521 1100 FORMAT(1x,'START DAMAGE IN SOLID ELEMENT NUMBER ',i10,1x,' AT TIME :',g11.4)
522c-----------------------------------------------------------------
523 RETURN
524 END
#define alpha
Definition eval.h:35
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21
subroutine sigeps120_tab_dp(nel, ngl, nuparam, nuvar, time, timestep, uparam, uvar, off, pla, epsd, soundsp, epspxx, epspyy, epspzz, epspxy, epspyz, epspzx, depsxx, depsyy, depszz, depsxy, depsyz, depszx, sigoxx, sigoyy, sigozz, sigoxy, sigoyz, sigozx, signxx, signyy, signzz, signxy, signyz, signzx, numtabl, itable, table, nvartmp, vartmp, temp, inloc, dplanl, dmg, dmg_scale)