further simplification
This commit is contained in:
parent
8627739963
commit
73f0fa3aba
|
@ -38,17 +38,13 @@ module constitutive
|
||||||
module subroutine plastic_none_init
|
module subroutine plastic_none_init
|
||||||
end subroutine plastic_none_init
|
end subroutine plastic_none_init
|
||||||
|
|
||||||
module subroutine plastic_isotropic_init(debug_constitutive)
|
module subroutine plastic_isotropic_init
|
||||||
class(tNode), pointer , intent(in) :: &
|
|
||||||
debug_constitutive !< pointer to constitutive debug options
|
|
||||||
end subroutine plastic_isotropic_init
|
end subroutine plastic_isotropic_init
|
||||||
|
|
||||||
module subroutine plastic_phenopowerlaw_init
|
module subroutine plastic_phenopowerlaw_init
|
||||||
end subroutine plastic_phenopowerlaw_init
|
end subroutine plastic_phenopowerlaw_init
|
||||||
|
|
||||||
module subroutine plastic_kinehardening_init(debug_constitutive)
|
module subroutine plastic_kinehardening_init
|
||||||
class(tNode), pointer , intent(in) :: &
|
|
||||||
debug_constitutive !< pointer to constitutive debug options
|
|
||||||
end subroutine plastic_kinehardening_init
|
end subroutine plastic_kinehardening_init
|
||||||
|
|
||||||
module subroutine plastic_dislotwin_init
|
module subroutine plastic_dislotwin_init
|
||||||
|
@ -57,14 +53,11 @@ module constitutive
|
||||||
module subroutine plastic_disloUCLA_init
|
module subroutine plastic_disloUCLA_init
|
||||||
end subroutine plastic_disloUCLA_init
|
end subroutine plastic_disloUCLA_init
|
||||||
|
|
||||||
module subroutine plastic_nonlocal_init(debug_constitutive)
|
module subroutine plastic_nonlocal_init
|
||||||
class(tNode), pointer , intent(in) :: &
|
|
||||||
debug_constitutive !< pointer to constitutive debug options
|
|
||||||
end subroutine plastic_nonlocal_init
|
end subroutine plastic_nonlocal_init
|
||||||
|
|
||||||
|
|
||||||
module subroutine plastic_isotropic_LpAndItsTangent(Lp,dLp_dMp,Mp,instance,of, &
|
module subroutine plastic_isotropic_LpAndItsTangent(Lp,dLp_dMp,Mp,instance,of)
|
||||||
debug_constitutive)
|
|
||||||
real(pReal), dimension(3,3), intent(out) :: &
|
real(pReal), dimension(3,3), intent(out) :: &
|
||||||
Lp !< plastic velocity gradient
|
Lp !< plastic velocity gradient
|
||||||
real(pReal), dimension(3,3,3,3), intent(out) :: &
|
real(pReal), dimension(3,3,3,3), intent(out) :: &
|
||||||
|
@ -75,8 +68,6 @@ module constitutive
|
||||||
integer, intent(in) :: &
|
integer, intent(in) :: &
|
||||||
instance, &
|
instance, &
|
||||||
of
|
of
|
||||||
class(tNode), pointer , intent(in) :: &
|
|
||||||
debug_constitutive !< pointer to constitutive debug options
|
|
||||||
end subroutine plastic_isotropic_LpAndItsTangent
|
end subroutine plastic_isotropic_LpAndItsTangent
|
||||||
|
|
||||||
pure module subroutine plastic_phenopowerlaw_LpAndItsTangent(Lp,dLp_dMp,Mp,instance,of)
|
pure module subroutine plastic_phenopowerlaw_LpAndItsTangent(Lp,dLp_dMp,Mp,instance,of)
|
||||||
|
@ -154,8 +145,7 @@ module constitutive
|
||||||
end subroutine plastic_nonlocal_LpAndItsTangent
|
end subroutine plastic_nonlocal_LpAndItsTangent
|
||||||
|
|
||||||
|
|
||||||
module subroutine plastic_isotropic_LiAndItsTangent(Li,dLi_dMi,Mi,instance,of, &
|
module subroutine plastic_isotropic_LiAndItsTangent(Li,dLi_dMi,Mi,instance,of)
|
||||||
debug_constitutive)
|
|
||||||
real(pReal), dimension(3,3), intent(out) :: &
|
real(pReal), dimension(3,3), intent(out) :: &
|
||||||
Li !< inleastic velocity gradient
|
Li !< inleastic velocity gradient
|
||||||
real(pReal), dimension(3,3,3,3), intent(out) :: &
|
real(pReal), dimension(3,3,3,3), intent(out) :: &
|
||||||
|
@ -166,8 +156,6 @@ module constitutive
|
||||||
integer, intent(in) :: &
|
integer, intent(in) :: &
|
||||||
instance, &
|
instance, &
|
||||||
of
|
of
|
||||||
class(tNode), pointer , intent(in) :: &
|
|
||||||
debug_constitutive !< pointer to constitutive debug options
|
|
||||||
end subroutine plastic_isotropic_LiAndItsTangent
|
end subroutine plastic_isotropic_LiAndItsTangent
|
||||||
|
|
||||||
|
|
||||||
|
@ -216,7 +204,7 @@ module constitutive
|
||||||
end subroutine plastic_disloUCLA_dotState
|
end subroutine plastic_disloUCLA_dotState
|
||||||
|
|
||||||
module subroutine plastic_nonlocal_dotState(Mp, F, Fp, Temperature,timestep, &
|
module subroutine plastic_nonlocal_dotState(Mp, F, Fp, Temperature,timestep, &
|
||||||
instance,of,ip,el,debug_constitutive)
|
instance,of,ip,el)
|
||||||
real(pReal), dimension(3,3), intent(in) ::&
|
real(pReal), dimension(3,3), intent(in) ::&
|
||||||
Mp !< MandelStress
|
Mp !< MandelStress
|
||||||
real(pReal), dimension(3,3,homogenization_maxNgrains,discretization_nIP,discretization_nElem), intent(in) :: &
|
real(pReal), dimension(3,3,homogenization_maxNgrains,discretization_nIP,discretization_nElem), intent(in) :: &
|
||||||
|
@ -230,8 +218,6 @@ module constitutive
|
||||||
of, &
|
of, &
|
||||||
ip, & !< current integration point
|
ip, & !< current integration point
|
||||||
el !< current element number
|
el !< current element number
|
||||||
class(tNode), pointer , intent(in) :: &
|
|
||||||
debug_constitutive !< pointer to constitutive debug options
|
|
||||||
end subroutine plastic_nonlocal_dotState
|
end subroutine plastic_nonlocal_dotState
|
||||||
|
|
||||||
|
|
||||||
|
@ -249,8 +235,7 @@ module constitutive
|
||||||
of
|
of
|
||||||
end subroutine plastic_disloUCLA_dependentState
|
end subroutine plastic_disloUCLA_dependentState
|
||||||
|
|
||||||
module subroutine plastic_nonlocal_dependentState(F, Fp, instance, of, ip, el, &
|
module subroutine plastic_nonlocal_dependentState(F, Fp, instance, of, ip, el)
|
||||||
debug_constitutive)
|
|
||||||
real(pReal), dimension(3,3), intent(in) :: &
|
real(pReal), dimension(3,3), intent(in) :: &
|
||||||
F, &
|
F, &
|
||||||
Fp
|
Fp
|
||||||
|
@ -259,22 +244,18 @@ module constitutive
|
||||||
of, &
|
of, &
|
||||||
ip, &
|
ip, &
|
||||||
el
|
el
|
||||||
class(tNode), pointer , intent(in) :: &
|
|
||||||
debug_constitutive !< pointer to constitutive debug options
|
|
||||||
end subroutine plastic_nonlocal_dependentState
|
end subroutine plastic_nonlocal_dependentState
|
||||||
|
|
||||||
|
|
||||||
module subroutine plastic_kinehardening_deltaState(Mp,instance,of,debug_constitutive)
|
module subroutine plastic_kinehardening_deltaState(Mp,instance,of)
|
||||||
real(pReal), dimension(3,3), intent(in) :: &
|
real(pReal), dimension(3,3), intent(in) :: &
|
||||||
Mp !< Mandel stress
|
Mp !< Mandel stress
|
||||||
integer, intent(in) :: &
|
integer, intent(in) :: &
|
||||||
instance, &
|
instance, &
|
||||||
of
|
of
|
||||||
class(tNode), pointer , intent(in) :: &
|
|
||||||
debug_constitutive !< pointer to constitutive debug options
|
|
||||||
end subroutine plastic_kinehardening_deltaState
|
end subroutine plastic_kinehardening_deltaState
|
||||||
|
|
||||||
module subroutine plastic_nonlocal_deltaState(Mp,instance,of,ip,el,debug_constitutive)
|
module subroutine plastic_nonlocal_deltaState(Mp,instance,of,ip,el)
|
||||||
real(pReal), dimension(3,3), intent(in) :: &
|
real(pReal), dimension(3,3), intent(in) :: &
|
||||||
Mp
|
Mp
|
||||||
integer, intent(in) :: &
|
integer, intent(in) :: &
|
||||||
|
@ -282,8 +263,6 @@ module constitutive
|
||||||
of, &
|
of, &
|
||||||
ip, &
|
ip, &
|
||||||
el
|
el
|
||||||
class(tNode), pointer , intent(in) :: &
|
|
||||||
debug_constitutive !< pointer to constitutive debug options
|
|
||||||
end subroutine plastic_nonlocal_deltaState
|
end subroutine plastic_nonlocal_deltaState
|
||||||
|
|
||||||
|
|
||||||
|
@ -362,20 +341,16 @@ subroutine constitutive_init
|
||||||
integer :: &
|
integer :: &
|
||||||
ph, & !< counter in phase loop
|
ph, & !< counter in phase loop
|
||||||
s !< counter in source loop
|
s !< counter in source loop
|
||||||
class(tNode), pointer :: &
|
|
||||||
debug_constitutive
|
|
||||||
|
|
||||||
debug_constitutive => debug_root%get('constitutuve',defaultVal=emptyList)
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! initialized plasticity
|
! initialized plasticity
|
||||||
if (any(phase_plasticity == PLASTICITY_NONE_ID)) call plastic_none_init
|
if (any(phase_plasticity == PLASTICITY_NONE_ID)) call plastic_none_init
|
||||||
if (any(phase_plasticity == PLASTICITY_ISOTROPIC_ID)) call plastic_isotropic_init(debug_constitutive)
|
if (any(phase_plasticity == PLASTICITY_ISOTROPIC_ID)) call plastic_isotropic_init
|
||||||
if (any(phase_plasticity == PLASTICITY_PHENOPOWERLAW_ID)) call plastic_phenopowerlaw_init
|
if (any(phase_plasticity == PLASTICITY_PHENOPOWERLAW_ID)) call plastic_phenopowerlaw_init
|
||||||
if (any(phase_plasticity == PLASTICITY_KINEHARDENING_ID)) call plastic_kinehardening_init(debug_constitutive)
|
if (any(phase_plasticity == PLASTICITY_KINEHARDENING_ID)) call plastic_kinehardening_init
|
||||||
if (any(phase_plasticity == PLASTICITY_DISLOTWIN_ID)) call plastic_dislotwin_init
|
if (any(phase_plasticity == PLASTICITY_DISLOTWIN_ID)) call plastic_dislotwin_init
|
||||||
if (any(phase_plasticity == PLASTICITY_DISLOUCLA_ID)) call plastic_disloucla_init
|
if (any(phase_plasticity == PLASTICITY_DISLOUCLA_ID)) call plastic_disloucla_init
|
||||||
if (any(phase_plasticity == PLASTICITY_NONLOCAL_ID)) then
|
if (any(phase_plasticity == PLASTICITY_NONLOCAL_ID)) then
|
||||||
call plastic_nonlocal_init(debug_constitutive)
|
call plastic_nonlocal_init
|
||||||
else
|
else
|
||||||
call geometry_plastic_nonlocal_disable
|
call geometry_plastic_nonlocal_disable
|
||||||
endif
|
endif
|
||||||
|
@ -454,10 +429,7 @@ subroutine constitutive_dependentState(F, Fp, ipc, ip, el)
|
||||||
ho, & !< homogenization
|
ho, & !< homogenization
|
||||||
tme, & !< thermal member position
|
tme, & !< thermal member position
|
||||||
instance, of
|
instance, of
|
||||||
class(tNode), pointer :: &
|
|
||||||
debug_constitutive
|
|
||||||
|
|
||||||
debug_constitutive => debug_root%get('constitutive',defaultVal=emptyList)
|
|
||||||
ho = material_homogenizationAt(el)
|
ho = material_homogenizationAt(el)
|
||||||
tme = thermalMapping(ho)%p(ip,el)
|
tme = thermalMapping(ho)%p(ip,el)
|
||||||
of = material_phasememberAt(ipc,ip,el)
|
of = material_phasememberAt(ipc,ip,el)
|
||||||
|
@ -469,7 +441,7 @@ subroutine constitutive_dependentState(F, Fp, ipc, ip, el)
|
||||||
case (PLASTICITY_DISLOUCLA_ID) plasticityType
|
case (PLASTICITY_DISLOUCLA_ID) plasticityType
|
||||||
call plastic_disloUCLA_dependentState(instance,of)
|
call plastic_disloUCLA_dependentState(instance,of)
|
||||||
case (PLASTICITY_NONLOCAL_ID) plasticityType
|
case (PLASTICITY_NONLOCAL_ID) plasticityType
|
||||||
call plastic_nonlocal_dependentState (F,Fp,instance,of,ip,el,debug_constitutive)
|
call plastic_nonlocal_dependentState (F,Fp,instance,of,ip,el)
|
||||||
end select plasticityType
|
end select plasticityType
|
||||||
|
|
||||||
end subroutine constitutive_dependentState
|
end subroutine constitutive_dependentState
|
||||||
|
@ -503,10 +475,7 @@ subroutine constitutive_LpAndItsTangents(Lp, dLp_dS, dLp_dFi, &
|
||||||
tme !< thermal member position
|
tme !< thermal member position
|
||||||
integer :: &
|
integer :: &
|
||||||
i, j, instance, of
|
i, j, instance, of
|
||||||
class(tNode), pointer :: &
|
|
||||||
debug_constitutive
|
|
||||||
|
|
||||||
debug_constitutive => debug_root%get('constitutive',defaultVal=emptyList)
|
|
||||||
|
|
||||||
ho = material_homogenizationAt(el)
|
ho = material_homogenizationAt(el)
|
||||||
tme = thermalMapping(ho)%p(ip,el)
|
tme = thermalMapping(ho)%p(ip,el)
|
||||||
|
@ -522,7 +491,7 @@ subroutine constitutive_LpAndItsTangents(Lp, dLp_dS, dLp_dFi, &
|
||||||
dLp_dMp = 0.0_pReal
|
dLp_dMp = 0.0_pReal
|
||||||
|
|
||||||
case (PLASTICITY_ISOTROPIC_ID) plasticityType
|
case (PLASTICITY_ISOTROPIC_ID) plasticityType
|
||||||
call plastic_isotropic_LpAndItsTangent (Lp,dLp_dMp,Mp,instance,of,debug_constitutive)
|
call plastic_isotropic_LpAndItsTangent (Lp,dLp_dMp,Mp,instance,of)
|
||||||
|
|
||||||
case (PLASTICITY_PHENOPOWERLAW_ID) plasticityType
|
case (PLASTICITY_PHENOPOWERLAW_ID) plasticityType
|
||||||
call plastic_phenopowerlaw_LpAndItsTangent(Lp,dLp_dMp,Mp,instance,of)
|
call plastic_phenopowerlaw_LpAndItsTangent(Lp,dLp_dMp,Mp,instance,of)
|
||||||
|
@ -582,10 +551,6 @@ subroutine constitutive_LiAndItsTangents(Li, dLi_dS, dLi_dFi, &
|
||||||
integer :: &
|
integer :: &
|
||||||
k, i, j, &
|
k, i, j, &
|
||||||
instance, of
|
instance, of
|
||||||
class(tNode), pointer :: &
|
|
||||||
debug_constitutive
|
|
||||||
|
|
||||||
debug_constitutive => debug_root%get('constitutive',defaultVal=emptyList)
|
|
||||||
|
|
||||||
Li = 0.0_pReal
|
Li = 0.0_pReal
|
||||||
dLi_dS = 0.0_pReal
|
dLi_dS = 0.0_pReal
|
||||||
|
@ -595,7 +560,7 @@ subroutine constitutive_LiAndItsTangents(Li, dLi_dS, dLi_dFi, &
|
||||||
case (PLASTICITY_isotropic_ID) plasticityType
|
case (PLASTICITY_isotropic_ID) plasticityType
|
||||||
of = material_phasememberAt(ipc,ip,el)
|
of = material_phasememberAt(ipc,ip,el)
|
||||||
instance = phase_plasticityInstance(material_phaseAt(ipc,el))
|
instance = phase_plasticityInstance(material_phaseAt(ipc,el))
|
||||||
call plastic_isotropic_LiAndItsTangent(my_Li, my_dLi_dS, S ,instance,of,debug_constitutive)
|
call plastic_isotropic_LiAndItsTangent(my_Li, my_dLi_dS, S ,instance,of)
|
||||||
case default plasticityType
|
case default plasticityType
|
||||||
my_Li = 0.0_pReal
|
my_Li = 0.0_pReal
|
||||||
my_dLi_dS = 0.0_pReal
|
my_dLi_dS = 0.0_pReal
|
||||||
|
@ -768,12 +733,8 @@ function constitutive_collectDotState(S, FArray, Fi, FpArray, subdt, ipc, ip, el
|
||||||
tme, & !< thermal member position
|
tme, & !< thermal member position
|
||||||
i, & !< counter in source loop
|
i, & !< counter in source loop
|
||||||
instance
|
instance
|
||||||
class(tNode), pointer :: &
|
|
||||||
debug_constitutive
|
|
||||||
logical :: broken
|
logical :: broken
|
||||||
|
|
||||||
debug_constitutive => debug_root%get('constitutive',defaultVal=emptyList)
|
|
||||||
|
|
||||||
ho = material_homogenizationAt(el)
|
ho = material_homogenizationAt(el)
|
||||||
tme = thermalMapping(ho)%p(ip,el)
|
tme = thermalMapping(ho)%p(ip,el)
|
||||||
instance = phase_plasticityInstance(phase)
|
instance = phase_plasticityInstance(phase)
|
||||||
|
@ -799,7 +760,7 @@ function constitutive_collectDotState(S, FArray, Fi, FpArray, subdt, ipc, ip, el
|
||||||
|
|
||||||
case (PLASTICITY_NONLOCAL_ID) plasticityType
|
case (PLASTICITY_NONLOCAL_ID) plasticityType
|
||||||
call plastic_nonlocal_dotState (Mp,FArray,FpArray,temperature(ho)%p(tme),subdt, &
|
call plastic_nonlocal_dotState (Mp,FArray,FpArray,temperature(ho)%p(tme),subdt, &
|
||||||
instance,of,ip,el,debug_constitutive)
|
instance,of,ip,el)
|
||||||
end select plasticityType
|
end select plasticityType
|
||||||
broken = any(IEEE_is_NaN(plasticState(phase)%dotState(:,of)))
|
broken = any(IEEE_is_NaN(plasticState(phase)%dotState(:,of)))
|
||||||
|
|
||||||
|
@ -851,24 +812,20 @@ function constitutive_deltaState(S, Fe, Fi, ipc, ip, el, phase, of) result(broke
|
||||||
instance, &
|
instance, &
|
||||||
myOffset, &
|
myOffset, &
|
||||||
mySize
|
mySize
|
||||||
class(tNode), pointer :: &
|
|
||||||
debug_constitutive
|
|
||||||
logical :: &
|
logical :: &
|
||||||
broken
|
broken
|
||||||
|
|
||||||
debug_constitutive => debug_root%get('constitutive',defaultVal=emptyList)
|
|
||||||
|
|
||||||
Mp = matmul(matmul(transpose(Fi),Fi),S)
|
Mp = matmul(matmul(transpose(Fi),Fi),S)
|
||||||
instance = phase_plasticityInstance(phase)
|
instance = phase_plasticityInstance(phase)
|
||||||
|
|
||||||
plasticityType: select case (phase_plasticity(phase))
|
plasticityType: select case (phase_plasticity(phase))
|
||||||
|
|
||||||
case (PLASTICITY_KINEHARDENING_ID) plasticityType
|
case (PLASTICITY_KINEHARDENING_ID) plasticityType
|
||||||
call plastic_kinehardening_deltaState(Mp,instance,of,debug_constitutive)
|
call plastic_kinehardening_deltaState(Mp,instance,of)
|
||||||
broken = any(IEEE_is_NaN(plasticState(phase)%deltaState(:,of)))
|
broken = any(IEEE_is_NaN(plasticState(phase)%deltaState(:,of)))
|
||||||
|
|
||||||
case (PLASTICITY_NONLOCAL_ID) plasticityType
|
case (PLASTICITY_NONLOCAL_ID) plasticityType
|
||||||
call plastic_nonlocal_deltaState(Mp,instance,of,ip,el,debug_constitutive)
|
call plastic_nonlocal_deltaState(Mp,instance,of,ip,el)
|
||||||
broken = any(IEEE_is_NaN(plasticState(phase)%deltaState(:,of)))
|
broken = any(IEEE_is_NaN(plasticState(phase)%deltaState(:,of)))
|
||||||
|
|
||||||
case default
|
case default
|
||||||
|
|
|
@ -36,6 +36,20 @@ submodule(constitutive) plastic_isotropic
|
||||||
gamma
|
gamma
|
||||||
end type tIsotropicState
|
end type tIsotropicState
|
||||||
|
|
||||||
|
#ifdef DEBUG
|
||||||
|
type :: tDebugOptions
|
||||||
|
logical :: &
|
||||||
|
extensive, &
|
||||||
|
selective
|
||||||
|
integer :: &
|
||||||
|
element, &
|
||||||
|
ip, &
|
||||||
|
grain
|
||||||
|
end type tDebugOptions
|
||||||
|
|
||||||
|
type(tDebugOptions) :: debug
|
||||||
|
|
||||||
|
#endif
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! containers for parameters and state
|
! containers for parameters and state
|
||||||
type(tParameters), allocatable, dimension(:) :: param
|
type(tParameters), allocatable, dimension(:) :: param
|
||||||
|
@ -49,32 +63,36 @@ contains
|
||||||
!> @brief Perform module initialization.
|
!> @brief Perform module initialization.
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module subroutine plastic_isotropic_init(debug_constitutive)
|
module subroutine plastic_isotropic_init
|
||||||
|
|
||||||
class(tNode), pointer, intent(in) :: &
|
|
||||||
debug_constitutive !< pointer to constitutive debug options
|
|
||||||
|
|
||||||
integer :: &
|
integer :: &
|
||||||
Ninstance, &
|
Ninstance, &
|
||||||
p, &
|
p, &
|
||||||
NipcMyPhase, &
|
NipcMyPhase, &
|
||||||
sizeState, sizeDotState, &
|
sizeState, sizeDotState
|
||||||
debug_g, &
|
|
||||||
debug_e, &
|
|
||||||
debug_i
|
|
||||||
real(pReal) :: &
|
real(pReal) :: &
|
||||||
xi_0 !< initial critical stress
|
xi_0 !< initial critical stress
|
||||||
character(len=pStringLen) :: &
|
character(len=pStringLen) :: &
|
||||||
extmsg = ''
|
extmsg = ''
|
||||||
|
class(tNode), pointer :: &
|
||||||
|
debug_constitutive
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- plastic_'//PLASTICITY_ISOTROPIC_LABEL//' init -+>>>'; flush(6)
|
write(6,'(/,a)') ' <<<+- plastic_'//PLASTICITY_ISOTROPIC_LABEL//' init -+>>>'
|
||||||
|
|
||||||
write(6,'(/,a)') ' Maiti and Eisenlohr, Scripta Materialia 145:37–40, 2018'
|
write(6,'(/,a)') ' Maiti and Eisenlohr, Scripta Materialia 145:37–40, 2018'
|
||||||
write(6,'(a)') ' https://doi.org/10.1016/j.scriptamat.2017.09.047'
|
write(6,'(a)') ' https://doi.org/10.1016/j.scriptamat.2017.09.047'
|
||||||
|
|
||||||
Ninstance = count(phase_plasticity == PLASTICITY_ISOTROPIC_ID)
|
Ninstance = count(phase_plasticity == PLASTICITY_ISOTROPIC_ID)
|
||||||
if (debug_constitutive%contains('basic')) &
|
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance; flush(6)
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
|
||||||
|
#ifdef DEBUG
|
||||||
|
debug_constitutive => debug_root%get('constitutuve', defaultVal=emptyList)
|
||||||
|
debug%extensive = debug_constitutive%contains('extensive')
|
||||||
|
debug%selective = debug_constitutive%contains('selective')
|
||||||
|
debug%element = debug_root%get_asInt('element',defaultVal = 1)
|
||||||
|
debug%ip = debug_root%get_asInt('integrationpoint',defaultVal = 1)
|
||||||
|
debug%grain = debug_root%get_asInt('grain',defaultVal = 1)
|
||||||
|
#endif
|
||||||
|
|
||||||
allocate(param(Ninstance))
|
allocate(param(Ninstance))
|
||||||
allocate(state(Ninstance))
|
allocate(state(Ninstance))
|
||||||
|
@ -90,12 +108,8 @@ module subroutine plastic_isotropic_init(debug_constitutive)
|
||||||
prm%output = config%getStrings('(output)',defaultVal=emptyStringArray)
|
prm%output = config%getStrings('(output)',defaultVal=emptyStringArray)
|
||||||
|
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
debug_g = debug_root%get_asInt('grain',defaultVal=1)
|
if (p==material_phaseAt(debug%grain,debug%element)) &
|
||||||
debug_e = debug_root%get_asInt('element',defaultVal=1)
|
prm%of_debug = material_phasememberAt(debug%grain,debug%ip,debug%element)
|
||||||
debug_i = debug_root%get_asInt('integrationpoint',defaultVal=1)
|
|
||||||
|
|
||||||
if (p==material_phaseAt(debug_g,debug_e)) &
|
|
||||||
prm%of_debug = material_phasememberAt(debug_g,debug_i,debug_e)
|
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
xi_0 = config%getFloat('tau0')
|
xi_0 = config%getFloat('tau0')
|
||||||
|
@ -160,7 +174,7 @@ end subroutine plastic_isotropic_init
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief Calculate plastic velocity gradient and its tangent.
|
!> @brief Calculate plastic velocity gradient and its tangent.
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module subroutine plastic_isotropic_LpAndItsTangent(Lp,dLp_dMp,Mp,instance,of,debug_constitutive)
|
module subroutine plastic_isotropic_LpAndItsTangent(Lp,dLp_dMp,Mp,instance,of)
|
||||||
|
|
||||||
real(pReal), dimension(3,3), intent(out) :: &
|
real(pReal), dimension(3,3), intent(out) :: &
|
||||||
Lp !< plastic velocity gradient
|
Lp !< plastic velocity gradient
|
||||||
|
@ -172,8 +186,6 @@ module subroutine plastic_isotropic_LpAndItsTangent(Lp,dLp_dMp,Mp,instance,of,de
|
||||||
integer, intent(in) :: &
|
integer, intent(in) :: &
|
||||||
instance, &
|
instance, &
|
||||||
of
|
of
|
||||||
class(tNode), pointer, intent(in) :: &
|
|
||||||
debug_constitutive !< pointer to constitutive debug options
|
|
||||||
|
|
||||||
real(pReal), dimension(3,3) :: &
|
real(pReal), dimension(3,3) :: &
|
||||||
Mp_dev !< deviatoric part of the Mandel stress
|
Mp_dev !< deviatoric part of the Mandel stress
|
||||||
|
@ -195,8 +207,8 @@ module subroutine plastic_isotropic_LpAndItsTangent(Lp,dLp_dMp,Mp,instance,of,de
|
||||||
|
|
||||||
Lp = dot_gamma/prm%M * Mp_dev/norm_Mp_dev
|
Lp = dot_gamma/prm%M * Mp_dev/norm_Mp_dev
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debug_constitutive%contains('extensive') &
|
if (debug%extensive &
|
||||||
.and. (of == prm%of_debug .or. .not. debug_constitutive%contains('selective'))) then
|
.and. (of == prm%of_debug .or. .not. debug%selective)) then
|
||||||
write(6,'(/,a,/,3(12x,3(f12.4,1x)/))') '<< CONST isotropic >> Tstar (dev) / MPa', &
|
write(6,'(/,a,/,3(12x,3(f12.4,1x)/))') '<< CONST isotropic >> Tstar (dev) / MPa', &
|
||||||
transpose(Mp_dev)*1.0e-6_pReal
|
transpose(Mp_dev)*1.0e-6_pReal
|
||||||
write(6,'(/,a,/,f12.5)') '<< CONST isotropic >> norm Tstar / MPa', norm_Mp_dev*1.0e-6_pReal
|
write(6,'(/,a,/,f12.5)') '<< CONST isotropic >> norm Tstar / MPa', norm_Mp_dev*1.0e-6_pReal
|
||||||
|
@ -223,7 +235,7 @@ end subroutine plastic_isotropic_LpAndItsTangent
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief Calculate inelastic velocity gradient and its tangent.
|
!> @brief Calculate inelastic velocity gradient and its tangent.
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module subroutine plastic_isotropic_LiAndItsTangent(Li,dLi_dMi,Mi,instance,of,debug_constitutive)
|
module subroutine plastic_isotropic_LiAndItsTangent(Li,dLi_dMi,Mi,instance,of)
|
||||||
|
|
||||||
real(pReal), dimension(3,3), intent(out) :: &
|
real(pReal), dimension(3,3), intent(out) :: &
|
||||||
Li !< inleastic velocity gradient
|
Li !< inleastic velocity gradient
|
||||||
|
@ -235,8 +247,6 @@ module subroutine plastic_isotropic_LiAndItsTangent(Li,dLi_dMi,Mi,instance,of,de
|
||||||
integer, intent(in) :: &
|
integer, intent(in) :: &
|
||||||
instance, &
|
instance, &
|
||||||
of
|
of
|
||||||
class(tNode), pointer, intent(in) :: &
|
|
||||||
debug_constitutive !< pointer to constitutive debug options
|
|
||||||
|
|
||||||
real(pReal) :: &
|
real(pReal) :: &
|
||||||
tr !< trace of spherical part of Mandel stress (= 3 x pressure)
|
tr !< trace of spherical part of Mandel stress (= 3 x pressure)
|
||||||
|
@ -253,8 +263,8 @@ module subroutine plastic_isotropic_LiAndItsTangent(Li,dLi_dMi,Mi,instance,of,de
|
||||||
* tr * abs(tr)**(prm%n-1.0_pReal)
|
* tr * abs(tr)**(prm%n-1.0_pReal)
|
||||||
|
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debug_constitutive%contains('extensive') &
|
if (debug%extensive &
|
||||||
.and. (of == prm%of_debug .or. .not. debug_constitutive%contains('selective'))) then
|
.and. (of == prm%of_debug .or. .not. debug%selective)) then
|
||||||
write(6,'(/,a,/,f12.5)') '<< CONST isotropic >> pressure / MPa', tr/3.0_pReal*1.0e-6_pReal
|
write(6,'(/,a,/,f12.5)') '<< CONST isotropic >> pressure / MPa', tr/3.0_pReal*1.0e-6_pReal
|
||||||
write(6,'(/,a,/,f12.5)') '<< CONST isotropic >> gdot', prm%dot_gamma_0 * (3.0_pReal*prm%M*stt%xi(of))**(-prm%n) &
|
write(6,'(/,a,/,f12.5)') '<< CONST isotropic >> gdot', prm%dot_gamma_0 * (3.0_pReal*prm%M*stt%xi(of))**(-prm%n) &
|
||||||
* tr * abs(tr)**(prm%n-1.0_pReal)
|
* tr * abs(tr)**(prm%n-1.0_pReal)
|
||||||
|
|
|
@ -43,6 +43,21 @@ submodule(constitutive) plastic_kinehardening
|
||||||
accshear !< accumulated (absolute) shear
|
accshear !< accumulated (absolute) shear
|
||||||
end type tKinehardeningState
|
end type tKinehardeningState
|
||||||
|
|
||||||
|
#ifdef DEBUG
|
||||||
|
type :: tDebugOptions
|
||||||
|
logical :: &
|
||||||
|
extensive, &
|
||||||
|
selective
|
||||||
|
integer :: &
|
||||||
|
element, &
|
||||||
|
ip, &
|
||||||
|
grain
|
||||||
|
end type tDebugOptions
|
||||||
|
|
||||||
|
type(tDebugOptions) :: debug
|
||||||
|
|
||||||
|
#endif
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! containers for parameters and state
|
! containers for parameters and state
|
||||||
type(tParameters), allocatable, dimension(:) :: param
|
type(tParameters), allocatable, dimension(:) :: param
|
||||||
|
@ -58,18 +73,14 @@ contains
|
||||||
!> @brief Perform module initialization.
|
!> @brief Perform module initialization.
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module subroutine plastic_kinehardening_init(debug_constitutive)
|
module subroutine plastic_kinehardening_init
|
||||||
|
|
||||||
class(tNode), pointer, intent(in) :: &
|
|
||||||
debug_constitutive !< pointer to constitutive debug options
|
|
||||||
|
|
||||||
integer :: &
|
integer :: &
|
||||||
Ninstance, &
|
Ninstance, &
|
||||||
p, o, &
|
p, o, &
|
||||||
NipcMyPhase, &
|
NipcMyPhase, &
|
||||||
sizeState, sizeDeltaState, sizeDotState, &
|
sizeState, sizeDeltaState, sizeDotState, &
|
||||||
startIndex, endIndex, &
|
startIndex, endIndex
|
||||||
debug_e, debug_i, debug_g
|
|
||||||
integer, dimension(:), allocatable :: &
|
integer, dimension(:), allocatable :: &
|
||||||
N_sl
|
N_sl
|
||||||
real(pReal), dimension(:), allocatable :: &
|
real(pReal), dimension(:), allocatable :: &
|
||||||
|
@ -77,12 +88,22 @@ module subroutine plastic_kinehardening_init(debug_constitutive)
|
||||||
a !< non-Schmid coefficients
|
a !< non-Schmid coefficients
|
||||||
character(len=pStringLen) :: &
|
character(len=pStringLen) :: &
|
||||||
extmsg = ''
|
extmsg = ''
|
||||||
|
class(tNode), pointer :: &
|
||||||
|
debug_constitutive
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- plastic_'//PLASTICITY_KINEHARDENING_LABEL//' init -+>>>'; flush(6)
|
write(6,'(/,a)') ' <<<+- plastic_'//PLASTICITY_KINEHARDENING_LABEL//' init -+>>>'
|
||||||
|
|
||||||
Ninstance = count(phase_plasticity == PLASTICITY_KINEHARDENING_ID)
|
Ninstance = count(phase_plasticity == PLASTICITY_KINEHARDENING_ID)
|
||||||
if (debug_constitutive%contains('basic')) &
|
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance; flush(6)
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
|
||||||
|
#ifdef DEBUG
|
||||||
|
debug_constitutive => debug_root%get('constitutuve', defaultVal=emptyList)
|
||||||
|
debug%extensive = debug_constitutive%contains('extensive')
|
||||||
|
debug%selective = debug_constitutive%contains('selective')
|
||||||
|
debug%element = debug_root%get_asInt('element',defaultVal = 1)
|
||||||
|
debug%ip = debug_root%get_asInt('integrationpoint',defaultVal = 1)
|
||||||
|
debug%grain = debug_root%get_asInt('grain',defaultVal = 1)
|
||||||
|
#endif
|
||||||
|
|
||||||
allocate(param(Ninstance))
|
allocate(param(Ninstance))
|
||||||
allocate(state(Ninstance))
|
allocate(state(Ninstance))
|
||||||
|
@ -100,12 +121,8 @@ module subroutine plastic_kinehardening_init(debug_constitutive)
|
||||||
prm%output = config%getStrings('(output)',defaultVal=emptyStringArray)
|
prm%output = config%getStrings('(output)',defaultVal=emptyStringArray)
|
||||||
|
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
debug_g = debug_root%get_asInt('grain',defaultVal=1)
|
if (p==material_phaseAt(debug%grain,debug%element)) then
|
||||||
debug_e = debug_root%get_asInt('element',defaultVal=1)
|
prm%of_debug = material_phasememberAt(debug%grain,debug%ip,debug%element)
|
||||||
debug_i = debug_root%get_asInt('integrationpoint',defaultVal=1)
|
|
||||||
|
|
||||||
if (p==material_phaseAt(debug_g,debug_e)) then
|
|
||||||
prm%of_debug = material_phasememberAt(debug_g,debug_i,debug_e)
|
|
||||||
endif
|
endif
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
|
@ -316,15 +333,13 @@ end subroutine plastic_kinehardening_dotState
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief Calculate (instantaneous) incremental change of microstructure.
|
!> @brief Calculate (instantaneous) incremental change of microstructure.
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module subroutine plastic_kinehardening_deltaState(Mp,instance,of,debug_constitutive)
|
module subroutine plastic_kinehardening_deltaState(Mp,instance,of)
|
||||||
|
|
||||||
real(pReal), dimension(3,3), intent(in) :: &
|
real(pReal), dimension(3,3), intent(in) :: &
|
||||||
Mp !< Mandel stress
|
Mp !< Mandel stress
|
||||||
integer, intent(in) :: &
|
integer, intent(in) :: &
|
||||||
instance, &
|
instance, &
|
||||||
of
|
of
|
||||||
class(tNode), pointer , intent(in) :: &
|
|
||||||
debug_constitutive !< pointer to constitutive debug options
|
|
||||||
|
|
||||||
real(pReal), dimension(param(instance)%sum_N_sl) :: &
|
real(pReal), dimension(param(instance)%sum_N_sl) :: &
|
||||||
gdot_pos,gdot_neg, &
|
gdot_pos,gdot_neg, &
|
||||||
|
@ -338,9 +353,9 @@ module subroutine plastic_kinehardening_deltaState(Mp,instance,of,debug_constitu
|
||||||
dEq0(gdot_pos+gdot_neg,1e-10_pReal)) ! current sense of shear direction
|
dEq0(gdot_pos+gdot_neg,1e-10_pReal)) ! current sense of shear direction
|
||||||
|
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debug_constitutive%contains('extensive') &
|
if (debug%extensive &
|
||||||
.and. (of == prm%of_debug &
|
.and. (of == prm%of_debug &
|
||||||
.or. .not. debug_constitutive%contains('selective'))) then
|
.or. .not. debug%selective)) then
|
||||||
write(6,'(a)') '======= kinehardening delta state ======='
|
write(6,'(a)') '======= kinehardening delta state ======='
|
||||||
write(6,*) sense,state(instance)%sense(:,of)
|
write(6,*) sense,state(instance)%sense(:,of)
|
||||||
endif
|
endif
|
||||||
|
|
|
@ -147,6 +147,22 @@ submodule(constitutive) plastic_nonlocal
|
||||||
v_scr_neg
|
v_scr_neg
|
||||||
end type tNonlocalState
|
end type tNonlocalState
|
||||||
|
|
||||||
|
#ifdef DEBUG
|
||||||
|
type :: tDebugOptions
|
||||||
|
logical :: &
|
||||||
|
basic, &
|
||||||
|
extensive, &
|
||||||
|
selective
|
||||||
|
integer :: &
|
||||||
|
element, &
|
||||||
|
ip, &
|
||||||
|
grain
|
||||||
|
end type tDebugOptions
|
||||||
|
|
||||||
|
type(tDebugOptions) :: debug
|
||||||
|
|
||||||
|
#endif
|
||||||
|
|
||||||
type(tNonlocalState), allocatable, dimension(:) :: &
|
type(tNonlocalState), allocatable, dimension(:) :: &
|
||||||
deltaState, &
|
deltaState, &
|
||||||
dotState, &
|
dotState, &
|
||||||
|
@ -163,10 +179,7 @@ contains
|
||||||
!> @brief module initialization
|
!> @brief module initialization
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module subroutine plastic_nonlocal_init(debug_constitutive)
|
module subroutine plastic_nonlocal_init
|
||||||
|
|
||||||
class(tNode), pointer, intent(in) :: &
|
|
||||||
debug_constitutive !< pointer to constitutive debug options
|
|
||||||
|
|
||||||
integer :: &
|
integer :: &
|
||||||
Ninstance, &
|
Ninstance, &
|
||||||
|
@ -181,8 +194,10 @@ module subroutine plastic_nonlocal_init(debug_constitutive)
|
||||||
extmsg = ''
|
extmsg = ''
|
||||||
type(tInitialParameters) :: &
|
type(tInitialParameters) :: &
|
||||||
ini
|
ini
|
||||||
|
class(tNode), pointer :: &
|
||||||
|
debug_constitutive
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- constitutive_'//PLASTICITY_NONLOCAL_LABEL//' init -+>>>'; flush(6)
|
write(6,'(/,a)') ' <<<+- constitutive_'//PLASTICITY_NONLOCAL_LABEL//' init -+>>>'
|
||||||
|
|
||||||
write(6,'(/,a)') ' Reuber et al., Acta Materialia 71:333–348, 2014'
|
write(6,'(/,a)') ' Reuber et al., Acta Materialia 71:333–348, 2014'
|
||||||
write(6,'(a)') ' https://doi.org/10.1016/j.actamat.2014.03.012'
|
write(6,'(a)') ' https://doi.org/10.1016/j.actamat.2014.03.012'
|
||||||
|
@ -191,8 +206,17 @@ module subroutine plastic_nonlocal_init(debug_constitutive)
|
||||||
write(6,'(a)') ' http://publications.rwth-aachen.de/record/229993'
|
write(6,'(a)') ' http://publications.rwth-aachen.de/record/229993'
|
||||||
|
|
||||||
Ninstance = count(phase_plasticity == PLASTICITY_NONLOCAL_ID)
|
Ninstance = count(phase_plasticity == PLASTICITY_NONLOCAL_ID)
|
||||||
if (debug_constitutive%contains('basic')) &
|
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance; flush(6)
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
|
||||||
|
#ifdef DEBUG
|
||||||
|
debug_constitutive => debug_root%get('constitutuve', defaultVal=emptyList)
|
||||||
|
debug%basic = debug_constitutive%contains('basic')
|
||||||
|
debug%extensive = debug_constitutive%contains('extensive')
|
||||||
|
debug%selective = debug_constitutive%contains('selective')
|
||||||
|
debug%element = debug_root%get_asInt('element',defaultVal = 1)
|
||||||
|
debug%ip = debug_root%get_asInt('integrationpoint',defaultVal = 1)
|
||||||
|
debug%grain = debug_root%get_asInt('grain',defaultVal = 1)
|
||||||
|
#endif
|
||||||
|
|
||||||
allocate(param(Ninstance))
|
allocate(param(Ninstance))
|
||||||
allocate(state(Ninstance))
|
allocate(state(Ninstance))
|
||||||
|
@ -525,7 +549,7 @@ end subroutine plastic_nonlocal_init
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief calculates quantities characterizing the microstructure
|
!> @brief calculates quantities characterizing the microstructure
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module subroutine plastic_nonlocal_dependentState(F, Fp, instance, of, ip, el,debug_constitutive)
|
module subroutine plastic_nonlocal_dependentState(F, Fp, instance, of, ip, el)
|
||||||
|
|
||||||
real(pReal), dimension(3,3), intent(in) :: &
|
real(pReal), dimension(3,3), intent(in) :: &
|
||||||
F, &
|
F, &
|
||||||
|
@ -535,8 +559,6 @@ module subroutine plastic_nonlocal_dependentState(F, Fp, instance, of, ip, el,de
|
||||||
of, &
|
of, &
|
||||||
ip, &
|
ip, &
|
||||||
el
|
el
|
||||||
class(tNode), pointer, intent(in) :: &
|
|
||||||
debug_constitutive !< pointer to constitutive debug options
|
|
||||||
|
|
||||||
integer :: &
|
integer :: &
|
||||||
no, & !< neighbor offset
|
no, & !< neighbor offset
|
||||||
|
@ -546,8 +568,7 @@ module subroutine plastic_nonlocal_dependentState(F, Fp, instance, of, ip, el,de
|
||||||
c, & ! index of dilsocation character (edge, screw)
|
c, & ! index of dilsocation character (edge, screw)
|
||||||
s, & ! slip system index
|
s, & ! slip system index
|
||||||
dir, &
|
dir, &
|
||||||
n, &
|
n
|
||||||
debug_e, debug_i
|
|
||||||
real(pReal) :: &
|
real(pReal) :: &
|
||||||
FVsize, &
|
FVsize, &
|
||||||
nRealNeighbors ! number of really existing neighbors
|
nRealNeighbors ! number of really existing neighbors
|
||||||
|
@ -716,11 +737,9 @@ module subroutine plastic_nonlocal_dependentState(F, Fp, instance, of, ip, el,de
|
||||||
endif
|
endif
|
||||||
|
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
debug_e = debug_root%get_asInt('element',defaultVal=1)
|
if (debug%extensive &
|
||||||
debug_i = debug_root%get_asInt('integrationpoint',defaultVal=1)
|
.and. ((debug%element == el .and. debug%ip == ip)&
|
||||||
if (debug_constitutive%contains('extensive') &
|
.or. .not. debug%selective)) then
|
||||||
.and. ((debug_e == el .and. debug_i == ip)&
|
|
||||||
.or. .not. debug_constitutive%contains('selective'))) then
|
|
||||||
write(6,'(/,a,i8,1x,i2,1x,i1,/)') '<< CONST >> nonlocal_microstructure at el ip ',el,ip
|
write(6,'(/,a,i8,1x,i2,1x,i1,/)') '<< CONST >> nonlocal_microstructure at el ip ',el,ip
|
||||||
write(6,'(a,/,12x,12(e10.3,1x))') '<< CONST >> rhoForest', stt%rho_forest(:,of)
|
write(6,'(a,/,12x,12(e10.3,1x))') '<< CONST >> rhoForest', stt%rho_forest(:,of)
|
||||||
write(6,'(a,/,12x,12(f10.5,1x))') '<< CONST >> tauThreshold / MPa', dst%tau_pass(:,of)*1e-6
|
write(6,'(a,/,12x,12(f10.5,1x))') '<< CONST >> tauThreshold / MPa', dst%tau_pass(:,of)*1e-6
|
||||||
|
@ -844,7 +863,7 @@ end subroutine plastic_nonlocal_LpAndItsTangent
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief (instantaneous) incremental change of microstructure
|
!> @brief (instantaneous) incremental change of microstructure
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module subroutine plastic_nonlocal_deltaState(Mp,instance,of,ip,el,debug_constitutive)
|
module subroutine plastic_nonlocal_deltaState(Mp,instance,of,ip,el)
|
||||||
|
|
||||||
real(pReal), dimension(3,3), intent(in) :: &
|
real(pReal), dimension(3,3), intent(in) :: &
|
||||||
Mp !< MandelStress
|
Mp !< MandelStress
|
||||||
|
@ -853,16 +872,13 @@ module subroutine plastic_nonlocal_deltaState(Mp,instance,of,ip,el,debug_constit
|
||||||
of, & !< offset
|
of, & !< offset
|
||||||
ip, &
|
ip, &
|
||||||
el
|
el
|
||||||
class(tNode), pointer, intent(in) :: &
|
|
||||||
debug_constitutive !< pointer to constitutive debug options
|
|
||||||
|
|
||||||
integer :: &
|
integer :: &
|
||||||
ph, & !< phase
|
ph, & !< phase
|
||||||
ns, & ! short notation for the total number of active slip systems
|
ns, & ! short notation for the total number of active slip systems
|
||||||
c, & ! character of dislocation
|
c, & ! character of dislocation
|
||||||
t, & ! type of dislocation
|
t, & ! type of dislocation
|
||||||
s, & ! index of my current slip system
|
s ! index of my current slip system
|
||||||
debug_e, debug_i
|
|
||||||
real(pReal), dimension(param(instance)%sum_N_sl,10) :: &
|
real(pReal), dimension(param(instance)%sum_N_sl,10) :: &
|
||||||
deltaRhoRemobilization, & ! density increment by remobilization
|
deltaRhoRemobilization, & ! density increment by remobilization
|
||||||
deltaRhoDipole2SingleStress ! density increment by dipole dissociation (by stress change)
|
deltaRhoDipole2SingleStress ! density increment by dipole dissociation (by stress change)
|
||||||
|
@ -938,11 +954,9 @@ module subroutine plastic_nonlocal_deltaState(Mp,instance,of,ip,el,debug_constit
|
||||||
del%rho(:,of) = reshape(deltaRhoRemobilization + deltaRhoDipole2SingleStress, [10*ns])
|
del%rho(:,of) = reshape(deltaRhoRemobilization + deltaRhoDipole2SingleStress, [10*ns])
|
||||||
|
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
debug_e = debug_root%get_asInt('element',defaultVal=1)
|
if (debug%extensive &
|
||||||
debug_i = debug_root%get_asInt('integrationpoint',defaultVal=1)
|
.and. ((debug%element == el .and. debug%ip == ip)&
|
||||||
if (debug_constitutive%contains('extensive') &
|
.or. .not. debug%selective)) then
|
||||||
.and. ((debug_e == el .and. debug_i == ip)&
|
|
||||||
.or. .not. debug_constitutive%contains('selective'))) then
|
|
||||||
write(6,'(a,/,8(12x,12(e12.5,1x),/))') '<< CONST >> dislocation remobilization', deltaRhoRemobilization(:,1:8)
|
write(6,'(a,/,8(12x,12(e12.5,1x),/))') '<< CONST >> dislocation remobilization', deltaRhoRemobilization(:,1:8)
|
||||||
write(6,'(a,/,10(12x,12(e12.5,1x),/),/)') '<< CONST >> dipole dissociation by stress increase', deltaRhoDipole2SingleStress
|
write(6,'(a,/,10(12x,12(e12.5,1x),/),/)') '<< CONST >> dipole dissociation by stress increase', deltaRhoDipole2SingleStress
|
||||||
endif
|
endif
|
||||||
|
@ -957,7 +971,7 @@ end subroutine plastic_nonlocal_deltaState
|
||||||
!> @brief calculates the rate of change of microstructure
|
!> @brief calculates the rate of change of microstructure
|
||||||
!---------------------------------------------------------------------------------------------------
|
!---------------------------------------------------------------------------------------------------
|
||||||
module subroutine plastic_nonlocal_dotState(Mp, F, Fp, Temperature,timestep, &
|
module subroutine plastic_nonlocal_dotState(Mp, F, Fp, Temperature,timestep, &
|
||||||
instance,of,ip,el,debug_constitutive)
|
instance,of,ip,el)
|
||||||
|
|
||||||
real(pReal), dimension(3,3), intent(in) :: &
|
real(pReal), dimension(3,3), intent(in) :: &
|
||||||
Mp !< MandelStress
|
Mp !< MandelStress
|
||||||
|
@ -972,16 +986,13 @@ module subroutine plastic_nonlocal_dotState(Mp, F, Fp, Temperature,timestep, &
|
||||||
of, &
|
of, &
|
||||||
ip, & !< current integration point
|
ip, & !< current integration point
|
||||||
el !< current element number
|
el !< current element number
|
||||||
class(tNode), pointer, intent(in) :: &
|
|
||||||
debug_constitutive !< pointer to constitutive debug options
|
|
||||||
|
|
||||||
integer :: &
|
integer :: &
|
||||||
ph, &
|
ph, &
|
||||||
ns, & !< short notation for the total number of active slip systems
|
ns, & !< short notation for the total number of active slip systems
|
||||||
c, & !< character of dislocation
|
c, & !< character of dislocation
|
||||||
t, & !< type of dislocation
|
t, & !< type of dislocation
|
||||||
s, & !< index of my current slip system
|
s !< index of my current slip system
|
||||||
debug_e, debug_i
|
|
||||||
real(pReal), dimension(param(instance)%sum_N_sl,10) :: &
|
real(pReal), dimension(param(instance)%sum_N_sl,10) :: &
|
||||||
rho, &
|
rho, &
|
||||||
rho0, & !< dislocation density at beginning of time step
|
rho0, & !< dislocation density at beginning of time step
|
||||||
|
@ -1032,11 +1043,9 @@ module subroutine plastic_nonlocal_dotState(Mp, F, Fp, Temperature,timestep, &
|
||||||
gdot = rhoSgl(:,1:4) * v * spread(prm%burgers,2,4)
|
gdot = rhoSgl(:,1:4) * v * spread(prm%burgers,2,4)
|
||||||
|
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
debug_e = debug_root%get_asInt('element',defaultVal=1)
|
if (debug%basic &
|
||||||
debug_i = debug_root%get_asInt('integrationpoint',defaultVal=1)
|
.and. ((debug%element == el .and. debug%ip == ip) &
|
||||||
if (debug_constitutive%contains('basic') &
|
.or. .not. debug%selective)) then
|
||||||
.and. ((debug_e == el .and. debug_i == ip) &
|
|
||||||
.or. .not. debug_constitutive%contains('selective') )) then
|
|
||||||
write(6,'(a,/,10(12x,12(e12.5,1x),/))') '<< CONST >> rho / 1/m^2', rhoSgl, rhoDip
|
write(6,'(a,/,10(12x,12(e12.5,1x),/))') '<< CONST >> rho / 1/m^2', rhoSgl, rhoDip
|
||||||
write(6,'(a,/,4(12x,12(e12.5,1x),/))') '<< CONST >> gdot / 1/s',gdot
|
write(6,'(a,/,4(12x,12(e12.5,1x),/))') '<< CONST >> gdot / 1/s',gdot
|
||||||
endif
|
endif
|
||||||
|
@ -1135,7 +1144,7 @@ module subroutine plastic_nonlocal_dotState(Mp, F, Fp, Temperature,timestep, &
|
||||||
- rhoDip(s,1) / timestep - rhoDotAthermalAnnihilation(s,9) &
|
- rhoDip(s,1) / timestep - rhoDotAthermalAnnihilation(s,9) &
|
||||||
- rhoDotSingle2DipoleGlide(s,9)) ! make sure that we do not annihilate more dipoles than we have
|
- rhoDotSingle2DipoleGlide(s,9)) ! make sure that we do not annihilate more dipoles than we have
|
||||||
|
|
||||||
rhoDot = rhoDotFlux(F,Fp,timestep, instance,of,ip,el,debug_constitutive) &
|
rhoDot = rhoDotFlux(F,Fp,timestep, instance,of,ip,el) &
|
||||||
+ rhoDotMultiplication &
|
+ rhoDotMultiplication &
|
||||||
+ rhoDotSingle2DipoleGlide &
|
+ rhoDotSingle2DipoleGlide &
|
||||||
+ rhoDotAthermalAnnihilation &
|
+ rhoDotAthermalAnnihilation &
|
||||||
|
@ -1145,7 +1154,7 @@ module subroutine plastic_nonlocal_dotState(Mp, F, Fp, Temperature,timestep, &
|
||||||
if ( any(rho(:,mob) + rhoDot(:,1:4) * timestep < -prm%atol_rho) &
|
if ( any(rho(:,mob) + rhoDot(:,1:4) * timestep < -prm%atol_rho) &
|
||||||
.or. any(rho(:,dip) + rhoDot(:,9:10) * timestep < -prm%atol_rho)) then
|
.or. any(rho(:,dip) + rhoDot(:,9:10) * timestep < -prm%atol_rho)) then
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debug_constitutive%contains('extensive')) then
|
if (debug%extensive) then
|
||||||
write(6,'(a,i5,a,i2)') '<< CONST >> evolution rate leads to negative density at el ',el,' ip ',ip
|
write(6,'(a,i5,a,i2)') '<< CONST >> evolution rate leads to negative density at el ',el,' ip ',ip
|
||||||
write(6,'(a)') '<< CONST >> enforcing cutback !!!'
|
write(6,'(a)') '<< CONST >> enforcing cutback !!!'
|
||||||
endif
|
endif
|
||||||
|
@ -1164,7 +1173,7 @@ end subroutine plastic_nonlocal_dotState
|
||||||
!---------------------------------------------------------------------------------------------------
|
!---------------------------------------------------------------------------------------------------
|
||||||
!> @brief calculates the rate of change of microstructure
|
!> @brief calculates the rate of change of microstructure
|
||||||
!---------------------------------------------------------------------------------------------------
|
!---------------------------------------------------------------------------------------------------
|
||||||
function rhoDotFlux(F,Fp,timestep, instance,of,ip,el,debug_constitutive)
|
function rhoDotFlux(F,Fp,timestep, instance,of,ip,el)
|
||||||
|
|
||||||
real(pReal), dimension(3,3,homogenization_maxNgrains,discretization_nIP,discretization_nElem), intent(in) :: &
|
real(pReal), dimension(3,3,homogenization_maxNgrains,discretization_nIP,discretization_nElem), intent(in) :: &
|
||||||
F, & !< elastic deformation gradient
|
F, & !< elastic deformation gradient
|
||||||
|
@ -1176,8 +1185,6 @@ function rhoDotFlux(F,Fp,timestep, instance,of,ip,el,debug_constitutive)
|
||||||
of, &
|
of, &
|
||||||
ip, & !< current integration point
|
ip, & !< current integration point
|
||||||
el !< current element number
|
el !< current element number
|
||||||
class(tNode), pointer, intent(in) :: &
|
|
||||||
debug_constitutive !< pointer to constitutive debug options
|
|
||||||
|
|
||||||
integer :: &
|
integer :: &
|
||||||
ph, &
|
ph, &
|
||||||
|
@ -1259,7 +1266,7 @@ function rhoDotFlux(F,Fp,timestep, instance,of,ip,el,debug_constitutive)
|
||||||
.and. prm%CFLfactor * abs(v0) * timestep &
|
.and. prm%CFLfactor * abs(v0) * timestep &
|
||||||
> IPvolume(ip,el) / maxval(IParea(:,ip,el)))) then ! ...with velocity above critical value (we use the reference volume and area for simplicity here)
|
> IPvolume(ip,el) / maxval(IParea(:,ip,el)))) then ! ...with velocity above critical value (we use the reference volume and area for simplicity here)
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debug_constitutive%contains('extensive')) then
|
if (debug%extensive) then
|
||||||
write(6,'(a,i5,a,i2)') '<< CONST >> CFL condition not fullfilled at el ',el,' ip ',ip
|
write(6,'(a,i5,a,i2)') '<< CONST >> CFL condition not fullfilled at el ',el,' ip ',ip
|
||||||
write(6,'(a,e10.3,a,e10.3)') '<< CONST >> velocity is at ', &
|
write(6,'(a,e10.3,a,e10.3)') '<< CONST >> velocity is at ', &
|
||||||
maxval(abs(v0), abs(gdot) > 0.0_pReal &
|
maxval(abs(v0), abs(gdot) > 0.0_pReal &
|
||||||
|
|
Loading…
Reference in New Issue