Merge branch '268-name-of-output-label-of-damage-model' into 'development'

notation following paper

Closes #268

See merge request damask/DAMASK!746
This commit is contained in:
Yi Hu 2023-03-14 08:09:22 +00:00
commit 19f5b33515
6 changed files with 55 additions and 76 deletions

@ -1 +1 @@
Subproject commit fc04b9ef621161e60a2f8b72bfa8c99e77687c71
Subproject commit 8fbc1dd8a26bf359b72bc076dac8ea3edef3be6d

View File

@ -6,8 +6,8 @@ N_cl: [3]
g_crit: [0.5e+7]
s_crit: [0.006666]
dot_o: 1.e-3
q: 20
dot_o_0: 1.e-3
p: 20
l_c: 1.0
mu: 0.001

View File

@ -314,14 +314,14 @@ module phase
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
real(pReal), intent(in), dimension(3,3) :: &
S
M_i
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) :: &
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 interface

View File

@ -49,10 +49,10 @@ submodule(phase) damage
end subroutine isobrittle_deltaState
module subroutine anisobrittle_dotState(S, ph, en)
module subroutine anisobrittle_dotState(M_i, ph, en)
integer, intent(in) :: ph,en
real(pReal), intent(in), dimension(3,3) :: &
S
M_i
end subroutine anisobrittle_dotState
@ -384,7 +384,7 @@ function phase_damage_collectDotState(ph,en) result(broken)
sourceType: select case (phase_damage(ph))
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

View File

@ -8,8 +8,8 @@ submodule (phase:damage) anisobrittle
type :: tParameters !< container type for internal constitutive parameters
real(pReal) :: &
dot_o, & !< opening rate of cleavage planes
q !< damage rate sensitivity
dot_o_0, & !< opening rate of cleavage planes
p !< damage rate sensitivity
real(pReal), dimension(:), allocatable :: &
s_crit, & !< critical displacement
g_crit !< critical load
@ -71,8 +71,8 @@ module function anisobrittle_init() result(mySources)
N_cl = src%get_as1dInt('N_cl',defaultVal=emptyIntArray)
prm%sum_N_cl = sum(abs(N_cl))
prm%q = src%get_asFloat('q')
prm%dot_o = src%get_asFloat('dot_o')
prm%p = src%get_asFloat('p')
prm%dot_o_0 = src%get_asFloat('dot_o_0')
prm%s_crit = src%get_as1dFloat('s_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
! sanity checks
if (prm%q <= 0.0_pReal) extmsg = trim(extmsg)//' q'
if (prm%dot_o <= 0.0_pReal) extmsg = trim(extmsg)//' dot_o'
if (prm%p <= 0.0_pReal) extmsg = trim(extmsg)//' p'
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%s_crit < 0.0_pReal)) extmsg = trim(extmsg)//' s_crit'
@ -113,33 +113,30 @@ end function anisobrittle_init
!--------------------------------------------------------------------------------------------------
!> @brief
!--------------------------------------------------------------------------------------------------
module subroutine anisobrittle_dotState(S, ph,en)
module subroutine anisobrittle_dotState(M_i, ph,en)
integer, intent(in) :: &
ph,en
real(pReal), intent(in), dimension(3,3) :: &
S
M_i
integer :: &
i
a, i
real(pReal) :: &
traction_d, traction_t, traction_n, traction_crit
traction, traction_crit
associate(prm => param(ph))
damageState(ph)%dotState(1,en) = 0.0_pReal
do i = 1, prm%sum_N_cl
traction_d = math_tensordot(S,prm%cleavage_systems(1:3,1:3,1,i))
traction_t = math_tensordot(S,prm%cleavage_systems(1:3,1:3,2,i))
traction_n = math_tensordot(S,prm%cleavage_systems(1:3,1:3,3,i))
do a = 1, prm%sum_N_cl
traction_crit = damage_phi(ph,en)**2 * prm%g_crit(a)
do i = 1,3
traction = math_tensordot(M_i,prm%cleavage_systems(1:3,1:3,i,a))
traction_crit = prm%g_crit(i)*damage_phi(ph,en)**2
damageState(ph)%dotState(1,en) = damageState(ph)%dotState(1,en) &
+ prm%dot_o / prm%s_crit(i) &
* ((max(0.0_pReal, abs(traction_d) - traction_crit)/traction_crit)**prm%q + &
(max(0.0_pReal, abs(traction_t) - traction_crit)/traction_crit)**prm%q + &
(max(0.0_pReal, abs(traction_n) - traction_crit)/traction_crit)**prm%q)
damageState(ph)%dotState(1,en) = damageState(ph)%dotState(1,en) &
+ prm%dot_o_0 / prm%s_crit(a) &
* (max(0.0_pReal, abs(traction) - traction_crit)/traction_crit)**prm%p
end do
end do
end associate
@ -160,8 +157,8 @@ module subroutine anisobrittle_result(phase,group)
associate(prm => param(phase), stt => damageState(phase)%state)
outputsLoop: do o = 1,size(prm%output)
select case(trim(prm%output(o)))
case ('f_phi')
call result_writeDataset(stt,group,trim(prm%output(o)),'driving force','-')
case ('Psi_D')
call result_writeDataset(stt,group,trim(prm%output(o)),'damage energy density','-')
end select
end do outputsLoop
end associate
@ -172,60 +169,42 @@ end subroutine anisobrittle_result
!--------------------------------------------------------------------------------------------------
!> @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) :: &
ph,en
real(pReal), intent(in), dimension(3,3) :: &
S
M_i
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) :: &
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 :: &
i, k, l, m, n
a, k, l, m, n, i
real(pReal) :: &
traction_d, traction_t, traction_n, traction_crit, &
udotd, dudotd_dt, udott, dudott_dt, udotn, dudotn_dt
traction, traction_crit, &
udot, dudot_dt
Ld = 0.0_pReal
dLd_dTstar = 0.0_pReal
L_i = 0.0_pReal
dL_i_dM_i = 0.0_pReal
associate(prm => param(ph))
do i = 1,prm%sum_N_cl
traction_crit = prm%g_crit(i)*damage_phi(ph,en)**2
do a = 1,prm%sum_N_cl
traction_crit = damage_phi(ph,en)**2 * prm%g_crit(a)
traction_d = math_tensordot(S,prm%cleavage_systems(1:3,1:3,1,i))
if (abs(traction_d) > traction_crit + tol_math_check) then
udotd = sign(1.0_pReal,traction_d)* prm%dot_o * ((abs(traction_d) - traction_crit)/traction_crit)**prm%q
Ld = Ld + udotd*prm%cleavage_systems(1:3,1:3,1,i)
dudotd_dt = sign(1.0_pReal,traction_d)*udotd*prm%q / (abs(traction_d) - traction_crit)
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) &
+ dudotd_dt*prm%cleavage_systems(k,l,1,i) * prm%cleavage_systems(m,n,1,i)
end if
traction_t = math_tensordot(S,prm%cleavage_systems(1:3,1:3,2,i))
if (abs(traction_t) > traction_crit + tol_math_check) then
udott = sign(1.0_pReal,traction_t)* prm%dot_o * ((abs(traction_t) - traction_crit)/traction_crit)**prm%q
Ld = Ld + udott*prm%cleavage_systems(1:3,1:3,2,i)
dudott_dt = sign(1.0_pReal,traction_t)*udott*prm%q / (abs(traction_t) - traction_crit)
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) &
+ dudott_dt*prm%cleavage_systems(k,l,2,i) * prm%cleavage_systems(m,n,2,i)
end if
traction_n = math_tensordot(S,prm%cleavage_systems(1:3,1:3,3,i))
if (abs(traction_n) > traction_crit + tol_math_check) then
udotn = sign(1.0_pReal,traction_n)* prm%dot_o * ((abs(traction_n) - traction_crit)/traction_crit)**prm%q
Ld = Ld + udotn*prm%cleavage_systems(1:3,1:3,3,i)
dudotn_dt = sign(1.0_pReal,traction_n)*udotn*prm%q / (abs(traction_n) - traction_crit)
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) &
+ dudotn_dt*prm%cleavage_systems(k,l,3,i) * prm%cleavage_systems(m,n,3,i)
end if
end do
do i = 1, 3
traction = math_tensordot(M_i,prm%cleavage_systems(1:3,1:3,i,a))
if (abs(traction) > traction_crit + tol_math_check) then
udot = sign(1.0_pReal,traction)* prm%dot_o_0 * ((abs(traction) - traction_crit)/traction_crit)**prm%p
L_i = L_i + udot*prm%cleavage_systems(1:3,1:3,i,a)
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) &
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)
end if
end do
end do
end associate
end subroutine damage_anisobrittle_LiAndItsTangent

View File

@ -143,8 +143,8 @@ module subroutine isobrittle_result(phase,group)
outputsLoop: do o = 1,size(prm%output)
select case(trim(prm%output(o)))
case ('f_phi')
call result_writeDataset(stt,group,trim(prm%output(o)),'driving force','-')
case ('r_W')
call result_writeDataset(stt,group,trim(prm%output(o)),'ratio between actual and critical strain energy density','-')
end select
end do outputsLoop