OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
m25crak.F File Reference
#include "implicit_f.inc"
#include "comlock.inc"
#include "mvsiz_p.inc"
#include "com08_c.inc"
#include "units_c.inc"
#include "param_c.inc"
#include "impl1_c.inc"
#include "lockon.inc"
#include "lockoff.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine m25crak (nel, off, dmg, l_dmg, dir, ilayer, thly, ngl, strp1, strp2, ply_id, igtyp, ipg, epst1, epst2, epsm1, epsm2, dmax)

Function/Subroutine Documentation

◆ m25crak()

subroutine m25crak ( integer nel,
off,
intent(inout) dmg,
integer l_dmg,
dir,
integer ilayer,
thly,
integer, dimension(mvsiz) ngl,
strp1,
strp2,
integer ply_id,
integer igtyp,
integer ipg,
intent(in) epst1,
intent(in) epst2,
intent(in) epsm1,
intent(in) epsm2,
intent(in) dmax )

Definition at line 28 of file m25crak.F.

31C-----------------------------------------------
32C I m p l i c i t T y p e s
33C-----------------------------------------------
34#include "implicit_f.inc"
35#include "comlock.inc"
36C-----------------------------------------------
37C G l o b a l P a r a m e t e r s
38C-----------------------------------------------
39#include "mvsiz_p.inc"
40C-----------------------------------------------
41C C o m m o n B l o c k s
42C-----------------------------------------------
43#include "com08_c.inc"
44#include "units_c.inc"
45#include "param_c.inc"
46#include "impl1_c.inc"
47C-----------------------------------------------
48C D u m m y A r g u m e n t s
49C-----------------------------------------------
50 INTEGER NGL(MVSIZ)
51 INTEGER ILAYER,PLY_ID,IGTYP,NEL,IPG,L_DMG
52 my_real ,INTENT(IN) :: epst1,epst2,epsm1,epsm2,dmax
53 my_real :: dir(nel,2), off(*),thly(*),strp1(*),strp2(*)
54 my_real, DIMENSION(NEL,L_DMG), INTENT(INOUT) :: dmg
55C-----------------------------------------------
56C L o c a l V a r i a b l e s
57C-----------------------------------------------
58 INTEGER :: I,J,NINDX, IDIR
59 INTEGER :: INDX(NEL)
60 my_real :: dam1,dam2
61C-----------------------------------------------
62 nindx=0
63 DO i=1,nel
64 IF (strp1(i)<epst1 .OR.dmg(i,2)>zero.OR.off(i)<one) cycle
65 nindx=nindx+1
66 indx(nindx)=i
67 END DO
68!
69C.....1.FIRST FAILURE DIRECTION 1
70 IF(nindx>0)THEN
71 idir=1
72 DO j=1,nindx
73 i=indx(j)
74 dam1=(strp1(i)-epst1)/(epsm1-epst1)
75 dam2= dam1*epsm1/strp1(i)
76 dmg(i,2)= min(dam2,dmax)
77 IF(dmg(i,2)==dmax.AND.imconv==1)THEN
78!
79#include "lockon.inc"
80 IF(igtyp == 17 .OR. igtyp == 51 .OR. igtyp == 52 ) THEN
81 WRITE(iout, '(A,I1,A,I10,A,I3,A,I3,A,1PE11.4)')
82 + ' FAILURE-',idir,', ELEMENT #',ngl(i),', INTEGRATION POINT #',ipg,
83 + ', (PLY #',ply_id,'), TIME=',tt
84 ELSE
85 WRITE(iout, '(A,I1,A,I10,A,I3,A,I3,A,1PE11.4)')
86 + ' FAILURE-',idir,', ELEMENT #',ngl(i),', LAYER #',ilayer,
87 + ', INTEGRATION POINT #',ipg,', TIME=',tt
88 ENDIF
89#include "lockoff.inc"
90!
91 ENDIF
92 END DO
93 ENDIF
94!
95C.....GATHER DIRECTION 2
96 nindx=0
97 DO i=1,nel
98 IF (strp2(i)<epst2 .OR.dmg(i,3)>zero.OR.off(i)<one) cycle
99 nindx=nindx+1
100 indx(nindx)=i
101 END DO
102!
103C.....1.FIRST FAILURE DIRECTION 2
104!
105 IF (nindx > 0) THEN
106 idir=2
107!
108 DO j=1,nindx
109 i=indx(j)
110 dam1=(strp2(i)-epst2)/(epsm2-epst2)
111 dam2= dam1*epsm2/strp2(i)
112 dmg(i,3)= min(dam2,dmax)
113 IF (dmg(i,3)==dmax.AND.imconv==1) THEN
114!
115#include "lockon.inc"
116 IF(igtyp == 17 .OR. igtyp == 51 .OR. igtyp == 52 ) THEN
117 WRITE(iout, '(A,I1,A,I10,A,I3,A,I3,A,1PE11.4)')
118 + ' FAILURE-',idir,', ELEMENT #',ngl(i),', INTEGRATION POINT #',ipg,
119 + ', (PLY #',ply_id,'), TIME=',tt
120 ELSE
121 WRITE(iout, '(A,I1,A,I10,A,I3,A,I3,A,1PE11.4)')
122 + ' FAILURE-',idir,', ELEMENT #',ngl(i),', LAYER #',ilayer,
123 + ', INTEGRATION POINT #',ipg,', TIME=',tt
124 ENDIF
125#include "lockoff.inc"
126!
127 ENDIF
128 END DO
129 ENDIF
130C-----------
131 RETURN
#define my_real
Definition cppsort.cpp:32
#define min(a, b)
Definition macros.h:20