OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
fail_syazwan_s.F File Reference
#include "implicit_f.inc"
#include "mvsiz_p.inc"
#include "scr17_c.inc"
#include "units_c.inc"
#include "comlock.inc"
#include "param_c.inc"
#include "tabsiz_c.inc"
#include "lockon.inc"
#include "lockoff.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine fail_syazwan_s (nel, uparam, nuparam, uvar, nuvar, time, ngl, ipg, dpla, tdele, signxx, signyy, signzz, signxy, signyz, signzx, dfmax, nfunc, ifunc, aldt, off, npf, tf, uelr, npg, loff)

Function/Subroutine Documentation

◆ fail_syazwan_s()

subroutine fail_syazwan_s ( integer, intent(in) nel,
dimension(nuparam), intent(in) uparam,
integer, intent(in) nuparam,
dimension(nel,nuvar), intent(inout) uvar,
integer, intent(in) nuvar,
intent(in) time,
integer, dimension(nel), intent(in) ngl,
integer, intent(in) ipg,
dimension(nel), intent(in) dpla,
dimension(nel), intent(inout) tdele,
dimension(nel), intent(in) signxx,
dimension(nel), intent(in) signyy,
dimension(nel), intent(in) signzz,
dimension(nel), intent(in) signxy,
dimension(nel), intent(in) signyz,
dimension(nel), intent(in) signzx,
dimension(nel), intent(inout) dfmax,
integer, intent(in) nfunc,
integer, dimension(nfunc), intent(in) ifunc,
dimension(nel), intent(in) aldt,
dimension(nel), intent(inout) off,
integer, dimension(snpc), intent(in) npf,
dimension(stf), intent(in) tf,
dimension(nel), intent(inout) uelr,
integer, intent(in) npg,
dimension(nel), intent(inout) loff )

Definition at line 32 of file fail_syazwan_s.F.

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 "mvsiz_p.inc"
46#include "scr17_c.inc"
47#include "units_c.inc"
48#include "comlock.inc"
49#include "param_c.inc"
50#include "tabsiz_c.inc"
51C-----------------------------------------------
52C I N P U T A r g u m e n t s
53C-----------------------------------------------
54 INTEGER, INTENT(IN) ::
55 . NEL ,NUPARAM,NUVAR,NGL(NEL),IPG ,
56 . NFUNC ,IFUNC(NFUNC) ,NPG
57 my_real, INTENT(IN) ::
58 . time ,uparam(nuparam),dpla(nel) ,
59 . signxx(nel),signyy(nel),signzz(nel),
60 . signxy(nel),signyz(nel),signzx(nel),
61 . aldt(nel)
62C-----------------------------------------------
63C I N P U T O U T P U T A r g u m e n t s
64C-----------------------------------------------
65 my_real, INTENT(INOUT) ::
66 . uvar(nel,nuvar),loff(nel),off(nel),
67 . dfmax(nel),tdele(nel),uelr(nel)
68C-----------------------------------------------
69C VARIABLES FOR FUNCTION INTERPOLATION
70C-----------------------------------------------
71 INTEGER, INTENT(IN) :: NPF(SNPC)
72 my_real, INTENT(IN) :: tf(stf)
74 . finter
75 EXTERNAL finter
76C!-----------------------------------------------
77C! L o c a l V a r i a b l e s
78C!-----------------------------------------------
79 INTEGER I,J,NINDX,NINDX2,FAILIP
80 INTEGER, DIMENSION(NEL) :: INDX,INDX2
82 . c1 ,c2 ,c3 ,c4 ,c5 ,
83 . c6 ,ref_len ,reg_scale
85 . lambda ,dydx ,fac(nel),p ,svm ,
86 . triax ,cos3theta,lodep ,epsfail,
87 . det ,sxx ,syy ,szz ,epfmin
88 !=======================================================================
89 ! - INITIALISATION OF COMPUTATION ON TIME STEP
90 !=======================================================================
91 ! Recovering failure criterion parameters
92 c1 = uparam(1)
93 c2 = uparam(2)
94 c3 = uparam(3)
95 c4 = uparam(4)
96 c5 = uparam(5)
97 c6 = uparam(6)
98 ref_len = uparam(14)
99 reg_scale = uparam(15)
100 epfmin = uparam(16)
101 failip = min(nint(uparam(17)),npg)
102c
103 ! At first timestep, initialization of the critical damage and
104 ! the element size scaling factor
105 IF (uvar(1,1) == zero) THEN
106 IF (ifunc(1) > 0) THEN
107 DO i=1,nel
108 lambda = aldt(i)/ref_len
109 uvar(i,1) = finter(ifunc(1),lambda,npf,tf,dydx)
110 uvar(i,1) = uvar(i,1)*reg_scale
111 ENDDO
112 ELSE
113 uvar(1:nel,1) = one
114 ENDIF
115 ENDIF
116c
117 DO i=1,nel
118 ! Recover element size scaling
119 fac(i) = uvar(i,1)
120 IF (off(i) < em01) off(i) = zero
121 IF (off(i) < one .AND. off(i) > zero) off(i) = off(i)*four_over_5
122 ENDDO
123c
124 !====================================================================
125 ! - COMPUTATION OF THE DAMAGE VARIABLE EVOLUTION
126 !====================================================================
127 ! Initialization of element failure index
128 nindx = 0
129 indx(1:nel) = 0
130 nindx2 = 0
131 indx2(1:nel) = 0
132c
133 ! Loop over the elements
134 DO i=1,nel
135c
136 IF (loff(i) == one .AND. dpla(i) > zero .AND. off(i) == one) THEN
137c
138 ! Computation of hydrostatic stress, Von Mises stress, and stress triaxiality
139 p = third*(signxx(i) + signyy(i) + signzz(i))
140 sxx = signxx(i) - p
141 syy = signyy(i) - p
142 szz = signzz(i) - p
143 svm = half*(sxx**2 + syy**2 + szz**2)
144 . + signxy(i)**2+ signzx(i)**2 + signyz(i)**2
145 svm = sqrt(three*svm)
146 triax = p/max(em20,svm)
147 IF (triax < -two_third) triax = -two_third
148 IF (triax > two_third) triax = two_third
149c
150 ! Computation of Lode parameter
151 det = sxx*syy*szz + two*signxy(i)*signzx(i)*signyz(i)-
152 . sxx*signyz(i)**2-szz*signxy(i)**2-syy*signzx(i)**2
153 cos3theta = half*twenty7*det/max(em20,svm**3)
154 IF(cos3theta < -one) cos3theta = -one
155 IF(cos3theta > one) cos3theta = one
156 lodep = one - two*acos(cos3theta)/pi
157c
158 ! Computation of the plastic strain at failure
159 epsfail = c1 + c2*triax + c3*lodep + c4*(triax**2) +
160 . c5*(lodep**2) + c6*triax*lodep
161 epsfail = epsfail*fac(i)
162 epsfail = max(epfmin,epsfail)
163c
164 ! Computation of the damage variable update
165 dfmax(i) = dfmax(i) + dpla(i)/max(epsfail,em20)
166 dfmax(i) = min(dfmax(i),one)
167c
168 ! Check element failure
169 IF (dfmax(i) >= one) THEN
170 loff(i) = zero
171 nindx = nindx + 1
172 indx(nindx) = i
173 uelr(i) = uelr(i) + one
174 IF (nint(uelr(i)) >= failip) THEN
175 off(i) = four_over_5
176 tdele(i) = time
177 nindx2 = nindx2 + 1
178 indx2(nindx2) = i
179 ENDIF
180 ENDIF
181 ENDIF
182 ENDDO
183c
184 !====================================================================
185 ! - PRINTOUT DATA ABOUT FAILED ELEMENTS
186 !====================================================================
187 IF (nindx>0) THEN
188 DO j=1,nindx
189 i = indx(j)
190#include "lockon.inc"
191 WRITE(iout, 1000) ngl(i),ipg,time
192 WRITE(istdo,1000) ngl(i),ipg,time
193#include "lockoff.inc"
194 END DO
195 ENDIF
196 IF (nindx2>0) THEN
197 DO j=1,nindx2
198 i = indx2(j)
199#include "lockon.inc"
200 WRITE(iout, 2000) ngl(i),time
201 WRITE(istdo,2000) ngl(i),time
202#include "lockoff.inc"
203 END DO
204 ENDIF
205C------------------
206 1000 FORMAT(1x,'FOR SOLID ELEMENT NUMBER el#',i10,
207 . ' FAILURE (SYAZWAN) AT GAUSS POINT ',i5,
208 . ' AT TIME :',1pe12.4)
209 2000 FORMAT(1x,'-- RUPTURE OF SOLID ELEMENT :',i10,
210 . ' at time :',1PE12.4)
#define my_real
Definition cppsort.cpp:32
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21