OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
fail_maxstrain_s.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!|| fail_maxstrain_s ../engine/source/materials/fail/max_strain/fail_maxstrain_s.F
25!||--- called by ------------------------------------------------------
26!|| mmain ../engine/source/materials/mat_share/mmain.F90
27!|| mulaw ../engine/source/materials/mat_share/mulaw.F90
28!|| usermat_solid ../engine/source/materials/mat_share/usermat_solid.F
29!||====================================================================
30 SUBROUTINE fail_maxstrain_s(
31 1 NEL ,NUVAR ,IP ,ILAY ,NPG ,TIME ,
32 2 TIMESTEP,UPARAM ,NGL ,OFF ,LOFF ,NOFF ,
33 3 EPSXX ,EPSYY ,EPSZZ ,EPSXY ,EPSYZ ,EPSZX ,
34 4 UVAR ,NUPARAM ,DFMAX ,LF_DAMMX,TDELE ,DMG_SCALE)
35C-----------------------------------------------
36C I m p l i c i t T y p e s
37C-----------------------------------------------
38#include "implicit_f.inc"
39C-----------------------------------------------
40#include "units_c.inc"
41#include "comlock.inc"
42C-----------------------------------------------
43C I N P U T A r g u m e n t s
44C-----------------------------------------------
45 INTEGER, INTENT(IN) :: NEL,NUPARAM,NUVAR,
46 . ILAY,IP,NPG,NGL(NEL),LF_DAMMX
47 my_real, INTENT(IN) ::
48 . TIME,TIMESTEP,UPARAM(NUPARAM)
49 my_real, INTENT(INOUT) ::
50 . epsxx(nel),epsyy(nel),epszz(nel),
51 . epsxy(nel),epsyz(nel),epszx(nel)
52C-----------------------------------------------
53C I N P U T O U T P U T A r g u m e n t s
54C-----------------------------------------------
55 INTEGER, INTENT(INOUT) :: NOFF(NEL)
56 my_real, INTENT(INOUT) ::
57 . UVAR(NEL,NUVAR),OFF(NEL),
58 . TDELE(NEL),DMG_SCALE(NEL),LOFF(NEL)
59 my_real ,DIMENSION(NEL,LF_DAMMX),INTENT(INOUT) :: dfmax
60C-----------------------------------------------
61C L o c a l V a r i a b l e s
62C-----------------------------------------------
63 INTEGER
64 . I,J,INDX(NEL),NINDX,INDX0(NEL),NINDX0,
65 . IFAIL_SO
66 my_real
67 . eps1_max,eps2_max,gam12_max,tmax,fcut
68 my_real
69 . asrate,exx(nel),eyy(nel),ezz(nel),
70 . exy(nel),eyz(nel),ezx(nel),findex,rfactr
71C--------------------------------------------------------------
72 !=======================================================================
73 ! - INITIALISATION OF COMPUTATION ON TIME STEP
74 !=======================================================================
75 ! Recovering model parameters
76 eps1_max = uparam(1)
77 eps2_max = uparam(2)
78 gam12_max = uparam(3)
79 tmax = uparam(4)
80 fcut = uparam(5)
81 ifail_so = int(uparam(7))
82c
83 ! Stress tensor filtering
84 IF (fcut > zero) THEN
85 DO i = 1,nel
86 asrate = two*pi*fcut*timestep
87 asrate = asrate/(one+asrate)
88 exx(i) = asrate*epsxx(i) + (one - asrate)*uvar(i,2)
89 eyy(i) = asrate*epsyy(i) + (one - asrate)*uvar(i,3)
90 ezz(i) = asrate*epszz(i) + (one - asrate)*uvar(i,4)
91 exy(i) = asrate*epsxy(i) + (one - asrate)*uvar(i,5)
92 eyz(i) = asrate*epsyz(i) + (one - asrate)*uvar(i,6)
93 ezx(i) = asrate*epszx(i) + (one - asrate)*uvar(i,7)
94 uvar(i,2) = exx(i)
95 uvar(i,3) = eyy(i)
96 uvar(i,4) = ezz(i)
97 uvar(i,5) = exy(i)
98 uvar(i,6) = eyz(i)
99 uvar(i,7) = ezx(i)
100 ENDDO
101 ELSE
102 DO i = 1,nel
103 exx(i) = epsxx(i)
104 eyy(i) = epsyy(i)
105 ezz(i) = epszz(i)
106 exy(i) = epsxy(i)
107 eyz(i) = epsyz(i)
108 ezx(i) = epszx(i)
109 ENDDO
110 ENDIF
111c
112 !====================================================================
113 ! - COMPUTATION OF THE DAMAGE VARIABLE EVOLUTION
114 !====================================================================
115 ! Initialization of element failure index
116 nindx = 0
117 nindx0 = 0
118 indx = 0
119 indx0 = 0
120c
121 ! Loop over the elements
122 DO i=1,nel
123c
124 ! If damage has not been reached yet
125 IF (dfmax(i,1)<one) THEN
126c
127 ! Compute failure index and reserve factor
128 findex = max(abs(exx(i))/eps1_max,
129 . abs(eyy(i))/eps2_max,
130 . abs(exy(i))/gam12_max,
131 . abs(ezz(i))/eps2_max,
132 . abs(ezx(i))/gam12_max)
133 findex = max(zero,findex)
134c
135 ! Compute reserve factor
136 dfmax(i,2) = one/max(sqrt(findex),em20)
137c
138 IF (findex > zero) THEN
139 rfactr = one/sqrt(findex)
140 ELSE
141 rfactr = zero
142 ENDIF
143c
144 ! Damage variable update
145 dfmax(i,1) = min(one ,max(findex,dfmax(i,1)))
146 IF (dfmax(i,1) >= one) THEN
147 nindx = nindx+1
148 indx(nindx) = i
149 IF (ifail_so > 0) THEN
150 uvar(i,1) = time
151 ENDIF
152 ENDIF
153 ENDIF
154c
155 ! Stress relaxation in case of damage reached
156 IF ((uvar(i,1) > zero).AND.(loff(i) /= zero).AND.
157 . (ifail_so > 0).AND.(off(i) /= zero)) THEN
158 dmg_scale(i) = exp(-(time - uvar(i,1))/tmax)
159 IF (dmg_scale(i) < em02) THEN
160 loff(i) = zero
161 tdele(i) = time
162 dmg_scale(i) = zero
163 IF (ifail_so == 1) THEN
164 off(i) = zero
165 nindx0 = nindx0 + 1
166 indx0(nindx0) = i
167 ELSEIF (ifail_so == 2) THEN
168 noff(i) = noff(i) + 1
169 IF (int(noff(i)) >= npg) THEN
170 off(i) = zero
171 nindx0 = nindx0 + 1
172 indx0(nindx0) = i
173 ENDIF
174 ENDIF
175 ENDIF
176 ENDIF
177 ENDDO
178c
179 !====================================================================
180 ! - PRINTOUT DATA ABOUT FAILED ELEMENTS
181 !====================================================================
182 IF(nindx > 0)THEN
183 DO j=1,nindx
184 i = indx(j)
185#include "lockon.inc"
186 WRITE(iout, 1000) ngl(i),ip,ilay
187 WRITE(istdo,1100) ngl(i),ip,ilay,time
188#include "lockoff.inc"
189 END DO
190 ENDIF
191C
192 IF(nindx0 > 0)THEN
193 DO j=1,nindx0
194 i = indx0(j)
195#include "lockon.inc"
196 WRITE(iout, 1200) ngl(i),time
197 WRITE(istdo,1200) ngl(i),time
198#include "lockoff.inc"
199 END DO
200 ENDIF
201C--------------------------------------------
202 1000 FORMAT(1x,'FAILURE (MAXSTRAIN) OF SOLID ELEMENT ',i10,1x,
203 .',GAUSS PT',i5,1x,',LAYER',i5)
204 1100 FORMAT(1x,'FAILURE (MAXSTRAIN) OF SOLID ELEMENT ',i10,1x,
205 .',GAUSS PT',i5,1x,',LAYER',i5,1x,'AT TIME :',1pe20.13)
206 1200 FORMAT(1x,'-- rupture of solid element : ',I10,1X,
207 .'at time :',1PE20.13)
208C--------------------------------------------
209 RETURN
210 END
subroutine fail_maxstrain_s(nel, nuvar, ip, ilay, npg, time, timestep, uparam, ngl, off, loff, noff, epsxx, epsyy, epszz, epsxy, epsyz, epszx, uvar, nuparam, dfmax, lf_dammx, tdele, dmg_scale)
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21