improved naming

This commit is contained in:
Martin Diehl 2023-07-18 04:12:57 +02:00
parent ddeb218728
commit d85ad0b554
4 changed files with 61 additions and 69 deletions

View File

@ -176,8 +176,8 @@ end module DAMASK_interface
#include "../phase_mechanical_eigen_cleavageopening.f90" #include "../phase_mechanical_eigen_cleavageopening.f90"
#include "../phase_mechanical_eigen_thermalexpansion.f90" #include "../phase_mechanical_eigen_thermalexpansion.f90"
#include "../phase_thermal.f90" #include "../phase_thermal.f90"
#include "../phase_thermal_dissipation.f90" #include "../phase_thermal_source_dissipation.f90"
#include "../phase_thermal_externalheat.f90" #include "../phase_thermal_source_externalheat.f90"
#include "../phase_damage.f90" #include "../phase_damage.f90"
#include "../phase_damage_isobrittle.f90" #include "../phase_damage_isobrittle.f90"
#include "../phase_damage_anisobrittle.f90" #include "../phase_damage_anisobrittle.f90"

View File

@ -21,13 +21,13 @@ submodule(phase) thermal
THERMAL_EXTERNALHEAT_ID THERMAL_EXTERNALHEAT_ID
end enum end enum
type :: tDataContainer ! ?? not very telling name. Better: "fieldQuantities" ?? type :: tFieldQuantities
real(pREAL), dimension(:), allocatable :: T, dot_T real(pREAL), dimension(:), allocatable :: T, dot_T
end type tDataContainer end type tFieldQuantities
integer(kind(THERMAL_UNDEFINED_ID)), dimension(:,:), allocatable :: & integer(kind(THERMAL_UNDEFINED_ID)), dimension(:,:), allocatable :: &
thermal_source thermal_source
type(tDataContainer), dimension(:), allocatable :: current ! ?? not very telling name. Better: "field" ?? MD: current(ho)%T(en) reads quite good type(tFieldQuantities), dimension(:), allocatable :: current
type(tThermalParameters), dimension(:), allocatable :: param type(tThermalParameters), dimension(:), allocatable :: param
@ -36,36 +36,36 @@ submodule(phase) thermal
interface interface
module function dissipation_init(source_length) result(mySources) module function source_dissipation_init(source_length) result(mySources)
integer, intent(in) :: source_length integer, intent(in) :: source_length
logical, dimension(:,:), allocatable :: mySources logical, dimension(:,:), allocatable :: mySources
end function dissipation_init end function source_dissipation_init
module function externalheat_init(source_length) result(mySources) module function source_externalheat_init(source_length) result(mySources)
integer, intent(in) :: source_length integer, intent(in) :: source_length
logical, dimension(:,:), allocatable :: mySources logical, dimension(:,:), allocatable :: mySources
end function externalheat_init end function source_externalheat_init
module subroutine externalheat_dotState(ph, en) module subroutine source_externalheat_dotState(ph, en)
integer, intent(in) :: & integer, intent(in) :: &
ph, & ph, &
en en
end subroutine externalheat_dotState end subroutine source_externalheat_dotState
module function dissipation_f_T(ph,en) result(f_T) module function source_dissipation_f_T(ph,en) result(f_T)
integer, intent(in) :: & integer, intent(in) :: &
ph, & ph, &
en en
real(pREAL) :: f_T real(pREAL) :: f_T
end function dissipation_f_T end function source_dissipation_f_T
module function externalheat_f_T(ph,en) result(f_T) module function source_externalheat_f_T(ph,en) result(f_T)
integer, intent(in) :: & integer, intent(in) :: &
ph, & ph, &
en en
real(pREAL) :: f_T real(pREAL) :: f_T
end function externalheat_f_T end function source_externalheat_f_T
end interface end interface
@ -132,8 +132,8 @@ module subroutine thermal_init(phases)
allocate(thermal_source(maxval(thermal_Nsources),phases%length), source = THERMAL_UNDEFINED_ID) allocate(thermal_source(maxval(thermal_Nsources),phases%length), source = THERMAL_UNDEFINED_ID)
if (maxval(thermal_Nsources) /= 0) then if (maxval(thermal_Nsources) /= 0) then
where(dissipation_init (maxval(thermal_Nsources))) thermal_source = THERMAL_DISSIPATION_ID where(source_dissipation_init (maxval(thermal_Nsources))) thermal_source = THERMAL_DISSIPATION_ID
where(externalheat_init(maxval(thermal_Nsources))) thermal_source = THERMAL_EXTERNALHEAT_ID where(source_externalheat_init(maxval(thermal_Nsources))) thermal_source = THERMAL_EXTERNALHEAT_ID
end if end if
thermal_source_maxSizeDotState = 0 thermal_source_maxSizeDotState = 0
@ -151,7 +151,7 @@ end subroutine thermal_init
!---------------------------------------------------------------------------------------------- !----------------------------------------------------------------------------------------------
!< @brief Calculate thermal source. !< @brief Calculate thermal source (forcing term).
!---------------------------------------------------------------------------------------------- !----------------------------------------------------------------------------------------------
module function phase_f_T(ph,en) result(f) module function phase_f_T(ph,en) result(f)
@ -168,10 +168,10 @@ module function phase_f_T(ph,en) result(f)
select case(thermal_source(so,ph)) select case(thermal_source(so,ph))
case (THERMAL_DISSIPATION_ID) case (THERMAL_DISSIPATION_ID)
f = f + dissipation_f_T(ph,en) f = f + source_dissipation_f_T(ph,en)
case (THERMAL_EXTERNALHEAT_ID) case (THERMAL_EXTERNALHEAT_ID)
f = f + externalheat_f_T(ph,en) f = f + source_externalheat_f_T(ph,en)
end select end select
@ -183,22 +183,22 @@ end function phase_f_T
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief tbd. !> @brief tbd.
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
function phase_thermal_collectDotState(ph,en) result(broken) function phase_thermal_collectDotState(ph,en) result(ok)
integer, intent(in) :: ph, en integer, intent(in) :: ph, en
logical :: broken logical :: ok
integer :: i integer :: i
broken = .false. ok = .true.
SourceLoop: do i = 1, thermal_Nsources(ph) SourceLoop: do i = 1, thermal_Nsources(ph)
if (thermal_source(i,ph) == THERMAL_EXTERNALHEAT_ID) & if (thermal_source(i,ph) == THERMAL_EXTERNALHEAT_ID) &
call externalheat_dotState(ph,en) call source_externalheat_dotState(ph,en)
broken = broken .or. any(IEEE_is_NaN(thermalState(ph)%p(i)%dotState(:,en))) ok = ok .and. .not. any(IEEE_is_NaN(thermalState(ph)%p(i)%dotState(:,en)))
end do SourceLoop end do SourceLoop
@ -241,34 +241,35 @@ module function phase_thermal_constitutive(Delta_t,ph,en) result(converged_)
logical :: converged_ logical :: converged_
converged_ = .not. integrateThermalState(Delta_t,ph,en) converged_ = integrateThermalState(Delta_t,ph,en)
end function phase_thermal_constitutive end function phase_thermal_constitutive
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief integrate state with 1st order explicit Euler method !> @brief Integrate state with 1st order explicit Euler method.
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
function integrateThermalState(Delta_t, ph,en) result(broken) function integrateThermalState(Delta_t, ph,en) result(converged)
real(pREAL), intent(in) :: Delta_t real(pREAL), intent(in) :: Delta_t
integer, intent(in) :: ph, en integer, intent(in) :: ph, en
logical :: & logical :: converged
broken
integer :: & integer :: &
so, & so, &
sizeDotState sizeDotState
broken = phase_thermal_collectDotState(ph,en) converged = phase_thermal_collectDotState(ph,en)
if (broken) return if (converged) then
do so = 1, thermal_Nsources(ph) do so = 1, thermal_Nsources(ph)
sizeDotState = thermalState(ph)%p(so)%sizeDotState sizeDotState = thermalState(ph)%p(so)%sizeDotState
thermalState(ph)%p(so)%state(1:sizeDotState,en) = thermalState(ph)%p(so)%state0(1:sizeDotState,en) & thermalState(ph)%p(so)%state(1:sizeDotState,en) = thermalState(ph)%p(so)%state0(1:sizeDotState,en) &
+ thermalState(ph)%p(so)%dotState(1:sizeDotState,en) * Delta_t + thermalState(ph)%p(so)%dotState(1:sizeDotState,en) * Delta_t
end do end do
end if
end function integrateThermalState end function integrateThermalState
@ -318,7 +319,7 @@ end subroutine thermal_forward
!---------------------------------------------------------------------------------------------- !----------------------------------------------------------------------------------------------
!< @brief Get temperature (for use by non-thermal physics) !< @brief Get temperature (for use by non-thermal physics).
!---------------------------------------------------------------------------------------------- !----------------------------------------------------------------------------------------------
pure module function thermal_T(ph,en) result(T) pure module function thermal_T(ph,en) result(T)
@ -332,7 +333,7 @@ end function thermal_T
!---------------------------------------------------------------------------------------------- !----------------------------------------------------------------------------------------------
!< @brief Get rate of temperature (for use by non-thermal physics) !< @brief Get rate of temperature (for use by non-thermal physics).
!---------------------------------------------------------------------------------------------- !----------------------------------------------------------------------------------------------
module function thermal_dot_T(ph,en) result(dot_T) module function thermal_dot_T(ph,en) result(dot_T)

View File

@ -5,7 +5,7 @@
!> @brief material subroutine for thermal source due to plastic dissipation !> @brief material subroutine for thermal source due to plastic dissipation
!> @details to be done !> @details to be done
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
submodule(phase:thermal) dissipation submodule(phase:thermal) source_dissipation
type :: tParameters !< container type for internal constitutive parameters type :: tParameters !< container type for internal constitutive parameters
real(pREAL) :: & real(pREAL) :: &
@ -22,7 +22,7 @@ contains
!> @brief module initialization !> @brief module initialization
!> @details reads in material parameters, allocates arrays, and does sanity checks !> @details reads in material parameters, allocates arrays, and does sanity checks
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module function dissipation_init(source_length) result(mySources) module function source_dissipation_init(source_length) result(mySources)
integer, intent(in) :: source_length integer, intent(in) :: source_length
logical, dimension(:,:), allocatable :: mySources logical, dimension(:,:), allocatable :: mySources
@ -41,7 +41,7 @@ module function dissipation_init(source_length) result(mySources)
mySources = thermal_active('dissipation',source_length) mySources = thermal_active('dissipation',source_length)
if (count(mySources) == 0) return if (count(mySources) == 0) return
print'(/,1x,a)', '<<<+- phase:thermal:dissipation init -+>>>' print'(/,1x,a)', '<<<+- phase:thermal:source_dissipation init -+>>>'
print'(/,a,i2)', ' # phases: ',count(mySources); flush(IO_STDOUT) print'(/,a,i2)', ' # phases: ',count(mySources); flush(IO_STDOUT)
@ -71,13 +71,13 @@ module function dissipation_init(source_length) result(mySources)
end do end do
end function dissipation_init end function source_dissipation_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief Ninstancess dissipation rate !> @brief Ninstancess dissipation rate
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module function dissipation_f_T(ph,en) result(f_T) module function source_dissipation_f_T(ph,en) result(f_T)
integer, intent(in) :: ph, en integer, intent(in) :: ph, en
real(pREAL) :: & real(pREAL) :: &
@ -91,6 +91,6 @@ module function dissipation_f_T(ph,en) result(f_T)
f_T = prm%kappa*sum(abs(Mp*mechanical_L_p(ph,en))) f_T = prm%kappa*sum(abs(Mp*mechanical_L_p(ph,en)))
end associate end associate
end function dissipation_f_T end function source_dissipation_f_T
end submodule dissipation end submodule source_dissipation

View File

@ -4,11 +4,11 @@
!> @author Philip Eisenlohr, Michigan State University !> @author Philip Eisenlohr, Michigan State University
!> @brief material subroutine for variable heat source !> @brief material subroutine for variable heat source
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
submodule(phase:thermal) externalheat submodule(phase:thermal) source_externalheat
integer, dimension(:), allocatable :: & integer, dimension(:), allocatable :: &
source_thermal_externalheat_offset !< which source is my current thermal dissipation mechanism? source_ID !< which source is my current thermal dissipation mechanism?
type :: tParameters !< container type for internal constitutive parameters type :: tParameters !< container type for internal constitutive parameters
type(tTable) :: f type(tTable) :: f
@ -24,7 +24,7 @@ contains
!> @brief module initialization !> @brief module initialization
!> @details reads in material parameters, allocates arrays, and does sanity checks !> @details reads in material parameters, allocates arrays, and does sanity checks
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module function externalheat_init(source_length) result(mySources) module function source_externalheat_init(source_length) result(mySources)
integer, intent(in) :: source_length integer, intent(in) :: source_length
logical, dimension(:,:), allocatable :: mySources logical, dimension(:,:), allocatable :: mySources
@ -43,13 +43,13 @@ module function externalheat_init(source_length) result(mySources)
mySources = thermal_active('externalheat',source_length) mySources = thermal_active('externalheat',source_length)
if (count(mySources) == 0) return if (count(mySources) == 0) return
print'(/,1x,a)', '<<<+- phase:thermal:externalheat init -+>>>' print'(/,1x,a)', '<<<+- phase:thermal:source_externalheat init -+>>>'
print'(/,a,i2)', ' # phases: ',count(mySources); flush(IO_STDOUT) print'(/,a,i2)', ' # phases: ',count(mySources); flush(IO_STDOUT)
phases => config_material%get_dict('phase') phases => config_material%get_dict('phase')
allocate(param(phases%length)) allocate(param(phases%length))
allocate(source_thermal_externalheat_offset (phases%length), source=0) allocate(source_ID(phases%length), source=0)
do ph = 1, phases%length do ph = 1, phases%length
phase => phases%get_dict(ph) phase => phases%get_dict(ph)
@ -58,7 +58,7 @@ module function externalheat_init(source_length) result(mySources)
sources => thermal%get_list('source') sources => thermal%get_list('source')
do so = 1, sources%length do so = 1, sources%length
if (mySources(so,ph)) then if (mySources(so,ph)) then
source_thermal_externalheat_offset(ph) = so source_ID(ph) = so
associate(prm => param(ph)) associate(prm => param(ph))
src => sources%get_dict(so) src => sources%get_dict(so)
print'(1x,a,i0,a,i0)', 'phase ',ph,' source ',so print'(1x,a,i0,a,i0)', 'phase ',ph,' source ',so
@ -74,33 +74,29 @@ module function externalheat_init(source_length) result(mySources)
end do end do
end do end do
end function externalheat_init end function source_externalheat_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief rate of change of state !> @brief rate of change of state
!> @details state only contains current time to linearly interpolate given heat powers !> @details state only contains current time to linearly interpolate given heat powers
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine externalheat_dotState(ph, en) module subroutine source_externalheat_dotState(ph, en)
integer, intent(in) :: & integer, intent(in) :: &
ph, & ph, &
en en
integer :: &
so
so = source_thermal_externalheat_offset(ph) thermalState(ph)%p(source_ID(ph))%dotState(1,en) = 1.0_pREAL ! state is current time
thermalState(ph)%p(so)%dotState(1,en) = 1.0_pREAL ! state is current time end subroutine source_externalheat_dotState
end subroutine externalheat_dotState
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief returns local heat generation rate !> @brief returns local heat generation rate
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module function externalheat_f_T(ph,en) result(f_T) module function source_externalheat_f_T(ph,en) result(f_T)
integer, intent(in) :: & integer, intent(in) :: &
ph, & ph, &
@ -108,16 +104,11 @@ module function externalheat_f_T(ph,en) result(f_T)
real(pREAL) :: & real(pREAL) :: &
f_T f_T
integer :: &
so
so = source_thermal_externalheat_offset(ph)
associate(prm => param(ph)) associate(prm => param(ph))
f_T = prm%f%at(thermalState(ph)%p(so)%state(1,en)) f_T = prm%f%at(thermalState(ph)%p(source_ID(ph))%state(1,en))
end associate end associate
end function externalheat_f_T end function source_externalheat_f_T
end submodule externalheat end submodule source_externalheat