OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
fail_hoffman_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_hoffman_c ../engine/source/materials/fail/hoffman/fail_hoffman_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_hoffman_c(
30 1 NEL ,NUPARAM ,NUVAR ,UPARAM ,UVAR ,
31 2 TIME ,NGL ,IPG ,ILAY ,IPT ,
32 3 SIGNXX ,SIGNYY ,SIGNXY ,SIGNYZ ,SIGNZX ,
33 4 OFF ,FOFF ,DMG_FLAG ,DMG_SCALE ,
34 5 DFMAX ,LF_DAMMX ,TDEL ,TIMESTEP )
35C-----------------------------------------------
36C modified Puck model ------
37C-----------------------------------------------
38C I m p l i c i t T y p e s
39C-----------------------------------------------
40#include "implicit_f.inc"
41C-----------------------------------------------
42C G l o b a l P a r a m e t e r s
43C-----------------------------------------------
44#include "units_c.inc"
45#include "comlock.inc"
46C-----------------------------------------------
47C I N P U T A r g u m e n t s
48C-----------------------------------------------
49 INTEGER ,INTENT(IN) :: NEL,NUPARAM,NUVAR,IPG,ILAY,IPT,LF_DAMMX
50 INTEGER ,DIMENSION(NEL) ,INTENT(IN) :: NGL
51 my_real ,INTENT(IN) :: TIME,TIMESTEP
52 my_real ,DIMENSION(NEL) ,INTENT(IN) :: OFF,
53 . SIGNXX,SIGNYY,SIGNXY,SIGNYZ,SIGNZX
54 my_real,DIMENSION(NUPARAM) ,INTENT(IN) :: uparam
55C-----------------------------------------------
56C I N P U T O U T P U T A r g u m e n t s
57C-----------------------------------------------
58 INTEGER ,INTENT(OUT) ::DMG_FLAG
59 INTEGER ,DIMENSION(NEL) ,INTENT(INOUT) :: FOFF
60 my_real ,DIMENSION(NEL,LF_DAMMX),INTENT(INOUT) :: DFMAX
61 my_real ,DIMENSION(NEL) ,INTENT(OUT) :: TDEL,DMG_SCALE
62 my_real ,DIMENSION(NEL,NUVAR) ,INTENT(INOUT) :: UVAR
63C-----------------------------------------------
64C L o c a l V a r i a b l e s
65C-----------------------------------------------
66 INTEGER :: I,J,NINDX,IFAIL_SH
67 INTEGER ,DIMENSION(NEL) :: INDX
68 my_real
69 . TMAX,FCUT
70 my_real
71 . f1,f2,f11,f22,f66,f12,asrate,a,b,
72 . sxx(nel),syy(nel),sxy(nel),findex,rfactr
73C!----------------------------------------------
74 !=======================================================================
75 ! - INITIALISATION OF COMPUTATION ON TIME STEP
76 !=======================================================================
77 ! Recovering model parameters
78 f1 = uparam(1)
79 f2 = uparam(2)
80 f11 = uparam(3)
81 f22 = uparam(4)
82 f66 = uparam(5)
83 f12 = uparam(6)
84 tmax = uparam(7)
85 fcut = uparam(8)
86 ifail_sh = int(uparam(9))
87c
88 ! Stress softening activation
89 dmg_flag = 1
90c
91 ! Stress tensor filtering
92 IF (fcut > zero) THEN
93 asrate = two*pi*fcut*timestep
94 asrate = asrate/(one+asrate)
95 DO i = 1,nel
96 sxx(i) = asrate*signxx(i) + (one - asrate)*uvar(i,2)
97 syy(i) = asrate*signyy(i) + (one - asrate)*uvar(i,3)
98 sxy(i) = asrate*signxy(i) + (one - asrate)*uvar(i,4)
99 uvar(i,2) = sxx(i)
100 uvar(i,3) = syy(i)
101 uvar(i,4) = sxy(i)
102 ENDDO
103 ELSE
104 DO i = 1,nel
105 sxx(i) = signxx(i)
106 syy(i) = signyy(i)
107 sxy(i) = signxy(i)
108 ENDDO
109 ENDIF
110c
111 !====================================================================
112 ! - COMPUTATION OF THE DAMAGE VARIABLE EVOLUTION
113 !====================================================================
114 ! Initialization of element failure index
115 nindx = 0
116 indx(1:nel) = 0
117c
118 ! Loop over the elements
119 DO i=1,nel
120c
121 ! If damage has not been reached yet
122 IF (dfmax(i,1)<one) THEN
123c
124 ! Compute parameters A and B
125 a = f11*(sxx(i)**2) + f22*(syy(i)**2) +
126 . f66*(sxy(i)**2) + f12*sxx(i)*syy(i)
127 b = f1*sxx(i) + f2*syy(i)
128c
129 ! Compute failure index and reserve factor
130 findex = a + b
131 findex = max(zero,findex)
132c
133 ! Compute reserve factor
134 rfactr = (-b + sqrt((b**2)+four*a))/max((two*a),em20)
135 dfmax(i,2) = rfactr
136c
137 ! Damage variable update
138 dfmax(i,1) = min(one ,max(findex,dfmax(i,1)))
139 IF (dfmax(i,1) >= one) THEN
140 nindx = nindx+1
141 indx(nindx) = i
142 IF (ifail_sh > 0) THEN
143 uvar(i,1) = time
144 ENDIF
145 ENDIF
146 ENDIF
147c
148 ! Stress relaxation in case of damage reached
149 IF ((uvar(i,1) > zero).AND.(foff(i) /= 0).AND.(ifail_sh > 0)) THEN
150 dmg_scale(i) = exp(-(time - uvar(i,1))/tmax)
151 IF (dmg_scale(i) < em02) THEN
152 foff(i) = 0
153 tdel(i) = time
154 dmg_scale(i) = zero
155 ENDIF
156 ENDIF
157 ENDDO
158c
159 !====================================================================
160 ! - PRINTOUT DATA ABOUT FAILED ELEMENTS
161 !====================================================================
162 IF (nindx > 0) THEN
163 DO j=1,nindx
164 i = indx(j)
165#include "lockon.inc"
166 WRITE(iout, 2000) ngl(i),ipg,ilay,ipt
167 WRITE(istdo,2100) ngl(i),ipg,ilay,ipt,time
168#include "lockoff.inc"
169 END DO
170 END IF
171c------------------------
172 2000 FORMAT(1x,'FAILURE (HOFFMAN) OF SHELL ELEMENT ',i10,1x,',GAUSS PT',
173 . i2,1x,',LAYER',i3,1x,',INTEGRATION PT',i3)
174 2100 FORMAT(1x,'FAILURE (HOFFMAN) OF SHELL ELEMENT ',i10,1x,',GAUSS PT',
175 . i2,1x,',LAYER',i3,1x,',INTEGRATION PT',i3,1x,'at time :',1PE12.4)
176c------------------------
177 END
subroutine fail_hoffman_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)
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21