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

Go to the source code of this file.

Functions/Subroutines

subroutine law104_upd (ifailg, nuparam, nuparf, uparam, uparf, nloc_dmg, imat, mlaw_tag, ipm, matparam)

Function/Subroutine Documentation

◆ law104_upd()

subroutine law104_upd ( integer ifailg,
integer nuparam,
integer nuparf,
intent(inout) uparam,
intent(in) uparf,
type (nlocal_str_) nloc_dmg,
integer imat,
type(mlaw_tag_), intent(inout) mlaw_tag,
integer, dimension(npropmi,*) ipm,
type(matparam_struct_), intent(inout) matparam )

Definition at line 32 of file law104_upd.F.

34C-----------------------------------------------
35C M o d u l e s
36C-----------------------------------------------
37 USE message_mod
39 USE elbuftag_mod
40 USE matparam_def_mod
41C-----------------------------------------------
42C I m p l i c i t T y p e s
43C-----------------------------------------------
44#include "implicit_f.inc"
45C-----------------------------------------------
46C C o m m o n B l o c k s
47C-----------------------------------------------
48#include "param_c.inc"
49C-----------------------------------------------
50C D u m m y A r g u m e n t s
51C-----------------------------------------------
52 INTEGER IFAILG,NUPARAM,NUPARF,IMAT,IPM(NPROPMI,*)
53 my_real, DIMENSION(NUPARF) , INTENT(IN) :: uparf
54 my_real, DIMENSION(NUPARAM), INTENT(INOUT) :: uparam
55 TYPE (NLOCAL_STR_) :: NLOC_DMG
56 TYPE(MLAW_TAG_),INTENT(INOUT) :: MLAW_TAG
57 TYPE(MATPARAM_STRUCT_) ,INTENT(INOUT) :: MATPARAM
58C-----------------------------------------------
59C L o c a l V a r i a b l e s
60C-----------------------------------------------
61 INTEGER ILOC,IGURSON
62 my_real
63 . q1,q2,q3,epn,as,kw,f0,fc,fr,rlen,hkhi
64C=======================================================================
65 igurson = 0
66 IF (ifailg == 1) THEN
67 iloc = matparam%NLOC
68 !IGURSON = 0 no damage (default)
69 IF (iloc == 0) THEN
70 igurson = 1 ! local damage
71 ELSEIF (iloc == 1) THEN
72 igurson = 2 ! non local forest(micromorphic)
73 ELSEIF (iloc == 2) THEN
74 igurson = 3 ! Non local (Peerling)
75 mlaw_tag%NUVAR = mlaw_tag%NUVAR + 1
76 ENDIF
77 ipm(8,imat) = mlaw_tag%NUVAR
78 ! Gurson yield criterion parameters
79 q1 = uparf(2)
80 q2 = uparf(3)
81 q3 = uparf(4)
82 ! Trigger plastic strain for damage nucleation
83 epn = uparf(5)
84 ! Nucleation rate
85 as = uparf(6)
86 ! Nahshon-Hutchinson shear parameter
87 kw = uparf(7)
88 ! Void volume fraction at fracture
89 fr = uparf(8)
90 ! Critical void volume fraction
91 fc = uparf(9)
92 ! Initial void volume fraction
93 f0 = uparf(10)
94 ! Non-local internal length
95 rlen = uparf(11)
96 ! Micromorphic penalty parameter
97 hkhi = uparf(12)
98c
99 ! Storage of the non-local internal length
100 IF (iloc>0) THEN
101 nloc_dmg%LEN(imat) = max(nloc_dmg%LEN(imat), rlen)
102 CALL get_lemax(nloc_dmg%LE_MAX(imat),nloc_dmg%LEN(imat))
103 mlaw_tag%G_PLANL = 1
104 mlaw_tag%L_PLANL = 1
105 mlaw_tag%G_EPSDNL = 1
106 mlaw_tag%L_EPSDNL = 1
107 ENDIF
108c
109 ! Tag for damage output
110 ! -> Number of output modes (stored in DMG(NEL,I), I>1)
111 matparam%NMOD = 5
112 ! Total number of damage outputs
113 ! -> DMG(NEL,1) = Global damage output
114 ! -> DMG(NEL,2:NMOD+1) = Damage modes output
115 mlaw_tag%G_DMG = 1 + matparam%NMOD
116 mlaw_tag%L_DMG = 1 + matparam%NMOD
117 ! -> Modes allocation and definition
118 ALLOCATE(matparam%MODE(matparam%NMOD))
119 matparam%MODE(1) = "Void growth volume fraction fg"
120 matparam%MODE(2) = "Nucleation volume fraction fn"
121 matparam%MODE(3) = "Shear growth volume fraction fsh"
122 matparam%MODE(4) = "Total void volume fraction ft"
123 matparam%MODE(5) = "Effective void volume fraction f*"
124c
125 ! Storage of damage parameters
126 uparam(30) = igurson
127 uparam(31) = q1
128 uparam(32) = q2
129 uparam(33) = q3
130 uparam(34) = epn
131 uparam(35) = as
132 uparam(36) = kw
133 uparam(37) = fr
134 uparam(38) = fc
135 uparam(39) = f0
136 uparam(40) = hkhi
137 ENDIF
138c-----------
139 RETURN
#define my_real
Definition cppsort.cpp:32
#define max(a, b)
Definition macros.h:21
subroutine get_lemax(le_max, nloc_length)