OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
fail_puck_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!||====================================================================
25!|| fail_puck_c ../engine/source/materials/fail/puck/fail_puck_c.F
26!||--- called by ------------------------------------------------------
27!|| mulawc ../engine/source/materials/mat_share/mulawc.F90
28!|| usermat_shell ../engine/source/materials/mat_share/usermat_shell.F
29!||====================================================================
30 SUBROUTINE fail_puck_c(
31 1 NEL ,NUPARAM ,NUVAR ,UPARAM ,UVAR ,
32 2 TIME ,NGL ,IPG ,ILAY ,IPT ,
33 3 SIGNXX ,SIGNYY ,SIGNXY ,SIGNYZ ,SIGNZX ,
34 4 OFF ,FOFF ,DMG_FLAG ,DMG_SCALE ,
35 5 DFMAX ,LF_DAMMX ,TDEL ,TIMESTEP )
36C-----------------------------------------------
37C modified Puck model ------
38C-----------------------------------------------
39C I m p l i c i t T y p e s
40C-----------------------------------------------
41#include "implicit_f.inc"
42C-----------------------------------------------
43C G l o b a l P a r a m e t e r s
44C-----------------------------------------------
45#include "units_c.inc"
46#include "comlock.inc"
47C---------+---------+---+---+--------------------------------------------
48C VAR | SIZE |TYP| RW| DEFINITION
49C---------+---------+---+---+--------------------------------------------
50C NEL | 1 | I | R | SIZE OF THE ELEMENT GROUP NEL
51C NUPARAM | 1 | I | R | SIZE OF THE USER PARAMETER ARRAY
52C UPARAM | NUPARAM | F | R | USER MATERIAL PARAMETER ARRAY
53C NUVAR | 1 | I | R | NUMBER OF USER ELEMENT VARIABLES
54C UVAR |NEL*NUVAR| F |R/W| USER ELEMENT VARIABLE ARRAY
55C---------+---------+---+---+--------------------------------------------
56C TIME | 1 | F | R | CURRENT TIME
57C---------+---------+---+---+--------------------------------------------
58C SIGNXX | NEL | F | W | NEW ELASTO PLASTIC STRESS XX
59C SIGNYY | NEL | F | W | NEW ELASTO PLASTIC STRESS YY
60C ... | | | |
61C---------+---------+---+---+--------------------------------------------
62C OFF | NEL | F | R | DELETED ELEMENT FLAG (=1. ON, =0. OFF)
63C FOFF | NEL | I |R/W| DELETED INTEGRATION POINT FLAG (=1 ON, =0 OFF)
64C DFMAX | NEL | F |R/W| MAX DAMAGE FACTOR
65C TDEL | NEL | F | W | FAILURE TIME
66C DMG_FLAG| 1 | I | W | STRESS REDUCTION FLAG DUE TO DAMAGE
67C DMG_SCALE| NEL | F | W | STRESS REDUCTION FACTOR
68C---------+---------+---+---+--------------------------------------------
69C NGL ELEMENT ID
70C IPG CURRENT GAUSS POINT (in plane)
71C ILAY CURRENT LAYER
72C IPT CURRENT INTEGRATION POINT IN THE LAYER
73C---------+---------+---+---+--------------------------------------------
74C I N P U T A r g u m e n t s
75C-----------------------------------------------
76 INTEGER ,INTENT(IN) :: NEL,NUPARAM,NUVAR,IPG,ILAY,IPT,LF_DAMMX
77 INTEGER ,DIMENSION(NEL) ,INTENT(IN) :: NGL
78 my_real ,INTENT(IN) :: TIME,TIMESTEP
79 my_real ,DIMENSION(NEL) ,INTENT(IN) :: OFF,
80 . SIGNXX,SIGNYY,SIGNXY,SIGNYZ,SIGNZX
81 my_real,DIMENSION(NUPARAM) ,INTENT(IN) :: uparam
82C-----------------------------------------------
83C I N P U T O U T P U T A r g u m e n t s
84C-----------------------------------------------
85 INTEGER ,INTENT(OUT) ::DMG_FLAG
86 INTEGER ,DIMENSION(NEL) ,INTENT(INOUT) :: FOFF
87 my_real ,DIMENSION(NEL,LF_DAMMX),INTENT(INOUT) :: DFMAX
88 my_real ,DIMENSION(NEL) ,INTENT(OUT) :: TDEL,DMG_SCALE
89 my_real ,DIMENSION(NEL,NUVAR) ,INTENT(INOUT) :: UVAR
90C-----------------------------------------------
91C L o c a l V a r i a b l e s
92C-----------------------------------------------
93 INTEGER :: I,J,NINDX,FSMOOTH
94 INTEGER ,DIMENSION(NEL) :: INDX
95 my_real :: SIGT1,SIGT2, SIGC1,SIGC2,FSIG12,F1,FA,FB,FC,
96 . PN12,PP12,PN22,FAC,TMAX,DAMMX,FCUT,ASRATE,
97 . SXX(NEL),SYY(NEL),SXY(NEL)
98C=======================================================================
99 sigt1 = uparam(1)
100 sigt2 = uparam(2)
101 sigc1 = uparam(3)
102 sigc2 = uparam(4)
103 fsig12 = uparam(5)
104 pp12 = uparam(6)
105 pn12 = uparam(7)
106 pn22 = uparam(8)
107 tmax = uparam(9)
108 fcut = uparam(12)
109 IF (fcut > zero) THEN
110 fsmooth = 1
111 asrate = two*pi*fcut*timestep
112 asrate = asrate/(one+asrate)
113 ELSE
114 fsmooth = 0
115 ENDIF
116c
117 dmg_flag = 1
118 nindx = 0
119 IF (fsmooth > 0) THEN
120 DO i = 1,nel
121 sxx(i) = asrate*signxx(i) + (one - asrate)*uvar(i,2)
122 syy(i) = asrate*signyy(i) + (one - asrate)*uvar(i,3)
123 sxy(i) = asrate*signxy(i) + (one - asrate)*uvar(i,4)
124 uvar(i,2) = sxx(i)
125 uvar(i,3) = syy(i)
126 uvar(i,4) = sxy(i)
127 ENDDO
128 ELSE
129 DO i = 1,nel
130 sxx(i) = signxx(i)
131 syy(i) = signyy(i)
132 sxy(i) = signxy(i)
133 ENDDO
134 ENDIF
135c-------------------------------
136 DO i=1,nel
137 IF (off(i) == one .and. foff(i) == 1) THEN
138 f1 = zero
139 fa = zero
140 fb = zero
141 fc = zero
142C
143 IF (uvar(i,1) == zero) THEN
144c
145c fiber criteria
146c
147 IF (sxx(i) >= zero) THEN
148 f1 = sxx(i)/sigt1
149 dfmax(i,2) = max(dfmax(i,2),f1)
150 dfmax(i,2) = min(dfmax(i,2),one)
151 ELSE
152 f1 = -sxx(i)/sigc1
153 dfmax(i,3) = max(dfmax(i,3),f1)
154 dfmax(i,3) = min(dfmax(i,3),one)
155 ENDIF
156c
157c matrix criteria
158c
159 IF (syy(i) >= zero) THEN
160 fac = one - pp12*sigt2/fsig12
161 fac = fac*syy(i)/sigt2
162 fa = sqrt((sxy(i)/fsig12)**2 + fac*fac)
163 . + pp12*syy(i)/fsig12
164 dfmax(i,4) = max(dfmax(i,4),fa)
165 dfmax(i,4) = min(dfmax(i,4),one)
166 ELSE
167 fac = half/(one + pn22)/fsig12
168 fc = (sxy(i)*fac)**2 + (syy(i)/sigc2)**2
169 fc =-fc*sigc2/syy(i)
170 dfmax(i,6) = max(dfmax(i,6),fc)
171 dfmax(i,6) = min(dfmax(i,6),one)
172 ENDIF
173 fb = sqrt(sxy(i)**2 + (pn12*syy(i))**2 )
174 . + pn12*syy(i)
175 fb = fb/fsig12
176 dfmax(i,5) = max(dfmax(i,5),fb)
177 dfmax(i,5) = min(dfmax(i,5),one)
178C
179 dammx = min(one,max(f1,fa,fb,fc))
180 dfmax(i,1) = min(one,dammx)
181 IF (dammx >= one) THEN
182 nindx = nindx+1
183 indx(nindx) = i
184 uvar(i,1) = time
185 ENDIF
186 ENDIF
187c
188 IF (uvar(i,1) > zero) THEN
189 dmg_scale(i) = exp(-(time - uvar(i,1))/tmax)
190 IF (dmg_scale(i) < em02) THEN
191 foff(i) = 0
192 tdel(i) = time
193 dmg_scale(i) = zero
194 ENDIF
195 ENDIF
196 ENDIF
197 ENDDO
198c------------------------
199c print
200c------------------------
201 IF (nindx > 0) THEN
202 DO j=1,nindx
203 i = indx(j)
204#include "lockon.inc"
205 WRITE(iout, 2000) ngl(i),ipg,ilay,ipt
206 WRITE(istdo,2100) ngl(i),ipg,ilay,ipt,time
207#include "lockoff.inc"
208 END DO
209 END IF
210c------------------------
211 2000 FORMAT(1x,'FAILURE (PUCK) OF SHELL ELEMENT ',i10,1x,',GAUSS PT',
212 . i2,1x,',LAYER',i3,1x,',INTEGRATION PT',i3)
213 2100 FORMAT(1x,'FAILURE (PUCK) OF SHELL ELEMENT ',i10,1x,',GAUSS PT',
214 . i2,1x,',LAYER',i3,1x,',INTEGRATION PT',i3,1x,'AT TIME :',1pe12.4)
215c------------------------
216 RETURN
217 END
subroutine fail_puck_c(nel, nuparam, nuvar, uparam, uvar, time, ngl, ipg, ilay, ipt, signxx, signyy, signxy, signyz, signzx, off, foff, dmg_flag, dmg_scale, dfmax, lf_dammx, tdel, timestep)
Definition fail_puck_c.F:36
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21