reworking damage routines

This commit is contained in:
Pratheek Shanthraj 2014-10-28 01:18:10 +00:00
parent 88159d1458
commit ebd285f565
6 changed files with 394 additions and 286 deletions

View File

@ -488,55 +488,36 @@ function constitutive_homogenizedC(ipc,ip,el)
end function constitutive_homogenizedC
!--------------------------------------------------------------------------------------------------
!> @brief returns the damaged elasticity matrix in case where not implementing Fe..Fd..Fp decomposition
!> and the undamaged elasticity matrix in case where implementing Fe..Fd..Fp decomposition
!> @brief returns the damaged elasticity matrix if relevant
!--------------------------------------------------------------------------------------------------
function constitutive_damagedC(ipc,ip,el)
use prec, only: &
pReal
use material, only: &
material_phase, &
LOCAL_DAMAGE_none_ID, &
LOCAL_DAMAGE_brittle_ID, &
LOCAL_DAMAGE_ductile_ID, &
LOCAL_DAMAGE_gurson_ID, &
LOCAL_DAMAGE_anisotropic_ID, &
phase_damage
use damage_brittle, only: &
constitutive_brittle_getDamage
! use damage_ductile, only: &
! constitutive_ductile_getDamage
use damage_gurson, only: &
constitutive_gurson_getDamage
use damage_anisotropic, only: &
constitutive_anisotropic_getDamage
damage_brittle_getDamage
implicit none
real(pReal), dimension(6,6) :: constitutive_damagedC
integer(pInt), intent(in) :: &
ipc, & !< grain number
ip, & !< integration point number
el !< element number
el
real(pReal) :: damage !< element number
select case (phase_damage(material_phase(ipc,ip,el)))
case (LOCAL_DAMAGE_none_ID)
case (LOCAL_DAMAGE_brittle_ID)
damage = damage_brittle_getDamage(ipc, ip, el)
constitutive_damagedC = damage*damage* &
constitutive_homogenizedC(ipc,ip,el)
case default
constitutive_damagedC = constitutive_homogenizedC(ipc,ip,el)
case (LOCAL_DAMAGE_brittle_ID)
constitutive_damagedC = constitutive_brittle_getDamage(ipc,ip,el) * &
constitutive_homogenizedC(ipc,ip,el) !> No Fe..Fd..Fp decomposition
case (LOCAL_DAMAGE_ductile_ID)
constitutive_damagedC = constitutive_homogenizedC(ipc,ip,el) !> No Fe..Fd..Fp decomposition ??
case (LOCAL_DAMAGE_gurson_ID)
constitutive_damagedC = constitutive_homogenizedC(ipc,ip,el) !> Elasticity degradation by Fe..Fd..Fp decomposition
case (LOCAL_DAMAGE_anisotropic_ID)
constitutive_damagedC = constitutive_homogenizedC(ipc,ip,el) !> Elasticity degradation by Fe..Fd..Fp decomposition
end select
end function constitutive_damagedC
!--------------------------------------------------------------------------------------------------
@ -567,13 +548,12 @@ subroutine constitutive_microstructure(Tstar_v, Fe, Fp, ipc, ip, el)
use constitutive_dislokmc, only: &
constitutive_dislokmc_microstructure
use damage_brittle, only: &
damage_brittle_microstructure
damage_brittle_microstructure, &
damage_brittle_getDamage
use damage_ductile, only: &
damage_ductile_microstructure
use damage_gurson, only: &
damage_gurson_microstructure
use damage_anisotropic, only: &
damage_anisotropic_microstructure
implicit none
integer(pInt), intent(in) :: &
@ -608,9 +588,7 @@ subroutine constitutive_microstructure(Tstar_v, Fe, Fp, ipc, ip, el)
select case (phase_damage(material_phase(ipc,ip,el)))
case (LOCAL_DAMAGE_brittle_ID)
damage = constitutive_getDamage(ipc,ip,el)
Tstar_v_effective = Tstar_v/(damage*damage)
damage = constitutive_getDamage(ipc,ip,el)
damage = damage_brittle_getDamage(ipc,ip,el)
Tstar_v_effective = Tstar_v/(damage*damage)
call damage_brittle_microstructure(Tstar_v_effective, Fe, ipc, ip, el)
case (LOCAL_DAMAGE_ductile_ID)
@ -618,10 +596,6 @@ subroutine constitutive_microstructure(Tstar_v, Fe, Fp, ipc, ip, el)
call damage_ductile_microstructure(nSlip,accumulatedSlip,ipc, ip, el)
case (LOCAL_DAMAGE_gurson_ID)
call damage_gurson_microstructure(ipc, ip, el)
case (LOCAL_DAMAGE_anisotropic_ID)
call constitutive_getAccumulatedSlip(nSlip,accumulatedSlip,Fp,ipc, ip, el)
call damage_anisotropic_microstructure(nSlip,accumulatedSlip,ipc, ip, el)
end select
@ -887,7 +861,7 @@ subroutine constitutive_collectDotState(Tstar_v, Lp, FeArray, FpArray, subdt, su
case (LOCAL_DAMAGE_gurson_ID)
call damage_gurson_dotState(Tstar_v, Lp, ipc, ip, el)
case (LOCAL_DAMAGE_anisotropic_ID)
call damage_anisotropic_dotState(ipc, ip, el)
call damage_anisotropic_dotState(Tstar_v, ipc, ip, el)
end select
select case (phase_thermal(material_phase(ipc,ip,el)))
@ -989,13 +963,13 @@ function constitutive_getLocalDamage(ipc, ip, el)
LOCAL_DAMAGE_anisotropic_ID, &
phase_damage
use damage_brittle, only: &
constitutive_brittle_getDamage
damage_brittle_getLocalDamage
use damage_ductile, only: &
constitutive_ductile_getDamage
damage_ductile_getLocalDamage
use damage_gurson, only: &
constitutive_gurson_getDamage
damage_gurson_getLocalDamage
use damage_anisotropic, only: &
constitutive_anisotropic_getDamage
damage_anisotropic_getLocalDamage
implicit none
integer(pInt), intent(in) :: &
@ -1009,16 +983,16 @@ function constitutive_getLocalDamage(ipc, ip, el)
constitutive_getLocalDamage = 1.0_pReal
case (LOCAL_DAMAGE_brittle_ID)
constitutive_getLocalDamage = constitutive_brittle_getDamage(ipc, ip, el)
constitutive_getLocalDamage = damage_brittle_getLocalDamage(ipc, ip, el)
case (LOCAL_DAMAGE_ductile_ID)
constitutive_getLocalDamage = constitutive_ductile_getDamage(ipc, ip, el)
constitutive_getLocalDamage = damage_ductile_getLocalDamage(ipc, ip, el)
case (LOCAL_DAMAGE_gurson_ID)
constitutive_getLocalDamage = constitutive_gurson_getDamage(ipc, ip, el)
constitutive_getLocalDamage = damage_gurson_getLocalDamage(ipc, ip, el)
case (LOCAL_DAMAGE_anisotropic_ID)
!constitutive_getLocalDamage = constitutive_anisotropic_getDamage(ipc, ip, el)
constitutive_getLocalDamage = damage_anisotropic_getLocalDamage(ipc, ip, el)
end select
end function constitutive_getLocalDamage
@ -1037,13 +1011,13 @@ subroutine constitutive_putLocalDamage(ipc, ip, el, localDamage)
LOCAL_DAMAGE_anisotropic_ID, &
phase_damage
use damage_brittle, only: &
constitutive_brittle_putDamage
damage_brittle_putLocalDamage
use damage_ductile, only: &
constitutive_ductile_putDamage
damage_ductile_putLocalDamage
use damage_gurson, only: &
constitutive_gurson_putDamage
damage_gurson_putLocalDamage
use damage_anisotropic, only: &
constitutive_anisotropic_putDamage
damage_anisotropic_putLocalDamage
implicit none
integer(pInt), intent(in) :: &
@ -1055,16 +1029,16 @@ subroutine constitutive_putLocalDamage(ipc, ip, el, localDamage)
select case (phase_damage(material_phase(ipc,ip,el)))
case (LOCAL_DAMAGE_BRITTLE_ID)
call constitutive_brittle_putDamage(ipc, ip, el, localDamage)
call damage_brittle_putLocalDamage(ipc, ip, el, localDamage)
case (LOCAL_DAMAGE_DUCTILE_ID)
call constitutive_ductile_putDamage(ipc, ip, el, localDamage)
call damage_ductile_putLocalDamage(ipc, ip, el, localDamage)
case (LOCAL_DAMAGE_gurson_ID)
call constitutive_gurson_putDamage(ipc, ip, el, localDamage)
call damage_gurson_putLocalDamage(ipc, ip, el, localDamage)
case (LOCAL_DAMAGE_anisotropic_ID)
!call constitutive_anisotropic_putDamage(ipc, ip, el, localDamage)
call damage_anisotropic_putLocalDamage(ipc, ip, el, localDamage)
end select
@ -1077,12 +1051,21 @@ function constitutive_getDamage(ipc, ip, el)
use prec, only: &
pReal
use material, only: &
material_homog, &
mappingHomogenization, &
fieldDamage, &
field_damage_type, &
FIELD_DAMAGE_LOCAL_ID, &
FIELD_DAMAGE_NONLOCAL_ID
material_phase, &
LOCAL_DAMAGE_none_ID, &
LOCAL_DAMAGE_BRITTLE_ID, &
LOCAL_DAMAGE_DUCTILE_ID, &
LOCAL_DAMAGE_gurson_ID, &
LOCAL_DAMAGE_anisotropic_ID, &
phase_damage
use damage_brittle, only: &
damage_brittle_getDamage
use damage_ductile, only: &
damage_ductile_getDamage
use damage_gurson, only: &
damage_gurson_getDamage
use damage_anisotropic, only: &
damage_anisotropic_getDamage
implicit none
integer(pInt), intent(in) :: &
@ -1091,19 +1074,60 @@ function constitutive_getDamage(ipc, ip, el)
el !< element number
real(pReal) :: constitutive_getDamage
select case(field_damage_type(material_homog(ip,el)))
select case (phase_damage(material_phase(ipc,ip,el)))
case (LOCAL_DAMAGE_none_ID)
constitutive_getDamage = 1.0_pReal
case (FIELD_DAMAGE_LOCAL_ID)
constitutive_getDamage = constitutive_getLocalDamage(ipc, ip, el)
case (LOCAL_DAMAGE_brittle_ID)
constitutive_getDamage = damage_brittle_getDamage(ipc, ip, el)
case (FIELD_DAMAGE_NONLOCAL_ID)
constitutive_getDamage = fieldDamage(material_homog(ip,el))% &
field(1,mappingHomogenization(1,ip,el)) ! Taylor type
case (LOCAL_DAMAGE_ductile_ID)
constitutive_getDamage = damage_ductile_getDamage(ipc, ip, el)
case (LOCAL_DAMAGE_gurson_ID)
constitutive_getDamage = damage_gurson_getDamage(ipc, ip, el)
case (LOCAL_DAMAGE_anisotropic_ID)
constitutive_getDamage = damage_anisotropic_getDamage(ipc, ip, el)
end select
end function constitutive_getDamage
!--------------------------------------------------------------------------------------------------
!> @brief returns damage deformation gradient
!--------------------------------------------------------------------------------------------------
function constitutive_getDamageStrain(ipc, ip, el)
use prec, only: &
pReal
use math, only: &
math_I3
use material, only: &
material_phase, &
LOCAL_DAMAGE_anisotropic_ID, &
phase_damage
use damage_anisotropic, only: &
damage_anisotropic_getDamageStrain
implicit none
integer(pInt), intent(in) :: &
ipc, & !< grain number
ip, & !< integration point number
el !< element number
real(pReal), dimension(3,3) :: &
constitutive_getDamageStrain
select case (phase_damage(material_phase(ipc,ip,el)))
case (LOCAL_DAMAGE_anisotropic_ID)
constitutive_getDamageStrain = damage_anisotropic_getDamageStrain(ipc, ip, el)
case default
constitutive_getDamageStrain = math_I3
end select
end function constitutive_getDamageStrain
!--------------------------------------------------------------------------------------------------
!> @brief returns damage diffusion tensor
!--------------------------------------------------------------------------------------------------
@ -1225,74 +1249,17 @@ function constitutive_getTemperature(ipc, ip, el)
el !< element number
real(pReal) :: constitutive_getTemperature
select case(field_thermal_type(material_homog(ip,el)))
select case(field_thermal_type(material_homog(ip,el)))
case (FIELD_THERMAL_local_ID)
constitutive_getTemperature = constitutive_getAdiabaticTemperature(ipc, ip, el)
case (FIELD_THERMAL_local_ID)
constitutive_getTemperature = constitutive_getAdiabaticTemperature(ipc, ip, el)
case (FIELD_THERMAL_nonlocal_ID)
constitutive_getTemperature = fieldThermal(material_homog(ip,el))% &
field(1,mappingHomogenization(1,ip,el)) ! Taylor type
case (FIELD_THERMAL_nonlocal_ID)
constitutive_getTemperature = fieldThermal(material_homog(ip,el))% &
field(1,mappingHomogenization(1,ip,el)) ! Taylor type
end select
end function constitutive_getTemperature
!--------------------------------------------------------------------------------------------------
!> @brief returns damage deformation gradient
!--------------------------------------------------------------------------------------------------
function constitutive_getDamageStrain(ipc, ip, el)
use prec, only: &
pReal
use math, only: &
math_I3
use material, only: &
material_phase, &
LOCAL_DAMAGE_none_ID, &
LOCAL_DAMAGE_brittle_ID, &
LOCAL_DAMAGE_ductile_ID, &
LOCAL_DAMAGE_gurson_ID, &
LOCAL_DAMAGE_anisotropic_ID, &
phase_damage
! use damage_brittle_iso, only: &
! constitutive_brittle_iso_getDamageStrain
! use damage_brittle_iso, only: &
! constitutive_brittle_iso_getDamageStrain
use damage_ductile, only: &
constitutive_ductile_getDamageStrain
! use damage_gurson, only: &
! constitutive_gurson_getDamageStrain
! use damage_anisotropic, only: &
! constitutive_anisotropic_getDamageStrain
implicit none
integer(pInt), intent(in) :: &
ipc, & !< grain number
ip, & !< integration point number
el !< element number
real(pReal), dimension(3,3) :: &
constitutive_getDamageStrain
select case (phase_damage(material_phase(ipc,ip,el)))
case (LOCAL_DAMAGE_none_ID)
constitutive_getDamageStrain = math_I3 !
case (LOCAL_DAMAGE_brittle_ID)
constitutive_getDamageStrain = math_I3 !
case (LOCAL_DAMAGE_ductile_ID)
constitutive_getDamageStrain = constitutive_ductile_getDamageStrain(ipc, ip, el)
case (LOCAL_DAMAGE_gurson_ID)
constitutive_getDamageStrain = math_I3 !
case (LOCAL_DAMAGE_anisotropic_ID)
constitutive_getDamageStrain = math_I3 !
end select
end function constitutive_getDamageStrain
end function constitutive_getTemperature
!--------------------------------------------------------------------------------------------------
!> @brief returns thermal deformation gradient

View File

@ -3424,9 +3424,8 @@ logical function crystallite_integrateStress(&
return
endif
A = math_mul33x33(Fg_new,invFp_current) ! intermediate tensor needed later to calculate dFe_dLp
Fi = math_I3 ! intermediate configuration, assume decomposition as F = Fe Fi Fp
Fi = math_mul33x33(math_mul33x33(Fi,constitutive_getThermalStrain(g,i,e)), &
constitutive_getDamageStrain(g,i,e)) ! Fi = Ft Fd
Fi = constitutive_getDamageStrain(g,i,e) ! intermediate configuration, assume decomposition as F = Fe Fi Fp
Fi = math_mul33x33(Fi,constitutive_getThermalStrain(g,i,e)) ! Fi = Ft Fd
Ci = math_mul33x33(math_transpose33(Fi),Fi) ! non-plastic stretch tensor (neglecting elastic contributions)
invFi = math_inv33(Fi)
detFi = math_det33(Fi)

View File

@ -32,10 +32,13 @@ module damage_anisotropic
damage_anisotropic_Nslip !< Todo
real(pReal), dimension(:), allocatable, private :: &
damage_anisotropic_aTol
damage_anisotropic_aTol, &
damage_anisotropic_sdot_0, &
damage_anisotropic_N
real(pReal), dimension(:,:), allocatable, private :: &
damage_anisotropic_critpStrain
damage_anisotropic_critDisp, &
damage_anisotropic_critLoad
enum, bind(c)
enumerator :: undefined_ID, &
@ -51,9 +54,10 @@ module damage_anisotropic
damage_anisotropic_stateInit, &
damage_anisotropic_aTolState, &
damage_anisotropic_dotState, &
damage_anisotropic_microstructure, &
constitutive_anisotropic_getDamage, &
constitutive_anisotropic_putDamage, &
damage_anisotropic_getDamage, &
damage_anisotropic_putLocalDamage, &
damage_anisotropic_getLocalDamage, &
damage_anisotropic_getDamageStrain, &
damage_anisotropic_postResults
contains
@ -133,10 +137,13 @@ subroutine damage_anisotropic_init(fileUnit)
damage_anisotropic_output = ''
allocate(damage_anisotropic_outputID(maxval(phase_Noutput),maxNinstance), source=undefined_ID)
allocate(damage_anisotropic_Noutput(maxNinstance), source=0_pInt)
allocate(damage_anisotropic_critpStrain(lattice_maxNslipFamily,maxNinstance), source=0.0_pReal)
allocate(damage_anisotropic_critDisp(lattice_maxNslipFamily,maxNinstance), source=0.0_pReal)
allocate(damage_anisotropic_critLoad (lattice_maxNslipFamily,maxNinstance), source=0.0_pReal)
allocate(damage_anisotropic_Nslip(lattice_maxNslipFamily,maxNinstance), source=0_pInt)
allocate(damage_anisotropic_totalNslip(maxNinstance), source=0_pInt)
allocate(damage_anisotropic_aTol(maxNinstance), source=0.0_pReal)
allocate(damage_anisotropic_sdot_0(maxNinstance), source=0.0_pReal)
allocate(damage_anisotropic_N(maxNinstance), source=0.0_pReal)
rewind(fileUnit)
phase = 0_pInt
@ -172,6 +179,12 @@ subroutine damage_anisotropic_init(fileUnit)
case ('atol_damage')
damage_anisotropic_aTol(instance) = IO_floatValue(line,positions,2_pInt)
case ('sdot_0')
damage_anisotropic_sdot_0(instance) = IO_floatValue(line,positions,2_pInt)
case ('n_damage')
damage_anisotropic_N(instance) = IO_floatValue(line,positions,2_pInt)
case ('Nslip') !
Nchunks_SlipFamilies = positions(1) - 1_pInt
do j = 1_pInt, Nchunks_SlipFamilies
@ -179,9 +192,14 @@ subroutine damage_anisotropic_init(fileUnit)
enddo
damage_anisotropic_totalNslip(instance) = sum(damage_anisotropic_Nslip(:,instance))
case ('critical_plastic_strain')
case ('critical_displacement')
do j = 1_pInt, Nchunks_SlipFamilies
damage_anisotropic_critpStrain(j,instance) = IO_floatValue(line,positions,1_pInt+j)
damage_anisotropic_critDisp(j,instance) = IO_floatValue(line,positions,1_pInt+j)
enddo
case ('critical_load')
do j = 1_pInt, Nchunks_SlipFamilies
damage_anisotropic_critLoad(j,instance) = IO_floatValue(line,positions,1_pInt+j)
enddo
end select
@ -207,8 +225,10 @@ subroutine damage_anisotropic_init(fileUnit)
endif
enddo outputsLoop
! Determine size of state array
sizeDotState = damage_anisotropic_totalNslip(instance)
sizeState = 2_pInt * damage_anisotropic_totalNslip(instance)
sizeDotState = 2_pInt + & ! viscous and non-viscous damage values
9_pInt + & ! damage deformation gradient
damage_anisotropic_totalNslip(instance) ! opening on each damage system
sizeState = sizeDotState
damageState(phase)%sizeState = sizeState
damageState(phase)%sizeDotState = sizeDotState
@ -251,7 +271,18 @@ subroutine damage_anisotropic_stateInit(phase)
real(pReal), dimension(damageState(phase)%sizeState) :: tempState
tempState = 1.0_pReal
tempState = 0.0_pReal
tempState(1) = 1.0_pReal
tempState(2) = 1.0_pReal
tempState(3) = 1.0_pReal
tempState(4) = 0.0_pReal
tempState(5) = 0.0_pReal
tempState(6) = 0.0_pReal
tempState(7) = 1.0_pReal
tempState(8) = 0.0_pReal
tempState(9) = 0.0_pReal
tempState(10) = 0.0_pReal
tempState(11) = 1.0_pReal
damageState(phase)%state = spread(tempState,2,size(damageState(phase)%state(1,:)))
damageState(phase)%state0 = damageState(phase)%state
damageState(phase)%partionedState0 = damageState(phase)%state
@ -277,14 +308,18 @@ end subroutine damage_anisotropic_aTolState
!--------------------------------------------------------------------------------------------------
!> @brief calculates derived quantities from state
!--------------------------------------------------------------------------------------------------
subroutine damage_anisotropic_dotState(ipc, ip, el)
subroutine damage_anisotropic_dotState(Tstar_v,ipc, ip, el)
use material, only: &
mappingConstitutive, &
phase_damageInstance, &
damageState
use math, only: &
math_norm33
math_mul33x33
use lattice, only: &
lattice_Sslip, &
lattice_Sslip_v, &
lattice_maxNslipFamily, &
lattice_NslipSystem, &
lattice_DamageMobility
implicit none
@ -292,97 +327,92 @@ subroutine damage_anisotropic_dotState(ipc, ip, el)
ipc, & !< component-ID of integration point
ip, & !< integration point
el !< element
real(pReal), intent(in), dimension(6) :: &
Tstar_v !< 2nd Piola Kirchhoff stress tensor (Mandel)
integer(pInt) :: &
phase, &
constituent, &
instance, &
i
j, f, i, index_myFamily
real(pReal), dimension(3,3) :: &
Ld
real(pReal) :: &
tau, &
tau_critical, &
nonLocalFactor
phase = mappingConstitutive(2,ipc,ip,el)
constituent = mappingConstitutive(1,ipc,ip,el)
instance = phase_damageInstance(phase)
do i = 1_pInt,damage_anisotropic_totalNslip(instance)
damageState(phase)%dotState(i,constituent) = &
(1.0_pReal/lattice_DamageMobility(phase))* &
(damageState(phase)%state(i+damage_anisotropic_totalNslip(instance),constituent) - &
damageState(phase)%state(i,constituent))
enddo
damageState(phase)%dotState(1,constituent) = &
(1.0_pReal/lattice_DamageMobility(phase))* &
(damageState(phase)%state(2,constituent) - &
damageState(phase)%state(1,constituent))
nonLocalFactor = 1.0_pReal + &
(damageState(phase)%state(1,constituent) - &
damage_anisotropic_getDamage(ipc, ip, el))
Ld = 0.0_pReal
j = 0_pInt
slipFamiliesLoop: do f = 1_pInt,lattice_maxNslipFamily
index_myFamily = sum(lattice_NslipSystem(1:f-1_pInt,phase)) ! at which index starts my family
do i = 1_pInt,damage_anisotropic_Nslip(f,instance) ! process each (active) slip system in family
j = j+1_pInt
tau = dot_product(Tstar_v,lattice_Sslip_v(1:6,1,index_myFamily+i,phase))
tau_critical = (1.0_pReal - damageState(phase)%state(11+j,constituent)/&
damage_anisotropic_critDisp(f,instance))* &
damage_anisotropic_critLoad(f,instance)*nonLocalFactor
damageState(phase)%dotState(11+j,constituent) = &
damage_anisotropic_sdot_0(instance)*(tau/tau_critical)**damage_anisotropic_N(instance)
damageState(phase)%dotState(2,constituent) = &
damageState(phase)%dotState(2,constituent) - &
2.0_pReal*tau*damageState(phase)%dotState(11+j,constituent)/ &
(damage_anisotropic_critDisp(f,instance)*damage_anisotropic_critLoad(f,instance))
Ld = Ld + damageState(phase)%dotState(11+j,constituent)* &
lattice_Sslip(1:3,1:3,1,index_myFamily+i,phase)
enddo
enddo slipFamiliesLoop
damageState(phase)%dotState(3:11,constituent) = &
reshape(math_mul33x33(Ld,reshape(damageState(phase)%state(3:11,constituent),shape=[3,3])),shape=[9])
end subroutine damage_anisotropic_dotState
!--------------------------------------------------------------------------------------------------
!> @brief calculates derived quantities from state
!> @brief returns damage
!--------------------------------------------------------------------------------------------------
subroutine damage_anisotropic_microstructure(nSlip,accumulatedSlip,ipc, ip, el)
function damage_anisotropic_getDamage(ipc, ip, el)
use material, only: &
mappingConstitutive, &
phase_damageInstance, &
damageState
use math, only: &
math_Mandel6to33, &
math_mul33x33, &
math_transpose33, &
math_I3, &
math_norm33
use lattice, only: &
lattice_maxNslipFamily
implicit none
integer(pInt), intent(in) :: &
nSlip, &
ipc, & !< component-ID of integration point
ip, & !< integration point
el !< element
real(pReal), dimension(nSlip), intent(in) :: &
accumulatedSlip
integer(pInt) :: &
phase, constituent, instance, i, j, f
phase = mappingConstitutive(2,ipc,ip,el)
constituent = mappingConstitutive(1,ipc,ip,el)
instance = phase_damageInstance(phase)
j = 0_pInt
do f = 1_pInt,lattice_maxNslipFamily
do i = 1_pInt,damage_anisotropic_Nslip(f,instance) ! process each (active) slip system in family
j = j+1_pInt
damageState(phase)%state(j+damage_anisotropic_totalNslip(instance),constituent) = &
min(damageState(phase)%state(j+damage_anisotropic_totalNslip(instance),constituent), &
damage_anisotropic_critpStrain(f,instance)/accumulatedSlip(j))
enddo
enddo
end subroutine damage_anisotropic_microstructure
!--------------------------------------------------------------------------------------------------
!> @brief returns temperature based on local damage model state layout
!--------------------------------------------------------------------------------------------------
function constitutive_anisotropic_getDamage(ipc, ip, el)
use material, only: &
mappingConstitutive, &
phase_damageInstance, &
damageState
material_homog, &
mappingHomogenization, &
fieldDamage, &
field_damage_type, &
FIELD_DAMAGE_LOCAL_ID, &
FIELD_DAMAGE_NONLOCAL_ID
implicit none
integer(pInt), intent(in) :: &
ipc, & !< grain number
ip, & !< integration point number
el !< element number
real(pReal) :: &
constitutive_anisotropic_getDamage(damage_anisotropic_totalNslip(phase_damageInstance(mappingConstitutive(2,ipc,ip,el))))
real(pReal) :: damage_anisotropic_getDamage
constitutive_anisotropic_getDamage = &
damageState(mappingConstitutive(2,ipc,ip,el))% &
state(1:damage_anisotropic_totalNslip(phase_damageInstance(mappingConstitutive(2,ipc,ip,el))), &
mappingConstitutive(1,ipc,ip,el))
select case(field_damage_type(material_homog(ip,el)))
case (FIELD_DAMAGE_LOCAL_ID)
damage_anisotropic_getDamage = damage_anisotropic_getLocalDamage(ipc, ip, el)
end function constitutive_anisotropic_getDamage
case (FIELD_DAMAGE_NONLOCAL_ID)
damage_anisotropic_getDamage = fieldDamage(material_homog(ip,el))% &
field(1,mappingHomogenization(1,ip,el)) ! Taylor type
end select
end function damage_anisotropic_getDamage
!--------------------------------------------------------------------------------------------------
!> @brief returns damage value based on local damage
!--------------------------------------------------------------------------------------------------
subroutine constitutive_anisotropic_putDamage(ipc, ip, el, localDamage)
subroutine damage_anisotropic_putLocalDamage(ipc, ip, el, localDamage)
use material, only: &
mappingConstitutive, &
phase_damageInstance, &
@ -394,17 +424,57 @@ subroutine constitutive_anisotropic_putDamage(ipc, ip, el, localDamage)
ip, & !< integration point number
el !< element number
real(pReal), intent(in) :: &
localDamage(damage_anisotropic_totalNslip(phase_damageInstance(mappingConstitutive(2,ipc,ip,el))))
integer(pInt) :: &
phase, constituent, instance
phase = mappingConstitutive(2,ipc,ip,el)
constituent = mappingConstitutive(1,ipc,ip,el)
instance = phase_damageInstance(phase)
damageState(phase)%state(1:damage_anisotropic_totalNslip(instance),constituent) = &
localDamage
end subroutine constitutive_anisotropic_putDamage
damageState(mappingConstitutive(2,ipc,ip,el))%state(1,mappingConstitutive(1,ipc,ip,el)) = &
localDamage
end subroutine damage_anisotropic_putLocalDamage
!--------------------------------------------------------------------------------------------------
!> @brief returns local damage
!--------------------------------------------------------------------------------------------------
function damage_anisotropic_getLocalDamage(ipc, ip, el)
use material, only: &
mappingConstitutive, &
phase_damageInstance, &
damageState
implicit none
integer(pInt), intent(in) :: &
ipc, & !< grain number
ip, & !< integration point number
el !< element number
real(pReal) :: &
damage_anisotropic_getLocalDamage
damage_anisotropic_getLocalDamage = &
damageState(mappingConstitutive(2,ipc,ip,el))%state(1,mappingConstitutive(1,ipc,ip,el))
end function damage_anisotropic_getLocalDamage
!--------------------------------------------------------------------------------------------------
!> @brief returns local damage deformation gradient
!--------------------------------------------------------------------------------------------------
function damage_anisotropic_getDamageStrain(ipc, ip, el)
use material, only: &
mappingConstitutive, &
phase_damageInstance, &
damageState
implicit none
integer(pInt), intent(in) :: &
ipc, & !< grain number
ip, & !< integration point number
el !< element number
real(pReal), dimension(3,3) :: &
damage_anisotropic_getDamageStrain
damage_anisotropic_getDamageStrain = &
reshape(damageState(mappingConstitutive(2,ipc,ip,el))%state(3:11,mappingConstitutive(1,ipc,ip,el)), &
shape=[3,3])
end function damage_anisotropic_getDamageStrain
!--------------------------------------------------------------------------------------------------
!> @brief return array of constitutive results

View File

@ -44,8 +44,9 @@ module damage_brittle
damage_brittle_aTolState, &
damage_brittle_dotState, &
damage_brittle_microstructure, &
constitutive_brittle_getDamage, &
constitutive_brittle_putDamage, &
damage_brittle_getDamage, &
damage_brittle_putLocalDamage, &
damage_brittle_getLocalDamage, &
damage_brittle_getDamageDiffusion33, &
damage_brittle_postResults
@ -323,29 +324,40 @@ subroutine damage_brittle_microstructure(Tstar_v, Fe, ipc, ip, el)
end subroutine damage_brittle_microstructure
!--------------------------------------------------------------------------------------------------
!> @brief returns temperature based on local damage model state layout
!> @brief returns damage
!--------------------------------------------------------------------------------------------------
function constitutive_brittle_getDamage(ipc, ip, el)
function damage_brittle_getDamage(ipc, ip, el)
use material, only: &
mappingConstitutive, &
damageState
material_homog, &
mappingHomogenization, &
fieldDamage, &
field_damage_type, &
FIELD_DAMAGE_LOCAL_ID, &
FIELD_DAMAGE_NONLOCAL_ID
implicit none
integer(pInt), intent(in) :: &
ipc, & !< grain number
ip, & !< integration point number
el !< element number
real(pReal) :: constitutive_brittle_getDamage
real(pReal) :: damage_brittle_getDamage
constitutive_brittle_getDamage = &
damageState(mappingConstitutive(2,ipc,ip,el))%state(1,mappingConstitutive(1,ipc,ip,el))
select case(field_damage_type(material_homog(ip,el)))
case (FIELD_DAMAGE_LOCAL_ID)
damage_brittle_getDamage = damage_brittle_getLocalDamage(ipc, ip, el)
end function constitutive_brittle_getDamage
case (FIELD_DAMAGE_NONLOCAL_ID)
damage_brittle_getDamage = fieldDamage(material_homog(ip,el))% &
field(1,mappingHomogenization(1,ip,el)) ! Taylor type
end select
end function damage_brittle_getDamage
!--------------------------------------------------------------------------------------------------
!> @brief returns temperature based on local damage model state layout
!--------------------------------------------------------------------------------------------------
subroutine constitutive_brittle_putDamage(ipc, ip, el, localDamage)
subroutine damage_brittle_putLocalDamage(ipc, ip, el, localDamage)
use material, only: &
mappingConstitutive, &
damageState
@ -360,7 +372,27 @@ subroutine constitutive_brittle_putDamage(ipc, ip, el, localDamage)
damageState(mappingConstitutive(2,ipc,ip,el))%state(1,mappingConstitutive(1,ipc,ip,el)) = &
localDamage
end subroutine constitutive_brittle_putDamage
end subroutine damage_brittle_putLocalDamage
!--------------------------------------------------------------------------------------------------
!> @brief returns local damage
!--------------------------------------------------------------------------------------------------
function damage_brittle_getLocalDamage(ipc, ip, el)
use material, only: &
mappingConstitutive, &
damageState
implicit none
integer(pInt), intent(in) :: &
ipc, & !< grain number
ip, & !< integration point number
el !< element number
real(pReal) :: damage_brittle_getLocalDamage
damage_brittle_getLocalDamage = &
damageState(mappingConstitutive(2,ipc,ip,el))%state(1,mappingConstitutive(1,ipc,ip,el))
end function damage_brittle_getLocalDamage
!--------------------------------------------------------------------------------------------------
!> @brief returns brittle damage diffusion tensor

View File

@ -44,9 +44,9 @@ module damage_ductile
damage_ductile_aTolState, &
damage_ductile_dotState, &
damage_ductile_microstructure, &
constitutive_ductile_getDamage, &
constitutive_ductile_getDamageStrain, &
constitutive_ductile_putDamage, &
damage_ductile_getDamage, &
damage_ductile_putLocalDamage, &
damage_ductile_getLocalDamage, &
damage_ductile_postResults
contains
@ -322,52 +322,40 @@ subroutine damage_ductile_microstructure(nSlip,accumulatedSlip,ipc, ip, el)
end subroutine damage_ductile_microstructure
!--------------------------------------------------------------------------------------------------
!> @brief returns damage value based on local damage model state layout
!> @brief returns damage
!--------------------------------------------------------------------------------------------------
function constitutive_ductile_getDamage(ipc, ip, el)
function damage_ductile_getDamage(ipc, ip, el)
use material, only: &
mappingConstitutive, &
damageState
material_homog, &
mappingHomogenization, &
fieldDamage, &
field_damage_type, &
FIELD_DAMAGE_LOCAL_ID, &
FIELD_DAMAGE_NONLOCAL_ID
implicit none
integer(pInt), intent(in) :: &
ipc, & !< grain number
ip, & !< integration point number
el !< element number
real(pReal) :: constitutive_ductile_getDamage
real(pReal) :: damage_ductile_getDamage
constitutive_ductile_getDamage = &
damageState(mappingConstitutive(2,ipc,ip,el))%state(1,mappingConstitutive(1,ipc,ip,el))
select case(field_damage_type(material_homog(ip,el)))
case (FIELD_DAMAGE_LOCAL_ID)
damage_ductile_getDamage = damage_ductile_getLocalDamage(ipc, ip, el)
end function constitutive_ductile_getDamage
!--------------------------------------------------------------------------------------------------
!> @brief returns damage deformation gradient (extra intermediate configuration) based on
!> local damage model state layout
!--------------------------------------------------------------------------------------------------
function constitutive_ductile_getDamageStrain(ipc, ip, el)
use math, only: &
math_I3
use material, only: &
mappingConstitutive, &
damageState
case (FIELD_DAMAGE_NONLOCAL_ID)
damage_ductile_getDamage = fieldDamage(material_homog(ip,el))% &
field(1,mappingHomogenization(1,ip,el)) ! Taylor type
implicit none
integer(pInt), intent(in) :: &
ipc, & !< grain number
ip, & !< integration point number
el !< element number
real(pReal), dimension(3,3) :: &
constitutive_ductile_getDamageStrain
end select
constitutive_ductile_getDamageStrain = &
math_I3 / ( &
damageState(mappingConstitutive(2,ipc,ip,el))%state(1,mappingConstitutive(1,ipc,ip,el)) )**(1_pInt/3_pInt) ! volumetric deformation gradient due to damage
end function constitutive_ductile_getDamageStrain
end function damage_ductile_getDamage
!--------------------------------------------------------------------------------------------------
!> @brief returns damage value based on local damage
!> @brief puts local damage
!--------------------------------------------------------------------------------------------------
subroutine constitutive_ductile_putDamage(ipc, ip, el, localDamage)
subroutine damage_ductile_putLocalDamage(ipc, ip, el, localDamage)
use material, only: &
mappingConstitutive, &
damageState
@ -382,7 +370,27 @@ subroutine constitutive_ductile_putDamage(ipc, ip, el, localDamage)
damageState(mappingConstitutive(2,ipc,ip,el))%state(1,mappingConstitutive(1,ipc,ip,el)) = &
localDamage
end subroutine constitutive_ductile_putDamage
end subroutine damage_ductile_putLocalDamage
!--------------------------------------------------------------------------------------------------
!> @brief returns local damage
!--------------------------------------------------------------------------------------------------
function damage_ductile_getLocalDamage(ipc, ip, el)
use material, only: &
mappingConstitutive, &
damageState
implicit none
integer(pInt), intent(in) :: &
ipc, & !< grain number
ip, & !< integration point number
el !< element number
real(pReal) :: damage_ductile_getLocalDamage
damage_ductile_getLocalDamage = &
damageState(mappingConstitutive(2,ipc,ip,el))%state(1,mappingConstitutive(1,ipc,ip,el))
end function damage_ductile_getLocalDamage
!--------------------------------------------------------------------------------------------------
!> @brief return array of constitutive results

View File

@ -50,8 +50,9 @@ module damage_gurson
damage_gurson_aTolState, &
damage_gurson_dotState, &
damage_gurson_microstructure, &
constitutive_gurson_getDamage, &
constitutive_gurson_putDamage, &
damage_gurson_getDamage, &
damage_gurson_putLocalDamage, &
damage_gurson_getLocalDamage, &
damage_gurson_postResults
contains
@ -379,29 +380,40 @@ subroutine damage_gurson_microstructure(ipc, ip, el)
end subroutine damage_gurson_microstructure
!--------------------------------------------------------------------------------------------------
!> @brief returns temperature based on local damage model state layout
!> @brief returns damage
!--------------------------------------------------------------------------------------------------
function constitutive_gurson_getDamage(ipc, ip, el)
function damage_gurson_getDamage(ipc, ip, el)
use material, only: &
mappingConstitutive, &
damageState
material_homog, &
mappingHomogenization, &
fieldDamage, &
field_damage_type, &
FIELD_DAMAGE_LOCAL_ID, &
FIELD_DAMAGE_NONLOCAL_ID
implicit none
integer(pInt), intent(in) :: &
ipc, & !< grain number
ip, & !< integration point number
el !< element number
real(pReal) :: constitutive_gurson_getDamage
real(pReal) :: damage_gurson_getDamage
constitutive_gurson_getDamage = &
damageState(mappingConstitutive(2,ipc,ip,el))%state(1,mappingConstitutive(1,ipc,ip,el))
select case(field_damage_type(material_homog(ip,el)))
case (FIELD_DAMAGE_LOCAL_ID)
damage_gurson_getDamage = damage_gurson_getLocalDamage(ipc, ip, el)
end function constitutive_gurson_getDamage
case (FIELD_DAMAGE_NONLOCAL_ID)
damage_gurson_getDamage = fieldDamage(material_homog(ip,el))% &
field(1,mappingHomogenization(1,ip,el)) ! Taylor type
end select
end function damage_gurson_getDamage
!--------------------------------------------------------------------------------------------------
!> @brief returns damage value based on local damage
!> @brief puts local damage
!--------------------------------------------------------------------------------------------------
subroutine constitutive_gurson_putDamage(ipc, ip, el, localDamage)
subroutine damage_gurson_putLocalDamage(ipc, ip, el, localDamage)
use material, only: &
mappingConstitutive, &
damageState
@ -416,7 +428,27 @@ subroutine constitutive_gurson_putDamage(ipc, ip, el, localDamage)
damageState(mappingConstitutive(2,ipc,ip,el))%state(1,mappingConstitutive(1,ipc,ip,el)) = &
localDamage
end subroutine constitutive_gurson_putDamage
end subroutine damage_gurson_putLocalDamage
!--------------------------------------------------------------------------------------------------
!> @brief returns local damage
!--------------------------------------------------------------------------------------------------
function damage_gurson_getLocalDamage(ipc, ip, el)
use material, only: &
mappingConstitutive, &
damageState
implicit none
integer(pInt), intent(in) :: &
ipc, & !< grain number
ip, & !< integration point number
el !< element number
real(pReal) :: damage_gurson_getLocalDamage
damage_gurson_getLocalDamage = &
damageState(mappingConstitutive(2,ipc,ip,el))%state(1,mappingConstitutive(1,ipc,ip,el))
end function damage_gurson_getLocalDamage
!--------------------------------------------------------------------------------------------------
!> @brief return array of constitutive results