consistent names
This commit is contained in:
parent
b1674b6835
commit
440790ca01
|
@ -400,14 +400,14 @@ end subroutine damage_results
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief contains the constitutive equation for calculating the rate of change of microstructure
|
!> @brief contains the constitutive equation for calculating the rate of change of microstructure
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
function constitutive_damage_collectDotState(co,ip,el,ph,of) result(broken)
|
function constitutive_damage_collectDotState(co,ip,el,ph,me) result(broken)
|
||||||
|
|
||||||
integer, intent(in) :: &
|
integer, intent(in) :: &
|
||||||
co, & !< component-ID of integration point
|
co, & !< component-ID me integration point
|
||||||
ip, & !< integration point
|
ip, & !< integration point
|
||||||
el, & !< element
|
el, & !< element
|
||||||
ph, &
|
ph, &
|
||||||
of
|
me
|
||||||
integer :: &
|
integer :: &
|
||||||
so !< counter in source loop
|
so !< counter in source loop
|
||||||
logical :: broken
|
logical :: broken
|
||||||
|
@ -426,12 +426,11 @@ function constitutive_damage_collectDotState(co,ip,el,ph,of) result(broken)
|
||||||
call source_damage_anisoDuctile_dotState(co, ip, el)
|
call source_damage_anisoDuctile_dotState(co, ip, el)
|
||||||
|
|
||||||
case (DAMAGE_ANISOBRITTLE_ID) sourceType
|
case (DAMAGE_ANISOBRITTLE_ID) sourceType
|
||||||
call source_damage_anisoBrittle_dotState(mech_S(material_phaseAt(co,el),material_phaseMemberAt(co,ip,el)),&
|
call source_damage_anisoBrittle_dotState(mech_S(ph,me),co, ip, el) ! correct stress?
|
||||||
co, ip, el) ! correct stress?
|
|
||||||
|
|
||||||
end select sourceType
|
end select sourceType
|
||||||
|
|
||||||
broken = broken .or. any(IEEE_is_NaN(damageState(ph)%p(so)%dotState(:,of)))
|
broken = broken .or. any(IEEE_is_NaN(damageState(ph)%p(so)%dotState(:,me)))
|
||||||
|
|
||||||
enddo SourceLoop
|
enddo SourceLoop
|
||||||
|
|
||||||
|
|
|
@ -15,7 +15,7 @@ submodule (constitutive:constitutive_damage) source_damage_anisoBrittle
|
||||||
dot_o, & !< opening rate of cleavage planes
|
dot_o, & !< opening rate of cleavage planes
|
||||||
q !< damage rate sensitivity
|
q !< 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
|
||||||
real(pReal), dimension(:,:,:,:), allocatable :: &
|
real(pReal), dimension(:,:,:,:), allocatable :: &
|
||||||
cleavage_systems
|
cleavage_systems
|
||||||
|
@ -37,7 +37,7 @@ contains
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module function source_damage_anisoBrittle_init(source_length) result(mySources)
|
module function source_damage_anisoBrittle_init(source_length) result(mySources)
|
||||||
|
|
||||||
integer, intent(in) :: source_length
|
integer, intent(in) :: source_length
|
||||||
logical, dimension(:,:), allocatable :: mySources
|
logical, dimension(:,:), allocatable :: mySources
|
||||||
|
|
||||||
class(tNode), pointer :: &
|
class(tNode), pointer :: &
|
||||||
|
@ -62,7 +62,7 @@ module function source_damage_anisoBrittle_init(source_length) result(mySources)
|
||||||
allocate(source_damage_anisoBrittle_instance(phases%length), source=0)
|
allocate(source_damage_anisoBrittle_instance(phases%length), source=0)
|
||||||
|
|
||||||
do p = 1, phases%length
|
do p = 1, phases%length
|
||||||
phase => phases%get(p)
|
phase => phases%get(p)
|
||||||
if(any(mySources(:,p))) source_damage_anisoBrittle_instance(p) = count(mySources(:,1:p))
|
if(any(mySources(:,p))) source_damage_anisoBrittle_instance(p) = count(mySources(:,1:p))
|
||||||
if(count(mySources(:,p)) == 0) cycle
|
if(count(mySources(:,p)) == 0) cycle
|
||||||
sources => phase%get('source')
|
sources => phase%get('source')
|
||||||
|
@ -70,20 +70,20 @@ module function source_damage_anisoBrittle_init(source_length) result(mySources)
|
||||||
if(mySources(sourceOffset,p)) then
|
if(mySources(sourceOffset,p)) then
|
||||||
source_damage_anisoBrittle_offset(p) = sourceOffset
|
source_damage_anisoBrittle_offset(p) = sourceOffset
|
||||||
associate(prm => param(source_damage_anisoBrittle_instance(p)))
|
associate(prm => param(source_damage_anisoBrittle_instance(p)))
|
||||||
src => sources%get(sourceOffset)
|
src => sources%get(sourceOffset)
|
||||||
|
|
||||||
N_cl = src%get_asInts('N_cl',defaultVal=emptyIntArray)
|
N_cl = src%get_asInts('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%q = src%get_asFloat('q')
|
||||||
prm%dot_o = src%get_asFloat('dot_o')
|
prm%dot_o = src%get_asFloat('dot_o')
|
||||||
|
|
||||||
prm%s_crit = src%get_asFloats('s_crit', requiredSize=size(N_cl))
|
prm%s_crit = src%get_asFloats('s_crit', requiredSize=size(N_cl))
|
||||||
prm%g_crit = src%get_asFloats('g_crit', requiredSize=size(N_cl))
|
prm%g_crit = src%get_asFloats('g_crit', requiredSize=size(N_cl))
|
||||||
|
|
||||||
prm%cleavage_systems = lattice_SchmidMatrix_cleavage(N_cl,phase%get_asString('lattice'),&
|
prm%cleavage_systems = lattice_SchmidMatrix_cleavage(N_cl,phase%get_asString('lattice'),&
|
||||||
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
phase%get_asFloat('c/a',defaultVal=0.0_pReal))
|
||||||
|
|
||||||
! expand: family => system
|
! expand: family => system
|
||||||
prm%s_crit = math_expand(prm%s_crit,N_cl)
|
prm%s_crit = math_expand(prm%s_crit,N_cl)
|
||||||
prm%g_crit = math_expand(prm%g_crit,N_cl)
|
prm%g_crit = math_expand(prm%g_crit,N_cl)
|
||||||
|
@ -93,7 +93,7 @@ module function source_damage_anisoBrittle_init(source_length) result(mySources)
|
||||||
#else
|
#else
|
||||||
prm%output = src%get_asStrings('output',defaultVal=emptyStringArray)
|
prm%output = src%get_asStrings('output',defaultVal=emptyStringArray)
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
! sanity checks
|
! sanity checks
|
||||||
if (prm%q <= 0.0_pReal) extmsg = trim(extmsg)//' q'
|
if (prm%q <= 0.0_pReal) extmsg = trim(extmsg)//' q'
|
||||||
if (prm%dot_o <= 0.0_pReal) extmsg = trim(extmsg)//' dot_o'
|
if (prm%dot_o <= 0.0_pReal) extmsg = trim(extmsg)//' dot_o'
|
||||||
|
@ -130,8 +130,8 @@ module subroutine source_damage_anisoBrittle_dotState(S, co, ip, el)
|
||||||
S
|
S
|
||||||
|
|
||||||
integer :: &
|
integer :: &
|
||||||
phase, &
|
ph, &
|
||||||
constituent, &
|
me, &
|
||||||
sourceOffset, &
|
sourceOffset, &
|
||||||
damageOffset, &
|
damageOffset, &
|
||||||
homog, &
|
homog, &
|
||||||
|
@ -139,14 +139,14 @@ module subroutine source_damage_anisoBrittle_dotState(S, co, ip, el)
|
||||||
real(pReal) :: &
|
real(pReal) :: &
|
||||||
traction_d, traction_t, traction_n, traction_crit
|
traction_d, traction_t, traction_n, traction_crit
|
||||||
|
|
||||||
phase = material_phaseAt(co,el)
|
ph = material_phaseAt(co,el)
|
||||||
constituent = material_phasememberAt(co,ip,el)
|
me = material_phasememberAt(co,ip,el)
|
||||||
sourceOffset = source_damage_anisoBrittle_offset(phase)
|
sourceOffset = source_damage_anisoBrittle_offset(ph)
|
||||||
homog = material_homogenizationAt(el)
|
homog = material_homogenizationAt(el)
|
||||||
damageOffset = material_homogenizationMemberAt(ip,el)
|
damageOffset = material_homogenizationMemberAt(ip,el)
|
||||||
|
|
||||||
associate(prm => param(source_damage_anisoBrittle_instance(phase)))
|
associate(prm => param(source_damage_anisoBrittle_instance(ph)))
|
||||||
damageState(phase)%p(sourceOffset)%dotState(1,constituent) = 0.0_pReal
|
damageState(ph)%p(sourceOffset)%dotState(1,me) = 0.0_pReal
|
||||||
do i = 1, prm%sum_N_cl
|
do i = 1, prm%sum_N_cl
|
||||||
traction_d = math_tensordot(S,prm%cleavage_systems(1:3,1:3,1,i))
|
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_t = math_tensordot(S,prm%cleavage_systems(1:3,1:3,2,i))
|
||||||
|
@ -154,8 +154,8 @@ module subroutine source_damage_anisoBrittle_dotState(S, co, ip, el)
|
||||||
|
|
||||||
traction_crit = prm%g_crit(i)*damage(homog)%p(damageOffset)**2.0_pReal
|
traction_crit = prm%g_crit(i)*damage(homog)%p(damageOffset)**2.0_pReal
|
||||||
|
|
||||||
damageState(phase)%p(sourceOffset)%dotState(1,constituent) &
|
damageState(ph)%p(sourceOffset)%dotState(1,me) &
|
||||||
= damageState(phase)%p(sourceOffset)%dotState(1,constituent) &
|
= damageState(ph)%p(sourceOffset)%dotState(1,me) &
|
||||||
+ prm%dot_o / prm%s_crit(i) &
|
+ 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_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_t) - traction_crit)/traction_crit)**prm%q + &
|
||||||
|
|
|
@ -30,7 +30,7 @@ contains
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module function source_damage_anisoDuctile_init(source_length) result(mySources)
|
module function source_damage_anisoDuctile_init(source_length) result(mySources)
|
||||||
|
|
||||||
integer, intent(in) :: source_length
|
integer, intent(in) :: source_length
|
||||||
logical, dimension(:,:), allocatable :: mySources
|
logical, dimension(:,:), allocatable :: mySources
|
||||||
|
|
||||||
class(tNode), pointer :: &
|
class(tNode), pointer :: &
|
||||||
|
@ -67,7 +67,7 @@ module function source_damage_anisoDuctile_init(source_length) result(mySources)
|
||||||
if(mySources(sourceOffset,p)) then
|
if(mySources(sourceOffset,p)) then
|
||||||
source_damage_anisoDuctile_offset(p) = sourceOffset
|
source_damage_anisoDuctile_offset(p) = sourceOffset
|
||||||
associate(prm => param(source_damage_anisoDuctile_instance(p)))
|
associate(prm => param(source_damage_anisoDuctile_instance(p)))
|
||||||
src => sources%get(sourceOffset)
|
src => sources%get(sourceOffset)
|
||||||
|
|
||||||
N_sl = pl%get_asInts('N_sl',defaultVal=emptyIntArray)
|
N_sl = pl%get_asInts('N_sl',defaultVal=emptyIntArray)
|
||||||
prm%q = src%get_asFloat('q')
|
prm%q = src%get_asFloat('q')
|
||||||
|
@ -81,7 +81,7 @@ module function source_damage_anisoDuctile_init(source_length) result(mySources)
|
||||||
#else
|
#else
|
||||||
prm%output = src%get_asStrings('output',defaultVal=emptyStringArray)
|
prm%output = src%get_asStrings('output',defaultVal=emptyStringArray)
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
! sanity checks
|
! sanity checks
|
||||||
if (prm%q <= 0.0_pReal) extmsg = trim(extmsg)//' q'
|
if (prm%q <= 0.0_pReal) extmsg = trim(extmsg)//' q'
|
||||||
if (any(prm%gamma_crit < 0.0_pReal)) extmsg = trim(extmsg)//' gamma_crit'
|
if (any(prm%gamma_crit < 0.0_pReal)) extmsg = trim(extmsg)//' gamma_crit'
|
||||||
|
@ -115,21 +115,21 @@ module subroutine source_damage_anisoDuctile_dotState(co, ip, el)
|
||||||
el !< element
|
el !< element
|
||||||
|
|
||||||
integer :: &
|
integer :: &
|
||||||
phase, &
|
ph, &
|
||||||
constituent, &
|
me, &
|
||||||
sourceOffset, &
|
sourceOffset, &
|
||||||
damageOffset, &
|
damageOffset, &
|
||||||
homog
|
homog
|
||||||
|
|
||||||
phase = material_phaseAt(co,el)
|
ph = material_phaseAt(co,el)
|
||||||
constituent = material_phasememberAt(co,ip,el)
|
me = material_phasememberAt(co,ip,el)
|
||||||
sourceOffset = source_damage_anisoDuctile_offset(phase)
|
sourceOffset = source_damage_anisoDuctile_offset(ph)
|
||||||
homog = material_homogenizationAt(el)
|
homog = material_homogenizationAt(el)
|
||||||
damageOffset = material_homogenizationMemberAt(ip,el)
|
damageOffset = material_homogenizationMemberAt(ip,el)
|
||||||
|
|
||||||
associate(prm => param(source_damage_anisoDuctile_instance(phase)))
|
associate(prm => param(source_damage_anisoDuctile_instance(ph)))
|
||||||
damageState(phase)%p(sourceOffset)%dotState(1,constituent) &
|
damageState(ph)%p(sourceOffset)%dotState(1,me) &
|
||||||
= sum(plasticState(phase)%slipRate(:,constituent)/(damage(homog)%p(damageOffset)**prm%q)/prm%gamma_crit)
|
= sum(plasticState(ph)%slipRate(:,me)/(damage(homog)%p(damageOffset)**prm%q)/prm%gamma_crit)
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
end subroutine source_damage_anisoDuctile_dotState
|
end subroutine source_damage_anisoDuctile_dotState
|
||||||
|
|
|
@ -30,7 +30,7 @@ contains
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module function source_damage_isoDuctile_init(source_length) result(mySources)
|
module function source_damage_isoDuctile_init(source_length) result(mySources)
|
||||||
|
|
||||||
integer, intent(in) :: source_length
|
integer, intent(in) :: source_length
|
||||||
logical, dimension(:,:), allocatable :: mySources
|
logical, dimension(:,:), allocatable :: mySources
|
||||||
|
|
||||||
class(tNode), pointer :: &
|
class(tNode), pointer :: &
|
||||||
|
@ -54,7 +54,7 @@ module function source_damage_isoDuctile_init(source_length) result(mySources)
|
||||||
allocate(source_damage_isoDuctile_instance(phases%length), source=0)
|
allocate(source_damage_isoDuctile_instance(phases%length), source=0)
|
||||||
|
|
||||||
do p = 1, phases%length
|
do p = 1, phases%length
|
||||||
phase => phases%get(p)
|
phase => phases%get(p)
|
||||||
if(count(mySources(:,p)) == 0) cycle
|
if(count(mySources(:,p)) == 0) cycle
|
||||||
if(any(mySources(:,p))) source_damage_isoDuctile_instance(p) = count(mySources(:,1:p))
|
if(any(mySources(:,p))) source_damage_isoDuctile_instance(p) = count(mySources(:,1:p))
|
||||||
sources => phase%get('source')
|
sources => phase%get('source')
|
||||||
|
@ -62,7 +62,7 @@ module function source_damage_isoDuctile_init(source_length) result(mySources)
|
||||||
if(mySources(sourceOffset,p)) then
|
if(mySources(sourceOffset,p)) then
|
||||||
source_damage_isoDuctile_offset(p) = sourceOffset
|
source_damage_isoDuctile_offset(p) = sourceOffset
|
||||||
associate(prm => param(source_damage_isoDuctile_instance(p)))
|
associate(prm => param(source_damage_isoDuctile_instance(p)))
|
||||||
src => sources%get(sourceOffset)
|
src => sources%get(sourceOffset)
|
||||||
|
|
||||||
prm%q = src%get_asFloat('q')
|
prm%q = src%get_asFloat('q')
|
||||||
prm%gamma_crit = src%get_asFloat('gamma_crit')
|
prm%gamma_crit = src%get_asFloat('gamma_crit')
|
||||||
|
@ -72,7 +72,7 @@ module function source_damage_isoDuctile_init(source_length) result(mySources)
|
||||||
#else
|
#else
|
||||||
prm%output = src%get_asStrings('output',defaultVal=emptyStringArray)
|
prm%output = src%get_asStrings('output',defaultVal=emptyStringArray)
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
! sanity checks
|
! sanity checks
|
||||||
if (prm%q <= 0.0_pReal) extmsg = trim(extmsg)//' q'
|
if (prm%q <= 0.0_pReal) extmsg = trim(extmsg)//' q'
|
||||||
if (prm%gamma_crit <= 0.0_pReal) extmsg = trim(extmsg)//' gamma_crit'
|
if (prm%gamma_crit <= 0.0_pReal) extmsg = trim(extmsg)//' gamma_crit'
|
||||||
|
@ -106,21 +106,21 @@ module subroutine source_damage_isoDuctile_dotState(co, ip, el)
|
||||||
el !< element
|
el !< element
|
||||||
|
|
||||||
integer :: &
|
integer :: &
|
||||||
phase, &
|
ph, &
|
||||||
constituent, &
|
me, &
|
||||||
sourceOffset, &
|
sourceOffset, &
|
||||||
damageOffset, &
|
damageOffset, &
|
||||||
homog
|
homog
|
||||||
|
|
||||||
phase = material_phaseAt(co,el)
|
ph = material_phaseAt(co,el)
|
||||||
constituent = material_phasememberAt(co,ip,el)
|
me = material_phasememberAt(co,ip,el)
|
||||||
sourceOffset = source_damage_isoDuctile_offset(phase)
|
sourceOffset = source_damage_isoDuctile_offset(ph)
|
||||||
homog = material_homogenizationAt(el)
|
homog = material_homogenizationAt(el)
|
||||||
damageOffset = material_homogenizationMemberAt(ip,el)
|
damageOffset = material_homogenizationMemberAt(ip,el)
|
||||||
|
|
||||||
associate(prm => param(source_damage_isoDuctile_instance(phase)))
|
associate(prm => param(source_damage_isoDuctile_instance(ph)))
|
||||||
damageState(phase)%p(sourceOffset)%dotState(1,constituent) = &
|
damageState(ph)%p(sourceOffset)%dotState(1,me) = &
|
||||||
sum(plasticState(phase)%slipRate(:,constituent))/(damage(homog)%p(damageOffset)**prm%q)/prm%gamma_crit
|
sum(plasticState(ph)%slipRate(:,me))/(damage(homog)%p(damageOffset)**prm%q)/prm%gamma_crit
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
end subroutine source_damage_isoDuctile_dotState
|
end subroutine source_damage_isoDuctile_dotState
|
||||||
|
|
Loading…
Reference in New Issue