polishing

This commit is contained in:
Martin Diehl 2021-01-26 23:56:20 +01:00
parent 69f6de0e4f
commit 1da1018d86
3 changed files with 45 additions and 48 deletions

View File

@ -44,21 +44,21 @@ submodule(phase) thermal
me me
end subroutine externalheat_dotState end subroutine externalheat_dotState
module subroutine thermal_dissipation_getRate(TDot, ph,me) module subroutine dissipation_getRate(TDot, ph,me)
integer, intent(in) :: & integer, intent(in) :: &
ph, & ph, &
me me
real(pReal), intent(out) :: & real(pReal), intent(out) :: &
TDot TDot
end subroutine thermal_dissipation_getRate end subroutine dissipation_getRate
module subroutine thermal_externalheat_getRate(TDot, ph,me) module subroutine externalheat_getRate(TDot, ph,me)
integer, intent(in) :: & integer, intent(in) :: &
ph, & ph, &
me me
real(pReal), intent(out) :: & real(pReal), intent(out) :: &
TDot TDot
end subroutine thermal_externalheat_getRate end subroutine externalheat_getRate
end interface end interface
@ -146,19 +146,19 @@ module subroutine constitutive_thermal_getRate(TDot, ph,me)
TDot = 0.0_pReal TDot = 0.0_pReal
do so = 1, thermal_Nsources(ph) do so = 1, thermal_Nsources(ph)
select case(thermal_source(so,ph)) select case(thermal_source(so,ph))
case (THERMAL_DISSIPATION_ID) case (THERMAL_DISSIPATION_ID)
call thermal_dissipation_getRate(my_Tdot, ph,me) call dissipation_getRate(my_Tdot, ph,me)
case (THERMAL_EXTERNALHEAT_ID) case (THERMAL_EXTERNALHEAT_ID)
call thermal_externalheat_getRate(my_Tdot, ph,me) call externalheat_getRate(my_Tdot, ph,me)
case default case default
my_Tdot = 0.0_pReal my_Tdot = 0.0_pReal
end select end select
Tdot = Tdot + my_Tdot Tdot = Tdot + my_Tdot
enddo enddo
end subroutine constitutive_thermal_getRate end subroutine constitutive_thermal_getRate

View File

@ -70,7 +70,7 @@ end function dissipation_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief Ninstancess dissipation rate !> @brief Ninstancess dissipation rate
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine thermal_dissipation_getRate(TDot, ph,me) module subroutine dissipation_getRate(TDot, ph,me)
integer, intent(in) :: ph, me integer, intent(in) :: ph, me
real(pReal), intent(out) :: & real(pReal), intent(out) :: &
@ -81,6 +81,6 @@ module subroutine thermal_dissipation_getRate(TDot, ph,me)
TDot = prm%kappa*sum(abs(mech_S(ph,me)*mech_L_p(ph,me))) TDot = prm%kappa*sum(abs(mech_S(ph,me)*mech_L_p(ph,me)))
end associate end associate
end subroutine thermal_dissipation_getRate end subroutine dissipation_getRate
end submodule dissipation end submodule dissipation

View File

@ -8,8 +8,7 @@ submodule(phase:thermal) externalheat
integer, dimension(:), allocatable :: & integer, dimension(:), allocatable :: &
source_thermal_externalheat_offset, & !< which source is my current thermal dissipation mechanism? source_thermal_externalheat_offset !< which source is my current thermal dissipation mechanism?
source_thermal_externalheat_instance !< instance of thermal dissipation source mechanism
type :: tParameters !< container type for internal constitutive parameters type :: tParameters !< container type for internal constitutive parameters
real(pReal), dimension(:), allocatable :: & real(pReal), dimension(:), allocatable :: &
@ -39,7 +38,7 @@ module function externalheat_init(source_length) result(mySources)
phase, & phase, &
sources, thermal, & sources, thermal, &
src src
integer :: Ninstances,so,Nconstituents,p integer :: Ninstances,so,Nconstituents,ph
print'(/,a)', ' <<<+- thermal_externalheat init -+>>>' print'(/,a)', ' <<<+- thermal_externalheat init -+>>>'
@ -50,29 +49,27 @@ module function externalheat_init(source_length) result(mySources)
if(Ninstances == 0) return if(Ninstances == 0) return
phases => config_material%get('phase') phases => config_material%get('phase')
allocate(param(Ninstances)) allocate(param(phases%length))
allocate(source_thermal_externalheat_offset (phases%length), source=0) allocate(source_thermal_externalheat_offset (phases%length), source=0)
allocate(source_thermal_externalheat_instance(phases%length), source=0)
do p = 1, phases%length do ph = 1, phases%length
phase => phases%get(p) phase => phases%get(ph)
if(any(mySources(:,p))) source_thermal_externalheat_instance(p) = count(mySources(:,1:p)) if(count(mySources(:,ph)) == 0) cycle
if(count(mySources(:,p)) == 0) cycle
thermal => phase%get('thermal') thermal => phase%get('thermal')
sources => thermal%get('source') sources => thermal%get('source')
do so = 1, sources%length do so = 1, sources%length
if(mySources(so,p)) then if(mySources(so,ph)) then
source_thermal_externalheat_offset(p) = so source_thermal_externalheat_offset(ph) = so
associate(prm => param(source_thermal_externalheat_instance(p))) associate(prm => param(ph))
src => sources%get(so) src => sources%get(so)
prm%t_n = src%get_asFloats('t_n') prm%t_n = src%get_asFloats('t_n')
prm%nIntervals = size(prm%t_n) - 1 prm%nIntervals = size(prm%t_n) - 1
prm%f_T = src%get_asFloats('f_T',requiredSize = size(prm%t_n)) prm%f_T = src%get_asFloats('f_T',requiredSize = size(prm%t_n))
Nconstituents = count(material_phaseAt==p) * discretization_nIPs Nconstituents = count(material_phaseAt2 == ph)
call constitutive_allocateState(thermalState(p)%p(so),Nconstituents,1,1,0) call constitutive_allocateState(thermalState(ph)%p(so),Nconstituents,1,1,0)
end associate end associate
endif endif
enddo enddo
@ -104,7 +101,7 @@ end subroutine externalheat_dotState
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief returns local heat generation rate !> @brief returns local heat generation rate
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine thermal_externalheat_getRate(TDot, ph, me) module subroutine externalheat_getRate(TDot, ph, me)
integer, intent(in) :: & integer, intent(in) :: &
ph, & ph, &
@ -119,19 +116,19 @@ module subroutine thermal_externalheat_getRate(TDot, ph, me)
so = source_thermal_externalheat_offset(ph) so = source_thermal_externalheat_offset(ph)
associate(prm => param(source_thermal_externalheat_instance(ph))) associate(prm => param(ph))
do interval = 1, prm%nIntervals ! scan through all rate segments do interval = 1, prm%nIntervals ! scan through all rate segments
frac_time = (thermalState(ph)%p(so)%state(1,me) - prm%t_n(interval)) & frac_time = (thermalState(ph)%p(so)%state(1,me) - prm%t_n(interval)) &
/ (prm%t_n(interval+1) - prm%t_n(interval)) ! fractional time within segment / (prm%t_n(interval+1) - prm%t_n(interval)) ! fractional time within segment
if ( (frac_time < 0.0_pReal .and. interval == 1) & if ( (frac_time < 0.0_pReal .and. interval == 1) &
.or. (frac_time >= 1.0_pReal .and. interval == prm%nIntervals) & .or. (frac_time >= 1.0_pReal .and. interval == prm%nIntervals) &
.or. (frac_time >= 0.0_pReal .and. frac_time < 1.0_pReal) ) & .or. (frac_time >= 0.0_pReal .and. frac_time < 1.0_pReal) ) &
TDot = prm%f_T(interval ) * (1.0_pReal - frac_time) + & TDot = prm%f_T(interval ) * (1.0_pReal - frac_time) + &
prm%f_T(interval+1) * frac_time ! interpolate heat rate between segment boundaries... prm%f_T(interval+1) * frac_time ! interpolate heat rate between segment boundaries...
! ...or extrapolate if outside me bounds ! ...or extrapolate if outside me bounds
enddo enddo
end associate end associate
end subroutine thermal_externalheat_getRate end subroutine externalheat_getRate
end submodule externalheat end submodule externalheat