OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
fail_emc.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_emc ../engine/source/materials/fail/emc/fail_emc.F
25!||--- called by ------------------------------------------------------
26!|| mmain ../engine/source/materials/mat_share/mmain.F90
27!|| mmain8 ../engine/source/materials/mat_share/mmain8.F
28!|| mulaw ../engine/source/materials/mat_share/mulaw.F90
29!|| mulaw8 ../engine/source/materials/mat_share/mulaw8.F90
30!|| usermat_solid ../engine/source/materials/mat_share/usermat_solid.F
31!||====================================================================
32 SUBROUTINE fail_emc(
33 1 NEL ,NUVAR ,TIME ,TIMESTEP,
34 2 UPARAM ,NGL ,
35 4 SIGNXX ,SIGNYY ,SIGNZZ ,SIGNXY ,SIGNYZ ,SIGNZX ,
36 5 PLAS ,DPLA ,EPSP ,UVAR ,
37 6 OFF ,DFMAX ,TDELE )
38C---------+---------+---+---+--------------------------------------------
39c---------+---------+---+---+--------------------------------------------
40C /FAIL/EMC - tabulated rupture criteria for solids
41C-----------------------------------------------
42C I m p l i c i t T y p e s
43C-----------------------------------------------
44#include "implicit_f.inc"
45C---------+---------+---+---+--------------------------------------------
46C VAR | SIZE |TYP| RW| DEFINITION
47C---------+---------+---+---+--------------------------------------------
48C NEL | 1 | I | R | SIZE OF THE ELEMENT GROUP NEL
49C NUPARAM | 1 | I | R | SIZE OF THE USER PARAMETER ARRAY
50C NUVAR | 1 | I | R | NUMBER OF FAILURE ELEMENT VARIABLES
51C---------+---------+---+---+--------------------------------------------
52C TIME | 1 | F | R | CURRENT TIME
53C TIMESTEP| 1 | F | R | CURRENT TIME STEP
54C UPARAM | NUPARAM | F | R | USER FAILURE PARAMETER ARRAY
55C---------+---------+---+---+--------------------------------------------
56C SIGNXX | NEL | F | W | NEW ELASTO PLASTIC STRESS XX
57C SIGNYY | NEL | F | W | NEW ELASTO PLASTIC STRESS YY
58C ... | | | |
59C ... | | | |
60C---------+---------+---+---+--------------------------------------------
61C UVAR |NEL*NUVAR| F |R/W| USER ELEMENT VARIABLE ARRAY
62C OFF | NEL | F |R/W| DELETED ELEMENT FLAG (=1. ON, =0. OFF)
63C---------+---------+---+---+--------------------------------------------
64#include "units_c.inc"
65#include "param_c.inc"
66#include "scr17_c.inc"
67#include "comlock.inc"
68C-----------------------------------------------
69C I N P U T A r g u m e n t s
70C-----------------------------------------------
71 INTEGER NEL,NUVAR
72 INTEGER NGL(NEL)
73c
74 my_real TIME,TIMESTEP,UPARAM(*),
75 . SIGNXX(NEL),SIGNYY(NEL),SIGNZZ(NEL),
76 . signxy(nel),signyz(nel),signzx(nel),
77 . plas(nel),dpla(nel),epsp(nel)
78C-----------------------------------------------
79C O U T P U T A r g u m e n t s
80C-----------------------------------------------
81cc my_real
82C-----------------------------------------------
83C I N P U T O U T P U T A r g u m e n t s
84C-----------------------------------------------
85 my_real
86 . uvar(nel,nuvar), off(nel),dfmax(nel),tdele(nel)
87C-----------------------------------------------
88C L o c a l V a r i a b l e s
89C-----------------------------------------------
90 INTEGER I,J,JJ,K,IR,IADBUF,NINDX,IFAIL
91 INTEGER, DIMENSION(NEL) ::
92 . INDX
93C
94 my_real
95 . seq,inv2,eta,sigm,xi,epsf,
96 . devxx,devyy,devzz,bcoef,lode,dam,
97 . bfrac,gama,cfrac,deps0,
98 . plap,f1,f2,f3,afrac,nfrac
99 my_real :: df12, df23, df13
100C=======================================================================
101C INITIALIZATIONS
102C-----------------------------------------------
103 afrac = uparam(1)
104 bfrac = uparam(2)
105 gama = uparam(3)
106 cfrac = uparam(4)
107 nfrac = uparam(5)
108 deps0 = uparam(6)
109 plap = 0
110C-----------------------------------------------
111 indx = 0
112 nindx = 0
113C-------------------------------------------------------------------
114c Failure strain value - function interpolation
115C-------------------------------------------------------------------
116 DO i=1,nel
117
118 dam = uvar(i,2)
119 IF (off(i) < 0.1) off(i)=zero
120 IF (off(i) < one) off(i)=off(i)*four_over_5
121
122 IF (plas(i) > zero .and. off(i) == one) THEN
123C--- failure strain interpolation
124
125 plap = dpla(i)/timestep
126
127 sigm = (signxx(i)+signyy(i)+signzz(i))*third
128 devxx = signxx(i) - sigm
129 devyy = signyy(i) - sigm
130 devzz = signzz(i) - sigm
131 seq = sqrt(three_half*(devxx*devxx
132 . +devyy*devyy
133 . +devzz*devzz
134 . + two*(signxy(i)*signxy(i)
135 . +signyz(i)*signyz(i)
136 . +signzx(i)*signzx(i))))
137
138 ! determinant du deviateur des contraintes
139 inv2 = devxx * devyy * devzz
140 . + two*signxy(i)*signzx(i)*signyz(i)
141 . - devxx*signyz(i)**2 - devyy*signzx(i)**2
142 . - devzz*signxy(i)**2
143
144 IF (seq == zero) THEN
145 eta = third
146 xi = zero
147 ELSE
148 eta = sigm/seq
149 xi = one/seq**3
150 xi = half*twenty7*inv2*xi
151 ENDIF
152
153 IF (xi < -one) xi =-one
154 IF (xi > one) xi = one
155
156 lode = one - two*acos(xi)/pi
157
158 f1 = two_third*cos((one -lode)*pi/six)
159 f2 = two_third*cos((three+lode)*pi/six)
160 f3 =-two_third*cos((one +lode)*pi/six)
161 plap = max(plap,deps0)
162 bcoef = bfrac*(one+gama*log(plap/deps0))
163
164 IF (eta < -third) THEN
165 epsf = ep02
166 ELSE
167 df12 = max(em20,f1-f2)
168 df23 = max(em20,f2-f3)
169 df13 = max(em20,f1-f3)
170 epsf = bcoef*(one+cfrac)**(one/nfrac)
171 . * ((half*(df12**afrac
172 . +df23**afrac
173 . +df13**afrac))**(one/afrac)
174 . + cfrac*(two*eta+f1+f3))**(-one/nfrac)
175
176 ENDIF
177
178 dam = uvar(i,2) + (plas(i) - uvar(i,1))/epsf
179
180 uvar(i,1) = plas(i)
181 uvar(i,2) = dam
182 dfmax(i) = min(one,max(dfmax(i),dam ))
183c
184 IF (dam >= one) THEN
185 off(i) = four_over_5
186 nindx = nindx+1
187 indx(nindx)=i
188 tdele(i) = time
189 ENDIF
190 ENDIF
191 ! EPSF(I) = YY
192c
193 ENDDO
194c-----------------------------
195 IF (nindx > 0 )THEN
196 DO j=1,nindx
197#include "lockon.inc"
198 WRITE(iout, 1000) ngl(indx(j))
199 WRITE(istdo,1100) ngl(indx(j)),time
200#include "lockoff.inc"
201 ENDDO
202
203 ENDIF
204c-----------------------------------------------
205 1000 FORMAT(1x,'DELETE SOLID ELEMENT NUMBER ',i10)
206 1100 FORMAT(1x,'DELETE SOLID ELEMENT NUMBER ',i10,
207 . ' AT TIME :',1pe12.4)
208c-----------
209 RETURN
210 END
subroutine fail_emc(nel, nuvar, time, timestep, uparam, ngl, signxx, signyy, signzz, signxy, signyz, signzx, plas, dpla, epsp, uvar, off, dfmax, tdele)
Definition fail_emc.F:38
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21