2020-07-15 18:05:21 +05:30
|
|
|
!----------------------------------------------------------------------------------------------------
|
2020-12-22 16:50:00 +05:30
|
|
|
!> @brief internal microstructure state for all damage sources and kinematics constitutive models
|
2020-07-15 18:05:21 +05:30
|
|
|
!----------------------------------------------------------------------------------------------------
|
2020-07-09 04:31:08 +05:30
|
|
|
submodule(constitutive) constitutive_damage
|
2021-01-08 04:20:06 +05:30
|
|
|
enum, bind(c); enumerator :: &
|
|
|
|
DAMAGE_UNDEFINED_ID, &
|
|
|
|
DAMAGE_ISOBRITTLE_ID, &
|
|
|
|
DAMAGE_ISODUCTILE_ID, &
|
|
|
|
DAMAGE_ANISOBRITTLE_ID, &
|
|
|
|
DAMAGE_ANISODUCTILE_ID
|
|
|
|
end enum
|
|
|
|
|
2021-01-21 01:24:31 +05:30
|
|
|
|
|
|
|
type :: tDataContainer
|
|
|
|
real(pReal), dimension(:), allocatable :: phi, d_phi_d_dot_phi
|
|
|
|
end type tDataContainer
|
|
|
|
|
2021-01-08 04:20:06 +05:30
|
|
|
integer(kind(DAMAGE_UNDEFINED_ID)), dimension(:,:), allocatable :: &
|
|
|
|
phase_source !< active sources mechanisms of each phase
|
2020-07-09 04:31:08 +05:30
|
|
|
|
2021-01-21 01:24:31 +05:30
|
|
|
type(tDataContainer), dimension(:), allocatable :: current
|
|
|
|
|
2020-07-09 04:31:08 +05:30
|
|
|
interface
|
|
|
|
|
2021-01-26 04:08:32 +05:30
|
|
|
module function anisobrittle_init(source_length) result(mySources)
|
|
|
|
integer, intent(in) :: source_length
|
|
|
|
logical, dimension(:,:), allocatable :: mySources
|
|
|
|
end function anisobrittle_init
|
2020-07-09 04:31:08 +05:30
|
|
|
|
2021-01-26 04:08:32 +05:30
|
|
|
module function anisoductile_init(source_length) result(mySources)
|
|
|
|
integer, intent(in) :: source_length
|
|
|
|
logical, dimension(:,:), allocatable :: mySources
|
|
|
|
end function anisoductile_init
|
2020-07-09 04:31:08 +05:30
|
|
|
|
2021-01-26 04:08:32 +05:30
|
|
|
module function isobrittle_init(source_length) result(mySources)
|
|
|
|
integer, intent(in) :: source_length
|
|
|
|
logical, dimension(:,:), allocatable :: mySources
|
|
|
|
end function isobrittle_init
|
2020-07-09 04:31:08 +05:30
|
|
|
|
2021-01-26 04:08:32 +05:30
|
|
|
module function isoductile_init(source_length) result(mySources)
|
|
|
|
integer, intent(in) :: source_length
|
|
|
|
logical, dimension(:,:), allocatable :: mySources
|
|
|
|
end function isoductile_init
|
2020-07-09 04:31:08 +05:30
|
|
|
|
|
|
|
|
2021-01-19 14:55:52 +05:30
|
|
|
module subroutine source_damage_isoBrittle_deltaState(C, Fe, ph, me)
|
|
|
|
integer, intent(in) :: ph,me
|
|
|
|
real(pReal), intent(in), dimension(3,3) :: &
|
|
|
|
Fe
|
|
|
|
real(pReal), intent(in), dimension(6,6) :: &
|
|
|
|
C
|
|
|
|
end subroutine source_damage_isoBrittle_deltaState
|
|
|
|
|
2020-07-10 18:29:07 +05:30
|
|
|
|
2021-01-26 04:08:32 +05:30
|
|
|
module subroutine anisobrittle_dotState(S, co, ip, el)
|
2021-01-19 15:00:10 +05:30
|
|
|
integer, intent(in) :: &
|
|
|
|
co, & !< component-ID of integration point
|
|
|
|
ip, & !< integration point
|
|
|
|
el !< element
|
|
|
|
real(pReal), intent(in), dimension(3,3) :: &
|
|
|
|
S
|
2021-01-26 04:08:32 +05:30
|
|
|
end subroutine anisobrittle_dotState
|
2021-01-19 15:00:10 +05:30
|
|
|
|
2021-01-26 04:08:32 +05:30
|
|
|
module subroutine anisoductile_dotState(co, ip, el)
|
2021-01-19 15:00:10 +05:30
|
|
|
integer, intent(in) :: &
|
|
|
|
co, & !< component-ID of integration point
|
|
|
|
ip, & !< integration point
|
|
|
|
el !< element
|
2021-01-26 04:08:32 +05:30
|
|
|
end subroutine anisoductile_dotState
|
2021-01-19 15:00:10 +05:30
|
|
|
|
2021-01-26 04:08:32 +05:30
|
|
|
module subroutine isoductile_dotState(co, ip, el)
|
2021-01-19 15:00:10 +05:30
|
|
|
integer, intent(in) :: &
|
|
|
|
co, & !< component-ID of integration point
|
|
|
|
ip, & !< integration point
|
|
|
|
el !< element
|
2021-01-26 04:08:32 +05:30
|
|
|
end subroutine isoductile_dotState
|
|
|
|
|
|
|
|
|
|
|
|
module subroutine source_damage_anisobrittle_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, phase, constituent)
|
|
|
|
integer, intent(in) :: &
|
|
|
|
phase, & !< phase ID of element
|
|
|
|
constituent !< position of element within its phase instance
|
|
|
|
real(pReal), intent(in) :: &
|
|
|
|
phi !< damage parameter
|
|
|
|
real(pReal), intent(out) :: &
|
|
|
|
localphiDot, &
|
|
|
|
dLocalphiDot_dPhi
|
|
|
|
end subroutine source_damage_anisoBrittle_getRateAndItsTangent
|
|
|
|
|
|
|
|
module subroutine source_damage_anisoDuctile_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, phase, constituent)
|
|
|
|
integer, intent(in) :: &
|
|
|
|
phase, & !< phase ID of element
|
|
|
|
constituent !< position of element within its phase instance
|
|
|
|
real(pReal), intent(in) :: &
|
|
|
|
phi !< damage parameter
|
|
|
|
real(pReal), intent(out) :: &
|
|
|
|
localphiDot, &
|
|
|
|
dLocalphiDot_dPhi
|
|
|
|
end subroutine source_damage_anisoDuctile_getRateAndItsTangent
|
|
|
|
|
|
|
|
module subroutine source_damage_isoBrittle_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, phase, constituent)
|
|
|
|
integer, intent(in) :: &
|
|
|
|
phase, & !< phase ID of element
|
|
|
|
constituent !< position of element within its phase instance
|
|
|
|
real(pReal), intent(in) :: &
|
|
|
|
phi !< damage parameter
|
|
|
|
real(pReal), intent(out) :: &
|
|
|
|
localphiDot, &
|
|
|
|
dLocalphiDot_dPhi
|
|
|
|
end subroutine source_damage_isoBrittle_getRateAndItsTangent
|
|
|
|
|
|
|
|
module subroutine source_damage_isoDuctile_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, phase, constituent)
|
|
|
|
integer, intent(in) :: &
|
|
|
|
phase, & !< phase ID of element
|
|
|
|
constituent !< position of element within its phase instance
|
|
|
|
real(pReal), intent(in) :: &
|
|
|
|
phi !< damage parameter
|
|
|
|
real(pReal), intent(out) :: &
|
|
|
|
localphiDot, &
|
|
|
|
dLocalphiDot_dPhi
|
|
|
|
end subroutine source_damage_isoDuctile_getRateAndItsTangent
|
|
|
|
|
|
|
|
module subroutine anisobrittle_results(phase,group)
|
|
|
|
integer, intent(in) :: phase
|
|
|
|
character(len=*), intent(in) :: group
|
|
|
|
end subroutine anisobrittle_results
|
|
|
|
|
|
|
|
module subroutine anisoductile_results(phase,group)
|
|
|
|
integer, intent(in) :: phase
|
|
|
|
character(len=*), intent(in) :: group
|
|
|
|
end subroutine anisoductile_results
|
|
|
|
|
|
|
|
module subroutine isobrittle_results(phase,group)
|
|
|
|
integer, intent(in) :: phase
|
|
|
|
character(len=*), intent(in) :: group
|
|
|
|
end subroutine isobrittle_results
|
|
|
|
|
|
|
|
module subroutine isoductile_results(phase,group)
|
|
|
|
integer, intent(in) :: phase
|
|
|
|
character(len=*), intent(in) :: group
|
|
|
|
end subroutine isoductile_results
|
2020-07-12 18:52:40 +05:30
|
|
|
|
2020-07-09 04:31:08 +05:30
|
|
|
end interface
|
|
|
|
|
|
|
|
contains
|
|
|
|
|
2020-07-12 20:14:26 +05:30
|
|
|
!----------------------------------------------------------------------------------------------
|
|
|
|
!< @brief initialize damage sources and kinematics mechanism
|
|
|
|
!----------------------------------------------------------------------------------------------
|
2020-07-09 04:31:08 +05:30
|
|
|
module subroutine damage_init
|
|
|
|
|
2020-08-15 19:32:10 +05:30
|
|
|
integer :: &
|
2021-01-21 01:24:31 +05:30
|
|
|
ph, & !< counter in phase loop
|
|
|
|
Nconstituents
|
2020-08-15 19:32:10 +05:30
|
|
|
class(tNode), pointer :: &
|
|
|
|
phases, &
|
|
|
|
phase, &
|
2021-01-26 01:01:12 +05:30
|
|
|
sources
|
2020-08-15 19:32:10 +05:30
|
|
|
|
2020-09-13 14:09:17 +05:30
|
|
|
phases => config_material%get('phase')
|
2020-08-15 19:32:10 +05:30
|
|
|
|
2021-01-21 01:24:31 +05:30
|
|
|
allocate(current(phases%length))
|
|
|
|
|
2021-01-08 11:40:38 +05:30
|
|
|
allocate(damageState (phases%length))
|
2021-01-26 04:08:32 +05:30
|
|
|
allocate(phase_Nsources(phases%length),source = 0)
|
2020-08-15 19:32:10 +05:30
|
|
|
|
|
|
|
do ph = 1,phases%length
|
2021-01-21 01:24:31 +05:30
|
|
|
|
2021-01-26 04:08:32 +05:30
|
|
|
Nconstituents = count(material_phaseAt2 == ph)
|
2021-01-21 01:24:31 +05:30
|
|
|
|
|
|
|
allocate(current(ph)%phi(Nconstituents),source=1.0_pReal)
|
|
|
|
allocate(current(ph)%d_phi_d_dot_phi(Nconstituents),source=0.0_pReal)
|
|
|
|
|
2020-08-15 19:32:10 +05:30
|
|
|
phase => phases%get(ph)
|
|
|
|
sources => phase%get('source',defaultVal=emptyList)
|
|
|
|
phase_Nsources(ph) = sources%length
|
2021-01-08 11:40:38 +05:30
|
|
|
allocate(damageState(ph)%p(phase_Nsources(ph)))
|
2020-08-15 19:32:10 +05:30
|
|
|
enddo
|
|
|
|
|
2021-01-08 04:20:06 +05:30
|
|
|
allocate(phase_source(maxval(phase_Nsources),phases%length), source = DAMAGE_UNDEFINED_ID)
|
2020-08-15 19:32:10 +05:30
|
|
|
|
2020-07-09 04:31:08 +05:30
|
|
|
! initialize source mechanisms
|
2020-08-15 19:32:10 +05:30
|
|
|
if(maxval(phase_Nsources) /= 0) then
|
2021-01-26 04:08:32 +05:30
|
|
|
where(isobrittle_init (maxval(phase_Nsources))) phase_source = DAMAGE_ISOBRITTLE_ID
|
|
|
|
where(isoductile_init (maxval(phase_Nsources))) phase_source = DAMAGE_ISODUCTILE_ID
|
|
|
|
where(anisobrittle_init (maxval(phase_Nsources))) phase_source = DAMAGE_ANISOBRITTLE_ID
|
|
|
|
where(anisoductile_init (maxval(phase_Nsources))) phase_source = DAMAGE_ANISODUCTILE_ID
|
2020-08-15 19:32:10 +05:30
|
|
|
endif
|
2020-07-09 04:31:08 +05:30
|
|
|
|
|
|
|
end subroutine damage_init
|
|
|
|
|
|
|
|
|
2020-07-12 20:14:26 +05:30
|
|
|
!----------------------------------------------------------------------------------------------
|
|
|
|
!< @brief returns local part of nonlocal damage driving force
|
|
|
|
!----------------------------------------------------------------------------------------------
|
|
|
|
module subroutine constitutive_damage_getRateAndItsTangents(phiDot, dPhiDot_dPhi, phi, ip, el)
|
|
|
|
|
|
|
|
integer, intent(in) :: &
|
2020-07-15 18:05:21 +05:30
|
|
|
ip, & !< integration point number
|
|
|
|
el !< element number
|
2020-07-12 20:14:26 +05:30
|
|
|
real(pReal), intent(in) :: &
|
2020-12-22 16:50:00 +05:30
|
|
|
phi !< damage parameter
|
2020-07-12 20:14:26 +05:30
|
|
|
real(pReal), intent(inout) :: &
|
|
|
|
phiDot, &
|
|
|
|
dPhiDot_dPhi
|
2020-07-09 04:31:08 +05:30
|
|
|
|
|
|
|
real(pReal) :: &
|
|
|
|
localphiDot, &
|
|
|
|
dLocalphiDot_dPhi
|
|
|
|
integer :: &
|
2021-01-26 04:08:32 +05:30
|
|
|
ph, &
|
|
|
|
co, &
|
|
|
|
so, &
|
|
|
|
me
|
2020-07-09 04:31:08 +05:30
|
|
|
|
|
|
|
phiDot = 0.0_pReal
|
|
|
|
dPhiDot_dPhi = 0.0_pReal
|
2020-12-22 16:50:00 +05:30
|
|
|
|
2021-01-26 04:08:32 +05:30
|
|
|
do co = 1, homogenization_Nconstituents(material_homogenizationAt(el))
|
|
|
|
ph = material_phaseAt(co,el)
|
|
|
|
me = material_phasememberAt(co,ip,el)
|
|
|
|
do so = 1, phase_Nsources(ph)
|
|
|
|
select case(phase_source(so,ph))
|
2021-01-08 04:20:06 +05:30
|
|
|
case (DAMAGE_ISOBRITTLE_ID)
|
2021-01-26 04:08:32 +05:30
|
|
|
call source_damage_isobrittle_getRateAndItsTangent (localphiDot, dLocalphiDot_dPhi, phi, ph, me)
|
2020-07-09 04:31:08 +05:30
|
|
|
|
2021-01-08 04:20:06 +05:30
|
|
|
case (DAMAGE_ISODUCTILE_ID)
|
2021-01-26 04:08:32 +05:30
|
|
|
call source_damage_isoductile_getRateAndItsTangent (localphiDot, dLocalphiDot_dPhi, phi, ph, me)
|
2020-07-09 04:31:08 +05:30
|
|
|
|
2021-01-08 04:20:06 +05:30
|
|
|
case (DAMAGE_ANISOBRITTLE_ID)
|
2021-01-26 04:08:32 +05:30
|
|
|
call source_damage_anisobrittle_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, ph, me)
|
2020-07-09 04:31:08 +05:30
|
|
|
|
2021-01-08 04:20:06 +05:30
|
|
|
case (DAMAGE_ANISODUCTILE_ID)
|
2021-01-26 04:08:32 +05:30
|
|
|
call source_damage_anisoductile_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, ph, me)
|
2020-07-09 04:31:08 +05:30
|
|
|
|
|
|
|
case default
|
|
|
|
localphiDot = 0.0_pReal
|
|
|
|
dLocalphiDot_dPhi = 0.0_pReal
|
|
|
|
|
|
|
|
end select
|
|
|
|
phiDot = phiDot + localphiDot
|
|
|
|
dPhiDot_dPhi = dPhiDot_dPhi + dLocalphiDot_dPhi
|
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
|
2020-07-12 20:14:26 +05:30
|
|
|
end subroutine constitutive_damage_getRateAndItsTangents
|
2020-07-09 04:31:08 +05:30
|
|
|
|
2020-07-12 18:52:40 +05:30
|
|
|
|
2021-01-08 04:02:54 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief integrate stress, state with adaptive 1st order explicit Euler method
|
|
|
|
!> using Fixed Point Iteration to adapt the stepsize
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
module function integrateDamageState(dt,co,ip,el) result(broken)
|
|
|
|
|
|
|
|
real(pReal), intent(in) :: dt
|
|
|
|
integer, intent(in) :: &
|
|
|
|
el, & !< element index in element loop
|
|
|
|
ip, & !< integration point index in ip loop
|
|
|
|
co !< grain index in grain loop
|
|
|
|
logical :: broken
|
|
|
|
|
|
|
|
integer :: &
|
|
|
|
NiterationState, & !< number of iterations in state loop
|
|
|
|
ph, &
|
|
|
|
me, &
|
|
|
|
so
|
|
|
|
integer, dimension(maxval(phase_Nsources)) :: &
|
|
|
|
size_so
|
|
|
|
real(pReal) :: &
|
|
|
|
zeta
|
|
|
|
real(pReal), dimension(constitutive_source_maxSizeDotState) :: &
|
|
|
|
r ! state residuum
|
|
|
|
real(pReal), dimension(constitutive_source_maxSizeDotState,2,maxval(phase_Nsources)) :: source_dotState
|
|
|
|
logical :: &
|
|
|
|
converged_
|
|
|
|
|
|
|
|
|
|
|
|
ph = material_phaseAt(co,el)
|
|
|
|
me = material_phaseMemberAt(co,ip,el)
|
|
|
|
|
|
|
|
converged_ = .true.
|
|
|
|
broken = constitutive_damage_collectDotState(co,ip,el,ph,me)
|
|
|
|
if(broken) return
|
|
|
|
|
|
|
|
do so = 1, phase_Nsources(ph)
|
2021-01-08 11:40:38 +05:30
|
|
|
size_so(so) = damageState(ph)%p(so)%sizeDotState
|
|
|
|
damageState(ph)%p(so)%state(1:size_so(so),me) = damageState(ph)%p(so)%subState0(1:size_so(so),me) &
|
|
|
|
+ damageState(ph)%p(so)%dotState (1:size_so(so),me) * dt
|
2021-01-08 04:02:54 +05:30
|
|
|
source_dotState(1:size_so(so),2,so) = 0.0_pReal
|
|
|
|
enddo
|
|
|
|
|
|
|
|
iteration: do NiterationState = 1, num%nState
|
|
|
|
|
|
|
|
do so = 1, phase_Nsources(ph)
|
|
|
|
if(nIterationState > 1) source_dotState(1:size_so(so),2,so) = source_dotState(1:size_so(so),1,so)
|
2021-01-08 11:40:38 +05:30
|
|
|
source_dotState(1:size_so(so),1,so) = damageState(ph)%p(so)%dotState(:,me)
|
2021-01-08 04:02:54 +05:30
|
|
|
enddo
|
|
|
|
|
|
|
|
broken = constitutive_damage_collectDotState(co,ip,el,ph,me)
|
|
|
|
if(broken) exit iteration
|
|
|
|
|
|
|
|
do so = 1, phase_Nsources(ph)
|
2021-01-08 11:40:38 +05:30
|
|
|
zeta = damper(damageState(ph)%p(so)%dotState(:,me), &
|
2021-01-08 04:02:54 +05:30
|
|
|
source_dotState(1:size_so(so),1,so),&
|
|
|
|
source_dotState(1:size_so(so),2,so))
|
2021-01-08 11:40:38 +05:30
|
|
|
damageState(ph)%p(so)%dotState(:,me) = damageState(ph)%p(so)%dotState(:,me) * zeta &
|
2021-01-08 04:02:54 +05:30
|
|
|
+ source_dotState(1:size_so(so),1,so)* (1.0_pReal - zeta)
|
2021-01-08 11:40:38 +05:30
|
|
|
r(1:size_so(so)) = damageState(ph)%p(so)%state (1:size_so(so),me) &
|
|
|
|
- damageState(ph)%p(so)%subState0(1:size_so(so),me) &
|
|
|
|
- damageState(ph)%p(so)%dotState (1:size_so(so),me) * dt
|
|
|
|
damageState(ph)%p(so)%state(1:size_so(so),me) = damageState(ph)%p(so)%state(1:size_so(so),me) &
|
2021-01-08 04:02:54 +05:30
|
|
|
- r(1:size_so(so))
|
|
|
|
converged_ = converged_ .and. converged(r(1:size_so(so)), &
|
2021-01-08 11:40:38 +05:30
|
|
|
damageState(ph)%p(so)%state(1:size_so(so),me), &
|
|
|
|
damageState(ph)%p(so)%atol(1:size_so(so)))
|
2021-01-08 04:02:54 +05:30
|
|
|
enddo
|
|
|
|
|
|
|
|
if(converged_) then
|
2021-01-19 14:55:52 +05:30
|
|
|
broken = constitutive_damage_deltaState(mech_F_e(ph,me),ph,me)
|
2021-01-08 04:02:54 +05:30
|
|
|
exit iteration
|
|
|
|
endif
|
|
|
|
|
|
|
|
enddo iteration
|
|
|
|
|
|
|
|
broken = broken .or. .not. converged_
|
|
|
|
|
|
|
|
|
|
|
|
contains
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief calculate the damping for correction of state and dot state
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
real(pReal) pure function damper(current,previous,previous2)
|
|
|
|
|
|
|
|
real(pReal), dimension(:), intent(in) ::&
|
|
|
|
current, previous, previous2
|
|
|
|
|
|
|
|
real(pReal) :: dot_prod12, dot_prod22
|
|
|
|
|
|
|
|
dot_prod12 = dot_product(current - previous, previous - previous2)
|
|
|
|
dot_prod22 = dot_product(previous - previous2, previous - previous2)
|
|
|
|
if ((dot_product(current,previous) < 0.0_pReal .or. dot_prod12 < 0.0_pReal) .and. dot_prod22 > 0.0_pReal) then
|
|
|
|
damper = 0.75_pReal + 0.25_pReal * tanh(2.0_pReal + 4.0_pReal * dot_prod12 / dot_prod22)
|
|
|
|
else
|
|
|
|
damper = 1.0_pReal
|
|
|
|
endif
|
|
|
|
|
|
|
|
end function damper
|
|
|
|
|
|
|
|
end function integrateDamageState
|
|
|
|
|
|
|
|
|
2020-07-12 20:14:26 +05:30
|
|
|
!----------------------------------------------------------------------------------------------
|
2020-08-15 19:32:10 +05:30
|
|
|
!< @brief writes damage sources results to HDF5 output file
|
2020-07-12 20:14:26 +05:30
|
|
|
!----------------------------------------------------------------------------------------------
|
2020-12-22 16:50:00 +05:30
|
|
|
module subroutine damage_results(group,ph)
|
2020-07-12 18:52:40 +05:30
|
|
|
|
2020-12-22 16:50:00 +05:30
|
|
|
character(len=*), intent(in) :: group
|
|
|
|
integer, intent(in) :: ph
|
2020-07-12 18:52:40 +05:30
|
|
|
|
2020-12-22 16:50:00 +05:30
|
|
|
integer :: so
|
2020-08-15 19:32:10 +05:30
|
|
|
|
2020-12-22 16:50:00 +05:30
|
|
|
sourceLoop: do so = 1, phase_Nsources(ph)
|
2020-07-12 18:52:40 +05:30
|
|
|
|
2021-01-08 04:20:06 +05:30
|
|
|
if (phase_source(so,ph) /= DAMAGE_UNDEFINED_ID) &
|
2020-12-23 02:52:43 +05:30
|
|
|
call results_closeGroup(results_addGroup(group//'sources/')) ! should be 'damage'
|
2020-07-12 18:52:40 +05:30
|
|
|
|
2020-12-22 16:50:00 +05:30
|
|
|
sourceType: select case (phase_source(so,ph))
|
2020-07-12 18:52:40 +05:30
|
|
|
|
2021-01-08 04:20:06 +05:30
|
|
|
case (DAMAGE_ISOBRITTLE_ID) sourceType
|
2021-01-26 04:08:32 +05:30
|
|
|
call isobrittle_results(ph,group//'sources/')
|
2020-12-22 16:50:00 +05:30
|
|
|
|
2021-01-08 04:20:06 +05:30
|
|
|
case (DAMAGE_ISODUCTILE_ID) sourceType
|
2021-01-26 04:08:32 +05:30
|
|
|
call isoductile_results(ph,group//'sources/')
|
2020-12-22 16:50:00 +05:30
|
|
|
|
2021-01-08 04:20:06 +05:30
|
|
|
case (DAMAGE_ANISOBRITTLE_ID) sourceType
|
2021-01-26 04:08:32 +05:30
|
|
|
call anisobrittle_results(ph,group//'sources/')
|
2020-12-22 16:50:00 +05:30
|
|
|
|
2021-01-08 04:20:06 +05:30
|
|
|
case (DAMAGE_ANISODUCTILE_ID) sourceType
|
2021-01-26 04:08:32 +05:30
|
|
|
call anisoductile_results(ph,group//'sources/')
|
2020-12-22 16:50:00 +05:30
|
|
|
|
|
|
|
end select sourceType
|
|
|
|
|
|
|
|
enddo SourceLoop
|
2020-07-12 18:52:40 +05:30
|
|
|
|
|
|
|
end subroutine damage_results
|
|
|
|
|
|
|
|
|
2021-01-08 04:02:54 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief contains the constitutive equation for calculating the rate of change of microstructure
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2021-01-19 15:09:16 +05:30
|
|
|
function constitutive_damage_collectDotState(co,ip,el,ph,me) result(broken)
|
2021-01-08 04:02:54 +05:30
|
|
|
|
|
|
|
integer, intent(in) :: &
|
2021-01-19 15:09:16 +05:30
|
|
|
co, & !< component-ID me integration point
|
2021-01-08 04:02:54 +05:30
|
|
|
ip, & !< integration point
|
|
|
|
el, & !< element
|
|
|
|
ph, &
|
2021-01-19 15:09:16 +05:30
|
|
|
me
|
2021-01-08 04:02:54 +05:30
|
|
|
integer :: &
|
|
|
|
so !< counter in source loop
|
|
|
|
logical :: broken
|
|
|
|
|
|
|
|
|
|
|
|
broken = .false.
|
|
|
|
|
|
|
|
SourceLoop: do so = 1, phase_Nsources(ph)
|
|
|
|
|
|
|
|
sourceType: select case (phase_source(so,ph))
|
|
|
|
|
2021-01-08 04:20:06 +05:30
|
|
|
case (DAMAGE_ISODUCTILE_ID) sourceType
|
2021-01-26 04:08:32 +05:30
|
|
|
call isoductile_dotState(co, ip, el)
|
2021-01-08 04:02:54 +05:30
|
|
|
|
2021-01-08 04:20:06 +05:30
|
|
|
case (DAMAGE_ANISODUCTILE_ID) sourceType
|
2021-01-26 04:08:32 +05:30
|
|
|
call anisoductile_dotState(co, ip, el)
|
2021-01-08 04:02:54 +05:30
|
|
|
|
2021-01-08 05:14:16 +05:30
|
|
|
case (DAMAGE_ANISOBRITTLE_ID) sourceType
|
2021-01-26 04:08:32 +05:30
|
|
|
call anisobrittle_dotState(mech_S(ph,me),co, ip, el) ! correct stress?
|
2021-01-08 05:14:16 +05:30
|
|
|
|
2021-01-08 04:02:54 +05:30
|
|
|
end select sourceType
|
|
|
|
|
2021-01-19 15:09:16 +05:30
|
|
|
broken = broken .or. any(IEEE_is_NaN(damageState(ph)%p(so)%dotState(:,me)))
|
2021-01-08 04:02:54 +05:30
|
|
|
|
|
|
|
enddo SourceLoop
|
|
|
|
|
|
|
|
end function constitutive_damage_collectDotState
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief for constitutive models having an instantaneous change of state
|
|
|
|
!> will return false if delta state is not needed/supported by the constitutive model
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2021-01-19 14:55:52 +05:30
|
|
|
function constitutive_damage_deltaState(Fe, ph, me) result(broken)
|
2021-01-08 04:02:54 +05:30
|
|
|
|
|
|
|
integer, intent(in) :: &
|
|
|
|
ph, &
|
2021-01-19 14:51:51 +05:30
|
|
|
me
|
2021-01-08 04:02:54 +05:30
|
|
|
real(pReal), intent(in), dimension(3,3) :: &
|
|
|
|
Fe !< elastic deformation gradient
|
|
|
|
integer :: &
|
|
|
|
so, &
|
|
|
|
myOffset, &
|
|
|
|
mySize
|
|
|
|
logical :: &
|
|
|
|
broken
|
|
|
|
|
|
|
|
|
|
|
|
broken = .false.
|
|
|
|
|
|
|
|
sourceLoop: do so = 1, phase_Nsources(ph)
|
|
|
|
|
|
|
|
sourceType: select case (phase_source(so,ph))
|
|
|
|
|
2021-01-08 04:20:06 +05:30
|
|
|
case (DAMAGE_ISOBRITTLE_ID) sourceType
|
2021-01-19 14:55:52 +05:30
|
|
|
call source_damage_isoBrittle_deltaState(constitutive_homogenizedC(ph,me), Fe, ph,me)
|
2021-01-19 14:51:51 +05:30
|
|
|
broken = any(IEEE_is_NaN(damageState(ph)%p(so)%deltaState(:,me)))
|
2021-01-08 04:02:54 +05:30
|
|
|
if(.not. broken) then
|
2021-01-08 11:40:38 +05:30
|
|
|
myOffset = damageState(ph)%p(so)%offsetDeltaState
|
|
|
|
mySize = damageState(ph)%p(so)%sizeDeltaState
|
2021-01-19 14:51:51 +05:30
|
|
|
damageState(ph)%p(so)%state(myOffset + 1: myOffset + mySize,me) = &
|
|
|
|
damageState(ph)%p(so)%state(myOffset + 1: myOffset + mySize,me) + damageState(ph)%p(so)%deltaState(1:mySize,me)
|
2021-01-08 04:02:54 +05:30
|
|
|
endif
|
|
|
|
|
|
|
|
end select sourceType
|
|
|
|
|
|
|
|
enddo SourceLoop
|
|
|
|
|
|
|
|
end function constitutive_damage_deltaState
|
|
|
|
|
|
|
|
|
2021-01-08 12:07:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief checks if a source mechanism is active or not
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
function source_active(source_label,src_length) result(active_source)
|
|
|
|
|
|
|
|
character(len=*), intent(in) :: source_label !< name of source mechanism
|
|
|
|
integer, intent(in) :: src_length !< max. number of sources in system
|
|
|
|
logical, dimension(:,:), allocatable :: active_source
|
|
|
|
|
|
|
|
class(tNode), pointer :: &
|
|
|
|
phases, &
|
|
|
|
phase, &
|
|
|
|
sources, &
|
|
|
|
src
|
|
|
|
integer :: p,s
|
|
|
|
|
|
|
|
phases => config_material%get('phase')
|
|
|
|
allocate(active_source(src_length,phases%length), source = .false. )
|
|
|
|
do p = 1, phases%length
|
|
|
|
phase => phases%get(p)
|
|
|
|
sources => phase%get('source',defaultVal=emptyList)
|
|
|
|
do s = 1, sources%length
|
|
|
|
src => sources%get(s)
|
|
|
|
if(src%get_asString('type') == source_label) active_source(s,p) = .true.
|
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
|
|
|
|
|
|
|
|
end function source_active
|
|
|
|
|
|
|
|
|
2021-01-21 01:24:31 +05:30
|
|
|
!----------------------------------------------------------------------------------------------
|
|
|
|
!< @brief Set damage parameter
|
|
|
|
!----------------------------------------------------------------------------------------------
|
|
|
|
module subroutine constitutive_damage_set_phi(phi,co,ce)
|
|
|
|
|
|
|
|
real(pReal), intent(in) :: phi
|
|
|
|
integer, intent(in) :: ce, co
|
|
|
|
|
|
|
|
|
|
|
|
current(material_phaseAt2(co,ce))%phi(material_phaseMemberAt2(co,ce)) = phi
|
|
|
|
|
|
|
|
end subroutine constitutive_damage_set_phi
|
|
|
|
|
|
|
|
|
|
|
|
module function constitutive_damage_get_phi(co,ip,el) result(phi)
|
2021-01-26 01:01:12 +05:30
|
|
|
|
2021-01-21 01:24:31 +05:30
|
|
|
integer, intent(in) :: co, ip, el
|
|
|
|
real(pReal) :: phi
|
|
|
|
|
|
|
|
phi = current(material_phaseAt(co,el))%phi(material_phaseMemberAt(co,ip,el))
|
|
|
|
|
|
|
|
end function constitutive_damage_get_phi
|
|
|
|
|
|
|
|
|
2020-07-15 18:05:21 +05:30
|
|
|
end submodule constitutive_damage
|