OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
fail_tsaihill_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_tsaihill_s ../engine/source/materials/fail/tsaihill/fail_tsaihill_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_tsaihill_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 . x11,x22,s12,tmax,fcut
68 my_real
69 . asrate,sxx(nel),syy(nel),szz(nel),
70 . sxy(nel),syz(nel),szx(nel),findex,rfactr
71C--------------------------------------------------------------
72 !=======================================================================
73 ! - INITIALISATION OF COMPUTATION ON TIME STEP
74 !=======================================================================
75 ! Recovering model parameters
76 x11 = uparam(1)
77 x22 = uparam(2)
78 s12 = 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 sxx(i) = asrate*signxx(i) + (one - asrate)*uvar(i,2)
89 syy(i) = asrate*signyy(i) + (one - asrate)*uvar(i,3)
90 szz(i) = asrate*signzz(i) + (one - asrate)*uvar(i,4)
91 sxy(i) = asrate*signxy(i) + (one - asrate)*uvar(i,5)
92 syz(i) = asrate*signyz(i) + (one - asrate)*uvar(i,6)
93 szx(i) = asrate*signzx(i) + (one - asrate)*uvar(i,7)
94 uvar(i,2) = sxx(i)
95 uvar(i,3) = syy(i)
96 uvar(i,4) = szz(i)
97 uvar(i,5) = sxy(i)
98 uvar(i,6) = syz(i)
99 uvar(i,7) = szx(i)
100 ENDDO
101 ELSE
102 DO i = 1,nel
103 sxx(i) = signxx(i)
104 syy(i) = signyy(i)
105 szz(i) = signzz(i)
106 sxy(i) = signxy(i)
107 syz(i) = signyz(i)
108 szx(i) = signzx(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 = (sxx(i)/x11)**2 - ((sxx(i)*syy(i))/(x11**2)) +
129 . (syy(i)/x22)**2 + (sxy(i)/s12)**2 -
130 . ((sxx(i)*szz(i))/(x11**2)) + (szz(i)/x22)**2 +
131 . (szx(i)/s12)**2
132 findex = max(zero,findex)
133c
134 ! compute reserve factor
135 dfmax(i,2) = one/max(sqrt(findex),em20)
136c
137 ! Damage variable update
138 dfmax(i,1) = min(one ,max(findex,dfmax(i,1)))
139 IF (dfmax(i,1) >= one) THEN
140 nindx = nindx+1
141 indx(nindx) = i
142 IF (ifail_so > 0) THEN
143 uvar(i,1) = time
144 ENDIF
145 ENDIF
146 ENDIF
147c
148 ! Stress relaxation in case of damage reached
149 IF ((uvar(i,1) > zero).AND.(loff(i) /= zero).AND.
150 . (ifail_so > 0).AND.(off(i) /= zero)) THEN
151 dmg_scale(i) = exp(-(time - uvar(i,1))/tmax)
152 IF (dmg_scale(i) < em02) THEN
153 loff(i) = zero
154 tdele(i) = time
155 dmg_scale(i) = zero
156 IF (ifail_so == 1) THEN
157 off(i) = zero
158 nindx0 = nindx0 + 1
159 indx0(nindx0) = i
160 ELSEIF (ifail_so == 2) THEN
161 noff(i) = noff(i) + 1
162 IF (int(noff(i)) >= npg) THEN
163 off(i) = zero
164 nindx0 = nindx0 + 1
165 indx0(nindx0) = i
166 ENDIF
167 ENDIF
168 ENDIF
169 ENDIF
170 ENDDO
171c
172 !====================================================================
173 ! - PRINTOUT DATA ABOUT FAILED ELEMENTS
174 !====================================================================
175 IF(nindx > 0)THEN
176 DO j=1,nindx
177 i = indx(j)
178#include "lockon.inc"
179 WRITE(iout, 1000) ngl(i),ip,ilay
180 WRITE(istdo,1100) ngl(i),ip,ilay,time
181#include "lockoff.inc"
182 END DO
183 ENDIF
184C
185 IF(nindx0 > 0)THEN
186 DO j=1,nindx0
187 i = indx0(j)
188#include "lockon.inc"
189 WRITE(iout, 1200) ngl(i),time
190 WRITE(istdo,1200) ngl(i),time
191#include "lockoff.inc"
192 END DO
193 ENDIF
194C--------------------------------------------
195 1000 FORMAT(1x,'FAILURE (TSAIHILL) OF SOLID ELEMENT ',i10,1x,
196 .',GAUSS PT',i5,1x,',LAYER',i5)
197 1100 FORMAT(1x,'FAILURE (TSAIHILL) OF SOLID ELEMENT ',i10,1x,
198 .',GAUSS PT',i5,1x,',LAYER',i5,1x,'AT TIME :',1pe20.13)
199 1200 FORMAT(1x,'-- RUPTURE OF SOLID ELEMENT : ',i10,1x,
200 .'AT TIME :',1pe20.13)
201C--------------------------------------------
202 RETURN
203 END
subroutine fail_tsaihill_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
subroutine mulaw(lft, llt, nft, mtn, jcvt, pm, off, sig, eint, rho, vol, strain, gama, uvar, bufmat, tf, npf, imat, ngl, nuvar, nvartmp, vartmp, geo, pid, epsd, wxx, wyy, wzz, jsph, ssp, voln, vis, d1, d2, d3, d4, d5, d6, dvol, sold1, sold2, sold3, sold4, sold5, sold6, rx, ry, rz, sx, sy, sz, tx, ty, tz, ismstr, mfxx, mfxy, mfxz, mfyx, mfyy, mfyz, mfzx, mfzy, mfzz, ipm, isorth, nel, matparam)
Definition mulaw.F:54