OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
fail_beam18.F File Reference
#include "implicit_f.inc"
#include "comlock.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine fail_beam18 (elbuf_str, fail, nummat, numgeo, npropm, npropg, snpc, stf, nel, npt, imat, iprop, jthe, tempel, ngl, pm, geo, off, epsd, npf, tf, dpla, eint, time, iout, istdo, al, ismstr, exx, exy, exz, kxx, kyy, kzz, dtime, ntable, table, sigy)

Function/Subroutine Documentation

◆ fail_beam18()

subroutine fail_beam18 ( type (elbuf_struct_), intent(inout), target elbuf_str,
type (fail_param_), intent(in) fail,
integer, intent(in) nummat,
integer, intent(in) numgeo,
integer, intent(in) npropm,
integer, intent(in) npropg,
integer, intent(in) snpc,
integer, intent(in) stf,
integer, intent(in) nel,
integer, intent(in) npt,
integer, intent(in) imat,
integer, intent(in) iprop,
integer, intent(in) jthe,
intent(in) tempel,
integer, dimension(nel), intent(in) ngl,
intent(in) pm,
intent(in) geo,
intent(inout) off,
intent(in) epsd,
integer, dimension(snpc), intent(in) npf,
intent(in) tf,
intent(in) dpla,
intent(in) eint,
intent(in) time,
integer, intent(in) iout,
integer, intent(in) istdo,
intent(in) al,
integer, intent(in) ismstr,
intent(in) exx,
intent(in) exy,
intent(in) exz,
intent(in) kxx,
intent(in) kyy,
intent(in) kzz,
intent(in) dtime,
integer, intent(in) ntable,
type(ttable), dimension(ntable), intent(inout) table,
intent(in) sigy )

Definition at line 45 of file fail_beam18.F.

54C-----------------------------------------------
55C M o d u l e s
56C-----------------------------------------------
57 USE mat_elem_mod
58 USE elbufdef_mod
59 USE fail_visual_ib_mod
60 USE fail_gene1_ib_mod
61 USE fail_inievo_ib_mod
62 USE fail_tab2_ib_mod
63C-----------------------------------------------
64C I m p l i c i t T y p e s
65C-----------------------------------------------
66#include "implicit_f.inc"
67C-----------------------------------------------
68C C o m m o n B l o c k s
69C-----------------------------------------------
70#include "comlock.inc"
71C-----------------------------------------------
72C D u m m y A r g u m e n t s
73C-----------------------------------------------
74 INTEGER ,INTENT(IN) :: NEL ! size of element group
75 INTEGER ,INTENT(IN) :: IMAT ! material law number
76 INTEGER ,INTENT(IN) :: IPROP ! beam property number
77 INTEGER ,INTENT(IN) :: NPT ! number of integration points in beam section
78 INTEGER ,INTENT(IN) :: JTHE ! thermal dependency flag
79 INTEGER ,INTENT(IN) :: NUMMAT ! number of defined materials
80 INTEGER ,INTENT(IN) :: NUMGEO ! number of defined properties
81 INTEGER ,INTENT(IN) :: NPROPM ! size of real material parameter table
82 INTEGER ,INTENT(IN) :: NPROPG ! size of real property parameter table
83 INTEGER ,INTENT(IN) :: SNPC
84 INTEGER ,INTENT(IN) :: STF
85 INTEGER ,INTENT(IN) :: NTABLE
86 TYPE(TTABLE), DIMENSION(NTABLE), INTENT(INOUT) :: TABLE ! TABLE DATA
87 INTEGER ,INTENT(IN) :: IOUT ! output file unit
88 INTEGER ,INTENT(IN) :: ISTDO ! output file unit
89 INTEGER ,INTENT(IN) :: ISMSTR
90 INTEGER ,DIMENSION(SNPC) ,INTENT(IN) :: NPF
91 INTEGER ,DIMENSION(NEL) ,INTENT(IN) :: NGL ! table of element identifiers
92 my_real ,INTENT(IN) :: time
93 my_real ,DIMENSION(NPROPM ,NUMMAT) ,INTENT(IN) :: pm
94 my_real ,DIMENSION(NPROPG ,NUMGEO) ,INTENT(IN) :: geo
95 my_real ,DIMENSION(NEL) ,INTENT(IN) :: epsd
96 my_real ,DIMENSION(NEL) ,INTENT(IN) :: al
97 my_real ,DIMENSION(NEL) ,INTENT(IN) :: tempel
98 my_real ,DIMENSION(STF) ,INTENT(IN) :: tf
99 my_real ,DIMENSION(NEL) ,INTENT(IN) :: exx,exy,exz,kxx,kyy,kzz
100 my_real ,DIMENSION(NEL,NPT) ,INTENT(IN) :: dpla
101 my_real ,DIMENSION(NEL,2) ,INTENT(IN) :: eint
102 my_real ,DIMENSION(NEL) ,INTENT(INOUT) :: off
103 my_real ,INTENT(IN) :: dtime
104 my_real ,DIMENSION(NEL,NPT) ,INTENT(IN) :: sigy
105C
106 TYPE (ELBUF_STRUCT_) ,INTENT(INOUT) :: ELBUF_STR
107 TYPE (FAIL_PARAM_) ,INTENT(IN) :: FAIL
108 TARGET :: elbuf_str
109C-----------------------------------------------
110C L o c a l V a r i a b l e s
111C-----------------------------------------------
112 INTEGER :: I,IFL,IPT,NFUNC,IPY,IPZ,IPA,NVARF,NPARAM,IRUPT
113 INTEGER :: II(3)
114 INTEGER ,DIMENSION(NEL) :: COUNT
115 my_real :: t0,tm
116 my_real ,DIMENSION(NEL) :: shfact,epsxx,epsxy,epsxz,
117 . signxx,signxy,signxz,ypt,zpt,apt,tstar,depsxx,depsxy,depsxz
118 my_real ,DIMENSION(NEL) :: dpla_ipt,pla_ipt,sigy_ipt
119 my_real :: bidon
120C
121 TYPE(L_BUFEL_) ,POINTER :: LBUF
122 TYPE(BUF_FAIL_),POINTER :: FBUF
123 my_real, DIMENSION(:), POINTER :: uvarf,dfmax,tdel
124 INTEGER, DIMENSION(:), POINTER :: FOFF
125C=======================================================================
126c to avoid compilation error with unused arguments
127c they will be necessary for next development step
128 bidon = eint(1,1)
129c-----------------------------------------------------
130 ipy = 200
131 ipz = 300
132 ipa = 400
133 ifl = 1 ! only one failure model for beams
134 shfact = five_over_6
135C--------------------------------------
136 DO i=1,3
137 ii(i) = nel*(i-1)
138 ENDDO
139 count(1:nel) = 0
140 nparam = fail%NUPARAM
141 nfunc = fail%NFUNC
142C---------------------------------------
143C START LOOP OVER INTEGRATION POINTS
144C---------------------------------------
145 DO ipt = 1,npt
146 lbuf => elbuf_str%BUFLY(1)%LBUF(1,1,ipt)
147 fbuf => elbuf_str%BUFLY(1)%FAIL(1,1,ipt)
148 uvarf => fbuf%FLOC(ifl)%VAR
149 nvarf = fbuf%FLOC(ifl)%NVAR
150 irupt = fbuf%FLOC(ifl)%ILAWF
151 dfmax => fbuf%FLOC(ifl)%DAMMX
152 tdel => fbuf%FLOC(ifl)%TDEL
153 foff => fbuf%FLOC(ifl)%OFF
154 pla_ipt = elbuf_str%BUFLY(1)%LBUF(1,1,ipt)%PLA
155 dpla_ipt = dpla(:,ipt)
156 sigy_ipt = sigy(:,ipt)
157
158c
159C--- Coordinates of integration points
160 DO i=1,nel
161 ypt(i) = geo(ipy+ipt,iprop)
162 zpt(i) = geo(ipz+ipt,iprop)
163 apt(i) = geo(ipa+ipt,iprop)
164 ENDDO
165C
166 DO i=1,nel
167 signxx(i) = lbuf%SIG(ii(1)+i)
168 signxy(i) = lbuf%SIG(ii(2)+i)
169 signxz(i) = lbuf%SIG(ii(3)+i)
170 ENDDO
171c--- Total strain
172 DO i= 1,nel
173 epsxx(i) = lbuf%STRA(ii(1)+i)
174 epsxy(i) = lbuf%STRA(ii(2)+i)
175 epsxz(i) = lbuf%STRA(ii(3)+i)
176 END DO
177c--- Incremental strain
178 DO i = 1,nel
179 depsxx(i) = exx(i) - ypt(i)*kzz(i) + zpt(i)*kyy(i)
180 depsxy(i) = exy(i) + zpt(i)*kxx(i)
181 depsxz(i) = exz(i) - ypt(i)*kxx(i)
182 depsxy(i) = depsxy(i) / shfact(i)
183 depsxz(i) = depsxz(i) / shfact(i)
184 ENDDO
185c
186c------------------------------------
187 SELECT CASE (irupt)
188c------------------------------------
189c
190c---------------
191 CASE (1) ! Johnson-Cook
192 ! Tstar computation for Jhonson-Cook failure : T* = (T-T0)/(TM-T0)
193 IF (jthe > 0) THEN
194 t0 = pm(79, imat)
195 tm = pm(80, imat)
196 DO i=1,nel
197 tstar(i) = max(zero,(tempel(i)-t0)/(tm-t0))
198 ENDDO
199 ELSE
200 tstar(1:nel) = zero
201 ENDIF
202 CALL fail_johnson_ib(
203 . nel ,ngl ,ipt ,nparam ,fail%UPARAM,
204 . time ,tstar ,signxx ,signxy ,signxz ,
205 . dpla_ipt ,epsd ,off ,foff ,dfmax ,
206 . tdel ,iout ,istdo ,elbuf_str%GBUF%UELR ,npt)
207c---------------
208 CASE (10) ! Tension Strain failure model
209 IF (jthe > 0) THEN
210 t0 = pm(79, imat)
211 tm = pm(80, imat)
212 DO i=1,nel
213 tstar(i) = max(zero,(tempel(i)-t0)/(tm-t0))
214 ENDDO
215 ELSE
216 tstar(1:nel) = zero
217 ENDIF
218
219 CALL fail_tensstrain_ib(
220 . nel ,ngl ,nparam ,fail%UPARAM ,
221 . time ,epsd ,off ,dfmax,
222 . tdel ,iout ,istdo ,fail%IFUNC ,
223 . epsxx ,al ,tstar ,lbuf%DMGSCL ,
224 . snpc ,npf ,stf ,uvarf ,nvarf,
225 . tf ,ipt ,foff ,ismstr ,elbuf_str%GBUF%UELR ,npt)
226c---------------
227 CASE (11) ! Energy failure model
228 CALL fail_energy_ib(
229 . nel ,ngl ,nparam ,fail%UPARAM ,
230 . time ,epsd ,off ,dfmax,
231 . tdel ,iout ,istdo ,fail%IFUNC ,
232 . lbuf%DMGSCL,uvarf ,nvarf ,
233 . snpc ,npf ,stf ,
234 . tf ,ipt ,foff ,
235 . signxx ,signxy ,signxz ,
236 . depsxx ,depsxy ,depsxz ,elbuf_str%GBUF%UELR ,npt)
237
238c---------------
239 CASE (30) ! BIQUAD
240 CALL fail_biquad_ib (
241 . nel ,ngl ,nparam ,fail%UPARAM,
242 . time ,off ,dfmax ,tdel ,
243 . iout ,istdo ,nfunc ,fail%IFUNC,lbuf%DMGSCL,
244 . uvarf ,nvarf ,snpc ,npf ,
245 . stf ,tf ,ipt ,foff ,
246 . signxx ,signxy ,signxz ,dpla_ipt ,al,elbuf_str%GBUF%UELR ,npt)
247
248c---------------
249 CASE (34) ! cockroft failure model
250
251 CALL fail_cockroft_ib(
252 . nel ,ngl ,nparam ,fail%UPARAM ,
253 . time ,dpla_ipt ,off ,dfmax,
254 . tdel ,iout ,istdo ,epsxx ,
255 . ipt ,signxx ,signxy ,signxz ,
256 . nvarf ,uvarf ,foff ,elbuf_str%GBUF%UELR ,npt)
257
258C--------------
259 CASE (36) ! visual failure model
260 CALL fail_visual_ib(
261 . nel ,ngl ,nparam ,fail%UPARAM,
262 . time ,dfmax,
263 . iout ,istdo ,
264 . signxx ,signxy ,signxz ,
265 . epsxx ,epsxy ,epsxz ,
266 . nvarf ,
267 . uvarf ,ismstr ,dtime , ipt)
268c-------------
269 CASE (39) ! GENE1 failure model
270 CALL fail_gene1_ib(
271 . nel ,fail%NUPARAM ,fbuf%FLOC(ifl)%NVAR ,fail%NFUNC,
272 . fail%IFUNC ,npf ,tf ,
273 . time ,dtime ,fail%UPARAM ,ipt ,
274 . ngl ,elbuf_str%GBUF%DT,epsd ,fbuf%FLOC(ifl)%VAR,
275 . off ,epsxx ,
276 . epsxy ,epsxz ,
277 . signxx ,signxy ,
278 . signxz ,tempel ,
279 . fbuf%FLOC(ifl)%DAMMX , al, table,
280 . fail%NTABLE ,
281 . fail%TABLE , fbuf%FLOC(ifl)%LF_DAMMX, fail%NIPARAM ,fail%IPARAM,
282 . snpc ,stf ,ntable, foff,elbuf_str%GBUF%UELR ,npt, tdel)
283
284
285c-------------
286 CASE (42) ! Inievo failure model
287
288 CALL fail_inievo_ib(
289 . nel ,fail%NUPARAM ,fbuf%FLOC(ifl)%NVAR ,
290 . table ,fail%NTABLE ,fail%TABLE ,time ,fail%UPARAM ,
291 . ngl ,al ,dpla_ipt ,epsd , fbuf%FLOC(ifl)%VAR,
292 . signxx ,signxy ,signxz ,
293 . pla_ipt ,sigy_ipt ,foff ,fbuf%FLOC(ifl)%DAMMX ,
294 . tdel ,lbuf%DMGSCL ,elbuf_str%GBUF%UELR ,ipt ,npt,
295 . fbuf%FLOC(ifl)%DAMINI ,
296 . ntable ,off)
297
298c-------------
299 CASE (41) ! TAB2 failure model
300
301 CALL fail_tab2_ib(
302 . nel ,fail%NUPARAM ,fbuf%FLOC(ifl)%NVAR ,fail%NFUNC ,fail%IFUNC ,
303 . npf ,table ,tf ,time ,fail%UPARAM ,
304 . ngl ,al ,dpla_ipt ,epsd ,fbuf%FLOC(ifl)%VAR,
305 . signxx ,signxy ,signxz ,
306 . tempel ,off ,fbuf%FLOC(ifl)%DAMMX ,tdel ,lbuf%DMGSCL,
307 . ipt, npt, foff, fail%NTABLE ,fail%TABLE,
308 . elbuf_str%GBUF%UELR,
309 . snpc ,stf ,ntable)
310 DO i= 1,nel
311 IF (foff(i) == 0) count(i) = count(i) + 1
312 END DO
313
314c-------------------------------------
315 END SELECT
316
317C-------------------------------------
318 ENDDO ! IPT = 1,NPT : END LOOP OVER INTEGRATION POINTS
319c------------------
320 RETURN
#define my_real
Definition cppsort.cpp:32
subroutine fail_biquad_ib(nel, ngl, nuparam, uparam, time, off, dfmax, tdel, iout, istdo, nfunc, ifunc, damscl, uvar, nuvar, snpc, npf, stf, tf, ipt, foff, signxx, signxy, signxz, dpla, al, uelr, npg)
subroutine fail_cockroft_ib(nel, ngl, nuparam, uparam, time, dpla, off, dfmax, tdel, iout, istdo, epsxx, ipt, signxx, signxy, signxz, nvarf, uvar, foff, uelr, npg)
subroutine fail_energy_ib(nel, ngl, nuparam, uparam, time, epsd, off, dfmax, tdel, iout, istdo, ifunc, damscl, uvar, nvar, snpc, npf, stf, tf, ipt, foff, signxx, signxy, signxz, depsxx, depsxy, depsxz, uelr, npg)
subroutine fail_johnson_ib(nel, ngl, ipt, nuparam, uparam, time, tstar, signxx, signxy, signzx, dpla, epsd, off, foff, dfmax, tdel, iout, istdo, uelr, npg)
subroutine fail_tensstrain_ib(nel, ngl, nuparam, uparam, time, epsd, off, dfmax, tdel, iout, istdo, ifunc, epsxx, al, tstar, damscl, snpc, npf, stf, uvar, nvarf, tf, ipt, foff, ismstr, uelr, npg)
#define max(a, b)
Definition macros.h:21
subroutine bidon
Definition machine.F:41