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

Go to the source code of this file.

Functions/Subroutines

subroutine sigeps76c (nel, nuparam, nuvar, nfunc, ifunc, npf, tf, matparam, time, timestep, uparam, uvar, rho0, off, ngl, depsxx, depsyy, depsxy, depsyz, depszx, sigoxx, sigoyy, sigoxy, sigoyz, sigozx, signxx, signyy, signxy, signyz, signzx, soundsp, thk, thkly, pla, epsd, etse, gs, yld, inloc, l_planl, planl, dplanl, dmg, nvartmp, vartmp, loff)

Function/Subroutine Documentation

◆ sigeps76c()

subroutine sigeps76c ( integer, intent(in) nel,
integer, intent(in) nuparam,
integer, intent(in) nuvar,
integer, intent(in) nfunc,
integer, dimension(nfunc), intent(in) ifunc,
integer, dimension(snpc) npf,
tf,
type(matparam_struct_), intent(in), target matparam,
intent(in) time,
intent(in) timestep,
intent(in) uparam,
intent(inout) uvar,
intent(in) rho0,
intent(inout) off,
integer, dimension(nel), intent(in) ngl,
intent(in) depsxx,
intent(in) depsyy,
intent(in) depsxy,
intent(in) depsyz,
intent(in) depszx,
intent(in) sigoxx,
intent(in) sigoyy,
intent(in) sigoxy,
intent(in) sigoyz,
intent(in) sigozx,
intent(inout) signxx,
intent(inout) signyy,
intent(inout) signxy,
intent(inout) signyz,
intent(inout) signzx,
intent(inout) soundsp,
intent(inout) thk,
intent(in) thkly,
intent(inout) pla,
intent(inout) epsd,
intent(inout) etse,
intent(in) gs,
intent(inout) yld,
integer, intent(in) inloc,
integer, intent(in) l_planl,
intent(in) planl,
intent(in) dplanl,
intent(inout) dmg,
integer, intent(in) nvartmp,
integer, dimension(nel,nvartmp), intent(inout) vartmp,
intent(in) loff )

Definition at line 35 of file sigeps76c.F.

46C-----------------------------------------------
47C M o d u l e s
48C-----------------------------------------------
49 USE matparam_def_mod
50C-----------------------------------------------
51C I m p l i c i t T y p e s
52C-----------------------------------------------
53#include "implicit_f.inc"
54C-----------------------------------------------
55C G l o b a l P a r a m e t e r s
56C-----------------------------------------------
57#include "tabsiz_c.inc"
58#include "comlock.inc"
59#include "units_c.inc"
60C-----------------------------------------------
61C D u m m y A r g u m e n t s
62C-----------------------------------------------
63 INTEGER ,INTENT(IN) :: NEL,NFUNC,NUPARAM,NUVAR,INLOC,L_PLANL
64 INTEGER ,INTENT(IN) :: NVARTMP
65 INTEGER ,DIMENSION(NEL,NVARTMP) ,INTENT(INOUT) :: VARTMP
66 INTEGER ,DIMENSION(NFUNC), INTENT(IN) :: IFUNC
67 INTEGER ,DIMENSION(NEL) , INTENT(IN) :: NGL
68 my_real ,INTENT(IN) :: time,timestep
69 my_real ,DIMENSION(NUPARAM), INTENT(IN) :: uparam
70 my_real ,DIMENSION(NEL), INTENT(IN) :: rho0,thkly,gs,
71 . depsxx,depsyy,depsxy,depsyz,depszx,
72 . sigoxx,sigoyy,sigoxy,sigoyz,sigozx,dplanl
73 my_real, DIMENSION(L_PLANL*NEL), INTENT(IN) :: planl
74 my_real, DIMENSION(NEL), INTENT(INOUT) ::
75 . epsd,pla,signxx,signyy,signxy,signyz,signzx,soundsp,
76 . etse,off,yld,thk,dmg
77 my_real, DIMENSION(NEL,NUVAR), INTENT(INOUT) :: uvar
78 TYPE(MATPARAM_STRUCT_), INTENT(IN), TARGET :: MATPARAM
79 my_real, DIMENSION(NEL), INTENT(IN) :: loff
80C-----------------------------------------------
81C VARIABLES FOR FUNCTION INTERPOLATION
82C-----------------------------------------------
83 INTEGER :: NPF(SNPC)
84 my_real :: tf(stf)
85C-----------------------------------------------
86C L o c a l V a r i a b l e s
87C-----------------------------------------------
88 INTEGER :: I,IFORM,IQUAD,NUMTABL,NINDX
89 INTEGER ,DIMENSION(NEL) :: INDX,IAD,ILEN
90 my_real :: epspf,epspr,yfac2
91 my_real ,DIMENSION(NEL) :: dezz,dpla,pla_dam,df
92 my_real ,DIMENSION(NEL) :: sig0xx,sig0yy,sig0xy,sig0yz,sig0zx
93 TYPE(TABLE_4D_), DIMENSION(:), POINTER :: TABLE
94C=======================================================================
95c
96 !====================================================================
97 ! - PARAMETERS INITIALIZATION
98 !====================================================================
99 epspf = uparam(10) ! Failure plastic strain
100 epspr = uparam(11) ! Rupture plastic strain
101 iform = nint(uparam(13)) ! Flag for plasticity
102 ! = 0 associated (with quadratic yield criterion only)
103 ! = 1 not associated
104 iquad = nint(uparam(14)) ! Flag for quadratic yield criterion
105 yfac2 = uparam(29) ! Damage function scale factor
106 dpla(1:nel) = zero ! Initialization of the plastic strain increment
107 etse(1:nel) = one
108 DO i = 1,nel
109 IF (off(i) < em01) off(i) = zero
110 IF (off(i) < one) off(i) = off(i)*four_over_5
111 ENDDO
112c
113 ! Table parameters
114 numtabl = matparam%NTABLE
115 table => matparam%TABLE(1:numtabl)
116c
117 !====================================================================
118 ! - COMPUTE INITIAL UNDAMAGED STRESSES
119 !====================================================================
120 DO i = 1,nel
121 sig0xx(i) = sigoxx(i)/max(one-dmg(i),em20)
122 sig0yy(i) = sigoyy(i)/max(one-dmg(i),em20)
123 sig0xy(i) = sigoxy(i)/max(one-dmg(i),em20)
124 sig0yz(i) = sigoyz(i)/max(one-dmg(i),em20)
125 sig0zx(i) = sigozx(i)/max(one-dmg(i),em20)
126 ENDDO
127c
128 !====================================================================
129 ! - ELASTO-PLASTIC BEHAVIOR
130 !====================================================================
131 IF (iform == 1) THEN ! Associated plastic flow, Quadratic yield criterion
132 CALL asso_qplas76c(
133 . nel ,nuparam ,nuvar ,nfunc ,ifunc ,
134 . npf ,tf ,numtabl ,table ,
135 . time ,timestep,uparam ,uvar ,rho0 ,
136 . depsxx ,depsyy ,depsxy ,depsyz ,depszx ,
137 . sig0xx ,sig0yy ,sig0xy ,sig0yz ,sig0zx ,
138 . signxx ,signyy ,signxy ,signyz ,signzx ,
139 . pla ,dpla ,epsd ,off ,gs ,
140 . yld ,soundsp ,dezz ,inloc ,dplanl ,
141 . nvartmp ,vartmp ,loff )
142c
143 ELSE ! Non-associated plastic flow
144 IF (iquad == 1) THEN ! Quadratic yield criterion
145 CALL no_asso_qplas76c(
146 . nel ,nuparam ,nuvar ,nfunc ,ifunc ,
147 . npf ,tf ,numtabl ,table ,
148 . time ,timestep,uparam ,uvar ,rho0 ,
149 . depsxx ,depsyy ,depsxy ,depsyz ,depszx ,
150 . sig0xx ,sig0yy ,sig0xy ,sig0yz ,sig0zx ,
151 . signxx ,signyy ,signxy ,signyz ,signzx ,
152 . pla ,dpla ,epsd ,off ,gs ,
153 . yld ,soundsp ,dezz ,inloc ,dplanl ,
154 . nvartmp ,vartmp ,loff )
155 ELSE ! Non-quadratic yield criterion
156 CALL no_asso_lplas76c(
157 . nel ,nuparam ,nuvar ,nfunc ,ifunc ,
158 . npf ,tf ,numtabl ,table ,
159 . time ,timestep,uparam ,uvar ,rho0 ,
160 . depsxx ,depsyy ,depsxy ,depsyz ,depszx ,
161 . sig0xx ,sig0yy ,sig0xy ,sig0yz ,sig0zx ,
162 . signxx ,signyy ,signxy ,signyz ,signzx ,
163 . pla ,dpla ,epsd ,off ,gs ,
164 . yld ,soundsp ,dezz ,inloc ,dplanl ,
165 . nvartmp ,vartmp ,loff )
166 ENDIF
167 ENDIF
168c
169 !====================================================================
170 ! - UPDATE DAMAGE VARIABLE
171 !====================================================================
172 nindx = 0
173 IF (inloc > 0) THEN
174 pla_dam(1:nel) = planl(1:nel)
175 ELSE
176 pla_dam(1:nel) = pla(1:nel)
177 ENDIF
178!
179 IF (ifunc(2) > 0) THEN
180 ! Tabulated damage
181 iad(1:nel) = npf(ifunc(2)) / 2 + 1
182 ilen(1:nel) = npf(ifunc(2)+1) / 2 - iad(1:nel) - vartmp(1:nel,7)
183!
184 CALL vinter(tf,iad,vartmp(1:nel,7),ilen,nel,pla_dam,df,dmg)
185!
186 dmg(1:nel) = abs(yfac2)*dmg(1:nel)
187 DO i=1,nel
188 IF (dmg(i) >= one) THEN
189 dmg(i) = one
190 IF (off(i) == one) THEN
191 off(i) = four_over_5
192 nindx = nindx+1
193 indx(nindx) = i
194 ENDIF
195 ENDIF
196 ENDDO
197 ! Analytical damage
198 ELSE
199 DO i=1,nel
200 IF (pla_dam(i) >= epspf) THEN
201 dmg(i) = (pla_dam(i) - epspf)/ (epspr - epspf)
202 dmg(i) = min(dmg(i),one)
203 ENDIF
204 IF (dmg(i) >= one) THEN
205 IF (off(i) == one) THEN
206 off(i) = four_over_5
207 nindx = nindx+1
208 indx(nindx) = i
209 ENDIF
210 ENDIF
211 ENDDO
212 ENDIF
213c
214 !====================================================================
215 ! - COMPUTE DAMAGED STRESSES
216 !====================================================================
217 DO i = 1,nel
218 signxx(i) = signxx(i)*(one-dmg(i))
219 signyy(i) = signyy(i)*(one-dmg(i))
220 signxy(i) = signxy(i)*(one-dmg(i))
221 signyz(i) = signyz(i)*(one-dmg(i))
222 signzx(i) = signzx(i)*(one-dmg(i))
223 ENDDO
224c
225 !====================================================================
226 ! - HOURGLASS COEFFICIENT AND THICKNESS UPDATE
227 !====================================================================
228 DO i=1,nel
229 IF (dpla(i) > zero) THEN
230 etse(i) = half
231 ENDIF
232 thk(i) = thk(i) + dezz(i)*thkly(i)*off(i)
233 ENDDO
234c
235 !====================================================================
236 ! - PRINTOUT ELEMENT DELETION
237 !====================================================================
238 IF (nindx > 0) THEN
239 DO i=1,nindx
240#include "lockon.inc"
241 WRITE(iout, 1000) ngl(indx(i))
242 WRITE(istdo,1100) ngl(indx(i)),time
243#include "lockoff.inc"
244 ENDDO
245 ENDIF
246c------------------------------------------------------
247 1000 FORMAT(1x,'RUPTURE (SAMP) OF SHELL ELEMENT NUMBER ',i10)
248 1100 FORMAT(1x,'RUPTURE (SAMP) OF SHELL ELEMENT NUMBER ',i10,'AT TIME :',g11.4)
249c------------------------------------------------------
subroutine asso_qplas76c(nel, nuparam, nuvar, nfunc, ifunc, npf, tf, numtabl, table, time, timestep, uparam, uvar, rho, depsxx, depsyy, depsxy, depsyz, depszx, sigoxx, sigoyy, sigoxy, sigoyz, sigozx, signxx, signyy, signxy, signyz, signzx, pla, dpla, epsd, off, gs, yld, soundsp, dezz, inloc, dplanl, nvartmp, vartmp, loff)
#define my_real
Definition cppsort.cpp:32
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21
subroutine no_asso_lplas76c(nel, nuparam, nuvar, nfunc, ifunc, npf, tf, numtabl, table, time, timestep, uparam, uvar, rho, depsxx, depsyy, depsxy, depsyz, depszx, sigoxx, sigoyy, sigoxy, sigoyz, sigozx, signxx, signyy, signxy, signyz, signzx, pla, dpla, epsd, off, gs, yld, soundsp, dezz, inloc, dplanl, nvartmp, vartmp, loff)
subroutine no_asso_qplas76c(nel, nuparam, nuvar, nfunc, ifunc, npf, tf, numtabl, table, time, timestep, uparam, uvar, rho, depsxx, depsyy, depsxy, depsyz, depszx, sigoxx, sigoyy, sigoxy, sigoyz, sigozx, signxx, signyy, signxy, signyz, signzx, pla, dpla, epsd, off, gs, yld, soundsp, dezz, inloc, dplanl, nvartmp, vartmp, loff)
subroutine vinter(tf, iad, ipos, ilen, nel, x, dydx, y)
Definition vinter.F:72