notation following paper
https://doi.org/10.1016/j.jmps.2016.10.012 DAMASK paper
This commit is contained in:
parent
c1cb6a72c1
commit
13630325c3
2
PRIVATE
2
PRIVATE
|
@ -1 +1 @@
|
||||||
Subproject commit 9685fa71bac2d56e6fd73d40160007f09fdae8db
|
Subproject commit 8fbc1dd8a26bf359b72bc076dac8ea3edef3be6d
|
|
@ -6,8 +6,8 @@ N_cl: [3]
|
||||||
|
|
||||||
g_crit: [0.5e+7]
|
g_crit: [0.5e+7]
|
||||||
s_crit: [0.006666]
|
s_crit: [0.006666]
|
||||||
dot_o: 1.e-3
|
dot_o_0: 1.e-3
|
||||||
q: 20
|
p: 20
|
||||||
|
|
||||||
l_c: 1.0
|
l_c: 1.0
|
||||||
mu: 0.001
|
mu: 0.001
|
||||||
|
|
|
@ -314,14 +314,14 @@ module phase
|
||||||
end subroutine plastic_dependentState
|
end subroutine plastic_dependentState
|
||||||
|
|
||||||
|
|
||||||
module subroutine damage_anisobrittle_LiAndItsTangent(Ld, dLd_dTstar, S, ph,en)
|
module subroutine damage_anisobrittle_LiAndItsTangent(L_i, dL_i_dM_i, M_i, ph,en)
|
||||||
integer, intent(in) :: ph, en
|
integer, intent(in) :: ph, en
|
||||||
real(pReal), intent(in), dimension(3,3) :: &
|
real(pReal), intent(in), dimension(3,3) :: &
|
||||||
S
|
M_i
|
||||||
real(pReal), intent(out), dimension(3,3) :: &
|
real(pReal), intent(out), dimension(3,3) :: &
|
||||||
Ld !< damage velocity gradient
|
L_i !< damage velocity gradient
|
||||||
real(pReal), intent(out), dimension(3,3,3,3) :: &
|
real(pReal), intent(out), dimension(3,3,3,3) :: &
|
||||||
dLd_dTstar !< derivative of Ld with respect to Tstar (4th-order tensor)
|
dL_i_dM_i !< derivative of L_i with respect to M_i
|
||||||
end subroutine damage_anisobrittle_LiAndItsTangent
|
end subroutine damage_anisobrittle_LiAndItsTangent
|
||||||
|
|
||||||
end interface
|
end interface
|
||||||
|
|
|
@ -49,10 +49,10 @@ submodule(phase) damage
|
||||||
end subroutine isobrittle_deltaState
|
end subroutine isobrittle_deltaState
|
||||||
|
|
||||||
|
|
||||||
module subroutine anisobrittle_dotState(S, ph, en)
|
module subroutine anisobrittle_dotState(M_i, ph, en)
|
||||||
integer, intent(in) :: ph,en
|
integer, intent(in) :: ph,en
|
||||||
real(pReal), intent(in), dimension(3,3) :: &
|
real(pReal), intent(in), dimension(3,3) :: &
|
||||||
S
|
M_i
|
||||||
end subroutine anisobrittle_dotState
|
end subroutine anisobrittle_dotState
|
||||||
|
|
||||||
|
|
||||||
|
@ -384,7 +384,7 @@ function phase_damage_collectDotState(ph,en) result(broken)
|
||||||
sourceType: select case (phase_damage(ph))
|
sourceType: select case (phase_damage(ph))
|
||||||
|
|
||||||
case (DAMAGE_ANISOBRITTLE_ID) sourceType
|
case (DAMAGE_ANISOBRITTLE_ID) sourceType
|
||||||
call anisobrittle_dotState(mechanical_S(ph,en), ph,en) ! correct stress?
|
call anisobrittle_dotState(mechanical_S(ph,en), ph,en) ! ToDo: use M_d
|
||||||
|
|
||||||
end select sourceType
|
end select sourceType
|
||||||
|
|
||||||
|
|
|
@ -8,8 +8,8 @@ submodule (phase:damage) anisobrittle
|
||||||
|
|
||||||
type :: tParameters !< container type for internal constitutive parameters
|
type :: tParameters !< container type for internal constitutive parameters
|
||||||
real(pReal) :: &
|
real(pReal) :: &
|
||||||
dot_o, & !< opening rate of cleavage planes
|
dot_o_0, & !< opening rate of cleavage planes
|
||||||
q !< damage rate sensitivity
|
p !< damage rate sensitivity
|
||||||
real(pReal), dimension(:), allocatable :: &
|
real(pReal), dimension(:), allocatable :: &
|
||||||
s_crit, & !< critical displacement
|
s_crit, & !< critical displacement
|
||||||
g_crit !< critical load
|
g_crit !< critical load
|
||||||
|
@ -71,8 +71,8 @@ module function anisobrittle_init() result(mySources)
|
||||||
N_cl = src%get_as1dInt('N_cl',defaultVal=emptyIntArray)
|
N_cl = src%get_as1dInt('N_cl',defaultVal=emptyIntArray)
|
||||||
prm%sum_N_cl = sum(abs(N_cl))
|
prm%sum_N_cl = sum(abs(N_cl))
|
||||||
|
|
||||||
prm%q = src%get_asFloat('q')
|
prm%p = src%get_asFloat('p')
|
||||||
prm%dot_o = src%get_asFloat('dot_o')
|
prm%dot_o_0 = src%get_asFloat('dot_o_0')
|
||||||
|
|
||||||
prm%s_crit = src%get_as1dFloat('s_crit', requiredSize=size(N_cl))
|
prm%s_crit = src%get_as1dFloat('s_crit', requiredSize=size(N_cl))
|
||||||
prm%g_crit = src%get_as1dFloat('g_crit', requiredSize=size(N_cl))
|
prm%g_crit = src%get_as1dFloat('g_crit', requiredSize=size(N_cl))
|
||||||
|
@ -90,8 +90,8 @@ module function anisobrittle_init() result(mySources)
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
! sanity checks
|
! sanity checks
|
||||||
if (prm%q <= 0.0_pReal) extmsg = trim(extmsg)//' q'
|
if (prm%p <= 0.0_pReal) extmsg = trim(extmsg)//' p'
|
||||||
if (prm%dot_o <= 0.0_pReal) extmsg = trim(extmsg)//' dot_o'
|
if (prm%dot_o_0 <= 0.0_pReal) extmsg = trim(extmsg)//' dot_o_0'
|
||||||
if (any(prm%g_crit < 0.0_pReal)) extmsg = trim(extmsg)//' g_crit'
|
if (any(prm%g_crit < 0.0_pReal)) extmsg = trim(extmsg)//' g_crit'
|
||||||
if (any(prm%s_crit < 0.0_pReal)) extmsg = trim(extmsg)//' s_crit'
|
if (any(prm%s_crit < 0.0_pReal)) extmsg = trim(extmsg)//' s_crit'
|
||||||
|
|
||||||
|
@ -113,12 +113,12 @@ end function anisobrittle_init
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief
|
!> @brief
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module subroutine anisobrittle_dotState(S, ph,en)
|
module subroutine anisobrittle_dotState(M_i, ph,en)
|
||||||
|
|
||||||
integer, intent(in) :: &
|
integer, intent(in) :: &
|
||||||
ph,en
|
ph,en
|
||||||
real(pReal), intent(in), dimension(3,3) :: &
|
real(pReal), intent(in), dimension(3,3) :: &
|
||||||
S
|
M_i
|
||||||
|
|
||||||
integer :: &
|
integer :: &
|
||||||
a, i
|
a, i
|
||||||
|
@ -129,13 +129,13 @@ module subroutine anisobrittle_dotState(S, ph,en)
|
||||||
associate(prm => param(ph))
|
associate(prm => param(ph))
|
||||||
damageState(ph)%dotState(1,en) = 0.0_pReal
|
damageState(ph)%dotState(1,en) = 0.0_pReal
|
||||||
do a = 1, prm%sum_N_cl
|
do a = 1, prm%sum_N_cl
|
||||||
traction_crit = prm%g_crit(a)*damage_phi(ph,en)**2
|
traction_crit = damage_phi(ph,en)**2 * prm%g_crit(a)
|
||||||
do i = 1,3
|
do i = 1,3
|
||||||
traction = math_tensordot(S,prm%cleavage_systems(1:3,1:3,i,a))
|
traction = math_tensordot(M_i,prm%cleavage_systems(1:3,1:3,i,a))
|
||||||
|
|
||||||
damageState(ph)%dotState(1,en) = damageState(ph)%dotState(1,en) &
|
damageState(ph)%dotState(1,en) = damageState(ph)%dotState(1,en) &
|
||||||
+ prm%dot_o / prm%s_crit(a) &
|
+ prm%dot_o_0 / prm%s_crit(a) &
|
||||||
* (max(0.0_pReal, abs(traction) - traction_crit)/traction_crit)**prm%q
|
* (max(0.0_pReal, abs(traction) - traction_crit)/traction_crit)**prm%p
|
||||||
end do
|
end do
|
||||||
end do
|
end do
|
||||||
end associate
|
end associate
|
||||||
|
@ -157,8 +157,8 @@ module subroutine anisobrittle_result(phase,group)
|
||||||
associate(prm => param(phase), stt => damageState(phase)%state)
|
associate(prm => param(phase), stt => damageState(phase)%state)
|
||||||
outputsLoop: do o = 1,size(prm%output)
|
outputsLoop: do o = 1,size(prm%output)
|
||||||
select case(trim(prm%output(o)))
|
select case(trim(prm%output(o)))
|
||||||
case ('f_phi')
|
case ('Psi_D')
|
||||||
call result_writeDataset(stt,group,trim(prm%output(o)),'driving force','-')
|
call result_writeDataset(stt,group,trim(prm%output(o)),'damage energy density','-')
|
||||||
end select
|
end select
|
||||||
end do outputsLoop
|
end do outputsLoop
|
||||||
end associate
|
end associate
|
||||||
|
@ -169,16 +169,16 @@ end subroutine anisobrittle_result
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief contains the constitutive equation for calculating the velocity gradient
|
!> @brief contains the constitutive equation for calculating the velocity gradient
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module subroutine damage_anisobrittle_LiAndItsTangent(Ld, dLd_dTstar, S, ph,en)
|
module subroutine damage_anisobrittle_LiAndItsTangent(L_i, dL_i_dM_i, M_i, ph,en)
|
||||||
|
|
||||||
integer, intent(in) :: &
|
integer, intent(in) :: &
|
||||||
ph,en
|
ph,en
|
||||||
real(pReal), intent(in), dimension(3,3) :: &
|
real(pReal), intent(in), dimension(3,3) :: &
|
||||||
S
|
M_i
|
||||||
real(pReal), intent(out), dimension(3,3) :: &
|
real(pReal), intent(out), dimension(3,3) :: &
|
||||||
Ld !< damage velocity gradient
|
L_i !< damage velocity gradient
|
||||||
real(pReal), intent(out), dimension(3,3,3,3) :: &
|
real(pReal), intent(out), dimension(3,3,3,3) :: &
|
||||||
dLd_dTstar !< derivative of Ld with respect to Tstar (4th-order tensor)
|
dL_i_dM_i !< derivative of L_i with respect to M_i
|
||||||
|
|
||||||
integer :: &
|
integer :: &
|
||||||
a, k, l, m, n, i
|
a, k, l, m, n, i
|
||||||
|
@ -187,20 +187,20 @@ module subroutine damage_anisobrittle_LiAndItsTangent(Ld, dLd_dTstar, S, ph,en)
|
||||||
udot, dudot_dt
|
udot, dudot_dt
|
||||||
|
|
||||||
|
|
||||||
Ld = 0.0_pReal
|
L_i = 0.0_pReal
|
||||||
dLd_dTstar = 0.0_pReal
|
dL_i_dM_i = 0.0_pReal
|
||||||
associate(prm => param(ph))
|
associate(prm => param(ph))
|
||||||
do a = 1,prm%sum_N_cl
|
do a = 1,prm%sum_N_cl
|
||||||
traction_crit = prm%g_crit(a)*damage_phi(ph,en)**2
|
traction_crit = damage_phi(ph,en)**2 * prm%g_crit(a)
|
||||||
|
|
||||||
do i = 1, 3
|
do i = 1, 3
|
||||||
traction = math_tensordot(S,prm%cleavage_systems(1:3,1:3,i,a))
|
traction = math_tensordot(M_i,prm%cleavage_systems(1:3,1:3,i,a))
|
||||||
if (abs(traction) > traction_crit + tol_math_check) then
|
if (abs(traction) > traction_crit + tol_math_check) then
|
||||||
udot = sign(1.0_pReal,traction)* prm%dot_o * ((abs(traction) - traction_crit)/traction_crit)**prm%q
|
udot = sign(1.0_pReal,traction)* prm%dot_o_0 * ((abs(traction) - traction_crit)/traction_crit)**prm%p
|
||||||
Ld = Ld + udot*prm%cleavage_systems(1:3,1:3,i,a)
|
L_i = L_i + udot*prm%cleavage_systems(1:3,1:3,i,a)
|
||||||
dudot_dt = sign(1.0_pReal,traction)*udot*prm%q / (abs(traction) - traction_crit)
|
dudot_dt = sign(1.0_pReal,traction)*udot*prm%p / (abs(traction) - traction_crit)
|
||||||
forall (k=1:3,l=1:3,m=1:3,n=1:3) &
|
forall (k=1:3,l=1:3,m=1:3,n=1:3) &
|
||||||
dLd_dTstar(k,l,m,n) = dLd_dTstar(k,l,m,n) &
|
dL_i_dM_i(k,l,m,n) = dL_i_dM_i(k,l,m,n) &
|
||||||
+ dudot_dt*prm%cleavage_systems(k,l,i,a) * prm%cleavage_systems(m,n,i,a)
|
+ dudot_dt*prm%cleavage_systems(k,l,i,a) * prm%cleavage_systems(m,n,i,a)
|
||||||
end if
|
end if
|
||||||
end do
|
end do
|
||||||
|
|
Loading…
Reference in New Issue