OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
fail_rtcl_s.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_s ../engine/source/materials/fail/rtcl/fail_rtcl_s.F
25!||--- called by ------------------------------------------------------
26!|| mmain ../engine/source/materials/mat_share/mmain.F90
27!|| mmain8 ../engine/source/materials/mat_share/mmain8.F
28!|| mulaw ../engine/source/materials/mat_share/mulaw.F90
29!|| mulaw8 ../engine/source/materials/mat_share/mulaw8.F90
30!|| usermat_solid ../engine/source/materials/mat_share/usermat_solid.F
31!||====================================================================
32 SUBROUTINE fail_rtcl_s (
33 1 NEL ,NUPARAM ,NUVAR ,TIME ,TIMESTEP ,UPARAM ,
34 2 SIGNXX ,SIGNYY ,SIGNZZ ,SIGNXY ,SIGNYZ ,SIGNZX ,
35 3 NGL ,DPLA ,UVAR ,OFF ,DFMAX ,TDELE )
36C!-----------------------------------------------
37C! I m p l i c i t T y p e s
38C!-----------------------------------------------
39#include "implicit_f.inc"
40C!---------+---------+---+---+-------------------
41#include "mvsiz_p.inc"
42#include "scr17_c.inc"
43#include "units_c.inc"
44#include "comlock.inc"
45C!-----------------------------------------------
46 INTEGER NEL, NUPARAM, NUVAR,NGL(NEL)
47 my_real TIME,TIMESTEP,UPARAM(*),
48 . SIGNXX(NEL),SIGNYY(NEL),SIGNZZ(NEL),
49 . signxy(nel),signyz(nel),signzx(nel),uvar(nel,nuvar),
50 . dpla(nel),off(nel),dfmax(nel),tdele(nel)
51C!-----------------------------------------------
52C! L o c a l V a r i a b l e s
53C!-----------------------------------------------
54 INTEGER I,J,INDX(MVSIZ),NINDX
55 my_real
56 . P,triaxs,SVM,SXX,SYY,SZZ,EPS_CR,F_RTCL
57C!--------------------------------------------------------------
58 !=======================================================================
59 ! - INITIALISATION OF COMPUTATION ON TIME STEP
60 !=======================================================================
61 ! Recovering model parameters
62 eps_cr = uparam(1)
63c
64 ! Checking element failure and recovering user variable
65 DO i=1,nel
66 IF (off(i) < em01) off(i) = zero
67 IF (off(i) < one .AND. off(i) > zero) off(i) = off(i)*four_over_5
68 END DO
69C
70 ! Initialization of variable
71 nindx = 0
72c
73 !====================================================================
74 ! - LOOP OVER THE ELEMENT TO COMPUTE THE DAMAGE VARIABLE
75 !====================================================================
76 DO i=1,nel
77c
78 ! If the element is not broken
79 IF (off(i) == one .AND. dpla(i) /= zero) THEN
80c
81 ! Computation of hydrostatic stress, Von Mises stress, and stress triaxiality
82 p = third*(signxx(i) + signyy(i) + signzz(i))
83 sxx = signxx(i) - p
84 syy = signyy(i) - p
85 szz = signzz(i) - p
86 svm = half*(sxx**2 + syy**2 + szz**2)
87 . + signxy(i)**2 + signzx(i)**2 + signyz(i)**2
88 svm = sqrt(three*svm)
89 triaxs = p/max(em20,svm)
90 IF (triaxs > one) triaxs = one
91 IF (triaxs < -one) triaxs = -one
92c
93 ! Computing the plastic strain at failure according to stress triaxiality
94 IF (triaxs < -third) THEN
95 f_rtcl = zero
96 ELSEIF ((triaxs >= -third).AND.(triaxs < third)) THEN
97 f_rtcl = two*((one+triaxs*sqrt(twelve-twenty7*(triaxs**2)))/
98 . (three*triaxs+sqrt(twelve-twenty7*(triaxs**2))))
99 ELSE
100 f_rtcl = exp(-half)*exp(three_half*triaxs)
101 ENDIF
102c
103 ! Computation of damage variables
104 dfmax(i) = dfmax(i) + f_rtcl*dpla(i)/max(eps_cr,em6)
105 dfmax(i) = min(one,dfmax(i))
106c
107 ! Checking element failure using global damage
108 IF (dfmax(i) >= one .AND. off(i) == one) THEN
109 off(i) = four_over_5
110 nindx = nindx + 1
111 indx(nindx) = i
112 tdele(i) = time
113 ENDIF
114 ENDIF
115 ENDDO
116c------------------------
117c------------------------
118 IF (nindx > 0) THEN
119 DO j=1,nindx
120 i = indx(j)
121#include "lockon.inc"
122 WRITE(iout, 1000) ngl(i),time
123 WRITE(istdo,1100) ngl(i),time
124#include "lockoff.inc"
125 END DO
126 END IF
127c------------------------
128 1000 FORMAT(1x,'DELETE SOLID ELEMENT NUMBER (RTCL) el#',i10,
129 . ' AT TIME :',1pe12.4)
130 1100 FORMAT(1x,'DELETE SOLID ELEMENT NUMBER (RTCL) el#',i10,
131 . ' AT TIME :',1pe12.4)
132 END
subroutine fail_rtcl_s(nel, nuparam, nuvar, time, timestep, uparam, signxx, signyy, signzz, signxy, signyz, signzx, ngl, dpla, uvar, off, dfmax, tdele)
Definition fail_rtcl_s.F:36
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21