OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
fail_cockroft_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_cockroft_c ../engine/source/materials/fail/cockroft_latham/fail_cockroft_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_cockroft_c(
30 1 NEL ,NUVAR ,
31 2 TIME ,UPARAM ,NGL ,IPT ,ILAY ,
32 3 NPT0 ,IPTT ,IPG ,
33 4 SIGNXX ,SIGNYY ,SIGNXY ,
34 5 EPSXX ,EPSYY ,EPSXY ,EPSYZ ,EPSZX ,
35 6 DPLA ,UVAR ,UEL ,FOFF ,
36 7 OFF ,DFMAX ,TDEL )
37C--------------------------------------------------------------------
38C /FAIL/COCKROFT - Cockroft-Latham failure criteria for shells and solids
39C--------------------------------------------------------------------
40C-----------------------------------------------
41C I m p l i c i t T y p e s
42C-----------------------------------------------
43#include "implicit_f.inc"
44C-----------------------------------------------
45C G l o b a l P a r a m e t e r s
46C-----------------------------------------------
47#include "units_c.inc"
48#include "comlock.inc"
49C---------+--------+---+---+-------------------------------------------
50C VAR | SIZE |TYP| RW| DEFINITION
51C---------+--------+---+---+-------------------------------------------
52C NEL | 1 | I | R | SIZE OF THE ELEMENT GROUP NEL
53C NUPARAM | 1 | I | R | SIZE OF THE USER PARAMETER ARRAY
54C NUVAR | 1 | I | R | NUMBER OF USER ELEMENT VARIABLES
55C NPT0 | 1 | I | R | NUMBER OF LAYERS OR INTEGRATION POINTS
56C IPT | 1 | I | R | LAYER OR INTEGRATION POINT NUMBER
57C NGL | NEL | I | R | ELEMENT NUMBER
58C---------+--------+---+---+-------------------------------------------
59C TIME | 1 | F | R | CURRENT TIME
60C UPARAM | NUPARAM| F | R | USER MATERIAL PARAMETER ARRAY
61C EPSPXX | NEL | F | R | STRAIN RATE XX
62C EPSPYY | NEL | F | R | STRAIN RATE YY
63C ... | | | |
64C EPSXX | NEL | F | R | STRAIN XX
65C EPSYY | NEL | F | R | STRAIN YY
66C---------+--------+---+---+-------------------------------------------
67C SIGNXX | NEL | F |R/W| NEW ELASTO PLASTIC STRESS XX
68C SIGNYY | NEL | F |R/W| NEW ELASTO PLASTIC STRESS YY
69C ... | | | |
70C---------+--------+---+---+-------------------------------------------
71C PLA | NEL | F | R | PLASTIC STRAIN
72C DPLA | NEL | F | R | INCREMENTAL PLASTIC STRAIN
73C EPSP | NEL | F | R | EQUIVALENT STRAIN RATE
74C UVAR |NEL*NUVAR| F|R/W| USER ELEMENT VARIABLE ARRAY
75C OFF | NEL | F |R/W| DELETED ELEMENT FLAG (=1. ON, =0. OFF)
76C FOFF | NEL | I |R/W| DELETED INTEGRATION POINT FLAG (=1 ON, =0 OFF)
77C---------+--------+--+--+-------------------------------------------
78C I N P U T A r g u m e n t s
79C-----------------------------------------------
80 INTEGER, INTENT(IN) :: ILAY,IPTT,IPG
81 INTEGER NEL, NUVAR, NGL(NEL),
82 . IPT,NPT0,NOFF(NEL)
83 my_real TIME,UPARAM(*),DPLA(NEL),
84 . EPSXX(NEL) ,EPSYY(NEL) ,EPSXY(NEL),
85 . EPSYZ(NEL) ,EPSZX(NEL),
86 . DFMAX(NEL) ,TDEL(NEL)
87
88C
89C-----------------------------------------------
90C I N P U T O U T P U T A r g u m e n t s
91C-----------------------------------------------
92 INTEGER ,DIMENSION(NEL), INTENT(INOUT) :: FOFF
93 my_real UVAR(NEL,NUVAR), OFF(NEL),OFFL(NEL),
94 . SIGNXX(NEL),SIGNYY(NEL),UEL(NEL),
95 . SIGNXY(NEL)
96
97C-----------------------------------------------
98C L o c a l V a r i a b l e s
99C-----------------------------------------------
100 INTEGER I,J,NINDX,LEN
101 INTEGER, DIMENSION(NEL) :: INDX
102 my_real E_HYD,E_11,E_22,E_33,E_12,E_23,E_13,
103 . EEQ,D_EEQ,SIG_11,SIG_A,SIG_B
104C-----------------------------------------------
105C Ex : ELEMENT IS OFF iF COLA > C0
106C-----------------------------------------------
107 my_real c0 , ema
108
109C-----------------------------------------------
110C Ex : ELEMENT IS OFF number if IPs due to Cockroft-Latham criteria reached P_thick
111C-----------------------------------------------
112C! UVAR(I,1) contains previous equivalent strain value increment
113C! UVAR(I,2) contains the Cockroft-Latham accumulated value
114c! UVAR(I,3) contains the previous first principal stress
115 c0 = uparam(1)
116 ema = uparam(2)
117 nindx = 0
118C-----------------------------------------------
119 DO i =1,nel
120 IF(off(i) >= one .AND. foff(i) == 1 ) THEN
121c! equivalent strain calculation (negative = total strain ; positive = plastic strain)
122 IF(c0 < zero)THEN
123 e_hyd = third * (epsxx(i) + epsyy(i))
124 e_11 = epsxx(i) - e_hyd
125 e_22 = epsyy(i) - e_hyd
126 e_33 = -e_hyd
127 e_12 = half*epsxy(i)
128 e_23 = half*epsyz(i)
129 e_13 = half*epszx(i)
130
131 eeq = e_11**2 + e_22**2 + e_33**2
132 eeq = eeq + two * (e_12**2) + two * (e_23**2) + two * (e_13**2)
133 eeq = 0.8164965809 * sqrt(eeq) ! sqrt (2/3)*sqrt(...)
134
135 d_eeq = eeq - uvar(i,1)
136 IF (d_eeq <= zero) d_eeq = zero
137 uvar(i,1) = eeq
138 ELSE ! positive = plastic strain increment
139 d_eeq = dpla(i)
140 uvar(i,1) = uvar(i,1) + dpla(i)
141 ENDIF
142
143c! first principal stress Sigma_1 calculation
144 sig_a = (signxx(i) + signyy(i))/two
145 sig_b = sqrt(((signxx(i)-signyy(i))/two)**2+signxy(i)**2)
146 sig_11 = sig_a + sig_b
147 sig_11 = sig_11 * ema + (one-ema)* uvar(i,3)
148 uvar(i,3)= sig_11
149 uvar(i,2) = uvar(i,2) + max(sig_11,zero) * d_eeq
150
151 dfmax(i) = min(uvar(i,2) / max(em20,abs(c0)),one)
152
153 IF (dfmax(i) >= one) THEN
154 nindx = nindx + 1
155 indx(nindx) = i
156 foff(i) = 0
157 tdel(i) = time
158 ENDIF
159 ENDIF
160 ENDDO
161C!
162 DO j=1,nindx
163 i = indx(j)
164#include "lockon.inc"
165 WRITE(iout, 2000) ngl(i),ipg,ilay,iptt
166 WRITE(istdo,2100) ngl(i),ipg,ilay,iptt,time
167#include "lockoff.inc"
168
169 ENDDO
170c------------------
171 2000 FORMAT(1x,'FAILURE (COCKROFT-LATHAM) OF SHELL ELEMENT ',i10,1x,',GAUSS PT',i2,1x,',LAYER',i3,
172 . 1x,',INTEGRATION PT',i3)
173 2100 FORMAT(1x,'FAILURE (COCKROFT-LATHAM) OF SHELL ELEMENT ',i10,1x,',GAUSS PT',i2,1x,',LAYER',i3,
174 . 1x,',INTEGRATION PT',i3,1x,'AT TIME :',1pe12.4)
175c------------------
176
177 RETURN
178 END
subroutine fail_cockroft_c(nel, nuvar, time, uparam, ngl, ipt, ilay, npt0, iptt, ipg, signxx, signyy, signxy, epsxx, epsyy, epsxy, epsyz, epszx, dpla, uvar, uel, foff, off, dfmax, tdel)
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21