Nodes of different colours represent the following:
Solid arrows point from a parent (sub)module to the submodule which is descended from it. Dashed arrows point from a module being used to the module or program unit using it. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | PipeHTNum | |||
integer, | intent(in), | optional | :: | LengthIndex |
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.
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 CalcPipesHeatTransfer(PipeHTNum, LengthIndex)
! AUTHOR Simon Rees
! DATE WRITTEN July 2007
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine does all of the stuff that is necessary to simulate
! a Pipe Heat Transfer. Calls are made to appropriate routines
! for heat transfer coefficients
! METHODOLOGY EMPLOYED:
! Differential equations for pipe and fluid nodes along the pipe are solved
! taking backward differences in time.
! The heat loss/gain calculations are run continuously, even when the loop is off.
! Fluid temps will drift according to environmental conditions when there is zero flow.
! REFERENCES:
! USE STATEMENTS:
USE DataEnvironment
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: PipeHTNum ! component number
INTEGER, OPTIONAL, INTENT(IN) :: LengthIndex
! SUBROUTINE PARAMETER DEFINITIONS:
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
! fluid node heat balance (see engineering doc).
REAL(r64) :: A1 = 0.0d0 !sum of the heat balance terms
REAL(r64) :: A2 = 0.0d0 !mass flow term
REAL(r64) :: A3 = 0.0d0 !inside pipe wall convection term
REAL(r64) :: A4 = 0.0d0 !fluid node heat capacity term
! pipe wall node heat balance (see engineering doc).
REAL(r64) :: B1 = 0.0d0 !sum of the heat balance terms
REAL(r64) :: B2 = 0.0d0 !inside pipe wall convection term
REAL(r64) :: B3 = 0.0d0 !outside pipe wall convection term
REAL(r64) :: B4 = 0.0d0 !fluid node heat capacity term
REAL(r64) :: AirConvCoef = 0.0d0 ! air-pipe convection coefficient
REAL(r64) :: FluidConvCoef = 0.0d0 ! fluid-pipe convection coefficient
REAL(r64) :: EnvHeatTransCoef = 0.0d0 ! external convection coefficient (outside pipe)
REAL(r64) :: FluidNodeHeatCapacity = 0.0d0 ! local var for MCp for single node of pipe
INTEGER :: PipeDepth = 0
INTEGER :: PipeWidth = 0
INTEGER :: curnode
REAL(r64) :: TempBelow
REAL(r64) :: TempBeside
REAL(r64) :: TempAbove
REAL(r64) :: Numerator
REAL(r64) :: Denominator
REAL(r64) :: SurfaceTemp
! traps fluid properties problems such as freezing conditions
IF(PipeHT(PipeHTNum)%FluidSpecHeat <= 0.0d0 .OR. PipeHT(PipeHTNum)%FluidDensity <= 0.0d0)THEN
! leave the state of the pipe as it was
OutletTemp = PipeHT(PipeHTNum)%TentativeFluidTemp(PipeHT(PipeHTNum)%NumSections)
! set heat transfer rates to zero for consistency
EnvHeatLossRate = 0.0d0
FluidHeatLossRate = 0.0d0
RETURN
END IF
! AirConvCoef = OutsidePipeHeatTransCoef(PipeHTNum)
! Revised by L. Gu by including insulation conductance 6/19/08
IF (PipeHT(PipeHTNum)%EnvironmentPtr.NE.GroundEnv) THEN
AirConvCoef = 1.0/(1.0/OutsidePipeHeatTransCoef(PipeHTNum)+PipeHT(PipeHTNum)%InsulationResistance)
ENDIF
FluidConvCoef = CalcPipeHeatTransCoef(PipeHTNum, InletTemp,MassFlowRate, PipeHT(PipeHTNum)%PipeID)
! heat transfer to air or ground
SELECT CASE (PipeHT(PipeHTNum)%EnvironmentPtr)
CASE(GroundEnv)
!Approximate conductance using ground conductivity, (h=k/L), where L is grid spacing
! between pipe wall and next closest node.
EnvHeatTransCoef = PipeHT(PipeHTNum)%SoilConductivity/(PipeHT(PipeHTNum)%dSregular-(PipeHT(PipeHTNum)%PipeID/2.0d0))
CASE(OutsideAirEnv)
EnvHeatTransCoef = AirConvCoef
CASE(ZoneEnv)
EnvHeatTransCoef = AirConvCoef
CASE(ScheduleEnv)
EnvHeatTransCoef = AirConvCoef
CASE(None)
EnvHeatTransCoef = 0.0d0
CASE DEFAULT
EnvHeatTransCoef = 0.0d0
END SELECT
! work out the coefficients
FluidNodeHeatCapacity = PipeHT(PipeHTNum)%SectionArea * PipeHT(PipeHTNum)%Length / PipeHT(PipeHTNum)%NumSections * &
PipeHT(PipeHTNum)%FluidSpecHeat * PipeHT(PipeHTNum)%FluidDensity ! Mass of Node x Specific heat
! coef of fluid heat balance
A1 = FluidNodeHeatCapacity + MassFlowRate * PipeHT(PipeHTNum)%FluidSpecHeat * DeltaTime + &
FluidConvCoef * PipeHT(PipeHTNum)%InsideArea * DeltaTime
A2 = MassFlowRate * PipeHT(PipeHTNum)%FluidSpecHeat * DeltaTime
A3 = FluidConvCoef * PipeHT(PipeHTNum)%InsideArea * DeltaTime
A4 = FluidNodeHeatCapacity
! coef of pipe heat balance
B1 = PipeHT(PipeHTNum)%PipeHeatCapacity + FluidConvCoef * PipeHT(PipeHTNum)%InsideArea * DeltaTime + &
EnvHeatTransCoef * PipeHT(PipeHTNum)%OutsideArea * DeltaTime
B2 = A3
B3 = EnvHeatTransCoef * PipeHT(PipeHTNum)%OutsideArea * DeltaTime
B4 = PipeHT(PipeHTNum)%PipeHeatCapacity
PipeHT(PipeHTNum)%TentativeFluidTemp(0) = InletTemp
PipeHT(PipeHTNum)%TentativePipeTemp(0) = PipeHT(PipeHTNum)%PipeTemp(1) ! for convenience
IF(PRESENT(LengthIndex))THEN !Just simulate the single section if being called from Pipe:Underground
PipeDepth=PipeHT(PipeHTNum)%PipeNodeDepth
PipeWidth=PipeHT(PipeHTNum)%PipeNodeWidth
TempBelow=PipeHT(PipeHTNum)%T(CurrentTimeIndex, LengthIndex, PipeDepth+1, PipeWidth)
TempBeside=PipeHT(PipeHTNum)%T(CurrentTimeIndex, LengthIndex, PipeDepth, PipeWidth-1)
TempAbove=PipeHT(PipeHTNum)%T(CurrentTimeIndex, LengthIndex, PipeDepth-1, PipeWidth)
EnvironmentTemp=(TempBelow+TempBeside+TempAbove)/3.0d0
PipeHT(PipeHTNum)%TentativeFluidTemp(LengthIndex) = (A2 * PipeHT(PipeHTNum)%TentativeFluidTemp(LengthIndex-1) + &
A3/B1 * (B3* EnvironmentTemp + B4 * PipeHT(PipeHTNum)%PreviousPipeTemp(LengthIndex)) + &
A4 * PipeHT(PipeHTNum)%PreviousFluidTemp(LengthIndex)) /(A1 - A3*B2/B1)
PipeHT(PipeHTNum)%TentativePipeTemp(LengthIndex) = (B2 * PipeHT(PipeHTNum)%TentativeFluidTemp(LengthIndex) + B3 * &
EnvironmentTemp + B4 * PipeHT(PipeHTNum)%PreviousPipeTemp(LengthIndex)) / B1
! Get exterior surface temperature from energy balance at the surface
Numerator = EnvironmentTemp - PipeHT(PipeHTNum)%TentativeFluidTemp(LengthIndex)
Denominator = EnvHeatTransCoef * ( (1/EnvHeatTransCoef) + PipeHT(PipeHTNum)%SumTK )
SurfaceTemp = EnvironmentTemp - Numerator/Denominator
! keep track of environmental heat loss rate - not same as fluid loss at same time
EnvHeatLossRate = EnvHeatLossRate + &
EnvHeatTransCoef * PipeHT(PipeHTNum)%OutsideArea * (SurfaceTemp - EnvironmentTemp)
ELSE !Simulate all sections at once if not pipe:underground
! start loop along pipe
! b1 must not be zero but this should have been checked on input
DO curnode=1, PipeHT(PipeHTNum)%NumSections
PipeHT(PipeHTNum)%TentativeFluidTemp(curnode) = (A2 * PipeHT(PipeHTNum)%TentativeFluidTemp(curnode-1) + &
A3/B1 * (B3* EnvironmentTemp + B4 * PipeHT(PipeHTNum)%PreviousPipeTemp(curnode)) + &
A4 * PipeHT(PipeHTNum)%PreviousFluidTemp(curnode)) /(A1 - A3*B2/B1)
PipeHT(PipeHTNum)%TentativePipeTemp(curnode) = (B2 * PipeHT(PipeHTNum)%TentativeFluidTemp(curnode) + B3 * EnvironmentTemp + &
B4 * PipeHT(PipeHTNum)%PreviousPipeTemp(curnode)) / B1
! Get exterior surface temperature from energy balance at the surface
Numerator = EnvironmentTemp - PipeHT(PipeHTNum)%TentativeFluidTemp(curnode)
Denominator = EnvHeatTransCoef * ( (1/EnvHeatTransCoef) + PipeHT(PipeHTNum)%SumTK )
SurfaceTemp = EnvironmentTemp - Numerator/Denominator
! Keep track of environmental heat loss
EnvHeatLossRate = EnvHeatLossRate + &
EnvHeatTransCoef * PipeHT(PipeHTNum)%OutsideArea * (SurfaceTemp - EnvironmentTemp)
END DO
END IF
FluidHeatLossRate = MassFlowRate * PipeHT(PipeHTNum)%FluidSpecHeat * (PipeHT(PipeHTNum)%TentativeFluidTemp(0) - &
PipeHT(PipeHTNum)%TentativeFluidTemp(PipeHT(PipeHTNum)%NumSections))
OutletTemp = PipeHT(PipeHTNum)%TentativeFluidTemp(PipeHT(PipeHTNum)%NumSections)
RETURN
END SUBROUTINE CalcPipesHeatTransfer