OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
sigeps121c.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!|| sigeps121c ../engine/source/materials/mat/mat121/sigeps121c.F
25!||--- called by ------------------------------------------------------
26!|| mulawc ../engine/source/materials/mat_share/mulawc.F90
27!||--- calls -----------------------------------------------------
28!|| mat121c_newton ../engine/source/materials/mat/mat121/mat121c_newton.F
29!|| mat121c_nice ../engine/source/materials/mat/mat121/mat121c_nice.F
30!|| vinter2 ../engine/source/tools/curve/vinter.F
31!||--- uses -----------------------------------------------------
32!|| elbufdef_mod ../common_source/modules/mat_elem/elbufdef_mod.F90
33!||====================================================================
34 SUBROUTINE sigeps121c(
35 1 NEL ,NGL ,NUPARAM ,NUVAR ,NFUNC ,IFUNC ,NPF ,
36 2 TF ,TIMESTEP,TIME ,UPARAM ,UVAR ,RHO ,PLA ,
37 3 DPLA ,SOUNDSP ,EPSD ,GS ,THK ,THKLY ,OFF ,
38 4 DEPSXX ,DEPSYY ,DEPSXY ,DEPSYZ ,DEPSZX ,
39 5 EPSPXX ,EPSPYY ,EPSPXY ,EPSPYZ ,EPSPZX ,
40 6 SIGOXX ,SIGOYY ,SIGOXY ,SIGOYZ ,SIGOZX ,
41 7 SIGNXX ,SIGNYY ,SIGNXY ,SIGNYZ ,SIGNZX ,
42 8 SIGY ,ET ,VARNL ,INLOC ,DT ,
43 9 IPG ,IPT ,NPTR ,NPTS ,NPTT ,
44 A BUFLY ,OFFL ,IOFF_DUCT)
45C
46 USE elbufdef_mod
47C-----------------------------------------------
48C I m p l i c i t T y p e s
49C-----------------------------------------------
50#include "implicit_f.inc"
51C-----------------------------------------------
52C C O M M O N
53C-----------------------------------------------
54#include "com08_c.inc"
55#include "units_c.inc"
56#include "comlock.inc"
57C-----------------------------------------------
58C D u m m y A r g u m e n t s
59C-----------------------------------------------
60 INTEGER NEL,NUPARAM,NUVAR,NFUNC,INLOC,
61 . IPG,IPT,NPF(*),NGL(NEL),
62 . IFUNC(NFUNC),NPTR,NPTS,NPTT
63 INTEGER, DIMENSION(NEL), INTENT(INOUT) :: IOFF_DUCT
64 my_real
65 . TIMESTEP,TIME,TF(*),UPARAM(NUPARAM)
66 my_real,DIMENSION(NEL), INTENT(IN) ::
67 . RHO,THKLY,GS,DT,
68 . DEPSXX,DEPSYY,DEPSXY,DEPSYZ,DEPSZX,
69 . EPSPXX,EPSPYY,EPSPXY,EPSPYZ,EPSPZX,
70 . sigoxx,sigoyy,sigoxy,sigoyz,sigozx
71 my_real,DIMENSION(NEL), INTENT(OUT) ::
72 . soundsp,signxx,signyy,signxy,signyz,signzx
73 my_real,DIMENSION(NEL) :: sigy,et
74 my_real,DIMENSION(NEL), INTENT(INOUT) ::
75 . pla,epsd,thk,off,varnl,dpla,offl
76 my_real,DIMENSION(NEL,NUVAR), INTENT(INOUT) ::
77 . uvar
78 TYPE(buf_lay_) :: BUFLY
79C-----------------------------------------------
80C L o c a l V a r i a b l e s
81C-----------------------------------------------
82 INTEGER I,J,IRES,Ifail,NINDX,NINDX2,INDX(NEL),INDX2(NEL),
83 . ipos(nel),iad(nel),ilen(nel),ir,is,it
84 my_real dtmin,xscale_fail,yscale_fail,s1,s2,q,s11(nel),
85 . s22(nel),r_inter,dfdepsd(nel),fail(nel),seq(nel)
86C=======================================================================
87c
88 ires = nint(uparam(11)) ! Plastic projection method
89 ! = 1 => Nice method
90 ! = 2 => Newton-iteration method
91 ifail = nint(uparam(13)) ! Failure criterion flag
92 ! = 0 => Von Mises stress
93 ! = 1 => Plastic strain
94 ! = 2 => Maximum princ. stress +
95 ! abs(Minimum princ. stress)
96 ! = 3 => Maximum princ. stress
97 dtmin = uparam(15) ! Minimal timestep for element deletion
98 xscale_fail = uparam(22) ! Strain-rate scale factor for failure criterion function
99 yscale_fail = uparam(23) ! Ordinate scale factor for failure criterion function
100
101c--------------------------
102 SELECT CASE (ires)
103c
104 CASE(1)
105c
106 CALL mat121c_nice(
107 1 nel ,ngl ,nuparam ,nuvar ,nfunc ,ifunc ,npf ,
108 2 tf ,timestep,time ,uparam ,uvar ,rho ,pla ,
109 3 dpla ,soundsp ,epsd ,gs ,thk ,thkly ,off ,
110 4 depsxx ,depsyy ,depsxy ,depsyz ,depszx ,
111 5 epspxx ,epspyy ,epspxy ,epspyz ,epspzx ,
112 6 sigoxx ,sigoyy ,sigoxy ,sigoyz ,sigozx ,
113 7 signxx ,signyy ,signxy ,signyz ,signzx ,
114 8 sigy ,et ,varnl ,seq ,inloc ,offl )
115c
116 CASE(2)
117c
118 CALL mat121c_newton(
119 1 nel ,ngl ,nuparam ,nuvar ,nfunc ,ifunc ,npf ,
120 2 tf ,timestep,time ,uparam ,uvar ,rho ,pla ,
121 3 dpla ,soundsp ,epsd ,gs ,thk ,thkly ,off ,
122 4 depsxx ,depsyy ,depsxy ,depsyz ,depszx ,
123 5 epspxx ,epspyy ,epspxy ,epspyz ,epspzx ,
124 6 sigoxx ,sigoyy ,sigoxy ,sigoyz ,sigozx ,
125 7 signxx ,signyy ,signxy ,signyz ,signzx ,
126 8 sigy ,et ,varnl ,seq ,inloc ,offl )
127c
128 END SELECT
129c
130 ! Ductile failure activation
131 ioff_duct(1:nel) = 1
132c
133 !--------------------------------------------------------------------
134 ! Failure
135 !--------------------------------------------------------------------
136c
137 ! Compute failure criterion value
138 IF (ifunc(4) > 0) THEN
139 ipos(1:nel) = 1
140 iad(1:nel) = npf(ifunc(4)) / 2 + 1
141 ilen(1:nel) = npf(ifunc(4)+1) / 2 - iad(1:nel) - ipos(1:nel)
142 CALL vinter2(tf,iad,ipos,ilen,nel,epsd/xscale_fail,dfdepsd,fail)
143 fail(1:nel) = yscale_fail*fail(1:nel)
144 ENDIF
145c
146 ! Checking elements deletion criteria
147 nindx = 0
148 nindx2 = 0
149 IF (dtmin > zero .OR. ifunc(4) > 0) THEN
150 DO i = 1,nel
151c
152 ! Minimum timestep
153 IF ((dt(i) > em20).AND.(dt(i) < dtmin).AND.(off(i) == one)) THEN
154 off(i) = zero
155 nindx = nindx+1
156 indx(nindx) = i
157 ENDIF
158c
159 ! Failure criterion
160 IF ((ifunc(4) > 0).AND.(off(i) == one)) THEN
161 ! Failure indicator evolution
162 IF (offl(i) < em01) offl(i) = zero
163 IF (offl(i) < one) offl(i) = offl(i)*four_over_5
164 ! Case of under-integrated shells
165 IF ((nptr == 1).AND.(npts == 1)) THEN
166 !Initialization for checking complete failure of the shell (all integration points)
167 IF (ipt == 1) THEN
168 off(i) = zero
169 ENDIF
170 !If one integration points is not fully broken, the shell remains
171 IF (offl(i)>zero) off(i) = one
172 ! Case of fully integrated shells
173 ELSE
174 IF ((ipg == 1).AND.(ipt == 1)) THEN
175 !Initialization for checking complete failure of the shell (all integration points)
176 off(i) = zero
177 ! Loop over all Gauss points (thickness + surface)
178 DO ir = 1,nptr
179 DO is = 1,npts
180 DO it = 1,nptt
181 !If one integration points is not fully broken, the shell remains
182 IF (bufly%LBUF(ir,is,it)%OFF(i)>zero) off(i) = one
183 ENDDO
184 ENDDO
185 ENDDO
186 ENDIF
187 ENDIF
188 ! Check integration point failure
189 IF (offl(i) == one) THEN
190 ! -> Von Mises stress
191 IF (ifail == 0) THEN
192 IF (seq(i) >= fail(i)) offl(i) = four_over_5
193 ! -> Plastic strain
194 ELSEIF (ifail == 1) THEN
195 IF (pla(i) >= fail(i)) offl(i) = four_over_5
196 ! -> Maximum principal stress and absolute value of minimum principal stress
197 ELSEIF (ifail == 2) THEN
198 s1 = half*(signxx(i) + signyy(i))
199 s2 = half*(signxx(i) - signyy(i))
200 q = sqrt(s2**2 + signxy(i)**2)
201 s11(i) = s1 + q
202 s22(i) = s1 - q
203 IF (s22(i) >= s11(i)) THEN
204 r_inter = s22(i)
205 s22(i) = s11(i)
206 s11(i) = r_inter
207 ENDIF
208 IF ((s11(i)>=fail(i)).OR.(abs(s22(i))>=fail(i))) offl(i) = four_over_5
209 ! -> Maximum principal stress
210 ELSEIF (ifail == 3) THEN
211 s1 = half*(signxx(i) + signyy(i))
212 s2 = half*(signxx(i) - signyy(i))
213 q = sqrt(s2**2 + signxy(i)**2)
214 s11(i) = s1 + q
215 s22(i) = s1 - q
216 IF (s22(i) >= s11(i)) THEN
217 r_inter = s22(i)
218 s22(i) = s11(i)
219 s11(i) = r_inter
220 ENDIF
221 IF (s11(i)>=fail(i)) offl(i) = four_over_5
222 ENDIF
223 !Integration point failure
224 IF (offl(i) == four_over_5) THEN
225 nindx2 = nindx2+1
226 indx2(nindx2) = i
227 ENDIF
228 ENDIF
229 ENDIF
230 ENDDO
231 ENDIF
232c
233 ! Printout timestep element deletion
234 IF (nindx>0) THEN
235 DO j=1,nindx
236#include "lockon.inc"
237 WRITE(iout, 1000) ngl(indx(j))
238 WRITE(istdo,1100) ngl(indx(j)),tt
239#include "lockoff.inc"
240 ENDDO
241 ENDIF
242c
243 ! Printout failure
244 IF (nindx2>0) THEN
245 DO j=1,nindx2
246#include "lockon.inc"
247 WRITE(iout, 2000) ngl(indx2(j)),ipg,ipt
248 WRITE(istdo,2100) ngl(indx2(j)),ipg,ipt,tt
249#include "lockoff.inc"
250 ENDDO
251 ENDIF
252c
253 1000 FORMAT(1x,'minimum timestep(plas_rate) reached, deleted shell element ',I10)
254 1100 FORMAT(1X,'minimum timestep(plas_rate) reached, deleted shell element ',I10,1X,'at time :',1PE12.4)
255 2000 FORMAT(1X,'failure(plas_rate) in shell element ',I10,1X,',gauss pt',I2,1X,',thickness intg. pt',I3)
256 2100 FORMAT(1X,'failure(plas_rate) in shell element ',I10,1X,',gauss pt',I2,1X,',thickness intg. pt',I3,
257 . 1X,'at time :',1PE12.4)
258c
259c-----------
260 END
subroutine mat121c_newton(nel, ngl, nuparam, nuvar, nfunc, ifunc, npf, tf, timestep, time, uparam, uvar, rho, pla, dpla, soundsp, epsd, gs, thk, thkly, off, depsxx, depsyy, depsxy, depsyz, depszx, epspxx, epspyy, epspxy, epspyz, epspzx, sigoxx, sigoyy, sigoxy, sigoyz, sigozx, signxx, signyy, signxy, signyz, signzx, sigy, et, dplanl, seq, inloc, loff)
subroutine mat121c_nice(nel, ngl, nuparam, nuvar, nfunc, ifunc, npf, tf, timestep, time, uparam, uvar, rho, pla, dpla, soundsp, epsd, gs, thk, thkly, off, depsxx, depsyy, depsxy, depsyz, depszx, epspxx, epspyy, epspxy, epspyz, epspzx, sigoxx, sigoyy, sigoxy, sigoyz, sigozx, signxx, signyy, signxy, signyz, signzx, sigy, et, dplanl, seq, inloc, loff)
subroutine sigeps121c(nel, ngl, nuparam, nuvar, nfunc, ifunc, npf, tf, timestep, time, uparam, uvar, rho, pla, dpla, soundsp, epsd, gs, thk, thkly, off, depsxx, depsyy, depsxy, depsyz, depszx, epspxx, epspyy, epspxy, epspyz, epspzx, sigoxx, sigoyy, sigoxy, sigoyz, sigozx, signxx, signyy, signxy, signyz, signzx, sigy, et, varnl, inloc, dt, ipg, ipt, nptr, npts, nptt, bufly, offl, ioff_duct)
Definition sigeps121c.F:45
subroutine vinter2(tf, iad, ipos, ilen, nel0, x, dydx, y)
Definition vinter.F:143