OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
fail_snconnect.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_snconnect ../engine/source/materials/fail/snconnect/fail_snconnect.F
25!||--- called by ------------------------------------------------------
26!|| suser43 ../engine/source/elements/solid/sconnect/suser43.F
27!||--- calls -----------------------------------------------------
28!|| finter ../engine/source/tools/curve/finter.F
29!||====================================================================
30 SUBROUTINE fail_snconnect (
31 1 NEL ,NUPARAM ,NUVAR ,NFUNC ,IFUNC ,
32 2 NPF ,TF ,TIME ,TIMESTEP,UPARAM ,
33 3 UVAR ,NGL ,IPG ,NPG ,NDAMF ,
34 4 EPSD ,PLA ,OFFG ,OFFL ,ISOLID ,
35 5 SIGNZZ ,SIGNYZ ,SIGNZX ,SYM ,AREA ,
36 6 DMG ,DAMT ,DFMAX ,TDELE )
37C-----------------------------------------------
38c SNCONNECT failure model for solid spotwelds
39C-----------------------------------------------
40#include "implicit_f.inc"
41C---------+---------+---+---+--------------------------------------------
42C VAR | SIZE |TYP| RW| DEFINITION
43C---------+---------+---+---+--------------------------------------------
44C NEL | 1 | I | R | SIZE OF THE ELEMENT GROUP NEL
45C NUPARAM | 1 | I | R | SIZE OF THE USER PARAMETER ARRAY
46C NUVAR | 1 | I | R | NUMBER OF FAILURE ELEMENT VARIABLES
47C---------+---------+---+---+--------------------------------------------
48C NFUNC | 1 | I | R | NUMBER FUNCTION USED FOR THIS USER LAW not used
49C IFUNC | NFUNC | I | R | FUNCTION INDEX not used
50C NPF | * | I | R | FUNCTION ARRAY
51C TF | * | F | R | FUNCTION ARRAY
52C---------+---------+---+---+--------------------------------------------
53C TIME | 1 | F | R | CURRENT TIME
54C TIMESTEP| 1 | F | R | CURRENT TIME STEP
55C UPARAM | NUPARAM | F | R | USER FAILURE PARAMETER ARRAY
56C EPSP | NEL | F | W | STRAIN RATE
57C---------+---------+---+---+--------------------------------------------
58C UVAR |NEL*NUVAR| F |R/W| USER ELEMENT VARIABLE ARRAY
59C OFFG | NEL | F |R/W| DELETED ELEMENT FLAG (=1. ON, =0. OFF)
60C-----------------------------------------------
61C Y = FINTER(IFUNC(J),X,NPF,TF,DYDX)
62C Y : y = f(x)
63C X : x
64C DYDX : f'(x) = dy/dx
65C IFUNC(J): FUNCTION INDEX
66C J : FIRST(J=1), SECOND(J=2) .. FUNCTION USED FOR THIS LAW
67C NPF,TF : FUNCTION PARAMETER
68CC-----------------------------------------------
69C C o m m o n B l o c k s
70C-----------------------------------------------
71#include "units_c.inc"
72#include "comlock.inc"
73C-----------------------------------------------
74C D u m m y A r g u m e n t s
75C-----------------------------------------------
76 INTEGER NEL,NUPARAM,NUVAR,NFUNC,IPG,NPG,NDAMF,ISOLID
77 INTEGER NGL(NEL),NPF(*),IFUNC(*)
78 my_real TIME,TIMESTEP
79 my_real UPARAM(NUPARAM),UVAR(NEL,NUVAR),DAMT(NEL,NDAMF),TF(*)
80 my_real , DIMENSION(NEL) :: OFFG,OFFL,EPSD,PLA,DEIN,DEIT,
81 . SIGNZZ,SIGNYZ,SIGNZX,SYM,DMG,DFMAX,TDELE,AREA
82C-----------------------------------------------
83C L o c a l V a r i a b l e s
84C-----------------------------------------------
85 INTEGER I,J,IDEL,IDEV,NINDX,NINDXD,NINDXA,ISYM,FUNN,FUNT,IFUN2N,
86 . ifun2t,ifun3n,ifun3t
87 INTEGER INDX(NEL),INDXD(NEL),INDXA(NEL)
88 my_real A2,B2,A3,B3,XSCALE2,XSCALE3,SVMN,SVMT,T1,T2,TTN,TTS,FCT,
89 . DYDX,DAMA,SSYM,CPHI,SPHI,AREASCALE,DEFO
90 my_real , DIMENSION(NEL) :: FUN2N,FUN2T,FUN3N,FUN3T,DYDX2N,
91 . dydx2t,dydx3n,dydx3t,phi,pla1,pla2
92C-----------------------------------------------
93C E x t e r n a l F u n c t i o n s
94C-----------------------------------------------
95 my_real finter
96 EXTERNAL finter
97C=======================================================================
98c Internal VARIABLES :
99c-----------------
100c UVAR1 initial plastic elongation
101c UVAR2 final plastic elongation (at rupture)
102c-----------------
103c Damage output VARIABLES :
104c-----------------
105c DAMT1 damage factor d, where (sig = sig *(1-d))
106c DAMT2 damage function at damage start
107c DAMT3 damage function at rupture
108C=======================================================================
109 a2 = uparam(1)
110 b2 = uparam(2)
111 a3 = uparam(3)
112 b3 = uparam(4)
113 isolid = nint(uparam(5))
114 xscale2 = uparam(6)
115 xscale3 = uparam(7)
116 isym = nint(uparam(8))
117 areascale = uparam(9)
118
119 ifun2n = ifunc(1)
120 ifun2t = ifunc(2)
121 ifun3n = ifunc(3)
122 ifun3t = ifunc(4)
123C-----------------------------------------------
124 IF (uvar(1,3) == zero) THEN
125 DO i=1,nel
126 uvar(i,3)= area(i) ! initial area at time = 0
127 ENDDO
128 ENDIF
129c
130 DO i=1,nel
131 pla1(i) = uvar(i,1)
132 pla2(i) = uvar(i,2)
133 END DO
134C-----------------------------------------------
135C RATE FUNCTIONS INERPOLATION
136C-----------------------------------------------
137 IF (ifun2n == 0) THEN
138 fun2n(1:nel) = one
139 ELSE
140 DO i=1,nel
141 fun2n(i) = finter(ifun2n,epsd(i)*xscale2,npf,tf,dydx2n)
142 ENDDO
143 ENDIF
144 IF (ifun2t == 0) THEN
145 fun2t(1:nel) = one
146 ELSE
147 DO i=1,nel
148 fun2t(i) = finter(ifun2t,epsd(i)*xscale2,npf,tf,dydx2t)
149 ENDDO
150 ENDIF
151 IF (ifun3n == 0) THEN
152 DO i=1,nel
153 fun3n(i) = one
154 ENDDO
155 ELSE
156 DO i=1,nel
157 fun3n(i) = finter(ifun3n,epsd(i)*xscale3,npf,tf,dydx3n)
158 ENDDO
159 ENDIF
160 IF (ifun3t == 0) THEN
161 DO i=1,nel
162 fun3t(i) = one
163 ENDDO
164 ELSE
165 DO i=1,nel
166 fun3t(i) = finter(ifun3t,epsd(i)*xscale3,npf,tf,dydx3t)
167 ENDDO
168 ENDIF
169C-----------------------------------------------
170 nindx = 0
171 nindxd = 0
172 nindxa = 0
173c
174 DO i=1,nel
175 idel = 0
176 dama = zero
177 ssym = sin(sym(i))
178 svmn = abs(signzz(i))
179 svmt = sqrt(signyz(i)**2 + signzx(i)**2)
180 phi(i)= atan(svmn/max(em20,svmt))
181 sphi = sin(phi(i))
182 cphi = cos(phi(i))
183c
184 IF (pla1(i) == zero) THEN ! No damage yet
185 IF (isym == 1 .AND. signzz(i)<= zero) THEN
186 t1 = zero
187 ELSE
188 t1 = sphi/(one-a2*ssym)/fun2n(i)
189 ENDIF
190 t2 = cphi/fun2t(i)
191 ttn = t1*pla(i)
192 tts = t2*pla(i)
193 fct = (ttn**b2 + tts**b2)**(one/b2)
194 damt(i,2) = min(fct, one)
195 IF (fct > one ) THEN
196 pla1(i) = (t1**b2 + t2**b2)**(-one/b2)
197 IF (isym == 1 .AND. signzz(i) <= zero)THEN
198 t1 = zero
199 ELSE
200 t1 = sphi/(one-a3*ssym)/fun3n(i)
201 ENDIF
202 t2 = cphi/fun3t(i)
203 ttn = t1*pla(i)
204 tts = t2*pla(i)
205 fct = (ttn**b3 + tts**b3) **(one / b3)
206 pla2(i) = (t1**b3 + t2**b3)**(-one/b3)
207 damt(i,1) = (pla(i)-pla1(i))/max(em20,(pla2(i) - pla1(i)))
208 damt(i,1) = min(damt(i,1), one)
209 damt(i,3) = min(fct, one)
210 dama = damt(i,1)
211 nindxd = nindxd+1
212 indxd(nindxd) = i
213 ENDIF
214c
215 ELSE ! (PLA1(I) > ZERO)
216 IF (isym == 1 .AND. signzz(i) <= zero) THEN
217 t1 = zero
218 ELSE
219 t1 = sphi/(one-a3*ssym)/fun3n(i)
220 ENDIF
221 t2 = cphi/fun3t(i)
222 ttn = t1*pla(i)
223 tts = t2*pla(i)
224 fct = (ttn**b3 + tts**b3) **(one / b3)
225 pla2(i) = (t1**b3 + t2**b3)**(-one/b3)
226 damt(i,1) = (pla(i)-pla1(i))/max(em20,(pla2(i) - pla1(i)))
227 damt(i,1) = min(damt(i,1), one)
228 damt(i,3) = min(fct, one)
229 dama = damt(i,1)
230c----- check if rupture ...
231 IF (fct > one) THEN
232 idel =1
233 dama = one
234 ENDIF
235 ENDIF
236 dmg(i) = max(dmg(i),dama)
237 dmg(i) = min(dmg(i),one)
238c-----------------------------
239 IF (idel == 1 .AND. offl(i) == one) THEN
240 offl(i) = zero ! local integ point rupture
241 nindx = nindx+1
242 indx(nindx) = i
243 tdele(i) = time
244 ENDIF
245C
246 uvar(i,1) = pla1(i)
247 uvar(i,2) = pla2(i)
248C------------- Maximum Damage storing for output : 0 < DFMAX < 1
249 dfmax(i) = min(one,max(dfmax(i),damt(i,1)))
250c
251c--- deformed elements check
252 IF (areascale > zero ) THEN
253 defo = uvar(i,3) * areascale
254 IF (area(i) > defo .AND. offg(i) == one) THEN
255 offl(i) = zero
256 nindxa = nindxa+1
257 indxa(nindxa) = i
258 tdele(i) = time
259 isolid = 1
260 ENDIF
261 ENDIF
262c-------------------------------
263 ENDDO ! I=1,NEL
264C-----------------------------------------------
265 IF (nindxd > 0) THEN
266 DO j=1,nindxd
267 i = indxd(j)
268#include "lockon.inc"
269 WRITE(iout ,1000) ngl(i),ipg,pla1(i)
270 WRITE(istdo,1100) ngl(i),ipg,pla1(i),time
271#include "lockoff.inc"
272 END DO
273 ELSEIF (nindx > 0) THEN
274 DO j=1,nindx
275 i = indx(j)
276#include "lockon.inc"
277 WRITE(iout ,1200) ngl(i),ipg,pla2(i)
278 WRITE(istdo,1300) ngl(i),ipg,pla2(i),time
279#include "lockoff.inc"
280 END DO
281 ELSEIF (nindxa > 0) THEN
282 DO j=1,nindxa
283 i = indxa(j)
284#include "lockon.inc"
285 WRITE(iout ,1400) ngl(i),area(i)
286 WRITE(istdo,1500) ngl(i),area(i),time
287#include "lockoff.inc"
288 END DO
289 ENDIF
290C-----------------------------------------------
291 1000 FORMAT(5x,'START DAMAGE CONNECTION ELEMENT ',i10,
292 . ' INTEGRATION POINT',i2,', PLASTIC ELONGATION =',1pe16.9)
293 1100 FORMAT(5x,'START DAMAGE CONNECTION ELEMENT ',i10,
294 . ' INTEGRATION POINT',i2,', PLASTIC ELONGATION =',1pe16.9,
295 . ' AT TIME ',1pe16.9)
296 1200 FORMAT(5x,'FAILURE CONNECTION SOLID ELEMENT ',i10,
297 . ' INTEGRATION POINT',i2,', PLASTIC ELONGATION=',1pe16.9)
298 1300 FORMAT(5x,'FAILURE CONNECTION SOLID ELEMENT ',i10,
299 . ' INTEGRATION POINT',i2,', PLASTIC ELONGATION :',1pe16.9,
300 . ' AT TIME ',1pe16.9)
301 1400 FORMAT(5x,'FAILURE CONNECTION SOLID ELEMENT ',i10,
302 . ', AREA (LIMIT REACHED) :',1pe16.9)
303 1500 FORMAT(5x,'FAILURE CONNECTION SOLID ELEMENT ',i10,
304 . ', AREA (LIMIT REACHED) :',1pe16.9,' AT TIME ',1pe16.9)
305C-----------------------------------------------
306 RETURN
307 END
subroutine fail_snconnect(nel, nuparam, nuvar, nfunc, ifunc, npf, tf, time, timestep, uparam, uvar, ngl, ipg, npg, ndamf, epsd, pla, offg, offl, isolid, signzz, signyz, signzx, sym, area, dmg, damt, dfmax, tdele)
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21