2015-07-27 16:39:37 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2019-02-23 01:07:41 +05:30
|
|
|
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
|
2015-07-27 16:39:37 +05:30
|
|
|
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
2016-10-19 01:53:52 +05:30
|
|
|
!> @author Philip Eisenlohr, Michigan State University
|
|
|
|
!> @brief material subroutine for variable heat source
|
2015-07-27 16:39:37 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2023-07-18 07:42:57 +05:30
|
|
|
submodule(phase:thermal) source_externalheat
|
2015-07-27 16:39:37 +05:30
|
|
|
|
2019-05-28 15:36:21 +05:30
|
|
|
|
2019-12-21 12:25:42 +05:30
|
|
|
integer, dimension(:), allocatable :: &
|
2023-07-23 00:34:11 +05:30
|
|
|
source_ID !< index in phase source list corresponding to this source
|
2018-12-31 01:28:38 +05:30
|
|
|
|
2020-08-15 19:32:10 +05:30
|
|
|
type :: tParameters !< container type for internal constitutive parameters
|
2023-07-23 00:34:11 +05:30
|
|
|
type(tTable) :: f !< external heat power as (tabulated) function of time
|
2019-02-23 01:07:41 +05:30
|
|
|
end type tParameters
|
2018-12-31 01:28:38 +05:30
|
|
|
|
2020-10-28 02:03:30 +05:30
|
|
|
type(tParameters), dimension(:), allocatable :: param !< containers of constitutive parameters (len Ninstances)
|
2018-12-31 01:28:38 +05:30
|
|
|
|
|
|
|
|
2015-07-27 16:39:37 +05:30
|
|
|
contains
|
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief module initialization
|
|
|
|
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2023-07-23 00:34:11 +05:30
|
|
|
module function source_externalheat_init(maxNsources) result(isMySource)
|
2020-02-26 23:07:17 +05:30
|
|
|
|
2023-07-23 00:34:11 +05:30
|
|
|
integer, intent(in) :: maxNsources
|
|
|
|
logical, dimension(:,:), allocatable :: isMySource
|
2020-08-15 19:32:10 +05:30
|
|
|
|
2022-10-25 21:39:36 +05:30
|
|
|
type(tDict), pointer :: &
|
2020-08-15 19:32:10 +05:30
|
|
|
phases, &
|
|
|
|
phase, &
|
2022-10-25 21:39:36 +05:30
|
|
|
thermal, &
|
2021-01-08 02:45:18 +05:30
|
|
|
src
|
2022-10-25 21:39:36 +05:30
|
|
|
type(tList), pointer :: &
|
|
|
|
sources
|
2023-03-01 01:27:44 +05:30
|
|
|
character(len=:), allocatable :: refs
|
2023-07-23 00:47:30 +05:30
|
|
|
integer :: ph,Nmembers,so,Nsources
|
2020-02-26 23:07:17 +05:30
|
|
|
|
|
|
|
|
2023-07-23 00:34:11 +05:30
|
|
|
isMySource = thermal_active('externalheat',maxNsources)
|
|
|
|
if (count(isMySource) == 0) return
|
2023-01-18 23:20:01 +05:30
|
|
|
|
2023-07-18 07:42:57 +05:30
|
|
|
print'(/,1x,a)', '<<<+- phase:thermal:source_externalheat init -+>>>'
|
2023-08-29 07:11:48 +05:30
|
|
|
print'(/,1x,a,1x,i0)', '# phases:',count(isMySource); flush(IO_STDOUT)
|
2021-01-08 02:45:18 +05:30
|
|
|
|
2020-02-26 23:07:17 +05:30
|
|
|
|
2022-10-25 21:39:36 +05:30
|
|
|
phases => config_material%get_dict('phase')
|
2021-01-27 04:26:20 +05:30
|
|
|
allocate(param(phases%length))
|
2023-07-18 07:42:57 +05:30
|
|
|
allocate(source_ID(phases%length), source=0)
|
2020-08-15 19:32:10 +05:30
|
|
|
|
2021-01-27 04:26:20 +05:30
|
|
|
do ph = 1, phases%length
|
2023-07-23 00:47:30 +05:30
|
|
|
Nsources = count(isMySource(:,ph))
|
|
|
|
if (Nsources == 0) cycle
|
|
|
|
if (Nsources > 1) call IO_error(600,ext_msg='externalheat')
|
2023-07-22 23:31:53 +05:30
|
|
|
Nmembers = count(material_ID_phase == ph)
|
|
|
|
phase => phases%get_dict(ph)
|
2022-10-25 21:39:36 +05:30
|
|
|
thermal => phase%get_dict('thermal')
|
|
|
|
sources => thermal%get_list('source')
|
2021-01-27 04:14:11 +05:30
|
|
|
do so = 1, sources%length
|
2023-07-23 00:34:11 +05:30
|
|
|
if (isMySource(so,ph)) then
|
2023-07-18 07:42:57 +05:30
|
|
|
source_ID(ph) = so
|
2021-01-27 04:26:20 +05:30
|
|
|
associate(prm => param(ph))
|
2022-10-25 21:39:36 +05:30
|
|
|
src => sources%get_dict(so)
|
2023-08-29 07:11:48 +05:30
|
|
|
print'(/,1x,a,1x,i0,1x,a,1x,a,1x,i0)', 'phase',ph,'('//phases%key(ph)//')','source',so
|
2023-03-01 01:27:44 +05:30
|
|
|
refs = config_listReferences(src,indent=3)
|
|
|
|
if (len(refs) > 0) print'(/,1x,a)', refs
|
2020-02-26 23:07:17 +05:30
|
|
|
|
2022-12-08 21:27:26 +05:30
|
|
|
prm%f = table(src,'t','f')
|
2021-03-05 01:46:36 +05:30
|
|
|
call phase_allocateState(thermalState(ph)%p(so),Nmembers,1,1,0)
|
2020-08-15 19:32:10 +05:30
|
|
|
end associate
|
2023-07-23 00:47:30 +05:30
|
|
|
exit
|
2021-11-15 23:05:44 +05:30
|
|
|
end if
|
|
|
|
end do
|
|
|
|
end do
|
2019-02-23 01:07:41 +05:30
|
|
|
|
2023-07-18 07:42:57 +05:30
|
|
|
end function source_externalheat_init
|
2015-07-27 16:39:37 +05:30
|
|
|
|
2019-02-22 19:51:48 +05:30
|
|
|
|
2015-07-27 16:39:37 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2016-10-19 01:53:52 +05:30
|
|
|
!> @brief rate of change of state
|
|
|
|
!> @details state only contains current time to linearly interpolate given heat powers
|
2015-07-27 16:39:37 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2023-07-18 07:42:57 +05:30
|
|
|
module subroutine source_externalheat_dotState(ph, en)
|
2020-02-26 23:07:17 +05:30
|
|
|
|
2019-03-24 15:48:59 +05:30
|
|
|
integer, intent(in) :: &
|
2021-01-19 15:02:56 +05:30
|
|
|
ph, &
|
2021-04-25 11:36:52 +05:30
|
|
|
en
|
2020-02-29 12:28:33 +05:30
|
|
|
|
2020-02-26 23:07:17 +05:30
|
|
|
|
2023-07-18 07:42:57 +05:30
|
|
|
thermalState(ph)%p(source_ID(ph))%dotState(1,en) = 1.0_pREAL ! state is current time
|
2020-02-26 23:07:17 +05:30
|
|
|
|
2023-07-18 07:42:57 +05:30
|
|
|
end subroutine source_externalheat_dotState
|
2015-07-27 16:39:37 +05:30
|
|
|
|
2019-12-05 15:50:05 +05:30
|
|
|
|
2015-07-27 16:39:37 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2020-02-26 23:07:17 +05:30
|
|
|
!> @brief returns local heat generation rate
|
2015-07-27 16:39:37 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2023-07-18 07:42:57 +05:30
|
|
|
module function source_externalheat_f_T(ph,en) result(f_T)
|
2020-02-26 23:07:17 +05:30
|
|
|
|
2019-03-24 15:48:59 +05:30
|
|
|
integer, intent(in) :: &
|
2021-01-19 15:02:56 +05:30
|
|
|
ph, &
|
2021-04-25 11:36:52 +05:30
|
|
|
en
|
2023-06-04 10:52:25 +05:30
|
|
|
real(pREAL) :: &
|
2021-04-08 02:11:49 +05:30
|
|
|
f_T
|
2020-02-29 12:28:33 +05:30
|
|
|
|
2020-02-26 23:07:17 +05:30
|
|
|
|
2021-01-27 04:26:20 +05:30
|
|
|
associate(prm => param(ph))
|
2023-07-18 07:42:57 +05:30
|
|
|
f_T = prm%f%at(thermalState(ph)%p(source_ID(ph))%state(1,en))
|
2020-02-29 12:28:33 +05:30
|
|
|
end associate
|
2020-02-26 23:07:17 +05:30
|
|
|
|
2023-07-18 07:42:57 +05:30
|
|
|
end function source_externalheat_f_T
|
2020-02-26 23:07:17 +05:30
|
|
|
|
2023-07-18 07:42:57 +05:30
|
|
|
end submodule source_externalheat
|