simplified

damage currently works only for single constituent
This commit is contained in:
Martin Diehl 2021-04-07 09:11:40 +02:00
parent c53927ad6f
commit cdae867beb
7 changed files with 16 additions and 190 deletions

View File

@ -76,14 +76,10 @@ module subroutine damage_partition(ce)
real(pReal) :: phi real(pReal) :: phi
integer, intent(in) :: ce integer, intent(in) :: ce
integer :: co
if(damageState_h(material_homogenizationID(ce))%sizeState < 1) return if(damageState_h(material_homogenizationID(ce))%sizeState < 1) return
phi = damagestate_h(material_homogenizationID(ce))%state(1,material_homogenizationEntry(ce)) phi = damagestate_h(material_homogenizationID(ce))%state(1,material_homogenizationEntry(ce))
do co = 1, homogenization_Nconstituents(material_homogenizationID(ce)) call phase_damage_set_phi(phi,1,ce)
call phase_damage_set_phi(phi,co,ce)
enddo
end subroutine damage_partition end subroutine damage_partition
@ -95,17 +91,9 @@ end subroutine damage_partition
module function damage_nonlocal_getMobility(ce) result(M) module function damage_nonlocal_getMobility(ce) result(M)
integer, intent(in) :: ce integer, intent(in) :: ce
integer :: &
co
real(pReal) :: M real(pReal) :: M
M = 0.0_pReal M = lattice_M(material_phaseID(1,ce))
do co = 1, homogenization_Nconstituents(material_homogenizationID(ce))
M = M + lattice_M(material_phaseID(co,ce))
enddo
M = M/real(homogenization_Nconstituents(material_homogenizationID(ce)),pReal)
end function damage_nonlocal_getMobility end function damage_nonlocal_getMobility
@ -121,11 +109,7 @@ module subroutine damage_nonlocal_getSourceAndItsTangent(phiDot, phi, ce)
real(pReal), intent(out) :: & real(pReal), intent(out) :: &
phiDot phiDot
real(pReal) :: & phiDot = phase_damage_phi_dot(phi, ce)
dPhiDot_dPhi
call phase_damage_getRateAndItsTangents(phiDot, dPhiDot_dPhi, phi, ce)
phiDot = phiDot/real(homogenization_Nconstituents(material_homogenizationID(ce)),pReal)
end subroutine damage_nonlocal_getSourceAndItsTangent end subroutine damage_nonlocal_getSourceAndItsTangent

View File

@ -227,14 +227,13 @@ module phase
end function phase_homogenizedC end function phase_homogenizedC
module subroutine phase_damage_getRateAndItsTangents(phiDot, dPhiDot_dPhi, phi, ce) module function phase_damage_phi_dot(phi, ce) result(phi_dot)
integer, intent(in) :: ce integer, intent(in) :: ce
real(pReal), intent(in) :: & real(pReal), intent(in) :: &
phi !< damage parameter phi !< damage parameter
real(pReal), intent(inout) :: & real(pReal) :: &
phiDot, & phi_dot
dPhiDot_dPhi end function phase_damage_phi_dot
end subroutine phase_damage_getRateAndItsTangents
module subroutine phase_thermal_getRate(TDot, ph,me) module subroutine phase_thermal_getRate(TDot, ph,me)
integer, intent(in) :: ph, me integer, intent(in) :: ph, me
@ -301,7 +300,7 @@ module phase
public :: & public :: &
phase_init, & phase_init, &
phase_homogenizedC, & phase_homogenizedC, &
phase_damage_getRateAndItsTangents, & phase_damage_phi_dot, &
phase_thermal_getRate, & phase_thermal_getRate, &
phase_results, & phase_results, &
phase_allocateState, & phase_allocateState, &

View File

@ -65,43 +65,6 @@ submodule(phase) damage
integer, intent(in) :: ph,me integer, intent(in) :: ph,me
end subroutine isoductile_dotState end subroutine isoductile_dotState
module subroutine anisobrittle_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, ph, me)
integer, intent(in) :: ph,me
real(pReal), intent(in) :: &
phi !< damage parameter
real(pReal), intent(out) :: &
localphiDot, &
dLocalphiDot_dPhi
end subroutine anisobrittle_getRateAndItsTangent
module subroutine anisoductile_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, ph,me)
integer, intent(in) :: ph,me
real(pReal), intent(in) :: &
phi !< damage parameter
real(pReal), intent(out) :: &
localphiDot, &
dLocalphiDot_dPhi
end subroutine anisoductile_getRateAndItsTangent
module subroutine isobrittle_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, ph,me)
integer, intent(in) :: ph,me
real(pReal), intent(in) :: &
phi !< damage parameter
real(pReal), intent(out) :: &
localphiDot, &
dLocalphiDot_dPhi
end subroutine isobrittle_getRateAndItsTangent
module subroutine isoductile_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, ph,me)
integer, intent(in) :: ph,me
real(pReal), intent(in) :: &
phi !< damage parameter
real(pReal), intent(out) :: &
localphiDot, &
dLocalphiDot_dPhi
end subroutine isoductile_getRateAndItsTangent
module subroutine anisobrittle_results(phase,group) module subroutine anisobrittle_results(phase,group)
integer, intent(in) :: phase integer, intent(in) :: phase
character(len=*), intent(in) :: group character(len=*), intent(in) :: group
@ -179,53 +142,25 @@ end subroutine damage_init
!---------------------------------------------------------------------------------------------- !----------------------------------------------------------------------------------------------
!< @brief returns local part of nonlocal damage driving force !< @brief returns local part of nonlocal damage driving force
!---------------------------------------------------------------------------------------------- !----------------------------------------------------------------------------------------------
module subroutine phase_damage_getRateAndItsTangents(phiDot, dPhiDot_dPhi, phi, ce) module function phase_damage_phi_dot(phi, ce) result(phi_dot)
integer, intent(in) :: ce integer, intent(in) :: ce
real(pReal), intent(in) :: & real(pReal), intent(in) :: &
phi !< damage parameter phi !< damage parameter
real(pReal), intent(inout) :: &
phiDot, &
dPhiDot_dPhi
real(pReal) :: & real(pReal) :: &
localphiDot, & phi_dot
dLocalphiDot_dPhi
integer :: & integer :: &
ph, & ph, &
co, &
me me
phiDot = 0.0_pReal ph = material_phaseID(1,ce)
dPhiDot_dPhi = 0.0_pReal me = material_phaseEntry(1,ce)
do co = 1, homogenization_Nconstituents(material_homogenizationID(ce)) phi_dot = 1.0_pReal &
ph = material_phaseID(co,ce) - phi*damageState(ph)%state(1,me)
me = material_phaseEntry(co,ce)
select case(phase_source(ph)) end function phase_damage_phi_dot
case (DAMAGE_ISOBRITTLE_ID)
call isobrittle_getRateAndItsTangent (localphiDot, dLocalphiDot_dPhi, phi, ph, me)
case (DAMAGE_ISODUCTILE_ID)
call isoductile_getRateAndItsTangent (localphiDot, dLocalphiDot_dPhi, phi, ph, me)
case (DAMAGE_ANISOBRITTLE_ID)
call anisobrittle_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, ph, me)
case (DAMAGE_ANISODUCTILE_ID)
call anisoductile_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, ph, me)
case default
localphiDot = 0.0_pReal
dLocalphiDot_dPhi = 0.0_pReal
end select
phiDot = phiDot + localphiDot
dPhiDot_dPhi = dPhiDot_dPhi + dLocalphiDot_dPhi
enddo
end subroutine phase_damage_getRateAndItsTangents

View File

@ -148,29 +148,6 @@ module subroutine anisobrittle_dotState(S, ph,me)
end subroutine anisobrittle_dotState end subroutine anisobrittle_dotState
!--------------------------------------------------------------------------------------------------
!> @brief returns local part of nonlocal damage driving force
!--------------------------------------------------------------------------------------------------
module subroutine anisobrittle_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, ph, me)
integer, intent(in) :: &
ph, &
me
real(pReal), intent(in) :: &
phi
real(pReal), intent(out) :: &
localphiDot, &
dLocalphiDot_dPhi
dLocalphiDot_dPhi = -damageState(ph)%state(1,me)
localphiDot = 1.0_pReal &
+ dLocalphiDot_dPhi*phi
end subroutine anisobrittle_getRateAndItsTangent
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief writes results to HDF5 output file !> @brief writes results to HDF5 output file
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------

View File

@ -113,29 +113,6 @@ module subroutine anisoductile_dotState(ph,me)
end subroutine anisoductile_dotState end subroutine anisoductile_dotState
!--------------------------------------------------------------------------------------------------
!> @brief returns local part of nonlocal damage driving force
!--------------------------------------------------------------------------------------------------
module subroutine anisoductile_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, ph,me)
integer, intent(in) :: &
ph, &
me
real(pReal), intent(in) :: &
phi
real(pReal), intent(out) :: &
localphiDot, &
dLocalphiDot_dPhi
dLocalphiDot_dPhi = -damageState(ph)%state(1,me)
localphiDot = 1.0_pReal &
+ dLocalphiDot_dPhi*phi
end subroutine anisoductile_getRateAndItsTangent
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief writes results to HDF5 output file !> @brief writes results to HDF5 output file
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------

View File

@ -113,29 +113,6 @@ module subroutine isobrittle_deltaState(C, Fe, ph,me)
end subroutine isobrittle_deltaState end subroutine isobrittle_deltaState
!--------------------------------------------------------------------------------------------------
!> @brief returns local part of nonlocal damage driving force
!--------------------------------------------------------------------------------------------------
module subroutine isobrittle_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, ph, me)
integer, intent(in) :: &
ph, me
real(pReal), intent(in) :: &
phi
real(pReal), intent(out) :: &
localphiDot, &
dLocalphiDot_dPhi
associate(prm => param(ph))
localphiDot = 1.0_pReal &
- phi*damageState(ph)%state(1,me)
dLocalphiDot_dPhi = - damageState(ph)%state(1,me)
end associate
end subroutine isobrittle_getRateAndItsTangent
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief writes results to HDF5 output file !> @brief writes results to HDF5 output file
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------

View File

@ -103,29 +103,6 @@ module subroutine isoductile_dotState(ph, me)
end subroutine isoductile_dotState end subroutine isoductile_dotState
!--------------------------------------------------------------------------------------------------
!> @brief returns local part of nonlocal damage driving force
!--------------------------------------------------------------------------------------------------
module subroutine isoductile_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, ph, me)
integer, intent(in) :: &
ph, &
me
real(pReal), intent(in) :: &
phi
real(pReal), intent(out) :: &
localphiDot, &
dLocalphiDot_dPhi
dLocalphiDot_dPhi = -damageState(ph)%state(1,me)
localphiDot = 1.0_pReal &
+ dLocalphiDot_dPhi*phi
end subroutine isoductile_getRateAndItsTangent
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief writes results to HDF5 output file !> @brief writes results to HDF5 output file
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------