hierarchical naming
This commit is contained in:
parent
11046f708e
commit
85dcd7af16
|
@ -18,17 +18,19 @@ submodule(constitutive) thermal
|
||||||
type(tDataContainer), dimension(:), allocatable :: current
|
type(tDataContainer), dimension(:), allocatable :: current
|
||||||
|
|
||||||
integer :: thermal_source_maxSizeDotState
|
integer :: thermal_source_maxSizeDotState
|
||||||
|
|
||||||
|
|
||||||
interface
|
interface
|
||||||
|
|
||||||
module function source_thermal_dissipation_init(source_length) result(mySources)
|
module function 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 source_thermal_dissipation_init
|
end function dissipation_init
|
||||||
|
|
||||||
module function source_thermal_externalheat_init(source_length) result(mySources)
|
module function 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 source_thermal_externalheat_init
|
end function externalheat_init
|
||||||
|
|
||||||
module function kinematics_thermal_expansion_init(kinematics_length) result(myKinematics)
|
module function kinematics_thermal_expansion_init(kinematics_length) result(myKinematics)
|
||||||
integer, intent(in) :: kinematics_length
|
integer, intent(in) :: kinematics_length
|
||||||
|
@ -36,12 +38,11 @@ submodule(constitutive) thermal
|
||||||
end function kinematics_thermal_expansion_init
|
end function kinematics_thermal_expansion_init
|
||||||
|
|
||||||
|
|
||||||
module subroutine source_thermal_externalheat_dotState(ph, me)
|
module subroutine externalheat_dotState(ph, me)
|
||||||
integer, intent(in) :: &
|
integer, intent(in) :: &
|
||||||
ph, &
|
ph, &
|
||||||
me
|
me
|
||||||
end subroutine source_thermal_externalheat_dotState
|
end subroutine externalheat_dotState
|
||||||
|
|
||||||
|
|
||||||
module subroutine thermal_dissipation_getRate(TDot, Tstar,Lp,phase)
|
module subroutine thermal_dissipation_getRate(TDot, Tstar,Lp,phase)
|
||||||
integer, intent(in) :: &
|
integer, intent(in) :: &
|
||||||
|
@ -91,7 +92,7 @@ module subroutine thermal_init(phases)
|
||||||
|
|
||||||
do ph = 1, phases%length
|
do ph = 1, phases%length
|
||||||
|
|
||||||
Nconstituents = count(material_phaseAt == ph) * discretization_nIPs
|
Nconstituents = count(material_phaseAt2 == ph)
|
||||||
|
|
||||||
allocate(current(ph)%T(Nconstituents),source=300.0_pReal)
|
allocate(current(ph)%T(Nconstituents),source=300.0_pReal)
|
||||||
allocate(current(ph)%dot_T(Nconstituents),source=0.0_pReal)
|
allocate(current(ph)%dot_T(Nconstituents),source=0.0_pReal)
|
||||||
|
@ -108,8 +109,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(source_thermal_dissipation_init (maxval(thermal_Nsources))) thermal_source = THERMAL_DISSIPATION_ID
|
where(dissipation_init (maxval(thermal_Nsources))) thermal_source = THERMAL_DISSIPATION_ID
|
||||||
where(source_thermal_externalheat_init(maxval(thermal_Nsources))) thermal_source = THERMAL_EXTERNALHEAT_ID
|
where(externalheat_init(maxval(thermal_Nsources))) thermal_source = THERMAL_EXTERNALHEAT_ID
|
||||||
endif
|
endif
|
||||||
|
|
||||||
thermal_source_maxSizeDotState = 0
|
thermal_source_maxSizeDotState = 0
|
||||||
|
@ -191,7 +192,7 @@ function constitutive_thermal_collectDotState(ph,me) result(broken)
|
||||||
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 source_thermal_externalheat_dotState(ph,me)
|
call externalheat_dotState(ph,me)
|
||||||
|
|
||||||
broken = broken .or. any(IEEE_is_NaN(thermalState(ph)%p(i)%dotState(:,me)))
|
broken = broken .or. any(IEEE_is_NaN(thermalState(ph)%p(i)%dotState(:,me)))
|
||||||
|
|
||||||
|
|
|
@ -25,7 +25,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 source_thermal_dissipation_init(source_length) result(mySources)
|
module function dissipation_init(source_length) result(mySources)
|
||||||
|
|
||||||
integer, intent(in) :: source_length
|
integer, intent(in) :: source_length
|
||||||
logical, dimension(:,:), allocatable :: mySources
|
logical, dimension(:,:), allocatable :: mySources
|
||||||
|
@ -72,7 +72,7 @@ module function source_thermal_dissipation_init(source_length) result(mySources)
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
|
|
||||||
end function source_thermal_dissipation_init
|
end function dissipation_init
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
|
|
@ -29,7 +29,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 source_thermal_externalheat_init(source_length) result(mySources)
|
module function externalheat_init(source_length) result(mySources)
|
||||||
|
|
||||||
integer, intent(in) :: source_length
|
integer, intent(in) :: source_length
|
||||||
logical, dimension(:,:), allocatable :: mySources
|
logical, dimension(:,:), allocatable :: mySources
|
||||||
|
@ -78,14 +78,14 @@ module function source_thermal_externalheat_init(source_length) result(mySources
|
||||||
enddo
|
enddo
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end function source_thermal_externalheat_init
|
end function 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 source_thermal_externalheat_dotState(ph, me)
|
module subroutine externalheat_dotState(ph, me)
|
||||||
|
|
||||||
integer, intent(in) :: &
|
integer, intent(in) :: &
|
||||||
ph, &
|
ph, &
|
||||||
|
@ -98,7 +98,7 @@ module subroutine source_thermal_externalheat_dotState(ph, me)
|
||||||
|
|
||||||
thermalState(ph)%p(sourceOffset)%dotState(1,me) = 1.0_pReal ! state is current time
|
thermalState(ph)%p(sourceOffset)%dotState(1,me) = 1.0_pReal ! state is current time
|
||||||
|
|
||||||
end subroutine source_thermal_externalheat_dotState
|
end subroutine externalheat_dotState
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
|
Loading…
Reference in New Issue