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) | :: | LoopNum | |||
integer, | intent(in) | :: | TankInletLoopSide | |||
integer, | intent(in) | :: | CommonPipeType | |||
real(kind=r64), | intent(out) | :: | MixedOutletTemp |
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 UpdateCommonPipe(LoopNum,TankInletLoopSide,CommonPipeType, MixedOutletTemp)
! SUBROUTINE INFORMATION:
! AUTHOR Rick Strand
! DATE WRITTEN September 2001
! MODIFIED Simon Rees, July 2007
! Brent Griffith, Feb. 2010, add LoopNum arg
! RE-ENGINEERED Brent Griffith, Sept 2010, generalize for both loop sides
! add pump heat from other loop
! B.Griffith and L.Gu, Oct 2011, solve via analytical soln, use average over timestep
! PURPOSE OF THIS SUBROUTINE:
! This subroutine calculates the new loop side inlet temperature
! based on the previous temperature of the mixed tank, mass flow rate and the new
! outlet temperature on the supply side. The temperature does not
! pass directly across because the loop has some capacitance. It is
! called separately but used for both supply-to-demand, and demand-to-supply
! METHODOLOGY EMPLOYED:
! This uses a analytical solution for changes in the
! fluid loop temperature. The user defines some volume of fluid
! for the loop which gets converted to a fixed amount of mass.
! The loop side inlet node is modeled as the outlet of a fully mixed
! tank. Note that this routine is called repeatedly to re calculate
! loop capacitance based on current plant conditions
! REFERENCES:
! na
! USE STATEMENTS:
USE DataHVACGlobals, ONLY : TimeStepSys, SysTimeElapsed
USE DataLoopNode, ONLY : Node
USE DataPlant, ONLY : PlantLoop,CommonPipe_Single,CommonPipe_TwoWay, DemandSide
USE DataGlobals, ONLY : SecInHour, TimeStepZone, TimeStep, HourOfDay
USE FluidProperties, ONLY : GetSpecificHeatGlycol
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENTS:
INTEGER, INTENT(IN) :: LoopNum
INTEGER, INTENT(IN) :: CommonPipeType
INTEGER, INTENT(IN) :: TankInletLoopSide
REAL(r64),INTENT(OUT) :: MixedOutletTemp
! SUBROUTINE PARAMETER DEFINITIONS:
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: TankOutletLoopSide ! inlet loopsidenumber
INTEGER :: TankInletNode ! inlet loop side outlet node
INTEGER :: TankOutletNode ! inlet loop side outlet node
REAL(r64) :: TankInletTemp ! temporary variable
REAL(r64) :: LastTankOutletTemp ! temporary variable
REAL(r64) :: Cp ! specific heat
REAL(r64) :: TimeElapsed ! temporary value based on current clock time during simulation, fractional hours
REAL(r64) :: FracTotLoopMass !Fraction of total loop mass assigned to the half loop
REAL(r64) :: TimeStepSeconds
REAL(r64) :: MassFlowRate
REAL(r64) :: PumpHeat
REAL(r64) :: ThisTankMass
REAL(r64) :: TankFinalTemp
REAL(r64) :: TankAverageTemp
! FLOW:
!find tank inlet and outlet nodes
TankOutletLoopSide = 3 - TankInletLoopSide
TankInletNode = PlantLoop(LoopNum)%LoopSide(TankInletLoopSide)%NodeNumOut
TankOutletNode = PlantLoop(LoopNum)%LoopSide(TankOutletLoopSide)%NodeNumIn
TankInletTemp = Node(TankInletNode)%Temp
IF (TankInletLoopSide == DemandSide) THEN
! for common pipe loops, assume 75% of plant loop volume is on the demand side
FracTotLoopMass = 0.25d0
ELSE
FracTotLoopMass = 0.75d0
ENDIF
! This needs to be based on time to deal with system downstepping and repeated timesteps
TimeElapsed = (HourOfDay-1) + TimeStep * TimeStepZone + SysTimeElapsed
IF (PlantLoop(LoopNum)%LoopSide(TankOutletLoopSide)%TimeElapsed /= TimeElapsed) THEN
PlantLoop(LoopNum)%LoopSide(TankOutletLoopSide)%LastTempInterfaceTankOutlet &
= PlantLoop(LoopNum)%LoopSide(TankOutletLoopSide)%TempInterfaceTankOutlet
PlantLoop(LoopNum)%LoopSide(TankOutletLoopSide)%TimeElapsed = TimeElapsed
ENDIF
LastTankOutletTemp = PlantLoop(LoopNum)%LoopSide(TankOutletLoopSide)%LastTempInterfaceTankOutlet
!calculate the specific heat for the capacitance calculation
Cp = GetSpecificHeatGlycol(PlantLoop(loopNum)%FluidName, &
LastTankOutletTemp, &
PlantLoop(loopNum)%FluidIndex,'UpdateCommonPipe')
!set the fraction of loop mass assigned to each half loop outlet capacitance ('tank') calculation
!calculate new loop inlet temperature. The calculation is a simple 'tank' (thermal capacitance) calculation that includes:
!--half of loop mass. The other half is accounted for at the other half loop interface
!--pump heat. Pump heat for a single loop setpoint with pumps only on the supply side is added at the supply side inlet.
!Pump heat for a dual setpoint loop is added to each loop side inlet
!The previous inlet side temp,'ThisLoopSideTankOutletTemp' is used to prevent accumulation of pump heat during iterations.
!The placement of the 'tank' for common pipes is *after* the outlet node and *before* the flow split or flow mixing.
!This requires no logical check in the code since for purposes of temperature calculations, it is identical to the
!no common pipe case.
! calculation is separated because for common pipe, a different split for mass fraction is applied
! The pump heat source is swapped around here compared to no common pipe (so pump heat sort stays on its own side).
TimeStepSeconds = TimeStepSys * SecInHour
MassFlowRate = Node(TankInletNode)%MassFlowRate
PumpHeat = PlantLoop(LoopNum)%LoopSide(TankInletLoopSide)%TotalPumpHeat
ThisTankMass = FracTotLoopMass * PlantLoop(LoopNum)%Mass
IF (ThisTankMass <= 0.d0) THEN ! no mass, no plant loop volume
IF (MassFlowRate > 0.d0) THEN
TankFinalTemp = TankInletTemp + PumpHeat/(MassFlowRate * Cp)
TankAverageTemp = (TankFinalTemp + LastTankOutletTemp)/2.0d0
ELSE
TankFinalTemp = LastTankOutletTemp
TankAverageTemp = LastTankOutletTemp
END IF
ELSE ! tank has mass
IF (MassFlowRate > 0.d0 ) THEN
TankFinalTemp = (LastTankOutletTemp - (MassFlowRate * Cp * TankInletTemp + PumpHeat)/(MassFlowRate * Cp)) * &
exp(-(MassFlowRate * Cp) / (ThisTankMass*Cp)*TimeStepSeconds) + &
(MassFlowRate * Cp * TankInletTemp + PumpHeat)/ (MassFlowRate * Cp)
TankAverageTemp = ((ThisTankMass*Cp)/(MassFlowRate * Cp)*(LastTankOutletTemp - &
(MassFlowRate * Cp * TankInletTemp + PumpHeat)/(MassFlowRate * Cp)) * &
(1.0d0-exp(-(MassFlowRate * Cp) / (ThisTankMass*Cp)*TimeStepSeconds))/TimeStepSeconds + &
(MassFlowRate * Cp * TankInletTemp + PumpHeat)/(MassFlowRate * Cp))
ELSE
TankFinalTemp = PumpHeat/(ThisTankMass*Cp)*TimeStepSeconds + LastTankOutletTemp
TankAverageTemp = (TankFinalTemp + LastTankOutletTemp)/2.0d0
END IF
ENDIF
!Common Pipe Simulation
IF(CommonPipeType == CommonPipe_Single) THEN
CALL ManageSingleCommonPipe(LoopNum,TankOutletLoopSide,TankAverageTemp, MixedOutletTemp)
!2-way (controlled) common pipe simulation
ELSE IF(CommonPipeType == CommonPipe_TwoWay) THEN
CALL ManageTwoWayCommonPipe(LoopNum, TankOutletLoopSide, TankAverageTemp)
MixedOutletTemp = Node(TankOutletNode)%Temp
END IF
PlantLoop(LoopNum)%LoopSide(TankOutletLoopSide)%TempInterfaceTankOutlet = TankFinalTemp
PlantLoop(LoopNum)%LoopSide(TankOutletLoopSide)%LoopSideInlet_TankTemp = TankAverageTemp
RETURN
END SUBROUTINE UpdateCommonPipe