2020-07-15 18:05:21 +05:30
|
|
|
!----------------------------------------------------------------------------------------------------
|
2020-08-13 00:44:00 +05:30
|
|
|
!> @brief internal microstructure state for all thermal sources and kinematics constitutive models
|
2020-07-15 18:05:21 +05:30
|
|
|
!----------------------------------------------------------------------------------------------------
|
2021-01-27 01:22:48 +05:30
|
|
|
submodule(phase) thermal
|
2020-12-30 18:27:37 +05:30
|
|
|
|
2021-01-08 04:20:06 +05:30
|
|
|
enum, bind(c); enumerator :: &
|
|
|
|
THERMAL_UNDEFINED_ID ,&
|
|
|
|
THERMAL_DISSIPATION_ID, &
|
|
|
|
THERMAL_EXTERNALHEAT_ID
|
|
|
|
end enum
|
|
|
|
|
2020-12-30 17:04:00 +05:30
|
|
|
type :: tDataContainer
|
2021-01-24 15:46:17 +05:30
|
|
|
real(pReal), dimension(:), allocatable :: T, dot_T
|
2020-12-30 17:04:00 +05:30
|
|
|
end type tDataContainer
|
2021-01-24 15:46:17 +05:30
|
|
|
integer(kind(THERMAL_UNDEFINED_ID)), dimension(:,:), allocatable :: &
|
2021-01-08 02:45:18 +05:30
|
|
|
thermal_source
|
2020-12-30 18:27:37 +05:30
|
|
|
|
2020-12-30 17:04:00 +05:30
|
|
|
type(tDataContainer), dimension(:), allocatable :: current
|
2020-07-09 04:31:08 +05:30
|
|
|
|
2021-01-08 02:45:18 +05:30
|
|
|
integer :: thermal_source_maxSizeDotState
|
2021-01-26 12:25:06 +05:30
|
|
|
|
|
|
|
|
2020-07-09 04:31:08 +05:30
|
|
|
interface
|
|
|
|
|
2021-01-26 12:25:06 +05:30
|
|
|
module function dissipation_init(source_length) result(mySources)
|
|
|
|
integer, intent(in) :: source_length
|
|
|
|
logical, dimension(:,:), allocatable :: mySources
|
|
|
|
end function dissipation_init
|
2020-12-30 14:24:06 +05:30
|
|
|
|
2021-01-26 12:25:06 +05:30
|
|
|
module function externalheat_init(source_length) result(mySources)
|
|
|
|
integer, intent(in) :: source_length
|
|
|
|
logical, dimension(:,:), allocatable :: mySources
|
|
|
|
end function externalheat_init
|
2020-08-13 00:44:00 +05:30
|
|
|
|
2021-01-27 04:36:41 +05:30
|
|
|
|
2020-07-09 04:31:08 +05:30
|
|
|
|
2020-07-10 18:29:07 +05:30
|
|
|
|
2021-01-26 12:25:06 +05:30
|
|
|
module subroutine externalheat_dotState(ph, me)
|
|
|
|
integer, intent(in) :: &
|
|
|
|
ph, &
|
|
|
|
me
|
|
|
|
end subroutine externalheat_dotState
|
|
|
|
|
2021-01-27 04:26:20 +05:30
|
|
|
module subroutine dissipation_getRate(TDot, ph,me)
|
2021-01-26 12:25:06 +05:30
|
|
|
integer, intent(in) :: &
|
2021-01-27 04:14:11 +05:30
|
|
|
ph, &
|
|
|
|
me
|
2021-01-26 12:25:06 +05:30
|
|
|
real(pReal), intent(out) :: &
|
|
|
|
TDot
|
2021-01-27 04:26:20 +05:30
|
|
|
end subroutine dissipation_getRate
|
2021-01-26 12:25:06 +05:30
|
|
|
|
2021-01-27 04:26:20 +05:30
|
|
|
module subroutine externalheat_getRate(TDot, ph,me)
|
2021-01-19 15:00:10 +05:30
|
|
|
integer, intent(in) :: &
|
2021-01-19 15:02:56 +05:30
|
|
|
ph, &
|
|
|
|
me
|
2021-01-26 12:25:06 +05:30
|
|
|
real(pReal), intent(out) :: &
|
|
|
|
TDot
|
2021-01-27 04:26:20 +05:30
|
|
|
end subroutine externalheat_getRate
|
2020-07-09 04:31:08 +05:30
|
|
|
|
|
|
|
end interface
|
2020-07-12 20:14:26 +05:30
|
|
|
|
2020-07-09 04:31:08 +05:30
|
|
|
contains
|
|
|
|
|
2020-07-12 20:14:26 +05:30
|
|
|
!----------------------------------------------------------------------------------------------
|
|
|
|
!< @brief initializes thermal sources and kinematics mechanism
|
|
|
|
!----------------------------------------------------------------------------------------------
|
2020-12-30 17:04:00 +05:30
|
|
|
module subroutine thermal_init(phases)
|
2020-12-30 18:27:37 +05:30
|
|
|
|
2020-12-30 17:04:00 +05:30
|
|
|
class(tNode), pointer :: &
|
|
|
|
phases
|
2020-12-30 18:27:37 +05:30
|
|
|
|
2021-01-08 02:45:18 +05:30
|
|
|
class(tNode), pointer :: &
|
|
|
|
phase, thermal, sources
|
|
|
|
|
2020-12-30 17:04:00 +05:30
|
|
|
integer :: &
|
2021-01-08 02:45:18 +05:30
|
|
|
ph, so, &
|
2020-12-30 17:04:00 +05:30
|
|
|
Nconstituents
|
|
|
|
|
|
|
|
|
2021-01-27 15:14:03 +05:30
|
|
|
print'(/,a)', ' <<<+- phase:thermal init -+>>>'
|
2020-12-30 17:04:00 +05:30
|
|
|
|
|
|
|
allocate(current(phases%length))
|
|
|
|
|
2021-01-08 02:45:18 +05:30
|
|
|
allocate(thermalState (phases%length))
|
|
|
|
allocate(thermal_Nsources(phases%length),source = 0)
|
2020-07-09 04:31:08 +05:30
|
|
|
|
2020-12-30 17:04:00 +05:30
|
|
|
do ph = 1, phases%length
|
2020-12-30 18:27:37 +05:30
|
|
|
|
2021-01-26 12:25:06 +05:30
|
|
|
Nconstituents = count(material_phaseAt2 == ph)
|
2020-12-30 17:04:00 +05:30
|
|
|
|
2021-01-17 14:00:42 +05:30
|
|
|
allocate(current(ph)%T(Nconstituents),source=300.0_pReal)
|
2021-01-24 15:46:17 +05:30
|
|
|
allocate(current(ph)%dot_T(Nconstituents),source=0.0_pReal)
|
2021-01-08 02:45:18 +05:30
|
|
|
phase => phases%get(ph)
|
|
|
|
if(phase%contains('thermal')) then
|
|
|
|
thermal => phase%get('thermal')
|
|
|
|
sources => thermal%get('source',defaultVal=emptyList)
|
|
|
|
|
|
|
|
thermal_Nsources(ph) = sources%length
|
|
|
|
endif
|
|
|
|
allocate(thermalstate(ph)%p(thermal_Nsources(ph)))
|
2020-12-30 17:04:00 +05:30
|
|
|
enddo
|
2020-12-30 18:27:37 +05:30
|
|
|
|
2021-01-08 04:20:06 +05:30
|
|
|
allocate(thermal_source(maxval(thermal_Nsources),phases%length), source = THERMAL_UNDEFINED_ID)
|
2021-01-08 02:45:18 +05:30
|
|
|
|
|
|
|
if(maxval(thermal_Nsources) /= 0) then
|
2021-01-26 12:25:06 +05:30
|
|
|
where(dissipation_init (maxval(thermal_Nsources))) thermal_source = THERMAL_DISSIPATION_ID
|
|
|
|
where(externalheat_init(maxval(thermal_Nsources))) thermal_source = THERMAL_EXTERNALHEAT_ID
|
2020-12-30 14:24:06 +05:30
|
|
|
endif
|
|
|
|
|
2021-01-08 02:45:18 +05:30
|
|
|
thermal_source_maxSizeDotState = 0
|
|
|
|
PhaseLoop2:do ph = 1,phases%length
|
|
|
|
|
|
|
|
do so = 1,thermal_Nsources(ph)
|
2021-01-25 18:33:49 +05:30
|
|
|
thermalState(ph)%p(so)%state = thermalState(ph)%p(so)%state0
|
2021-01-08 02:45:18 +05:30
|
|
|
enddo
|
|
|
|
|
2021-01-25 18:33:49 +05:30
|
|
|
thermal_source_maxSizeDotState = max(thermal_source_maxSizeDotState, &
|
|
|
|
maxval(thermalState(ph)%p%sizeDotState))
|
2021-01-08 02:45:18 +05:30
|
|
|
enddo PhaseLoop2
|
|
|
|
|
2020-07-09 04:31:08 +05:30
|
|
|
end subroutine thermal_init
|
|
|
|
|
|
|
|
|
2020-07-12 20:14:26 +05:30
|
|
|
!----------------------------------------------------------------------------------------------
|
|
|
|
!< @brief calculates thermal dissipation rate
|
|
|
|
!----------------------------------------------------------------------------------------------
|
2021-02-09 03:51:53 +05:30
|
|
|
module subroutine phase_thermal_getRate(TDot, ph,me)
|
2020-12-29 11:50:37 +05:30
|
|
|
|
2021-01-27 04:14:11 +05:30
|
|
|
integer, intent(in) :: ph, me
|
2021-01-08 12:56:17 +05:30
|
|
|
real(pReal), intent(out) :: &
|
2021-01-08 13:27:30 +05:30
|
|
|
TDot
|
2020-07-09 04:31:08 +05:30
|
|
|
|
|
|
|
real(pReal) :: &
|
2021-01-08 13:27:30 +05:30
|
|
|
my_Tdot
|
2020-07-09 04:31:08 +05:30
|
|
|
integer :: &
|
2021-01-27 04:14:11 +05:30
|
|
|
so
|
2020-08-13 00:44:00 +05:30
|
|
|
|
|
|
|
|
2021-01-08 13:27:30 +05:30
|
|
|
TDot = 0.0_pReal
|
2021-01-27 04:14:11 +05:30
|
|
|
|
2021-01-27 04:26:20 +05:30
|
|
|
do so = 1, thermal_Nsources(ph)
|
|
|
|
select case(thermal_source(so,ph))
|
|
|
|
case (THERMAL_DISSIPATION_ID)
|
|
|
|
call dissipation_getRate(my_Tdot, ph,me)
|
2020-08-13 00:44:00 +05:30
|
|
|
|
2021-01-27 04:26:20 +05:30
|
|
|
case (THERMAL_EXTERNALHEAT_ID)
|
|
|
|
call externalheat_getRate(my_Tdot, ph,me)
|
2020-08-13 00:44:00 +05:30
|
|
|
|
2021-01-27 04:26:20 +05:30
|
|
|
case default
|
|
|
|
my_Tdot = 0.0_pReal
|
|
|
|
end select
|
|
|
|
Tdot = Tdot + my_Tdot
|
|
|
|
enddo
|
2021-01-27 04:14:11 +05:30
|
|
|
|
2020-08-13 00:44:00 +05:30
|
|
|
|
2021-02-09 03:51:53 +05:30
|
|
|
end subroutine phase_thermal_getRate
|
2020-07-09 04:31:08 +05:30
|
|
|
|
2020-07-15 18:05:21 +05:30
|
|
|
|
2021-01-08 02:45:18 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief contains the constitutive equation for calculating the rate of change of microstructure
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2021-02-09 03:51:53 +05:30
|
|
|
function phase_thermal_collectDotState(ph,me) result(broken)
|
2021-01-08 02:45:18 +05:30
|
|
|
|
|
|
|
integer, intent(in) :: ph, me
|
|
|
|
logical :: broken
|
|
|
|
|
|
|
|
integer :: i
|
|
|
|
|
|
|
|
|
|
|
|
broken = .false.
|
|
|
|
|
|
|
|
SourceLoop: do i = 1, thermal_Nsources(ph)
|
|
|
|
|
2021-01-08 04:20:06 +05:30
|
|
|
if (thermal_source(i,ph) == THERMAL_EXTERNALHEAT_ID) &
|
2021-01-26 12:25:06 +05:30
|
|
|
call externalheat_dotState(ph,me)
|
2021-01-08 02:45:18 +05:30
|
|
|
|
|
|
|
broken = broken .or. any(IEEE_is_NaN(thermalState(ph)%p(i)%dotState(:,me)))
|
|
|
|
|
|
|
|
enddo SourceLoop
|
|
|
|
|
2021-02-09 03:51:53 +05:30
|
|
|
end function phase_thermal_collectDotState
|
2021-01-08 02:45:18 +05:30
|
|
|
|
|
|
|
|
2021-01-17 14:00:42 +05:30
|
|
|
module function thermal_stress(Delta_t,ph,me) result(converged_)
|
|
|
|
|
|
|
|
real(pReal), intent(in) :: Delta_t
|
|
|
|
integer, intent(in) :: ph, me
|
|
|
|
logical :: converged_
|
|
|
|
|
|
|
|
|
|
|
|
converged_ = .not. integrateThermalState(Delta_t,ph,me)
|
|
|
|
|
|
|
|
end function thermal_stress
|
|
|
|
|
2021-01-08 05:10:21 +05:30
|
|
|
|
2021-01-08 02:45:18 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2021-01-08 05:10:21 +05:30
|
|
|
!> @brief integrate state with 1st order explicit Euler method
|
2021-01-08 02:45:18 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2021-01-17 14:00:42 +05:30
|
|
|
function integrateThermalState(Delta_t, ph,me) result(broken)
|
2021-01-08 02:45:18 +05:30
|
|
|
|
2021-01-08 05:10:21 +05:30
|
|
|
real(pReal), intent(in) :: Delta_t
|
2021-01-17 14:00:42 +05:30
|
|
|
integer, intent(in) :: ph, me
|
2021-01-08 05:10:21 +05:30
|
|
|
logical :: &
|
|
|
|
broken
|
2021-01-08 02:45:18 +05:30
|
|
|
|
|
|
|
integer :: &
|
2021-01-08 05:10:21 +05:30
|
|
|
so, &
|
|
|
|
sizeDotState
|
2021-01-08 02:45:18 +05:30
|
|
|
|
2021-02-09 03:51:53 +05:30
|
|
|
broken = phase_thermal_collectDotState(ph,me)
|
2021-01-08 02:45:18 +05:30
|
|
|
if(broken) return
|
|
|
|
|
|
|
|
do so = 1, thermal_Nsources(ph)
|
2021-01-08 05:10:21 +05:30
|
|
|
sizeDotState = thermalState(ph)%p(so)%sizeDotState
|
2021-01-24 16:44:45 +05:30
|
|
|
thermalState(ph)%p(so)%state(1:sizeDotState,me) = thermalState(ph)%p(so)%state0(1:sizeDotState,me) &
|
2021-01-08 05:10:21 +05:30
|
|
|
+ thermalState(ph)%p(so)%dotState(1:sizeDotState,me) * Delta_t
|
2021-01-08 02:45:18 +05:30
|
|
|
enddo
|
|
|
|
|
|
|
|
end function integrateThermalState
|
|
|
|
|
|
|
|
|
2020-12-31 14:24:13 +05:30
|
|
|
module subroutine thermal_forward()
|
|
|
|
|
|
|
|
integer :: ph, so
|
|
|
|
|
|
|
|
|
|
|
|
do ph = 1, size(thermalState)
|
2021-01-08 02:45:18 +05:30
|
|
|
do so = 1, size(thermalState(ph)%p)
|
2020-12-31 14:24:13 +05:30
|
|
|
thermalState(ph)%p(so)%state0 = thermalState(ph)%p(so)%state
|
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
|
|
|
|
end subroutine thermal_forward
|
|
|
|
|
|
|
|
|
2020-12-30 18:27:37 +05:30
|
|
|
!----------------------------------------------------------------------------------------------
|
|
|
|
!< @brief Get temperature (for use by non-thermal physics)
|
|
|
|
!----------------------------------------------------------------------------------------------
|
2020-12-30 17:04:00 +05:30
|
|
|
module function thermal_T(ph,me) result(T)
|
2020-12-30 14:24:06 +05:30
|
|
|
|
2020-12-30 17:04:00 +05:30
|
|
|
integer, intent(in) :: ph, me
|
2020-12-30 14:24:06 +05:30
|
|
|
real(pReal) :: T
|
|
|
|
|
|
|
|
|
2020-12-30 17:04:00 +05:30
|
|
|
T = current(ph)%T(me)
|
2020-12-30 14:24:06 +05:30
|
|
|
|
2020-12-30 17:04:00 +05:30
|
|
|
end function thermal_T
|
2020-12-30 14:24:06 +05:30
|
|
|
|
|
|
|
|
2021-01-27 04:36:41 +05:30
|
|
|
!----------------------------------------------------------------------------------------------
|
|
|
|
!< @brief Get rate of temperature (for use by non-thermal physics)
|
|
|
|
!----------------------------------------------------------------------------------------------
|
|
|
|
module function thermal_dot_T(ph,me) result(dot_T)
|
|
|
|
|
|
|
|
integer, intent(in) :: ph, me
|
|
|
|
real(pReal) :: dot_T
|
|
|
|
|
|
|
|
|
|
|
|
dot_T = current(ph)%dot_T(me)
|
|
|
|
|
|
|
|
end function thermal_dot_T
|
|
|
|
|
|
|
|
|
2020-12-30 18:27:37 +05:30
|
|
|
!----------------------------------------------------------------------------------------------
|
|
|
|
!< @brief Set temperature
|
|
|
|
!----------------------------------------------------------------------------------------------
|
2021-02-09 03:51:53 +05:30
|
|
|
module subroutine phase_thermal_setField(T,dot_T, co,ce)
|
2020-12-30 18:27:37 +05:30
|
|
|
|
2021-01-24 17:56:01 +05:30
|
|
|
real(pReal), intent(in) :: T, dot_T
|
2021-01-17 19:22:52 +05:30
|
|
|
integer, intent(in) :: ce, co
|
2020-12-30 18:27:37 +05:30
|
|
|
|
|
|
|
|
2021-01-17 19:22:52 +05:30
|
|
|
current(material_phaseAt2(co,ce))%T(material_phaseMemberAt2(co,ce)) = T
|
2021-01-24 17:56:01 +05:30
|
|
|
current(material_phaseAt2(co,ce))%dot_T(material_phaseMemberAt2(co,ce)) = dot_T
|
2020-12-30 18:27:37 +05:30
|
|
|
|
2021-02-09 03:51:53 +05:30
|
|
|
end subroutine phase_thermal_setField
|
2020-12-30 16:30:47 +05:30
|
|
|
|
|
|
|
|
2021-01-08 02:45:18 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief checks if a source mechanism is active or not
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
function thermal_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, thermal, &
|
|
|
|
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)
|
|
|
|
if (phase%contains('thermal')) then
|
|
|
|
thermal => phase%get('thermal',defaultVal=emptyList)
|
|
|
|
sources => thermal%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
|
|
|
|
endif
|
|
|
|
enddo
|
|
|
|
|
|
|
|
|
|
|
|
end function thermal_active
|
|
|
|
|
|
|
|
|
2021-01-26 05:50:45 +05:30
|
|
|
end submodule thermal
|