OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
fail_rtcl_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_rtcl_c ../engine/source/materials/fail/rtcl/fail_rtcl_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_rtcl_c (
30 1 NEL ,NUPARAM ,NUVAR ,TIME ,TIMESTEP ,UPARAM ,
31 2 SIGNXX ,SIGNYY ,SIGNXY ,SIGNYZ ,SIGNZX ,NPTOT ,
32 3 NGL ,DPLA ,UVAR ,OFF ,DFMAX ,TDELE ,
33 4 AREA ,FOFF ,IGTYP ,OFFL ,IPT ,THK0 )
34C!-----------------------------------------------
35C! I m p l i c i t T y p e s
36C!-----------------------------------------------
37#include "implicit_f.inc"
38C!---------+---------+---+---+-------------------
39#include "units_c.inc"
40#include "comlock.inc"
41C!-----------------------------------------------
42 INTEGER NEL, NUPARAM, NUVAR,NGL(NEL),IGTYP,IPT,
43 . NPTOT
44 my_real TIME,TIMESTEP,UPARAM(*),
45 . SIGNXX(NEL),SIGNYY(NEL),OFFL(NEL),
46 . signxy(nel),signyz(nel),signzx(nel),uvar(nel,nuvar),
47 . dpla(nel),off(nel),dfmax(nel),tdele(nel),area(nel),thk0(nel)
48 INTEGER, DIMENSION(NEL), INTENT(INOUT) :: FOFF
49C!-----------------------------------------------
50C! L o c a l V a r i a b l e s
51C!-----------------------------------------------
52 INTEGER I,J,INDX(NEL),NINDX,CONDITION(NEL),INST
53 my_real
54 . NHARD,EPSCAL,P,triaxs,vmises,hydros,EPS_CR,F_RTCL
55C!--------------------------------------------------------------
56 !=======================================================================
57 ! - INITIALISATION OF COMPUTATION ON TIME STEP
58 !=======================================================================
59 ! Recovering model parameters
60 epscal = uparam(1)
61 inst = nint(uparam(2))
62 nhard = uparam(3)
63c
64 ! Store initial element size
65 IF (uvar(1,1) == zero) THEN
66 DO i = 1,nel
67 uvar(i,1) = sqrt(area(i))
68 uvar(i,2) = thk0(i)
69 ENDDO
70 ENDIF
71C
72 ! Initialization of variable
73 nindx = 0
74c
75 !====================================================================
76 ! - LOOP OVER THE ELEMENT TO COMPUTE THE DAMAGE VARIABLE
77 !====================================================================
78 DO i=1,nel
79c
80 ! If the element is not broken
81 IF (off(i) == one .AND. dpla(i) /= zero) THEN
82c
83 ! Computation of hydrostatic stress, Von Mises stress, and stress triaxiality
84 hydros = (signxx(i)+ signyy(i))/three
85 vmises = sqrt((signxx(i)**2)+(signyy(i)**2)-(signxx(i)*signyy(i))+(three*signxy(i)**2))
86 triaxs = hydros / max(em20,vmises)
87 IF (triaxs > two_third) triaxs = two_third
88 IF (triaxs < -two_third) triaxs = -two_third
89c
90 ! Computing the plastic strain at failure according to stress triaxiality
91 IF (triaxs < -third) THEN
92 f_rtcl = zero
93 ELSEIF ((triaxs >= -third).AND.(triaxs < third)) THEN
94 f_rtcl = two*((one+triaxs*sqrt(twelve-twenty7*(triaxs**2)))/
95 . (three*triaxs+sqrt(twelve-twenty7*(triaxs**2))))
96 ELSE
97 f_rtcl = exp(-half)*exp(three_half*triaxs)
98 ENDIF
99c
100 ! Computation of simple tension failure strain (according to mesh size)
101 IF (inst == 2) THEN
102 eps_cr = nhard + (epscal - nhard)*(uvar(i,2)/uvar(i,1))
103 ELSE
104 eps_cr = epscal
105 ENDIF
106c
107 ! Computation of damage variables
108 dfmax(i) = dfmax(i) + f_rtcl*dpla(i)/max(eps_cr,em6)
109 dfmax(i) = min(one,dfmax(i))
110c
111 ! Checking element failure using global damage
112 IF (offl(i) == one .AND. dfmax(i) >= one) THEN
113 offl(i) = zero
114 foff(i) = 0
115 nindx = nindx + 1
116 indx(nindx) = i
117 condition(nindx) = ipt
118 ENDIF
119 ENDIF
120 ENDDO
121c------------------------
122c------------------------
123 IF (nindx > 0) THEN
124 DO j=1,nindx
125 i = indx(j)
126#include "lockon.inc"
127 IF(condition(j) >= 1) THEN
128 WRITE(iout, 2000) ngl(i),condition(j),time
129 WRITE(istdo,2000) ngl(i),condition(j),time
130 ENDIF
131#include "lockoff.inc"
132 END DO
133 END IF ! NINDX
134c------------------------
135 2000 FORMAT(1x,'FOR SHELL ELEMENT (RTCL)',i10,1x,'LAYER',i3,':',/,
136 . 1x,'STRESS TENSOR SET TO ZERO',1x,'AT TIME :',1pe12.4)
137 END
subroutine fail_rtcl_c(nel, nuparam, nuvar, time, timestep, uparam, signxx, signyy, signxy, signyz, signzx, nptot, ngl, dpla, uvar, off, dfmax, tdele, area, foff, igtyp, offl, ipt, thk0)
Definition fail_rtcl_c.F:34
subroutine area(d1, x, x2, y, y2, eint, stif0)
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21