OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
delm24law.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/.
23C total strain delamination failure model ------
24!||====================================================================
25!|| delm24law ../engine/source/properties/composite_options/stack/delm24law.F
26!||--- called by ------------------------------------------------------
27!|| delamination ../engine/source/properties/composite_options/stack/delamination.F
28!||--- uses -----------------------------------------------------
29!|| fail_param_mod ../common_source/modules/mat_elem/fail_param_mod.F90
30!||====================================================================
31 SUBROUTINE delm24law(FAIL ,
32 1 NEL ,NUVAR ,TIME ,TIMESTEP ,
33 3 NGL ,IPLY ,
34 4 OFF ,SIGNYZ ,SIGNXZ ,SIGNZZ ,EPSYZ ,
35 5 EPSXZ ,EPSZZ ,UVAR , OFFI ,REDUC ,
36 6 COUNT)
37C-----------------------------------------------
38C M o d u l e s
39C-----------------------------------------------
40 USE fail_param_mod
41C-----------------------------------------------
42C I m p l i c i t T y p e s
43C-----------------------------------------------
44#include "implicit_f.inc"
45C---------+---------+---+---+--------------------------------------------
46C VAR | SIZE |TYP| RW| DEFINITION
47C---------+---------+---+---+--------------------------------------------
48C NEL | 1 | I | R | SIZE OF THE ELEMENT GROUP NEL
49C NUVAR | 1 | I | R | NUMBER OF USER ELEMENT VARIABLES
50C---------+---------+---+---+--------------------------------------------
51C TIME | 1 | F | R | CURRENT TIME
52C TIMESTEP| 1 | F | R | CURRENT TIME STEP
53C EPSPXX | NEL | F | R | STRAIN RATE XX
54C EPSPYY | NEL | F | R | STRAIN RATE YY
55C ... | | | |
56C DEPSXX | NEL | F | R | STRAIN INCREMENT XX
57C DEPSYY | NEL | F | R | STRAIN INCREMENT YY
58C ... | | | |
59C EPSXX | NEL | F | R | STRAIN XX
60C EPSYY | NEL | F | R | STRAIN YY
61C ... | | | |
62C SIGOXX | NEL | F | R | OLD ELASTO PLASTIC STRESS XX
63C SIGOYY | NEL | F | R | OLD ELASTO PLASTIC STRESS YY
64C ... | | | |
65C---------+---------+---+---+--------------------------------------------
66C SIGNXX | NEL | F | W | NEW ELASTO PLASTIC STRESS XX
67C SIGNYY | NEL | F | W | NEW ELASTO PLASTIC STRESS YY
68C ... | | | |
69C SIGVXX | NEL | F | W | VISCOUS STRESS XX
70C SIGVYY | NEL | F | W | VISCOUS STRESS YY
71C ... | | | |
72C SOUNDSP | NEL | F | W | SOUND SPEED (NEEDED FOR TIME STEP)
73C VISCMAX | NEL | F | W | MAXIMUM DAMPING MODULUS(NEEDED FOR TIME STEP)
74C---------+---------+---+---+--------------------------------------------
75C UVAR |NEL*NUVAR| F |R/W| USER ELEMENT VARIABLE ARRAY
76C OFF | NEL | F |R/W| DELETED ELEMENT FLAG (=1. ON, =0. OFF)
77C---------+---------+---+---+--------------------------------------------
78#include "mvsiz_p.inc"
79#include "units_c.inc"
80#include "comlock.inc"
81#include "param_c.inc"
82C-----------------------------------------------
83C I N P U T A r g u m e n t s
84C-----------------------------------------------
85 INTEGER NEL,NUVAR,NGL(*),IPLY
86 my_real
87 . TIME,TIMESTEP(*),SIGNZZ(*),
88 . SIGNYZ(*),SIGNXZ(*),EPSYZ(*),EPSXZ(*),EPSZZ(*),
89 . OFFI(*),REDUC(*),COUNT(*)
90 TYPE (FAIL_PARAM_) ,INTENT(IN) :: FAIL
91C-----------------------------------------------
92C I N P U T O U T P U T A r g u m e n t s
93C-----------------------------------------------
94 my_real uvar(nel,nuvar), off(nel)
95C-----------------------------------------------
96C L o c a l V a r i a b l e s
97C-----------------------------------------------
98 INTEGER
99 . i,j,idel,idel_l,iflag(mvsiz),indx(mvsiz),nindx,
100 . nindex,index(mvsiz),jst(mvsiz),ir,jj,imod,
101 . mode(mvsiz)
102 my_real
103 . dam1,dam2,dam3,dam
104 my_real
105 . epst3(mvsiz),epsf3(mvsiz),epst13(mvsiz),epsf13(mvsiz),
106 . epst23(mvsiz),epsf23(mvsiz)
107C--------------------------------------------------------------
108C
109 ir = 0
110 DO i=1,nel
111 IF (off(i)==zero) cycle
112 epst3(i) = fail%UPARAM(5)
113 epsf3(i) = fail%UPARAM(6)
114 epst23(i) = fail%UPARAM(9)
115 epsf23(i) = fail%UPARAM(10)
116 epst13(i) = fail%UPARAM(11)
117 epsf13(i) = fail%UPARAM(12)
118 reduc(i) = fail%UPARAM(16)
119 ir = ir + 1
120 jst(ir) = i
121C
122 indx(i) = 0
123 index(i) = 0
124 ENDDO
125C-----------------------------------------------
126C USER VARIABLES INITIALIZATION
127C-----------------------------------------------
128 IF(time == zero)THEN
129 DO jj=1,ir
130 i = jst(jj)
131 DO j=1,nuvar
132 uvar(i,j)= zero
133 ENDDO
134 ENDDO
135 ENDIF
136C-------------------------------
137C
138 nindx=0
139 nindex = 0
140 DO j =1,ir
141 i=jst(j)
142C
143 dam1 = zero
144 dam2 = zero
145 dam3 = zero
146 imod = 0
147 mode(i) = 0
148 IF(off(i) == one )THEN
149C-------------------------------
150C direction 33
151 IF(uvar(i,1) < one )THEN
152C direction 23
153 IF(epsyz(i) >= epst23(i) ) THEN
154 dam2 = (epsyz(i) - epst23(i))/(epsf23(i) - epst23(i))
155 dam2 = min(one, dam2)
156 IF(dam2 >= one) imod = 3
157 ENDIF
158C direction 13
159 IF(epsxz(i) >= epst13(i) ) THEN
160 dam3 = (epsxz(i) - epst13(i))/(epsf13(i) - epst13(i))
161 dam3 = min(one, dam3)
162 IF(dam3 >= one) imod = 2
163 ENDIF
164
165 IF(epszz(i) >= epst3(i) ) THEN
166 dam1= (epszz(i) - epst3(i))/(epsf3(i) - epst3(i))
167 dam1 = min(one, dam1)
168 IF(dam1 >= one) imod = 1
169 ENDIF
170C
171 dam = max(uvar(i,1),dam1, dam2, dam3)
172 uvar(i,1) = dam
173 signxz(i) = signxz(i)*max(one - dam,reduc(i))
174 signyz(i) = signyz(i)*max(one - dam,reduc(i))
175 signzz(i) = signzz(i)*max(one - dam,reduc(i))
176C
177 IF(dam == one) THEN
178 nindx=nindx+1
179 indx(nindx)=i
180!! OFFI(I) = REDUC(I)
181 mode(i) = imod
182 count(i) = count(i) + one
183 IF(int(count(i)) == 4)THEN
184 WRITE(iout, 1300) ngl(i),iply,mode(i),time
185 WRITE(istdo,1300) ngl(i),iply,mode(i), time
186 ENDIF
187 ENDIF
188 ELSE
189!! SIGNXZ(I) = ZERO
190!! SIGNYZ(I) = ZERO
191!! SIGNZZ(I) = ZERO
192!! OFFI(I) = MIN(OFFI(I), ZERO)
193 offi(i) = reduc(i)
194 ENDIF
195 ENDIF
196 ENDDO
197
198 IF(nindx > 0)THEN
199 DO j=1,nindx
200 i = indx(j)
201#include "lockon.inc"
202 WRITE(iout, 1200) ngl(i),iply,mode(i),time
203 WRITE(istdo,1200) ngl(i),iply,mode(i), time
204#include "lockoff.inc"
205 END DO
206 ENDIF
207C--------------------------------------------
208
209 1200 FORMAT(1x,'DELAMINATION OF SHELL #',i10,1x,
210 . 'INTERPLY', i10, 1x,'MODE #',i10,1x,
211 . 'at time # ',1PE20.13)
212 1300 FORMAT(1x,'FULL DELAMINATION OF SHELL #',i10,1x,
213 . 'INTERPLY', i10, 1x,'MODE #',i10,1x,
214 . 'AT TIME # ',1pe20.13)
215 RETURN
216 END
subroutine delm24law(fail, nel, nuvar, time, timestep, ngl, iply, off, signyz, signxz, signzz, epsyz, epsxz, epszz, uvar, offi, reduc, count)
Definition delm24law.F:37
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21