OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
fail_maxstrain_c.F File Reference
#include "implicit_f.inc"
#include "units_c.inc"
#include "comlock.inc"
#include "lockon.inc"
#include "lockoff.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine fail_maxstrain_c (nel, nuparam, nuvar, uparam, uvar, time, ngl, ipg, ilay, ipt, epsxx, epsyy, epsxy, epsyz, epszx, off, foff, dmg_flag, dmg_scale, dfmax, lf_dammx, tdel, timestep)

Function/Subroutine Documentation

◆ fail_maxstrain_c()

subroutine fail_maxstrain_c ( integer, intent(in) nel,
integer, intent(in) nuparam,
integer, intent(in) nuvar,
intent(in) uparam,
intent(inout) uvar,
intent(in) time,
integer, dimension(nel), intent(in) ngl,
integer, intent(in) ipg,
integer, intent(in) ilay,
integer, intent(in) ipt,
intent(in) epsxx,
intent(in) epsyy,
intent(in) epsxy,
intent(in) epsyz,
intent(in) epszx,
intent(in) off,
integer, dimension(nel), intent(inout) foff,
integer, intent(out) dmg_flag,
intent(out) dmg_scale,
intent(inout) dfmax,
integer, intent(in) lf_dammx,
intent(out) tdel,
intent(in) timestep )

Definition at line 29 of file fail_maxstrain_c.F.

35C-----------------------------------------------
36C modified Puck model ------
37C-----------------------------------------------
38C I m p l i c i t T y p e s
39C-----------------------------------------------
40#include "implicit_f.inc"
41C-----------------------------------------------
42C G l o b a l P a r a m e t e r s
43C-----------------------------------------------
44#include "units_c.inc"
45#include "comlock.inc"
46C-----------------------------------------------
47C I N P U T A r g u m e n t s
48C-----------------------------------------------
49 INTEGER ,INTENT(IN) :: NEL,NUPARAM,NUVAR,IPG,ILAY,IPT,LF_DAMMX
50 INTEGER ,DIMENSION(NEL) ,INTENT(IN) :: NGL
51 my_real ,INTENT(IN) :: time,timestep
52 my_real ,DIMENSION(NEL) ,INTENT(IN) :: off,
53 . epsxx,epsyy,epsxy,epsyz,epszx
54 my_real,DIMENSION(NUPARAM) ,INTENT(IN) :: uparam
55C-----------------------------------------------
56C I N P U T O U T P U T A r g u m e n t s
57C-----------------------------------------------
58 INTEGER ,INTENT(OUT) :: DMG_FLAG
59 INTEGER ,DIMENSION(NEL) ,INTENT(INOUT) :: FOFF
60 my_real ,DIMENSION(NEL,LF_DAMMX),INTENT(INOUT) :: dfmax
61 my_real ,DIMENSION(NEL) ,INTENT(OUT) :: tdel,dmg_scale
62 my_real ,DIMENSION(NEL,NUVAR) ,INTENT(INOUT) :: uvar
63C-----------------------------------------------
64C L o c a l V a r i a b l e s
65C-----------------------------------------------
66 INTEGER :: I,J,NINDX,IFAIL_SH
67 INTEGER ,DIMENSION(NEL) :: INDX
69 . eps1_max,eps2_max,gam12_max,tmax,fcut
71 . exx(nel),eyy(nel),exy(nel),findex,rfactr,asrate
72C!----------------------------------------------
73 !=======================================================================
74 ! - INITIALISATION OF COMPUTATION ON TIME STEP
75 !=======================================================================
76 ! Recovering model parameters
77 eps1_max = uparam(1)
78 eps2_max = uparam(2)
79 gam12_max = uparam(3)
80 tmax = uparam(4)
81 fcut = uparam(5)
82 ifail_sh = int(uparam(6))
83c
84 ! Stress softening activation
85 dmg_flag = 1
86c
87 ! Stress tensor filtering
88 IF (fcut > zero) THEN
89 asrate = two*pi*fcut*timestep
90 asrate = asrate/(one+asrate)
91 DO i = 1,nel
92 exx(i) = asrate*epsxx(i) + (one - asrate)*uvar(i,2)
93 eyy(i) = asrate*epsyy(i) + (one - asrate)*uvar(i,3)
94 exy(i) = asrate*epsxy(i) + (one - asrate)*uvar(i,4)
95 uvar(i,2) = exx(i)
96 uvar(i,3) = eyy(i)
97 uvar(i,4) = exy(i)
98 ENDDO
99 ELSE
100 DO i = 1,nel
101 exx(i) = epsxx(i)
102 eyy(i) = epsyy(i)
103 exy(i) = epsxy(i)
104 ENDDO
105 ENDIF
106c
107 !====================================================================
108 ! - COMPUTATION OF THE DAMAGE VARIABLE EVOLUTION
109 !====================================================================
110 ! Initialization of element failure index
111 nindx = 0
112 indx(1:nel) = 0
113c
114 ! Loop over the elements
115 DO i=1,nel
116c
117 ! If damage has not been reached yet
118 IF (dfmax(i,1)<one) THEN
119c
120 ! Compute failure index and reserve factor
121 findex = max(abs(exx(i))/eps1_max,
122 . abs(eyy(i))/eps2_max,
123 . abs(exy(i))/gam12_max)
124 findex = max(zero,findex)
125c
126 ! Compute reserve factor
127 dfmax(i,2) = one/max(sqrt(findex),em20)
128c
129 ! Damage variable update
130 dfmax(i,1) = min(one ,max(findex,dfmax(i,1)))
131 IF (dfmax(i,1) >= one) THEN
132 nindx = nindx+1
133 indx(nindx) = i
134 IF (ifail_sh > 0) THEN
135 uvar(i,1) = time
136 ENDIF
137 ENDIF
138 ENDIF
139c
140 ! Stress relaxation in case of damage reached
141 IF ((uvar(i,1) > zero).AND.(foff(i) /= 0).AND.(ifail_sh > 0)) THEN
142 dmg_scale(i) = exp(-(time - uvar(i,1))/tmax)
143 IF (dmg_scale(i) < em02) THEN
144 foff(i) = 0
145 tdel(i) = time
146 dmg_scale(i) = zero
147 ENDIF
148 ENDIF
149 ENDDO
150c
151 !====================================================================
152 ! - PRINTOUT DATA ABOUT FAILED ELEMENTS
153 !====================================================================
154 IF (nindx > 0) THEN
155 DO j=1,nindx
156 i = indx(j)
157#include "lockon.inc"
158 WRITE(iout, 2000) ngl(i),ipg,ilay,ipt
159 WRITE(istdo,2100) ngl(i),ipg,ilay,ipt,time
160#include "lockoff.inc"
161 END DO
162 END IF
163c------------------------
164 2000 FORMAT(1x,'FAILURE (MAXSTRAIN) OF SHELL ELEMENT ',i10,1x,',GAUSS PT',
165 . i2,1x,',LAYER',i3,1x,',INTEGRATION PT',i3)
166 2100 FORMAT(1x,'FAILURE (MAXSTRAIN) OF SHELL ELEMENT ',i10,1x,',GAUSS PT',
167 . i2,1x,',LAYER',i3,1x,',INTEGRATION PT',i3,1x,'AT TIME :',1pe12.4)
168c------------------------
#define my_real
Definition cppsort.cpp:32
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21