OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
fail_tsaiwu_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_tsaiwu_s ../engine/source/materials/fail/tsaiwu/fail_tsaiwu_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_tsaiwu_s(
31 1 NEL ,NUVAR ,IP ,ILAY ,NPG ,TIME ,
32 2 TIMESTEP,UPARAM ,NGL ,OFF ,LOFF ,NOFF ,
33 3 SIGNXX ,SIGNYY ,SIGNZZ ,SIGNXY ,SIGNYZ ,SIGNZX ,
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 . signxx(nel),signyy(nel),signzz(nel),
51 . signxy(nel),signyz(nel),signzx(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 . f1,f2,f11,f22,f66,f12,tmax,fcut
68 my_real
69 . asrate,sxx(nel),syy(nel),szz(nel),
70 . sxy(nel),syz(nel),szx(nel),a,b,findex,rfactr
71C--------------------------------------------------------------
72 !=======================================================================
73 ! - INITIALISATION OF COMPUTATION ON TIME STEP
74 !=======================================================================
75 ! Recovering model parameters
76 f1 = uparam(1)
77 f2 = uparam(2)
78 f11 = uparam(3)
79 f22 = uparam(4)
80 f66 = uparam(5)
81 f12 = uparam(6)
82 tmax = uparam(7)
83 fcut = uparam(8)
84 ifail_so = int(uparam(10))
85c
86 ! Stress tensor filtering
87 IF (fcut > zero) THEN
88 DO i = 1,nel
89 asrate = two*pi*fcut*timestep
90 asrate = asrate/(one+asrate)
91 sxx(i) = asrate*signxx(i) + (one - asrate)*uvar(i,2)
92 syy(i) = asrate*signyy(i) + (one - asrate)*uvar(i,3)
93 szz(i) = asrate*signzz(i) + (one - asrate)*uvar(i,4)
94 sxy(i) = asrate*signxy(i) + (one - asrate)*uvar(i,5)
95 syz(i) = asrate*signyz(i) + (one - asrate)*uvar(i,6)
96 szx(i) = asrate*signzx(i) + (one - asrate)*uvar(i,7)
97 uvar(i,2) = sxx(i)
98 uvar(i,3) = syy(i)
99 uvar(i,4) = szz(i)
100 uvar(i,5) = sxy(i)
101 uvar(i,6) = syz(i)
102 uvar(i,7) = szx(i)
103 ENDDO
104 ELSE
105 DO i = 1,nel
106 sxx(i) = signxx(i)
107 syy(i) = signyy(i)
108 szz(i) = signzz(i)
109 sxy(i) = signxy(i)
110 syz(i) = signyz(i)
111 szx(i) = signzx(i)
112 ENDDO
113 ENDIF
114c
115 !====================================================================
116 ! - COMPUTATION OF THE DAMAGE VARIABLE EVOLUTION
117 !====================================================================
118 ! Initialization of element failure index
119 nindx = 0
120 nindx0 = 0
121 indx = 0
122 indx0 = 0
123c
124 ! Loop over the elements
125 DO i=1,nel
126c
127 ! If damage has not been reached yet
128 IF (dfmax(i,1)<one) THEN
129c
130 ! Compute parameters A and B
131 a = f11*(sxx(i)**2) + f22*(syy(i)**2) +
132 . f22*(szz(i)**2) + f66*(sxy(i)**2) +
133 . f66*(szx(i)**2) + two*f12*sxx(i)*syy(i) +
134 . two*f12*sxx(i)*szz(i)
135 b = f1*sxx(i) + f2*syy(i) + f2*szz(i)
136c
137 ! Compute failure index and reserve factor
138 findex = a + b
139 findex = max(zero,findex)
140c
141 ! Compute reserve factor
142 rfactr = (-b + sqrt((b**2)+four*a))/max((two*a),em20)
143 dfmax(i,2) = rfactr
144c
145 ! Damage variable update
146 dfmax(i,1) = min(one ,max(findex,dfmax(i,1)))
147 IF (dfmax(i,1) >= one) THEN
148 nindx = nindx+1
149 indx(nindx) = i
150 IF (ifail_so > 0) THEN
151 uvar(i,1) = time
152 ENDIF
153 ENDIF
154 ENDIF
155c
156 ! Stress relaxation in case of damage reached
157 IF ((uvar(i,1) > zero).AND.(loff(i) /= zero).AND.
158 . (ifail_so > 0).AND.(off(i) /= zero)) THEN
159 dmg_scale(i) = exp(-(time - uvar(i,1))/tmax)
160 IF (dmg_scale(i) < em02) THEN
161 loff(i) = zero
162 tdele(i) = time
163 dmg_scale(i) = zero
164 IF (ifail_so == 1) THEN
165 off(i) = zero
166 nindx0 = nindx0 + 1
167 indx0(nindx0) = i
168 ELSEIF (ifail_so == 2) THEN
169 noff(i) = noff(i) + 1
170 IF (int(noff(i)) >= npg) THEN
171 off(i) = zero
172 nindx0 = nindx0 + 1
173 indx0(nindx0) = i
174 ENDIF
175 ENDIF
176 ENDIF
177 ENDIF
178 ENDDO
179c
180 !====================================================================
181 ! - PRINTOUT DATA ABOUT FAILED ELEMENTS
182 !====================================================================
183 IF(nindx > 0)THEN
184 DO j=1,nindx
185 i = indx(j)
186#include "lockon.inc"
187 WRITE(iout, 1000) ngl(i),ip,ilay
188 WRITE(istdo,1100) ngl(i),ip,ilay,time
189#include "lockoff.inc"
190 END DO
191 ENDIF
192C
193 IF(nindx0 > 0)THEN
194 DO j=1,nindx0
195 i = indx0(j)
196#include "lockon.inc"
197 WRITE(iout, 1200) ngl(i),time
198 WRITE(istdo,1200) ngl(i),time
199#include "lockoff.inc"
200 END DO
201 ENDIF
202C--------------------------------------------
203 1000 FORMAT(1x,'FAILURE (TSAIWU) OF SOLID ELEMENT ',i10,1x,
204 .',GAUSS PT',i5,1x,',LAYER',i5)
205 1100 FORMAT(1x,'FAILURE (TSAIWU) OF SOLID ELEMENT ',i10,1x,
206 .',GAUSS PT',i5,1x,',LAYER',i5,1x,'AT TIME :',1pe20.13)
207 1200 FORMAT(1x,'-- RUPTURE OF SOLID ELEMENT : ',i10,1x,
208 .'AT TIME :',1pe20.13)
209C--------------------------------------------
210 RETURN
211 END
subroutine fail_tsaiwu_s(nel, nuvar, ip, ilay, npg, time, timestep, uparam, ngl, off, loff, noff, signxx, signyy, signzz, signxy, signyz, signzx, uvar, nuparam, dfmax, lf_dammx, tdele, dmg_scale)
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21