Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | SurfaceGHENum | |||
real(kind=r64), | intent(in) | :: | Tbottom | |||
real(kind=r64), | intent(in) | :: | Ttop |
Nodes of different colours represent the following:
Solid arrows point from a procedure to one which it calls. Dashed arrows point from an interface to procedures which implement that interface. This could include the module procedures in a generic interface or the implementation in a submodule of an interface in a parent module. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
SUBROUTINE CalcSourceTempCoefficents(SurfaceGHENum, Tbottom, Ttop)
! AUTHOR Simon Rees
! DATE WRITTEN August 2002
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Calculates current version of constant variable parts of QTF equations.
! METHODOLOGY EMPLOYED:
! For given current surface temperatures the terms of the QTF equations can be
! grouped into constant terms, and those depending on the current source flux.
! This routine calculates the current coefficient values for the source temperature
! equation.
! REFERENCES:
! Strand, R.K. 1995. "Heat Source Transfer Functions and Their Application to
! Low Temperature Radiant Heating Systems", Ph.D. dissertation, University
! of Illinois at Urbana-Champaign, Department of Mechanical and Industrial
! Engineering.
! USE STATEMENTS:
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: SurfaceGHENum ! component number
REAL(r64), INTENT(IN) :: Tbottom ! current bottom (lower) surface temperature
REAL(r64), INTENT(IN) :: Ttop ! current top (upper) surface temperature
! SUBROUTINE PARAMETER DEFINITIONS:
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: Term
! add current surface temperatures to history data
SurfaceGHEQTF(SurfaceGHENum)%TbtmHistory(0) = Tbottom
SurfaceGHEQTF(SurfaceGHENum)%TtopHistory(0) = Ttop
SurfaceGHEQTF(SurfaceGHENum)%TsrcConstCoef = 0.0d0
DO Term = 0, SurfaceGHEQTF(SurfaceGHENum)%NumCTFTerms-1
SurfaceGHEQTF(SurfaceGHENum)%TsrcConstCoef = &
SurfaceGHEQTF(SurfaceGHENum)%TsrcConstCoef + &
(SurfaceGHEQTF(SurfaceGHENum)%CTFTSourceIn(Term) * SurfaceGHEQTF(SurfaceGHENum)%TbtmHistory(Term)) + &
(SurfaceGHEQTF(SurfaceGHENum)%CTFTSourceOut(Term) * SurfaceGHEQTF(SurfaceGHENum)%TtopHistory(Term)) + &
(SurfaceGHEQTF(SurfaceGHENum)%CTFflux(Term) * SurfaceGHEQTF(SurfaceGHENum)%TsrcHistory(Term)) + &
(SurfaceGHEQTF(SurfaceGHENum)%CTFTSourceQ(Term) * SurfaceGHEQTF(SurfaceGHENum)%QsrcHistory(Term))
ENDDO
! Source Temperature terms
! SurfaceGHEQTF(SurfaceGHENum)%TsrcConstCoef = SUM(SurfaceGHEQTF(SurfaceGHENum)%CTFTSourceIn * &
! SurfaceGHEQTF(SurfaceGHENum)%TbtmHistory + &
! SurfaceGHEQTF(SurfaceGHENum)%CTFTSourceOut * &
! SurfaceGHEQTF(SurfaceGHENum)%TtopHistory + &
! SurfaceGHEQTF(SurfaceGHENum)%CTFflux * &
! SurfaceGHEQTF(SurfaceGHENum)%TsrcHistory + &
! SurfaceGHEQTF(SurfaceGHENum)%CTFTSourceQ * &
! SurfaceGHEQTF(SurfaceGHENum)%QsrcHistory)
! correct for extra source flux term
SurfaceGHEQTF(SurfaceGHENum)%TsrcConstCoef = SurfaceGHEQTF(SurfaceGHENum)%TsrcConstCoef - &
SurfaceGHEQTF(SurfaceGHENum)%CTFTSourceQ(0) * &
SurfaceGHEQTF(SurfaceGHENum)%QsrcHistory(0)
! source flux current coefficient
SurfaceGHEQTF(SurfaceGHENum)%TsrcVarCoef = SurfaceGHEQTF(SurfaceGHENum)%CTFTSourceQ(0)
END SUBROUTINE CalcSourceTempCoefficents