OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
fail_cockroft_ib.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_ib ../engine/source/materials/fail/cockroft_latham/fail_cockroft_ib.F
25!||--- called by ------------------------------------------------------
26!|| fail_beam18 ../engine/source/elements/beam/fail_beam18.F
27!||====================================================================
28 SUBROUTINE fail_cockroft_ib(
29 . NEL ,NGL ,NUPARAM ,UPARAM ,
30 . TIME ,DPLA ,OFF ,DFMAX,
31 . TDEL ,IOUT ,ISTDO ,EPSXX ,
32 . IPT ,SIGNXX ,SIGNXY ,SIGNXZ ,
33 . NVARF , UVAR ,FOFF ,UELR,NPG)
34!====================================================================
35! cockroft failure model for integrated beams
36C-----------------------------------------------
37C I m p l i c i t T y p e s
38C-----------------------------------------------
39#include "implicit_f.inc"
40C-----------------------------------------------
41C G l o b a l P a r a m e t e r s
42C-----------------------------------------------
43#include "comlock.inc"
44C-----------------------------------------------
45C D u m m y A r g u m e n t s
46C-----------------------------------------------
47 INTEGER ,INTENT(IN) :: NEL ! size of element group
48 INTEGER ,INTENT(IN) :: NUPARAM ! size of parameter array
49 INTEGER ,INTENT(IN) :: IPT ! current integration point
50 INTEGER ,INTENT(IN) :: IOUT ! output file unit
51 INTEGER ,INTENT(IN) :: ISTDO ! output file unit
52 INTEGER ,INTENT(IN) :: NVARF
53 INTEGER ,DIMENSION(NEL) ,INTENT(IN) :: NGL ! table of element identifiers
54 my_real ,INTENT(IN) :: time ! current time
55 my_real ,DIMENSION(NUPARAM) ,INTENT(IN) :: uparam ! failure model parameter array
56 my_real ,DIMENSION(NEL) ,INTENT(IN) :: dpla ! plastic strain increment
57 my_real ,DIMENSION(NEL) ,INTENT(INOUT) :: off ! element deactivation flag
58 my_real ,DIMENSION(NEL) ,INTENT(IN) :: signxx ! stress component
59 my_real ,DIMENSION(NEL) ,INTENT(IN) :: signxy ! stress component
60 my_real ,DIMENSION(NEL) ,INTENT(IN) :: signxz ! stress component
61
62
63 my_real ,DIMENSION(NEL) ,INTENT(IN) :: epsxx
64 INTEGER ,DIMENSION(NEL) ,INTENT(INOUT) :: FOFF ! integration point deactivation flag
65 my_real ,DIMENSION(NEL) ,INTENT(INOUT) :: dfmax ! maximum damage
66 my_real ,DIMENSION(NEL) ,INTENT(INOUT) :: tdel ! deactivation time
67 my_real ,DIMENSION(NEL,NVARF),INTENT(INOUT) :: uvar
68 my_real, DIMENSION(NEL) ,INTENT(INOUT) :: uelr
69 INTEGER ,INTENT(IN) :: NPG
70C-----------------------------------------------
71C L o c a l V a r i a b l e s
72C-----------------------------------------------
73 INTEGER I,J,NINDXF,failip
74 INTEGER ,DIMENSION(NEL) :: INDXF
75 my_real
76 . C0,EMA,EEQ,SIG_A,SIG_FILTRE,R,Q,I1,S11,
77 . S22 , S33,R_INTER,PHI,I2
78 my_real ,DIMENSION(NEL) :: eps_eq,damage,epsrate,eps11,epsi,d_eeq
79C=======================================================================
80C UVAR(I,1) contains previous equivalent strain value increment
81C UVAR(I,2) contains the Cockroft-Latham accumulated value
82c UVAR(I,3) contains the previous first principal stress
83c UVAR(I,4) contains total strain
84 c0 = uparam(1)
85 ema = uparam(2)
86 failip = min(nint(uparam(3)),npg) ! Number of failed integration point prior to solid element deletion. default = 1 (integer)
87
88 nindxf = 0
89c-----------------------------
90 IF(c0 < zero)THEN ! equivalent strain
91 DO i =1,nel
92 IF(off(i) == one .AND. foff(i) == 1 ) THEN
93 eeq = abs(epsxx(i))
94 d_eeq(i) = eeq - uvar(i,1)
95 IF (d_eeq(i) <= zero) d_eeq(i) = zero
96 uvar(i,1) = eeq
97 ENDIF
98 ENDDO
99 ELSE ! positive = plastic strain increment
100 DO i =1,nel
101 IF(off(i) == one .AND. foff(i) == 1 ) THEN
102 d_eeq(i) = dpla(i)
103 uvar(i,1) = uvar(i,1) + dpla(i)
104 ENDIF
105 ENDDO
106 ENDIF
107
108
109 DO i =1,nel
110 IF(off(i) == one .AND. foff(i) == 1 ) THEN
111 ! principal stress calculation
112 i1 = signxx(i)
113 i2 = -signxy(i)*signxy(i)-signxz(i)*signxz(i)
114
115 q = (three*i2 - i1*i1)/nine
116 r = (two*i1*i1*i1 - nine*i1*i2 )/cinquante4
117
118 r_inter = min(r/sqrt(max(em20,(-q**3))),one)
119 phi = acos(max(r_inter,-one))
120
121 s11 = two*sqrt(-q)*cos(phi/three)+third*i1
122 s22 = two*sqrt(-q)*cos((phi+two*pi)/three)+third*i1
123 s33 = two*sqrt(-q)*cos((phi+four*pi)/three)+third*i1
124
125 sig_a = max(s11 ,s22 )
126 sig_a = max(sig_a,s33 )
127
128
129 IF (sig_a>zero)THEN
130 sig_filtre = sig_a * ema + (one-ema)* uvar(i,3)
131 uvar(i,3)= sig_filtre
132 !integral
133 uvar(i,2) = uvar(i,2) + max(sig_filtre,zero) * d_eeq(i)
134 ENDIF
135
136 !damage
137 dfmax(i) = min(uvar(i,2) / max(em20,abs(c0)) ,one)
138
139 IF (dfmax(i) >= one) THEN
140 foff(i) = 0
141 tdel(i) = time
142 nindxf = nindxf + 1
143 indxf(nindxf) = i
144 dfmax(i) = one
145 uelr(i) = uelr(i) + one
146 IF (nint(uelr(i)) >= failip) THEN
147 off(i) = four_over_5
148 ENDIF
149 ENDIF
150 ENDIF
151 ENDDO
152C!
153 DO j = 1,nindxf
154 i = indxf(j)
155#include "lockon.inc"
156 WRITE(iout, 1000) ngl(i),ipt,time
157 WRITE(istdo,1000) ngl(i),ipt,time
158 IF (off(i) == four_over_5) THEN
159 WRITE(iout, 1111) ngl(i),time
160 WRITE(istdo,1111) ngl(i),time
161 ENDIF
162#include "lockoff.inc"
163
164 ENDDO
165c------------------
166 1000 FORMAT(5x,'FAILURE (COCKROFT-LATHAM) OF BEAM ELEMENT ',i10,1x,',INTEGRATION PT',i5
167 . ,2x,'AT TIME :',1pe12.4)
168 1111 FORMAT(1x,'DELETED BEAM ELEMENT ',i10,1x,'AT TIME :',1pe12.4)
169c------------------
170
171 RETURN
172 END
#define my_real
Definition cppsort.cpp:32
subroutine fail_cockroft_ib(nel, ngl, nuparam, uparam, time, dpla, off, dfmax, tdel, iout, istdo, epsxx, ipt, signxx, signxy, signxz, nvarf, uvar, foff, uelr, npg)
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21