OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
sigeps59.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!|| sigeps59 ../engine/source/materials/mat/mat059/sigeps59.F
25!||--- called by ------------------------------------------------------
26!|| suser43 ../engine/source/elements/solid/sconnect/suser43.F
27!||--- calls -----------------------------------------------------
28!|| finter ../engine/source/tools/curve/finter.F
29!||====================================================================
30 SUBROUTINE sigeps59(
31 1 NEL ,TIME ,TIMESTEP,UPARAM ,OFF ,
32 2 EPSD ,STIFM ,NUPARAM ,
33 3 IFUNC ,MAXFUNC ,NPF ,TF ,AREA ,
34 4 EPSZZ ,EPSYZ ,EPSZX ,DEPSZZ ,DEPSYZ ,DEPSZX ,
35 5 SIGOZZ ,SIGOYZ ,SIGOZX ,SIGNZZ ,SIGNYZ ,SIGNZX ,
36 6 EPLASN ,EPLAST ,JSMS ,DMELS )
37C-----------------------------------------------
38C I m p l i c i t T y p e s
39C-----------------------------------------------
40#include "implicit_f.inc"
41#include "comlock.inc"
42C---------+---------+---+---+--------------------------------------------
43C VAR | SIZE |TYP| RW| DEFINITION
44C---------+---------+---+---+--------------------------------------------
45C NEL | 1 | I | R | SIZE OF THE ELEMENT GROUP NEL
46C NUPARAM | 1 | I | R | SIZE OF THE USER PARAMETER ARRAY
47C NUVAR | 1 | I | R | NUMBER OF USER ELEMENT VARIABLES
48C JSMS | 1 | I | R | 0/1 (=1 IF /DT/AMS APPLIES TO THIS ELEMENT GROUP)
49C---------+---------+---+---+--------------------------------------------
50C MFUNC | 1 | I | R | NUMBER FUNCTION USED FOR THIS USER LAW not used
51C KFUNC | NFUNC | I | R | FUNCTION INDEX not used
52C NPF | * | I | R | FUNCTION ARRAY
53C TF | * | F | R | FUNCTION ARRAY
54C---------+---------+---+---+--------------------------------------------
55C TIME | 1 | F | R | CURRENT TIME
56C TIMESTEP| 1 | F | R | CURRENT TIME STEP
57C UPARAM | NUPARAM | F | R | USER MATERIAL PARAMETER ARRAY
58C EPSPXX | NEL | F | R | STRAIN RATE XX
59C EPSPYY | NEL | F | R | STRAIN RATE YY
60C ... | | | |
61C DEPSXX | NEL | F | R | STRAIN INCREMENT XX
62C DEPSYY | NEL | F | R | STRAIN INCREMENT YY
63C ... | | | |
64C EPSXX | NEL | F | R | STRAIN XX
65C EPSYY | NEL | F | R | STRAIN YY
66C ... | | | |
67C SIGOXX | NEL | F | R | OLD ELASTO PLASTIC STRESS XX
68C SIGOYY | NEL | F | R | OLD ELASTO PLASTIC STRESS YY
69C ... | | | |
70C---------+---------+---+---+--------------------------------------------
71C SIGNXX | NEL | F | W | NEW ELASTO PLASTIC STRESS XX
72C SIGNYY | NEL | F | W | NEW ELASTO PLASTIC STRESS YY
73C ... | | | |
74C DMELS | NEL | F | W | NON DIAGONAL TERM FOR AMS
75C---------+---------+---+---+--------------------------------------------
76C UVAR |NEL*NUVAR| F |R/W| USER ELEMENT VARIABLE ARRAY
77C OFF | NEL | F |R/W| DELETED ELEMENT FLAG (=1. ON, =0. OFF)
78C---------+---------+---+---+--------------------------------------------
79#include "sms_c.inc"
80C----------------------------------------------------------
81C D u m m y A r g u m e n t s
82C----------------------------------------------------------
83 INTEGER NEL,NUPARAM,NUVAR,MAXFUNC, JSMS
84 INTEGER IFUNC(*),NPF(*)
85 my_real
86 . TIME,TIMESTEP
87 my_real
88 . UPARAM(NUPARAM),OFF(NEL),TF(*),EPLASN(NEL),EPLAST(NEL),AREA(NEL),
89 . epsd(nel),depszz(nel),depsyz(nel),depszx(nel),
90 . epszz(nel) ,epsyz(nel) ,epszx(nel) ,
91 . sigozz(nel),sigoyz(nel),sigozx(nel),
92 . stifm(nel),signzz(nel),signyz(nel),signzx(nel),
93 . dmels(*)
94C-----------------------------------------------
95C L o c a l V a r i a b l e s
96C-----------------------------------------------
97 INTEGER I1,I2,I,J,IEL,IRATE,NRATE,IFILTR,NTRAC
98 INTEGER IFUNN(MAXFUNC),IFUNT(MAXFUNC),JJ(NEL),ELTRAC(NEL),II(NEL)
99 my_real
100 . E,ECOMP,G,G3,G12,G23,FCUT,DYDX1,DYDX2,Y1,Y2,R,DSIG,DEPLA,
101 . SVM,SIGT,DTB
102 my_real
103 . dsigx(nel),dsigy(nel),dsigz(nel),yfac(maxfunc),rate(maxfunc),
104 . yld(2,nel),hc(2,nel),depst(nel),stf(nel),fac(nel)
105C----------------------------------------------------------
106C E x t e r n a l F u n c t i o n
107C----------------------------------------------------------
108 my_real
109 . finter
110C=======================================================================
111C USER VARIABLES INITIALIZATION
112C-----------------------------------------------
113 e = uparam(1)
114 g = uparam(2)
115 g3 = g*three
116 nrate = nint(uparam(3))
117 ifiltr= nint(uparam(4))
118 fcut = uparam(5)
119 ecomp = uparam(6)
120c
121 IF (ecomp > 0) THEN
122 eltrac(1:nel) = 0
123 ntrac = 0
124 DO iel=1,nel
125 IF (epszz(iel) > zero) THEN ! element in traction
126 stf(iel) = (e+g) * area(iel)
127 dsigz(iel) = e*depszz(iel)
128 ntrac = ntrac + 1
129 eltrac(ntrac) = iel
130 ELSE ! element in compression
131 stf(iel) = (ecomp+g) * area(iel)
132 dsigz(iel) = ecomp*depszz(iel)
133 ENDIF
134 ENDDO
135 DO iel=1,nel
136 dsigy(iel) = g*depsyz(iel)
137 dsigx(iel) = g*depszx(iel)
138 signzz(iel) = sigozz(iel) + dsigz(iel)
139 signyz(iel) = sigoyz(iel) + dsigy(iel)
140 signzx(iel) = sigozx(iel) + dsigx(iel)
141 stifm(iel) = stifm(iel) + stf(iel)*off(iel)
142 ENDDO
143 ELSE ! symmetric traction/compression
144 ntrac = nel
145 DO iel=1,nel
146 eltrac(iel) = iel
147 stf(iel) = (e+g) * area(iel)
148 dsigz(iel) = e*depszz(iel)
149 dsigy(iel) = g*depsyz(iel)
150 dsigx(iel) = g*depszx(iel)
151 signzz(iel) = sigozz(iel) + dsigz(iel)
152 signyz(iel) = sigoyz(iel) + dsigy(iel)
153 signzx(iel) = sigozx(iel) + dsigx(iel)
154 stifm(iel) = stifm(iel) + stf(iel)*off(iel)
155 ENDDO
156 ENDIF
157c
158 IF (idtmins==2 .AND. jsms/=0) THEN
159 dtb = (dtmins/dtfacs)**2
160 DO iel=1,nel
161c omega = sqrt(2k/2*dmels), dt=2/omega, 2*dmels=dt**2 * 2k / 4
162 dmels(iel) = max(dmels(iel),half*dtb*stf(iel)*off(iel))
163 ENDDO
164 END IF
165c---
166 IF (nrate > 0) THEN ! plasticity
167c---
168 DO irate=1,nrate
169 j = (irate-1)*2
170 ifunn(irate) = ifunc(j+1)
171 ifunt(irate) = ifunc(j+2)
172 yfac(irate) = uparam(7+irate)
173 rate(irate) = uparam(7+irate+nrate)
174 ENDDO
175c
176c--- Calculate yield values
177c
178 IF (nrate > 1) THEN ! strain rate dependent
179c
180 DO iel = 1,nel
181 ii(iel) = 1
182 DO j=2,nrate-1
183 IF (epsd(iel) > rate(j)) ii(iel) = j
184 EXIT
185 ENDDO
186 ENDDO
187c
188 DO iel = 1,nel
189 i1 = ii(iel)
190 i2 = i1 + 1
191 fac(iel) = (epsd(iel) - rate(i1)) / (rate(i2) - rate(i1))
192 y1 = finter(ifunt(i1),eplast(iel),npf,tf,dydx1)*yfac(i1)
193 y2 = finter(ifunt(i2),eplast(iel),npf,tf,dydx2)*yfac(i2)
194 y1 = max(zero, y1)
195 y2 = max(zero, y2)
196 dydx1 = dydx1*yfac(i1)
197 dydx2 = dydx2*yfac(i2)
198 yld(2,iel) = y1 + fac(iel)*(y2 - y1)
199 hc(2,iel) = dydx1 + fac(iel)*(dydx2-dydx1)
200 ENDDO
201 DO i=1,ntrac
202 iel = eltrac(i)
203 i1 = ii(iel)
204 i2 = i1 + 1
205 y1 = finter(ifunn(i1),eplasn(iel),npf,tf,dydx1)*yfac(i1)
206 y2 = finter(ifunn(i2),eplasn(iel),npf,tf,dydx2)*yfac(i2)
207 y1 = max(zero, y1)
208 y2 = max(zero, y2)
209 dydx1 = dydx1*yfac(i1)
210 dydx2 = dydx2*yfac(i2)
211 yld(1,iel) = y1 + fac(iel)*(y2 - y1)
212 hc(1,iel) = dydx1 + fac(iel)*(dydx2-dydx1)
213 ENDDO
214c
215 ELSEIF (nrate == 1) THEN ! independent on strain rate
216c
217 DO iel = 1,nel
218 i1 = 1
219 yld(2,iel) = max(zero,
220 . finter(ifunt(i1),eplast(iel),npf,tf,dydx1)*yfac(i1))
221 hc(2,iel) = dydx1*yfac(i1)
222 ENDDO
223 DO i=1,ntrac
224 iel = eltrac(i)
225 i1 = 1
226 yld(1,iel) = max(zero,
227 . finter(ifunn(i1),eplasn(iel),npf,tf,dydx1)*yfac(i1))
228 hc(1,iel) = dydx1*yfac(i1)
229 ENDDO
230 ENDIF
231c-------
232c plasticity - normal direction
233c-------
234 DO i=1,ntrac
235 iel = eltrac(i)
236 svm = abs(signzz(iel))
237 dsig = svm - yld(1,iel)
238 IF (dsig > zero) THEN
239 depla = dsig / max((e + hc(1,iel)),em20)
240 r = min(one, ((yld(1,iel)+depla*hc(1,iel))/max(em20,svm)))
241 eplasn(iel) = eplasn(iel) + depla*off(iel)
242 signzz(iel) = signzz(iel)*r
243 ENDIF
244 ENDDO
245c-------
246c plasticity - tangent direction
247c-------
248 DO iel=1,nel
249 svm = sqrt(signyz(iel)**2 + signzx(iel)**2)
250 dsig = svm - yld(2,iel)
251 IF (dsig > zero) THEN
252 depla = dsig / max((g + hc(2,iel)),em20)
253 r = min(one, ((yld(2,iel)+depla*hc(2,iel))/max(em20,svm)))
254 eplast(iel) = eplast(iel) + depla*off(iel)
255 signyz(iel) = signyz(iel)*r
256 signzx(iel) = signzx(iel)*r
257 ENDIF
258c
259 signzz(iel) = signzz(iel)*off(iel)
260 signyz(iel) = signyz(iel)*off(iel)
261 signzx(iel) = signzx(iel)*off(iel)
262 ENDDO
263c---
264 ENDIF
265C-----------
266 RETURN
267 END
268C
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21
subroutine sigeps59(nel, time, timestep, uparam, off, epsd, stifm, nuparam, ifunc, maxfunc, npf, tf, area, epszz, epsyz, epszx, depszz, depsyz, depszx, sigozz, sigoyz, sigozx, signzz, signyz, signzx, eplasn, eplast, jsms, dmels)
Definition sigeps59.F:37