DAMASK_EICMD/src/phase_thermal.f90

426 lines
12 KiB
Fortran
Raw Normal View History

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
!----------------------------------------------------------------------------------------------------
submodule(phase) thermal
2020-12-30 18:27:37 +05:30
2021-04-11 12:16:31 +05:30
type :: tThermalParameters
2022-06-24 10:34:52 +05:30
real(pReal) :: C_p = 0.0_pReal !< heat capacity
real(pReal), dimension(3,3) :: K = 0.0_pReal !< thermal conductivity
2022-02-19 23:26:41 +05:30
character(len=pStringLen), allocatable, dimension(:) :: output
2021-04-11 12:16:31 +05:30
end type tThermalParameters
2021-02-13 23:11:30 +05:30
integer, dimension(:), allocatable :: &
thermal_Nsources
2021-02-13 12:25:32 +05:30
type(tSourceState), allocatable, dimension(:) :: &
thermalState
2021-01-08 04:20:06 +05:30
enum, bind(c); enumerator :: &
THERMAL_UNDEFINED_ID ,&
THERMAL_DISSIPATION_ID, &
THERMAL_EXTERNALHEAT_ID
end enum
2021-03-05 01:46:36 +05:30
type :: tDataContainer ! ?? not very telling name. Better: "fieldQuantities" ??
2021-01-24 15:46:17 +05:30
real(pReal), dimension(:), allocatable :: T, dot_T
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
2021-04-25 11:36:52 +05:30
type(tDataContainer), dimension(:), allocatable :: current ! ?? not very telling name. Better: "field" ?? MD: current(ho)%T(en) reads quite good
2021-04-11 12:16:31 +05:30
type(tThermalParameters), dimension(:), allocatable :: param
2021-01-08 02:45:18 +05:30
integer :: thermal_source_maxSizeDotState
2021-01-26 12:25:06 +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-04-25 11:36:52 +05:30
module subroutine externalheat_dotState(ph, en)
2021-01-26 12:25:06 +05:30
integer, intent(in) :: &
ph, &
2021-04-25 11:36:52 +05:30
en
2021-01-26 12:25:06 +05:30
end subroutine externalheat_dotState
2021-04-25 11:36:52 +05:30
module function dissipation_f_T(ph,en) result(f_T)
2021-01-26 12:25:06 +05:30
integer, intent(in) :: &
2021-01-27 04:14:11 +05:30
ph, &
2021-04-25 11:36:52 +05:30
en
2021-04-08 02:11:49 +05:30
real(pReal) :: f_T
end function dissipation_f_T
2021-01-26 12:25:06 +05:30
2021-04-25 11:36:52 +05:30
module function externalheat_f_T(ph,en) result(f_T)
2021-01-19 15:00:10 +05:30
integer, intent(in) :: &
2021-01-19 15:02:56 +05:30
ph, &
2021-04-25 11:36:52 +05:30
en
2021-04-08 02:11:49 +05:30
real(pReal) :: f_T
end function externalheat_f_T
end interface
2020-07-12 20:14:26 +05:30
contains
2020-07-12 20:14:26 +05:30
!----------------------------------------------------------------------------------------------
2022-06-24 10:34:52 +05:30
!< @brief Initializes thermal sources and kinematics mechanism.
2020-07-12 20:14:26 +05:30
!----------------------------------------------------------------------------------------------
module subroutine thermal_init(phases)
2020-12-30 18:27:37 +05:30
type(tDict), pointer :: &
phases
2020-12-30 18:27:37 +05:30
type(tDict), pointer :: &
phase, &
thermal
type(tList), pointer :: &
sources
2021-01-08 02:45:18 +05:30
integer :: &
2021-01-08 02:45:18 +05:30
ph, so, &
2021-03-05 01:46:36 +05:30
Nmembers
print'(/,1x,a)', '<<<+- phase:thermal init -+>>>'
2023-01-18 23:20:01 +05:30
allocate(current(phases%length))
2021-03-05 01:46:36 +05:30
allocate(thermalState(phases%length))
2021-01-08 02:45:18 +05:30
allocate(thermal_Nsources(phases%length),source = 0)
2021-04-11 12:16:31 +05:30
allocate(param(phases%length))
do ph = 1, phases%length
2023-01-23 13:01:59 +05:30
Nmembers = count(material_ID_phase == ph)
2022-02-13 03:08:58 +05:30
allocate(current(ph)%T(Nmembers),source=T_ROOM)
2021-03-05 01:46:36 +05:30
allocate(current(ph)%dot_T(Nmembers),source=0.0_pReal)
phase => phases%get_dict(ph)
thermal => phase%get_dict('thermal',defaultVal=emptyDict)
2021-04-11 17:25:30 +05:30
2022-02-13 03:08:58 +05:30
! ToDo: temperature dependency of K and C_p
if (thermal%length > 0) then
param(ph)%C_p = thermal%get_asFloat('C_p')
param(ph)%K(1,1) = thermal%get_asFloat('K_11')
if (any(phase_lattice(ph) == ['hP','tI'])) param(ph)%K(3,3) = thermal%get_asFloat('K_33')
param(ph)%K = lattice_symmetrize_33(param(ph)%K,phase_lattice(ph))
2022-02-19 23:26:41 +05:30
#if defined(__GFORTRAN__)
param(ph)%output = output_as1dString(thermal)
#else
param(ph)%output = thermal%get_as1dString('output',defaultVal=emptyStringArray)
#endif
sources => thermal%get_list('source',defaultVal=emptyList)
2022-02-13 03:08:58 +05:30
thermal_Nsources(ph) = sources%length
else
thermal_Nsources(ph) = 0
end if
2021-01-08 02:45:18 +05:30
allocate(thermalstate(ph)%p(thermal_Nsources(ph)))
2021-04-11 17:25:30 +05:30
2022-06-09 02:36:01 +05:30
end do
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
2021-03-05 01:46:36 +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
2022-06-09 02:36:01 +05:30
end if
2020-12-30 14:24:06 +05:30
2021-01-08 02:45:18 +05:30
thermal_source_maxSizeDotState = 0
2021-03-05 01:46:36 +05:30
do ph = 1,phases%length
2021-01-08 02:45:18 +05:30
do so = 1,thermal_Nsources(ph)
thermalState(ph)%p(so)%state = thermalState(ph)%p(so)%state0
2022-06-09 02:36:01 +05:30
end do
2021-01-08 02:45:18 +05:30
thermal_source_maxSizeDotState = max(thermal_source_maxSizeDotState, &
maxval(thermalState(ph)%p%sizeDotState))
2022-06-09 02:36:01 +05:30
end do
2021-01-08 02:45:18 +05:30
end subroutine thermal_init
2020-07-12 20:14:26 +05:30
!----------------------------------------------------------------------------------------------
2022-06-24 10:34:52 +05:30
!< @brief Calculate thermal source.
2020-07-12 20:14:26 +05:30
!----------------------------------------------------------------------------------------------
2021-04-25 11:36:52 +05:30
module function phase_f_T(ph,en) result(f)
2020-12-29 11:50:37 +05:30
2021-04-25 11:36:52 +05:30
integer, intent(in) :: ph, en
2021-04-09 03:10:20 +05:30
real(pReal) :: f
2021-04-08 02:11:49 +05:30
integer :: so
2020-08-13 00:44:00 +05:30
2021-04-09 03:10:20 +05:30
f = 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))
2021-04-08 02:11:49 +05:30
2021-01-27 04:26:20 +05:30
case (THERMAL_DISSIPATION_ID)
2021-04-25 11:36:52 +05:30
f = f + dissipation_f_T(ph,en)
2020-08-13 00:44:00 +05:30
2021-01-27 04:26:20 +05:30
case (THERMAL_EXTERNALHEAT_ID)
2021-04-25 11:36:52 +05:30
f = f + externalheat_f_T(ph,en)
2020-08-13 00:44:00 +05:30
2021-01-27 04:26:20 +05:30
end select
2021-04-08 02:11:49 +05:30
2022-06-09 02:36:01 +05:30
end do
2021-01-27 04:14:11 +05:30
2021-04-08 02:11:49 +05:30
end function phase_f_T
2020-07-15 18:05:21 +05:30
2021-01-08 02:45:18 +05:30
!--------------------------------------------------------------------------------------------------
2022-06-24 10:34:52 +05:30
!> @brief tbd.
2021-01-08 02:45:18 +05:30
!--------------------------------------------------------------------------------------------------
2021-04-25 11:36:52 +05:30
function phase_thermal_collectDotState(ph,en) result(broken)
2021-01-08 02:45:18 +05:30
2021-04-25 11:36:52 +05:30
integer, intent(in) :: ph, en
2021-01-08 02:45:18 +05:30
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-04-25 11:36:52 +05:30
call externalheat_dotState(ph,en)
2021-01-08 02:45:18 +05:30
2021-04-25 11:36:52 +05:30
broken = broken .or. any(IEEE_is_NaN(thermalState(ph)%p(i)%dotState(:,en)))
2021-01-08 02:45:18 +05:30
2022-06-09 02:36:01 +05:30
end do SourceLoop
2021-01-08 02:45:18 +05:30
2021-02-09 03:51:53 +05:30
end function phase_thermal_collectDotState
2021-01-08 02:45:18 +05:30
2021-04-11 16:51:27 +05:30
!--------------------------------------------------------------------------------------------------
2021-04-15 15:37:33 +05:30
!> @brief Thermal viscosity.
2021-04-11 16:51:27 +05:30
!--------------------------------------------------------------------------------------------------
module function phase_mu_T(co,ce) result(mu)
integer, intent(in) :: co, ce
real(pReal) :: mu
2023-01-23 13:01:59 +05:30
mu = phase_rho(material_ID_phase(co,ce)) &
* param(material_ID_phase(co,ce))%C_p
2021-04-11 16:51:27 +05:30
end function phase_mu_T
!--------------------------------------------------------------------------------------------------
2022-06-24 10:34:52 +05:30
!> @brief Thermal conductivity in reference configuration.
2021-04-11 16:51:27 +05:30
!--------------------------------------------------------------------------------------------------
module function phase_K_T(co,ce) result(K)
integer, intent(in) :: co, ce
real(pReal), dimension(3,3) :: K
2023-01-23 13:01:59 +05:30
K = crystallite_push33ToRef(co,ce,param(material_ID_phase(co,ce))%K)
2021-04-11 16:51:27 +05:30
end function phase_K_T
2021-07-17 00:20:08 +05:30
module function phase_thermal_constitutive(Delta_t,ph,en) result(converged_)
real(pReal), intent(in) :: Delta_t
2021-04-25 11:36:52 +05:30
integer, intent(in) :: ph, en
logical :: converged_
2021-04-25 11:36:52 +05:30
converged_ = .not. integrateThermalState(Delta_t,ph,en)
2021-07-17 00:20:08 +05:30
end function phase_thermal_constitutive
2021-01-08 02:45:18 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief integrate state with 1st order explicit Euler method
2021-01-08 02:45:18 +05:30
!--------------------------------------------------------------------------------------------------
2021-04-25 11:36:52 +05:30
function integrateThermalState(Delta_t, ph,en) result(broken)
2021-01-08 02:45:18 +05:30
real(pReal), intent(in) :: Delta_t
2021-04-25 11:36:52 +05:30
integer, intent(in) :: ph, en
logical :: &
broken
2021-01-08 02:45:18 +05:30
integer :: &
so, &
sizeDotState
2021-01-08 02:45:18 +05:30
2022-06-24 10:34:52 +05:30
2021-04-25 11:36:52 +05:30
broken = phase_thermal_collectDotState(ph,en)
2021-03-05 01:46:36 +05:30
if (broken) return
2021-01-08 02:45:18 +05:30
do so = 1, thermal_Nsources(ph)
sizeDotState = thermalState(ph)%p(so)%sizeDotState
2021-04-25 11:36:52 +05:30
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
2022-06-09 02:36:01 +05:30
end do
2021-01-08 02:45:18 +05:30
end function integrateThermalState
2022-01-11 01:04:50 +05:30
module subroutine thermal_restartWrite(groupHandle,ph)
integer(HID_T), intent(in) :: groupHandle
integer, intent(in) :: ph
integer :: so
2022-02-03 12:28:51 +05:30
2022-01-11 01:04:50 +05:30
do so = 1,thermal_Nsources(ph)
2022-02-03 03:52:44 +05:30
call HDF5_write(thermalState(ph)%p(so)%state,groupHandle,'omega_thermal')
2022-06-09 02:36:01 +05:30
end do
2022-01-11 01:04:50 +05:30
end subroutine thermal_restartWrite
module subroutine thermal_restartRead(groupHandle,ph)
integer(HID_T), intent(in) :: groupHandle
integer, intent(in) :: ph
integer :: so
2022-02-03 12:28:51 +05:30
2022-01-11 01:04:50 +05:30
do so = 1,thermal_Nsources(ph)
2022-02-03 03:52:44 +05:30
call HDF5_read(thermalState(ph)%p(so)%state0,groupHandle,'omega_thermal')
2022-06-09 02:36:01 +05:30
end do
2022-01-11 01:04:50 +05:30
end subroutine thermal_restartRead
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
2022-06-09 02:36:01 +05:30
end do
end do
2020-12-31 14:24:13 +05:30
end subroutine thermal_forward
2020-12-30 18:27:37 +05:30
!----------------------------------------------------------------------------------------------
!< @brief Get temperature (for use by non-thermal physics)
!----------------------------------------------------------------------------------------------
pure module function thermal_T(ph,en) result(T)
2020-12-30 14:24:06 +05:30
2021-04-25 11:36:52 +05:30
integer, intent(in) :: ph, en
2020-12-30 14:24:06 +05:30
real(pReal) :: T
2021-04-25 11:36:52 +05:30
T = current(ph)%T(en)
2020-12-30 14:24:06 +05:30
end function thermal_T
2020-12-30 14:24:06 +05:30
!----------------------------------------------------------------------------------------------
!< @brief Get rate of temperature (for use by non-thermal physics)
!----------------------------------------------------------------------------------------------
2021-04-25 11:36:52 +05:30
module function thermal_dot_T(ph,en) result(dot_T)
2021-04-25 11:36:52 +05:30
integer, intent(in) :: ph, en
real(pReal) :: dot_T
2021-04-25 11:36:52 +05:30
dot_T = current(ph)%dot_T(en)
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
integer, intent(in) :: ce, co
2020-12-30 18:27:37 +05:30
2023-01-23 13:01:59 +05:30
current(material_ID_phase(co,ce))%T(material_entry_phase(co,ce)) = T
current(material_ID_phase(co,ce))%dot_T(material_entry_phase(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
type(tDict), pointer :: &
2021-01-08 02:45:18 +05:30
phases, &
phase, &
thermal, &
2021-01-08 02:45:18 +05:30
src
type(tList), pointer :: &
sources
2021-01-08 02:45:18 +05:30
integer :: p,s
phases => config_material%get_dict('phase')
2021-01-08 02:45:18 +05:30
allocate(active_source(src_length,phases%length), source = .false. )
do p = 1, phases%length
phase => phases%get_dict(p)
thermal => phase%get_dict('thermal',defaultVal=emptyDict)
sources => thermal%get_list('source',defaultVal=emptyList)
2021-03-05 01:46:36 +05:30
do s = 1, sources%length
src => sources%get_dict(s)
2021-03-05 01:46:36 +05:30
active_source(s,p) = src%get_asString('type') == source_label
2022-06-09 02:36:01 +05:30
end do
end do
2021-01-08 02:45:18 +05:30
end function thermal_active
2022-02-19 23:26:41 +05:30
!----------------------------------------------------------------------------------------------
2023-01-19 22:07:45 +05:30
!< @brief Write thermal sources results to HDF5 output file.
2022-02-19 23:26:41 +05:30
!----------------------------------------------------------------------------------------------
2023-01-19 22:07:45 +05:30
module subroutine thermal_result(group,ph)
2022-02-19 23:26:41 +05:30
character(len=*), intent(in) :: group
integer, intent(in) :: ph
integer :: ou
2022-02-23 03:46:14 +05:30
if (.not. allocated(param(ph)%output)) return
2023-01-19 22:07:45 +05:30
call result_closeGroup(result_addGroup(group//'thermal'))
2022-02-19 23:26:41 +05:30
do ou = 1, size(param(ph)%output)
select case(trim(param(ph)%output(ou)))
case ('T')
2023-01-19 22:07:45 +05:30
call result_writeDataset(current(ph)%T,group//'thermal','T', 'temperature','K')
2022-02-19 23:26:41 +05:30
end select
end do
2023-01-19 22:07:45 +05:30
end subroutine thermal_result
2022-02-19 23:26:41 +05:30
2021-01-26 05:50:45 +05:30
end submodule thermal