OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
fail_tbutcher_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_tbutcher_c ../engine/source/materials/fail/tuler_butcher/fail_tbutcher_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_tbutcher_c(
30 1 NEL ,NUPARAM ,NUVAR ,UPARAM ,UVAR ,
31 2 TIME ,TIMESTEP ,IPG ,ILAY ,IPT ,
32 3 SIGNXX ,SIGNYY ,SIGNXY ,SIGNYZ ,SIGNZX ,
33 4 NGL ,OFF ,FOFF ,DFMAX ,TDEL )
34C---------+---------+---+---+--------------------------------------------
35c Tuler Butcher Failure model
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 "units_c.inc"
44#include "comlock.inc"
45C-----------------------------------------------
46C VAR | SIZE |TYP| RW| DEFINITION
47C---------+---------+---+---+--------------------------------------------
48C NEL | 1 | I | R | SIZE OF THE ELEMENT GROUP NEL
49C NUPARAM | 1 | I | R | SIZE OF THE USER PARAMETER ARRAY
50C UPARAM | NUPARAM | F | R | USER MATERIAL PARAMETER ARRAY
51C NUVAR | 1 | I | R | NUMBER OF USER ELEMENT VARIABLES
52C UVAR |NEL*NUVAR| F |R/W| USER ELEMENT VARIABLE ARRAY
53C---------+---------+---+---+--------------------------------------------
54C TIME | 1 | F | R | CURRENT TIME
55C TIMESTEP| 1 | F | R | CURRENT TIME STEP
56C---------+---------+---+---+--------------------------------------------
57C SIGNXX | NEL | F | R | NEW ELASTO PLASTIC STRESS XX
58C SIGNYY | NEL | F | R | NEW ELASTO PLASTIC STRESS YY
59C ... | | | |
60C---------+---------+---+---+--------------------------------------------
61C OFF | NEL | F | R | DELETED ELEMENT FLAG (=1. ON, =0. OFF)
62C FOFF | NEL | I |R/W| DELETED INTEGRATION POINT FLAG (=1 ON, =0 OFF)
63C DFMAX | NEL | F |R/W| MAX DAMAGE FACTOR
64C TDEL | NEL | F | W | FAILURE TIME
65C---------+---------+---+---+--------------------------------------------
66C NGL ELEMENT ID
67C IPG CURRENT GAUSS POINT (in plane)
68C ILAY CURRENT LAYER
69C IPT CURRENT INTEGRATION POINT IN THE LAYER (FOR OUTPUT ONLY)
70C-----------------------------------------------
71C I N P U T A r g u m e n t s
72C-----------------------------------------------
73 INTEGER ,INTENT(IN) :: NEL,NUPARAM,NUVAR,IPG,ILAY,IPT
74 INTEGER ,DIMENSION(NEL), INTENT(IN) :: NGL
75 my_real ,INTENT(IN) :: TIME
76 my_real ,DIMENSION(NEL), INTENT(IN) :: TIMESTEP,OFF,
77 . signxx,signyy,signxy,signyz,signzx
78 my_real,DIMENSION(NUPARAM), INTENT(IN) :: uparam
79C-----------------------------------------------
80C I N P U T O U T P U T A r g u m e n t s
81C-----------------------------------------------
82 INTEGER ,DIMENSION(NEL), INTENT(INOUT) :: FOFF
83 my_real ,DIMENSION(NEL), INTENT(INOUT) :: DFMAX
84 my_real ,DIMENSION(NEL), INTENT(OUT) :: TDEL
85 my_real ,DIMENSION(NEL,NUVAR) ,INTENT(INOUT) :: UVAR
86C-----------------------------------------------
87C L o c a l V a r i a b l e s
88C-----------------------------------------------
89 INTEGER :: I,J,NINDX
90 INTEGER ,DIMENSION(NEL) :: INDX
91 my_real :: TBA,TBK,KK,SIGMAX,SIGR_INI,SIG1,SIG2,S1,S2
92C=======================================================================
93 tba = uparam(1)
94 tbk = uparam(2)
95 sigr_ini = uparam(3)
96 nindx = 0
97C-----------------------------------------------
98 DO i=1,nel
99 IF (off(i) == one .and. foff(i) == 1) THEN
100 s1 = half*(signxx(i) + signyy(i))
101 s2 = half*(signxx(i) - signyy(i))
102 sig1 = s1 + sqrt(s2**2 + signxy(i)**2)
103 sig2 = s1 - sqrt(s2**2 + signxy(i)**2)
104 sigmax = max(sig1,sig2)
105 IF (sigmax > sigr_ini) uvar(i,1) = uvar(i,1)
106 . + timestep(i)*(sigmax - sigr_ini)**tba
107 IF (uvar(i,1) >= tbk) THEN
108 nindx = nindx + 1
109 indx(nindx) = i
110 foff(i) = 0
111 tdel(i) = time
112 ENDIF
113 ENDIF
114 ENDDO
115c
116c--- Maximum Damage storing for output : 0 < DFMAX < 1
117 DO i=1,nel
118 dfmax(i) = min(one, max(dfmax(i),uvar(i,1)/tbk))
119 ENDDO
120c------------------------
121 IF (nindx > 0) THEN
122 DO j=1,nindx
123 i = indx(j)
124#include "lockon.inc"
125 WRITE(iout, 2000) ngl(i),ipg,ilay,ipt
126 WRITE(istdo,2100) ngl(i),ipg,ilay,ipt,time
127#include "lockoff.inc"
128 END DO
129 END IF
130c------------------------
131 2000 FORMAT(1x,'FAILURE (TB) OF SHELL ELEMENT ',i10,1x,',GAUSS PT',
132 . i2,1x,',LAYER',i3,1x,',INTEGRATION PT',i3)
133 2100 FORMAT(1x,'FAILURE (TB) OF SHELL ELEMENT ',i10,1x,',GAUSS PT',
134 . i2,1x,',LAYER',i3,1x,',INTEGRATION PT',i3,1x,'AT TIME :',1pe12.4)
135c------------------------
136 RETURN
137 END
subroutine fail_tbutcher_c(nel, nuparam, nuvar, uparam, uvar, time, timestep, ipg, ilay, ipt, signxx, signyy, signxy, signyz, signzx, ngl, off, foff, dfmax, tdel)
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21