OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
fail_tsaihill_c.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_c ../engine/source/materials/fail/tsaihill/fail_tsaihill_c.f
25!||--- called by ------------------------------------------------------
26!|| mulawc ../engine/source/materials/mat_share/mulawc.F90
27!|| usermat_shell ../engine/source/materials/mat_share/usermat_shell.F
28!||====================================================================
29 SUBROUTINE fail_tsaihill_c(
30 1 NEL ,NUPARAM ,NUVAR ,UPARAM ,UVAR ,
31 2 TIME ,NGL ,IPG ,ILAY ,IPT ,
32 3 SIGNXX ,SIGNYY ,SIGNXY ,SIGNYZ ,SIGNZX ,
33 4 OFF ,FOFF ,DMG_FLAG ,DMG_SCALE ,
34 5 DFMAX ,LF_DAMMX ,TDEL ,TIMESTEP )
35C-----------------------------------------------
36C Tsai-Hill failure model 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 . SIGNXX,SIGNYY,SIGNXY,SIGNYZ,SIGNZX
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
68 my_real
69 . X11,X22,S12,TMAX,FCUT
70 my_real
71 . asrate,findex,rfactr,
72 . sxx(nel),syy(nel),sxy(nel)
73C!----------------------------------------------
74 !=======================================================================
75 ! - INITIALISATION OF COMPUTATION ON TIME STEP
76 !=======================================================================
77 ! Recovering model parameters
78 x11 = uparam(1)
79 x22 = uparam(2)
80 s12 = uparam(3)
81 tmax = uparam(4)
82 fcut = uparam(5)
83 ifail_sh = int(uparam(6))
84c
85 ! Stress softening activation
86 dmg_flag = 1
87c
88 ! Stress tensor filtering
89 IF (fcut > zero) THEN
90 asrate = two*pi*fcut*timestep
91 asrate = asrate/(one+asrate)
92 DO i = 1,nel
93 sxx(i) = asrate*signxx(i) + (one - asrate)*uvar(i,2)
94 syy(i) = asrate*signyy(i) + (one - asrate)*uvar(i,3)
95 sxy(i) = asrate*signxy(i) + (one - asrate)*uvar(i,4)
96 uvar(i,2) = sxx(i)
97 uvar(i,3) = syy(i)
98 uvar(i,4) = sxy(i)
99 ENDDO
100 ELSE
101 DO i = 1,nel
102 sxx(i) = signxx(i)
103 syy(i) = signyy(i)
104 sxy(i) = signxy(i)
105 ENDDO
106 ENDIF
107c
108 !====================================================================
109 ! - COMPUTATION OF THE DAMAGE VARIABLE EVOLUTION
110 !====================================================================
111 ! Initialization of element failure index
112 nindx = 0
113 indx(1:nel) = 0
114c
115 ! Loop over the elements
116 DO i=1,nel
117c
118 ! If damage has not been reached yet
119 IF (dfmax(i,1)<one) THEN
120c
121 ! Compute failure index and reserve factor
122 findex = (sxx(i)/x11)**2 - ((sxx(i)*syy(i))/(x11**2)) +
123 . (syy(i)/x22)**2 + (sxy(i)/s12)**2
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 (TSAIHILL) OF SHELL ELEMENT ',i10,1x,',GAUSS PT',
165 . i2,1x,',LAYER',i3,1x,',INTEGRATION PT',i3)
166 2100 FORMAT(1x,'FAILURE (TSAIHILL) OF SHELL ELEMENT ',i10,1x,',GAUSS PT',
167 . i2,1x,',LAYER',i3,1x,',INTEGRATION PT',i3,1x,'AT TIME :',1pe12.4)
168c------------------------
169 END
subroutine fail_tsaihill_c(nel, nuparam, nuvar, uparam, uvar, time, ngl, ipg, ilay, ipt, signxx, signyy, signxy, signyz, signzx, off, foff, dmg_flag, dmg_scale, dfmax, lf_dammx, tdel, timestep)
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21