DAMASK_EICMD/src/phase_damage.f90

527 lines
16 KiB
Fortran
Raw Normal View History

!--------------------------------------------------------------------------------------------------
2020-12-22 16:50:00 +05:30
!> @brief internal microstructure state for all damage sources and kinematics constitutive models
!--------------------------------------------------------------------------------------------------
submodule(phase) damage
2021-04-11 12:16:31 +05:30
type :: tDamageParameters
real(pREAL) :: &
mu = 0.0_pREAL, & !< viscosity
l_c = 0.0_pREAL !< characteristic length
2021-04-11 12:16:31 +05:30
end type tDamageParameters
integer :: phase_damage_maxSizeDotState
2023-07-18 08:12:14 +05:30
type :: tFieldQuantities
real(pREAL), dimension(:), allocatable :: phi
2023-07-18 08:12:14 +05:30
end type tFieldQuantities
2021-01-21 01:24:31 +05:30
2023-07-18 08:12:14 +05:30
type(tFieldQuantities), dimension(:), allocatable :: current
2021-01-21 01:24:31 +05:30
2021-04-11 12:16:31 +05:30
type(tDamageParameters), dimension(:), allocatable :: param
interface
2021-02-13 17:14:47 +05:30
module function anisobrittle_init() result(mySources)
logical, dimension(:), allocatable :: mySources
2021-01-26 04:08:32 +05:30
end function anisobrittle_init
2021-02-13 17:14:47 +05:30
module function isobrittle_init() result(mySources)
logical, dimension(:), allocatable :: mySources
2021-01-26 04:08:32 +05:30
end function isobrittle_init
module subroutine isobrittle_deltaState(C, Fe, ph, en)
integer, intent(in) :: ph,en
real(pREAL), intent(in), dimension(3,3) :: &
2021-01-19 14:55:52 +05:30
Fe
real(pREAL), intent(in), dimension(6,6) :: &
2021-01-19 14:55:52 +05:30
C
2021-02-13 15:31:08 +05:30
end subroutine isobrittle_deltaState
2021-01-19 14:55:52 +05:30
2020-07-10 18:29:07 +05:30
module subroutine anisobrittle_dotState(M_i, ph, en)
integer, intent(in) :: ph,en
real(pREAL), intent(in), dimension(3,3) :: &
M_i
2021-01-26 04:08:32 +05:30
end subroutine anisobrittle_dotState
2021-01-19 15:00:10 +05:30
2023-01-19 22:07:45 +05:30
module subroutine anisobrittle_result(phase,group)
2021-01-26 04:08:32 +05:30
integer, intent(in) :: phase
character(len=*), intent(in) :: group
2023-01-19 22:07:45 +05:30
end subroutine anisobrittle_result
2021-01-26 04:08:32 +05:30
2023-01-19 22:07:45 +05:30
module subroutine isobrittle_result(phase,group)
2021-01-26 04:08:32 +05:30
integer, intent(in) :: phase
character(len=*), intent(in) :: group
2023-01-19 22:07:45 +05:30
end subroutine isobrittle_result
2021-01-26 04:08:32 +05:30
end interface
contains
2020-07-12 20:14:26 +05:30
!----------------------------------------------------------------------------------------------
!< @brief Initialize damage mechanisms.
2020-07-12 20:14:26 +05:30
!----------------------------------------------------------------------------------------------
module subroutine damage_init()
2020-08-15 19:32:10 +05:30
integer :: &
2021-07-07 02:28:18 +05:30
ph, &
2021-03-05 01:46:36 +05:30
Nmembers
type(tDict), pointer :: &
phases, &
phase, &
source
character(len=:), allocatable :: refs
logical:: damage_active
2021-01-27 15:14:03 +05:30
2023-01-18 23:20:01 +05:30
print'(/,1x,a)', '<<<+- phase:damage init -+>>>'
2021-01-27 15:14:03 +05:30
2020-08-15 19:32:10 +05:30
2023-01-18 23:20:01 +05:30
phases => config_material%get_dict('phase')
2021-01-21 01:24:31 +05:30
allocate(current(phases%length))
allocate(damageState(phases%length))
2021-04-11 12:16:31 +05:30
allocate(param(phases%length))
2020-08-15 19:32:10 +05:30
damage_active = .false.
2020-08-15 19:32:10 +05:30
do ph = 1,phases%length
2021-01-21 01:24:31 +05:30
2023-01-23 13:01:59 +05:30
Nmembers = count(material_ID_phase == ph)
2021-01-21 01:24:31 +05:30
allocate(current(ph)%phi(Nmembers),source=1.0_pREAL)
2021-01-21 01:24:31 +05:30
phase => phases%get_dict(ph)
source => phase%get_dict('damage',defaultVal=emptyDict)
if (source%length > 0) then
print'(/,1x,a,i0,a)', 'phase ',ph,': '//phases%key(ph)
refs = config_listReferences(source,indent=3)
if (len(refs) > 0) print'(/,1x,a)', refs
damage_active = .true.
param(ph)%mu = source%get_asReal('mu')
param(ph)%l_c = source%get_asReal('l_c')
end if
end do
2020-08-15 19:32:10 +05:30
allocate(damage_type(phases%length), source = UNDEFINED)
2020-08-15 19:32:10 +05:30
if (damage_active) then
where(isobrittle_init() ) damage_type = DAMAGE_ISOBRITTLE
where(anisobrittle_init()) damage_type = DAMAGE_ANISOBRITTLE
end if
2022-06-24 10:34:52 +05:30
phase_damage_maxSizeDotState = maxval(damageState%sizeDotState)
end subroutine damage_init
!--------------------------------------------------------------------------------------------------
!> @brief calculate stress (P)
!--------------------------------------------------------------------------------------------------
module function phase_damage_constitutive(Delta_t,co,ce) result(status)
real(pREAL), intent(in) :: Delta_t
integer, intent(in) :: &
co, &
2022-02-04 16:55:11 +05:30
ce
integer(kind(STATUS_OK)) :: status
integer :: &
ph, en
2021-11-18 21:26:36 +05:30
2023-01-23 13:01:59 +05:30
ph = material_ID_phase(co,ce)
en = material_entry_phase(co,ce)
status = integrateDamageState(Delta_t,ph,en)
end function phase_damage_constitutive
!--------------------------------------------------------------------------------------------------
!> @brief returns the degraded/modified elasticity matrix
!--------------------------------------------------------------------------------------------------
2021-11-19 02:29:09 +05:30
module function phase_damage_C66(C66,ph,en) result(C66_degraded)
2021-11-18 21:26:36 +05:30
real(pREAL), dimension(6,6), intent(in) :: C66
2021-11-18 21:26:36 +05:30
integer, intent(in) :: ph,en
real(pREAL), dimension(6,6) :: C66_degraded
damageType: select case (damage_type(ph))
case (DAMAGE_ISOBRITTLE) damageType
2022-06-24 10:34:52 +05:30
C66_degraded = C66 * damage_phi(ph,en)**2
case default damageType
2022-06-24 10:34:52 +05:30
C66_degraded = C66
end select damageType
2021-11-18 21:26:36 +05:30
end function phase_damage_C66
2021-07-17 03:02:08 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief Restore data after homog cutback.
!--------------------------------------------------------------------------------------------------
module subroutine damage_restore(ce)
integer, intent(in) :: ce
integer :: &
co
2023-01-23 13:01:59 +05:30
do co = 1,homogenization_Nconstituents(material_ID_homogenization(ce))
if (damageState(material_ID_phase(co,ce))%sizeState > 0) &
damageState(material_ID_phase(co,ce))%state( :,material_entry_phase(co,ce)) = &
damageState(material_ID_phase(co,ce))%state0(:,material_entry_phase(co,ce))
end do
2021-07-17 03:02:08 +05:30
end subroutine damage_restore
2020-07-12 20:14:26 +05:30
!----------------------------------------------------------------------------------------------
!< @brief returns local part of nonlocal damage driving force
!----------------------------------------------------------------------------------------------
2021-04-09 03:10:20 +05:30
module function phase_f_phi(phi,co,ce) result(f)
2020-07-12 20:14:26 +05:30
2021-04-07 16:32:42 +05:30
integer, intent(in) :: ce,co
real(pREAL), intent(in) :: &
2020-12-22 16:50:00 +05:30
phi !< damage parameter
real(pREAL) :: &
2021-04-09 03:10:20 +05:30
f
integer :: &
2021-01-26 04:08:32 +05:30
ph, &
en
2023-07-24 22:00:02 +05:30
2023-01-23 13:01:59 +05:30
ph = material_ID_phase(co,ce)
en = material_entry_phase(co,ce)
select case(damage_type(ph))
case(DAMAGE_ISOBRITTLE,DAMAGE_ANISOBRITTLE)
f = 1.0_pREAL &
2023-07-24 22:00:02 +05:30
- 2.0_pREAL * phi*damageState(ph)%state(1,en) ! ToDo: MD: seems to be phi**2
case default
f = 0.0_pREAL
end select
2021-04-08 17:01:21 +05:30
end function phase_f_phi
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
!--------------------------------------------------------------------------------------------------
2024-01-09 11:56:28 +05:30
function integrateDamageState(Delta_t,ph,en) result(status)
2021-01-08 04:02:54 +05:30
real(pREAL), intent(in) :: Delta_t
2021-01-08 04:02:54 +05:30
integer, intent(in) :: &
2021-07-18 13:18:49 +05:30
ph, &
en
2024-01-09 11:56:28 +05:30
integer(kind(STATUS_OK)) :: status
2021-01-08 04:02:54 +05:30
integer :: &
NiterationState, & !< number of iterations in state loop
size_so
real(pREAL) :: &
2021-01-08 04:02:54 +05:30
zeta
real(pREAL), dimension(phase_damage_maxSizeDotState) :: &
2021-01-08 04:02:54 +05:30
r ! state residuum
real(pREAL), dimension(phase_damage_maxSizeDotState,2) :: source_dotState
2021-01-08 04:02:54 +05:30
logical :: &
converged_
2021-02-13 23:11:30 +05:30
if (damageState(ph)%sizeState == 0) then
2024-01-09 11:56:28 +05:30
status = STATUS_OK
2021-02-13 18:45:41 +05:30
return
end if
2021-02-13 18:45:41 +05:30
2021-01-08 04:02:54 +05:30
converged_ = .true.
2024-01-09 11:56:28 +05:30
status = phase_damage_collectDotState(ph,en)
if (status /= STATUS_OK) return
2021-01-08 04:02:54 +05:30
2021-07-17 15:20:21 +05:30
size_so = damageState(ph)%sizeDotState
damageState(ph)%state(1:size_so,en) = damageState(ph)%state0 (1:size_so,en) &
+ damageState(ph)%dotState(1:size_so,en) * Delta_t
source_dotState(1:size_so,2) = 0.0_pREAL
2021-01-08 04:02:54 +05:30
iteration: do NiterationState = 1, num%nState
if (nIterationState > 1) source_dotState(1:size_so,2) = source_dotState(1:size_so,1)
source_dotState(1:size_so,1) = damageState(ph)%dotState(:,en)
2021-01-08 04:02:54 +05:30
2024-01-09 11:56:28 +05:30
status = phase_damage_collectDotState(ph,en)
if (status /= STATUS_OK) exit iteration
2021-01-08 04:02:54 +05:30
zeta = damper(damageState(ph)%dotState(:,en),source_dotState(1:size_so,1),source_dotState(1:size_so,2))
damageState(ph)%dotState(:,en) = damageState(ph)%dotState(:,en) * zeta &
+ source_dotState(1:size_so,1)* (1.0_pREAL - zeta)
r(1:size_so) = damageState(ph)%state (1:size_so,en) &
- damageState(ph)%State0 (1:size_so,en) &
- damageState(ph)%dotState(1:size_so,en) * Delta_t
damageState(ph)%state(1:size_so,en) = damageState(ph)%state(1:size_so,en) - r(1:size_so)
converged_ = converged_ .and. converged(r(1:size_so), &
damageState(ph)%state(1:size_so,en), &
damageState(ph)%atol(1:size_so))
2021-01-08 04:02:54 +05:30
if (converged_) then
2024-01-09 11:56:28 +05:30
status = phase_damage_deltaState(mechanical_F_e(ph,en),ph,en)
2021-01-08 04:02:54 +05:30
exit iteration
end if
2021-01-08 04:02:54 +05:30
end do iteration
2021-01-08 04:02:54 +05:30
2024-01-13 12:57:17 +05:30
if (.not. converged_) status = STATUS_FAIL_PHASE_DAMAGE_STATE
2021-01-08 04:02:54 +05:30
contains
!--------------------------------------------------------------------------------------------------
!> @brief Calculate the damping for correction of state and dot state.
2021-01-08 04:02:54 +05:30
!--------------------------------------------------------------------------------------------------
real(pREAL) pure function damper(omega_0,omega_1,omega_2)
2021-01-08 04:02:54 +05:30
real(pREAL), dimension(:), intent(in) :: &
omega_0, omega_1, omega_2
2021-01-08 04:02:54 +05:30
real(pREAL) :: dot_prod12, dot_prod22
2021-01-08 04:02:54 +05:30
dot_prod12 = dot_product(omega_0-omega_1, omega_1-omega_2)
dot_prod22 = dot_product(omega_1-omega_2, omega_1-omega_2)
if (min(dot_product(omega_0,omega_1),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)
2021-01-08 04:02:54 +05:30
else
damper = 1.0_pREAL
end if
2021-01-08 04:02:54 +05:30
end function damper
end function integrateDamageState
module subroutine damage_restartWrite(groupHandle,ph)
integer(HID_T), intent(in) :: groupHandle
integer, intent(in) :: ph
select case(damage_type(ph))
case(DAMAGE_ISOBRITTLE,DAMAGE_ANISOBRITTLE)
call HDF5_write(damageState(ph)%state,groupHandle,'omega_damage')
end select
end subroutine damage_restartWrite
module subroutine damage_restartRead(groupHandle,ph)
integer(HID_T), intent(in) :: groupHandle
integer, intent(in) :: ph
select case(damage_type(ph))
case(DAMAGE_ISOBRITTLE,DAMAGE_ANISOBRITTLE)
call HDF5_read(damageState(ph)%state0,groupHandle,'omega_damage')
end select
end subroutine damage_restartRead
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
!----------------------------------------------------------------------------------------------
2023-01-19 22:07:45 +05:30
module subroutine damage_result(group,ph)
2020-12-22 16:50:00 +05:30
character(len=*), intent(in) :: group
integer, intent(in) :: ph
if (damage_type(ph) /= UNDEFINED) &
2023-01-19 22:07:45 +05:30
call result_closeGroup(result_addGroup(group//'damage'))
sourceType: select case (damage_type(ph))
2020-12-22 16:50:00 +05:30
case (DAMAGE_ISOBRITTLE) sourceType
2023-01-19 22:07:45 +05:30
call isobrittle_result(ph,group//'damage/')
2020-12-22 16:50:00 +05:30
case (DAMAGE_ANISOBRITTLE) sourceType
2023-01-19 22:07:45 +05:30
call anisobrittle_result(ph,group//'damage/')
2020-12-22 16:50:00 +05:30
end select sourceType
2023-01-19 22:07:45 +05:30
end subroutine damage_result
2021-01-08 04:02:54 +05:30
!--------------------------------------------------------------------------------------------------
2022-02-19 23:26:41 +05:30
!> @brief Constitutive equation for calculating the rate of change of microstructure.
2021-01-08 04:02:54 +05:30
!--------------------------------------------------------------------------------------------------
2024-01-09 11:56:28 +05:30
function phase_damage_collectDotState(ph,en) result(status)
2021-01-08 04:02:54 +05:30
integer, intent(in) :: &
ph, &
en !< counter in source loop
2024-01-09 11:56:28 +05:30
integer(kind(STATUS_OK)) :: status
2021-01-08 04:02:54 +05:30
2024-01-09 11:56:28 +05:30
status = STATUS_OK
2021-01-08 04:02:54 +05:30
2021-02-13 23:11:30 +05:30
if (damageState(ph)%sizeState > 0) then
2021-01-08 04:02:54 +05:30
sourceType: select case (damage_type(ph))
2021-01-08 04:02:54 +05:30
case (DAMAGE_ANISOBRITTLE) sourceType
call anisobrittle_dotState(mechanical_S(ph,en), ph,en) ! ToDo: use M_d
2021-01-08 04:02:54 +05:30
end select sourceType
2024-01-13 12:57:17 +05:30
if (any(IEEE_is_NaN(damageState(ph)%dotState(:,en)))) status = STATUS_FAIL_PHASE_DAMAGE_STATE
2021-01-08 04:02:54 +05:30
end if
2021-01-08 04:02:54 +05:30
2021-02-09 03:51:53 +05:30
end function phase_damage_collectDotState
2021-01-08 04:02:54 +05:30
2021-04-11 16:51:27 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief Damage viscosity.
!--------------------------------------------------------------------------------------------------
module function phase_mu_phi(co,ce) result(mu)
integer, intent(in) :: co, ce
real(pREAL) :: mu
2021-04-11 16:51:27 +05:30
2023-01-23 13:01:59 +05:30
mu = param(material_ID_phase(co,ce))%mu
2021-04-11 16:51:27 +05:30
end function phase_mu_phi
!--------------------------------------------------------------------------------------------------
!> @brief Damage conductivity/diffusivity in reference configuration.
!--------------------------------------------------------------------------------------------------
module function phase_K_phi(co,ce) result(K)
integer, intent(in) :: co, ce
real(pREAL), dimension(3,3) :: K
2022-05-28 00:28:18 +05:30
2023-01-23 13:01:59 +05:30
K = crystallite_push33ToRef(co,ce,param(material_ID_phase(co,ce))%l_c**2*math_I3)
2021-04-11 16:51:27 +05:30
end function phase_K_phi
2021-01-08 04:02:54 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief for constitutive models having an instantaneous change of state
!> will return false if delta state is not needed/supported by the constitutive model
!--------------------------------------------------------------------------------------------------
2024-01-09 11:56:28 +05:30
function phase_damage_deltaState(Fe, ph, en) result(status)
2021-01-08 04:02:54 +05:30
integer, intent(in) :: &
ph, &
en
real(pREAL), intent(in), dimension(3,3) :: &
2021-01-08 04:02:54 +05:30
Fe !< elastic deformation gradient
2022-05-28 00:28:18 +05:30
2021-01-08 04:02:54 +05:30
integer :: &
myOffset, &
mySize
2024-01-09 11:56:28 +05:30
integer(kind(STATUS_OK)) :: status
2021-01-08 04:02:54 +05:30
2024-01-09 11:56:28 +05:30
status = STATUS_OK
2021-01-08 04:02:54 +05:30
2021-02-13 23:11:30 +05:30
if (damageState(ph)%sizeState == 0) return
2021-01-08 04:02:54 +05:30
sourceType: select case (damage_type(ph))
2021-01-08 04:02:54 +05:30
case (DAMAGE_ISOBRITTLE) sourceType
2021-11-18 21:07:34 +05:30
call isobrittle_deltaState(phase_homogenizedC66(ph,en), Fe, ph,en)
2024-01-13 12:57:17 +05:30
if (any(IEEE_is_NaN(damageState(ph)%deltaState(:,en)))) status = STATUS_FAIL_PHASE_DAMAGE_DELTASTATE
2024-01-09 11:56:28 +05:30
if (status == STATUS_OK) then
myOffset = damageState(ph)%offsetDeltaState
mySize = damageState(ph)%sizeDeltaState
damageState(ph)%state(myOffset + 1: myOffset + mySize,en) = &
damageState(ph)%state(myOffset + 1: myOffset + mySize,en) + damageState(ph)%deltaState(1:mySize,en)
end if
2021-01-08 04:02:54 +05:30
end select sourceType
2021-01-08 04:02:54 +05:30
2021-02-09 03:51:53 +05:30
end function phase_damage_deltaState
2021-01-08 04:02:54 +05:30
2021-01-08 12:07:51 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief Check if a source mechanism is active or not.
2021-01-08 12:07:51 +05:30
!--------------------------------------------------------------------------------------------------
2021-02-13 17:14:47 +05:30
function source_active(source_label) result(active_source)
2021-01-08 12:07:51 +05:30
character(len=*), intent(in) :: source_label !< name of source mechanism
2021-02-13 17:14:47 +05:30
logical, dimension(:), allocatable :: active_source
2021-01-08 12:07:51 +05:30
type(tDict), pointer :: &
2021-01-08 12:07:51 +05:30
phases, &
phase, &
src
2021-02-13 17:14:47 +05:30
integer :: ph
2021-01-08 12:07:51 +05:30
phases => config_material%get_dict('phase')
2021-02-13 17:14:47 +05:30
allocate(active_source(phases%length))
do ph = 1, phases%length
phase => phases%get_dict(ph)
src => phase%get_dict('damage',defaultVal=emptyDict)
2023-06-04 10:47:38 +05:30
active_source(ph) = src%get_asStr('type',defaultVal = 'x') == source_label
end do
2021-01-08 12:07:51 +05:30
end function source_active
2021-01-21 01:24:31 +05:30
!----------------------------------------------------------------------------------------------
!< @brief Set damage parameter
!----------------------------------------------------------------------------------------------
2021-04-08 17:01:21 +05:30
module subroutine phase_set_phi(phi,co,ce)
2021-01-21 01:24:31 +05:30
real(pREAL), intent(in) :: phi
2021-01-21 01:24:31 +05:30
integer, intent(in) :: ce, co
2023-01-23 13:01:59 +05:30
current(material_ID_phase(co,ce))%phi(material_entry_phase(co,ce)) = phi
2021-01-21 01:24:31 +05:30
2021-04-08 17:01:21 +05:30
end subroutine phase_set_phi
2021-01-21 01:24:31 +05:30
module function damage_phi(ph,en) result(phi)
2021-02-13 11:45:57 +05:30
integer, intent(in) :: ph, en
real(pREAL) :: phi
2021-02-13 11:45:57 +05:30
phi = current(ph)%phi(en)
2021-02-13 11:45:57 +05:30
end function damage_phi
2021-04-06 13:52:47 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief Forward data after successful increment.
!--------------------------------------------------------------------------------------------------
module subroutine damage_forward()
integer :: ph
do ph = 1, size(damageState)
if (damageState(ph)%sizeState > 0) &
damageState(ph)%state0 = damageState(ph)%state
end do
2021-04-06 13:52:47 +05:30
end subroutine damage_forward
end submodule damage