sorted and documented

This commit is contained in:
Martin Diehl 2021-04-11 08:32:13 +02:00
parent a386b82f74
commit 4b89e2f40c
3 changed files with 108 additions and 120 deletions

View File

@ -135,32 +135,26 @@ module homogenization
logical, dimension(2) :: doneAndHappy logical, dimension(2) :: doneAndHappy
end function mechanical_updateState end function mechanical_updateState
module function homogenization_mu_T(ce) result(mu)
integer, intent(in) :: ce
real(pReal) :: mu
end function homogenization_mu_T
module function homogenization_K_T(ce) result(K) module function homogenization_K_T(ce) result(K)
integer, intent(in) :: ce integer, intent(in) :: ce
real(pReal), dimension(3,3) :: K real(pReal), dimension(3,3) :: K
end function homogenization_K_T end function homogenization_K_T
module function homogenization_mu_T(ce) result(mu) module function homogenization_f_T(ce) result(f)
integer, intent(in) :: ce integer, intent(in) :: ce
real(pReal) :: mu real(pReal) :: f
end function homogenization_mu_T end function homogenization_f_T
module subroutine homogenization_thermal_setField(T,dot_T, ce) module subroutine homogenization_thermal_setField(T,dot_T, ce)
integer, intent(in) :: ce integer, intent(in) :: ce
real(pReal), intent(in) :: T, dot_T real(pReal), intent(in) :: T, dot_T
end subroutine homogenization_thermal_setField end subroutine homogenization_thermal_setField
module function homogenization_T(ce) result(T)
integer, intent(in) :: ce
real(pReal) :: T
end function homogenization_T
module function homogenization_f_T(ce) result(f)
integer, intent(in) :: ce
real(pReal) :: f
end function homogenization_f_T
module function homogenization_mu_phi(ce) result(mu) module function homogenization_mu_phi(ce) result(mu)
integer, intent(in) :: ce integer, intent(in) :: ce
real(pReal) :: mu real(pReal) :: mu
@ -191,12 +185,11 @@ module homogenization
homogenization_mu_T, & homogenization_mu_T, &
homogenization_K_T, & homogenization_K_T, &
homogenization_f_T, & homogenization_f_T, &
homogenization_K_phi, & homogenization_thermal_setfield, &
homogenization_mu_phi, & homogenization_mu_phi, &
homogenization_K_phi, &
homogenization_f_phi, & homogenization_f_phi, &
homogenization_set_phi, & homogenization_set_phi, &
homogenization_thermal_setfield, &
homogenization_T, &
homogenization_forward, & homogenization_forward, &
homogenization_results, & homogenization_results, &
homogenization_restartRead, & homogenization_restartRead, &

View File

@ -26,8 +26,8 @@ submodule(homogenization) damage
type(tparameters), dimension(:), allocatable :: & type(tparameters), dimension(:), allocatable :: &
param param
contains
contains
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief Allocate variables and set parameters. !> @brief Allocate variables and set parameters.
@ -105,57 +105,22 @@ module subroutine damage_partition(ce)
end subroutine damage_partition end subroutine damage_partition
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief Returns homogenized nonlocal damage mobility !> @brief Homogenized damage viscosity.
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module function homogenization_mu_phi(ce) result(mu) module function homogenization_mu_phi(ce) result(mu)
integer, intent(in) :: ce integer, intent(in) :: ce
real(pReal) :: mu real(pReal) :: mu
mu = lattice_mu_phi(material_phaseID(1,ce)) mu = lattice_mu_phi(material_phaseID(1,ce))
end function homogenization_mu_phi end function homogenization_mu_phi
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief calculates homogenized damage driving forces !> @brief Homogenized damage conductivity/diffusivity in reference configuration.
!--------------------------------------------------------------------------------------------------
module function homogenization_f_phi(phi,ce) result(f)
integer, intent(in) :: ce
real(pReal), intent(in) :: &
phi
real(pReal) :: f
f = phase_f_phi(phi, 1, ce)
end function homogenization_f_phi
!--------------------------------------------------------------------------------------------------
!> @brief updated nonlocal damage field with solution from damage phase field PDE
!--------------------------------------------------------------------------------------------------
module subroutine homogenization_set_phi(phi,ce)
integer, intent(in) :: ce
real(pReal), intent(in) :: &
phi
integer :: &
ho, &
en
ho = material_homogenizationID(ce)
en = material_homogenizationEntry(ce)
damagestate_h(ho)%state(1,en) = phi
current(ho)%phi(en) = phi
end subroutine homogenization_set_phi
!--------------------------------------------------------------------------------------------------
!> @brief returns homogenized non local damage diffusion tensor in reference configuration
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module function homogenization_K_phi(ce) result(K) module function homogenization_K_phi(ce) result(K)
@ -169,6 +134,44 @@ module function homogenization_K_phi(ce) result(K)
end function homogenization_K_phi end function homogenization_K_phi
!--------------------------------------------------------------------------------------------------
!> @brief Homogenized damage driving force.
!--------------------------------------------------------------------------------------------------
module function homogenization_f_phi(phi,ce) result(f)
integer, intent(in) :: ce
real(pReal), intent(in) :: &
phi
real(pReal) :: f
f = phase_f_phi(phi, 1, ce)
end function homogenization_f_phi
!--------------------------------------------------------------------------------------------------
!> @brief Set damage field.
!--------------------------------------------------------------------------------------------------
module subroutine homogenization_set_phi(phi,ce)
integer, intent(in) :: ce
real(pReal), intent(in) :: &
phi
integer :: &
ho, &
en
ho = material_homogenizationID(ce)
en = material_homogenizationEntry(ce)
damagestate_h(ho)%state(1,en) = phi
current(ho)%phi(en) = phi
end subroutine homogenization_set_phi
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief writes results to HDF5 output file !> @brief writes results to HDF5 output file
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------

View File

@ -107,15 +107,29 @@ end subroutine thermal_homogenize
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief return homogenized thermal conductivity in reference configuration !> @brief Homogenized thermal viscosity.
!--------------------------------------------------------------------------------------------------
module function homogenization_mu_T(ce) result(mu)
integer, intent(in) :: ce
real(pReal) :: mu
mu = c_P(ce) * rho(ce)
end function homogenization_mu_T
!--------------------------------------------------------------------------------------------------
!> @brief Homogenized thermal conductivity in reference configuration.
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module function homogenization_K_T(ce) result(K) module function homogenization_K_T(ce) result(K)
integer, intent(in) :: ce integer, intent(in) :: ce
real(pReal), dimension(3,3) :: K real(pReal), dimension(3,3) :: K
integer :: & integer :: co
co
K = crystallite_push33ToRef(co,1,lattice_K_T(:,:,material_phaseID(1,ce))) K = crystallite_push33ToRef(co,1,lattice_K_T(:,:,material_phaseID(1,ce)))
do co = 2, homogenization_Nconstituents(material_homogenizationID(ce)) do co = 2, homogenization_Nconstituents(material_homogenizationID(ce))
@ -127,61 +141,29 @@ module function homogenization_K_T(ce) result(K)
end function homogenization_K_T end function homogenization_K_T
module function homogenization_mu_T(ce) result(mu) !--------------------------------------------------------------------------------------------------
!> @brief Homogenized heat generation rate.
!--------------------------------------------------------------------------------------------------
module function homogenization_f_T(ce) result(f)
integer, intent(in) :: ce integer, intent(in) :: ce
real(pReal) :: mu real(pReal) :: f
mu = c_P(ce) * rho(ce)
end function homogenization_mu_T
!--------------------------------------------------------------------------------------------------
!> @brief returns homogenized specific heat capacity
!--------------------------------------------------------------------------------------------------
function c_P(ce)
integer, intent(in) :: ce
real(pReal) :: c_P
integer :: co integer :: co
c_P = lattice_c_p(material_phaseID(1,ce)) f = phase_f_T(material_phaseID(1,ce),material_phaseEntry(1,ce))
do co = 2, homogenization_Nconstituents(material_homogenizationID(ce)) do co = 2, homogenization_Nconstituents(material_homogenizationID(ce))
c_P = c_P + lattice_c_p(material_phaseID(co,ce)) f = f + phase_f_T(material_phaseID(co,ce),material_phaseEntry(co,ce))
enddo enddo
c_P = c_P / real(homogenization_Nconstituents(material_homogenizationID(ce)),pReal) f = f/real(homogenization_Nconstituents(material_homogenizationID(ce)),pReal)
end function c_P end function homogenization_f_T
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief returns homogenized mass density !> @brief Set thermal field and its rate (T and dot_T).
!--------------------------------------------------------------------------------------------------
function rho(ce)
integer, intent(in) :: ce
real(pReal) :: rho
integer :: co
rho = lattice_rho(material_phaseID(1,ce))
do co = 2, homogenization_Nconstituents(material_homogenizationID(ce))
rho = rho + lattice_rho(material_phaseID(co,ce))
enddo
rho = rho / real(homogenization_Nconstituents(material_homogenizationID(ce)),pReal)
end function rho
!--------------------------------------------------------------------------------------------------
!> @brief Set thermal field and its rate (T and dot_T)
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine homogenization_thermal_setField(T,dot_T, ce) module subroutine homogenization_thermal_setField(T,dot_T, ce)
@ -196,7 +178,6 @@ module subroutine homogenization_thermal_setField(T,dot_T, ce)
end subroutine homogenization_thermal_setField end subroutine homogenization_thermal_setField
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief writes results to HDF5 output file !> @brief writes results to HDF5 output file
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
@ -219,34 +200,45 @@ module subroutine thermal_results(ho,group)
end subroutine thermal_results end subroutine thermal_results
module function homogenization_T(ce) result(T) !--------------------------------------------------------------------------------------------------
!> @brief Homogenize specific heat capacity.
!--------------------------------------------------------------------------------------------------
function c_P(ce)
integer, intent(in) :: ce integer, intent(in) :: ce
real(pReal) :: T real(pReal) :: c_P
T = current(material_homogenizationID(ce))%T(material_homogenizationEntry(ce))
end function homogenization_T
!--------------------------------------------------------------------------------------------------
!> @brief return heat generation rate
!--------------------------------------------------------------------------------------------------
module function homogenization_f_T(ce) result(f)
integer, intent(in) :: ce
real(pReal) :: f
integer :: co integer :: co
f = phase_f_T(material_phaseID(1,ce),material_phaseEntry(1,ce))
c_P = lattice_c_p(material_phaseID(1,ce))
do co = 2, homogenization_Nconstituents(material_homogenizationID(ce)) do co = 2, homogenization_Nconstituents(material_homogenizationID(ce))
f = f + phase_f_T(material_phaseID(co,ce),material_phaseEntry(co,ce)) c_P = c_P + lattice_c_p(material_phaseID(co,ce))
enddo enddo
f = f/real(homogenization_Nconstituents(material_homogenizationID(ce)),pReal) c_P = c_P / real(homogenization_Nconstituents(material_homogenizationID(ce)),pReal)
end function homogenization_f_T end function c_P
!--------------------------------------------------------------------------------------------------
!> @brief Homogenize mass density.
!--------------------------------------------------------------------------------------------------
function rho(ce)
integer, intent(in) :: ce
real(pReal) :: rho
integer :: co
rho = lattice_rho(material_phaseID(1,ce))
do co = 2, homogenization_Nconstituents(material_homogenizationID(ce))
rho = rho + lattice_rho(material_phaseID(co,ce))
enddo
rho = rho / real(homogenization_Nconstituents(material_homogenizationID(ce)),pReal)
end function rho
end submodule thermal end submodule thermal