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 | :: | TowerNum |
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 CalcTwoSpeedTower(TowerNum)
! SUBROUTINE INFORMATION:
! AUTHOR Dan Fisher
! DATE WRITTEN Sept. 1998
! MODIFIED Chandan Sharma, FSEC, February 2010, Added basin heater
! A Flament, July 2010, added multi-cell capability for the 3 types of cooling tower
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
!
! To simulate the operation of a cooling tower with a two-speed fan.
! METHODOLOGY EMPLOYED:
!
! The cooling tower is modeled using effectiveness-NTU relationships for
! counterflow heat exchangers based on Merkel's theory.
!
! The subroutine calculates the period of time required to meet a
! leaving water temperature setpoint. It assumes that part-load
! operation represents a linear interpolation of three steady-state regimes
! (high-speed fan operation, low-speed fan operation and free convection regime).
! Cyclic losses are neglected. The period of time required to meet the
! leaving water temperature setpoint is used to determine the required
! fan power and energy. Free convection regime is also modeled. This
! occures when the pump is operating and the fan is off. If free convection
! regime cooling is all that is required for a given time step, the leaving
! water temperature is allowed to fall below the leaving water temperature
! setpoint (free cooling). At times when the cooling tower fan is required,
! the leaving water temperature is at or above the setpoint.
!
! A RunFlag is passed by the upper level manager to indicate the ON/OFF status,
! or schedule, of the cooling tower. If the tower is OFF, outlet water
! temperature and flow rate are passed through the model from inlet node to
! outlet node without intervention (with the exception of free convection
! where water temperature is allowed to float below the outlet water set
! point). Reports are also updated with fan power and fan energy being zero.
!
! When the RunFlag indicates an ON condition for the cooling tower, the
! mass flow rate and water temperature are read from the inlet node of the
! cooling tower (water-side). The outdoor air wet-bulb temperature is used
! as the entering condition to the cooling tower (air-side). Input deck
! parameters are read for the free convection regime (pump ON and fan OFF)
! and a leaving water temperature is calculated. If the leaving water temperature
! is at or below the setpoint, the calculated leaving water temperature is
! placed on the outlet node and no fan power is used. If the calculated leaving
! water temperature is above the setpoint, the cooling tower fan is turned on
! and parameters for low fan speed are used to again calculate the leaving
! water temperature. If the calculated leaving water temperature is
! below the setpoint, a fan run-time fraction (FanModeFrac) is calculated and
! used to determine fan power. The leaving water temperature setpoint is placed
! on the outlet node. If the calculated leaving water temperature is at or above
! the setpoint, the cooling tower fan is turned on 'high speed' and the routine is
! repeated. If the calculated leaving water temperature is below the setpoint,
! a fan run-time fraction is calculated for the second stage fan and fan power
! is calculated as FanModeFrac*HighSpeedFanPower+(1-FanModeFrac)*LowSpeedFanPower.
! If the calculated leaving water temperature is above the leaving water temp.
! setpoint, the calculated leaving water temperature is placed on the outlet
! node and the fan runs at full power (High Speed Fan Power). Water mass flow
! rate is passed from inlet node to outlet node with no intervention.
!
! If a tower has multiple cells, the specified inputs of or the autosized capacity
! and air/water flow rates are for the entire tower. The number of cells to operate
! is first determined based on the user entered minimal and maximal water flow fractions
! per cell. If the loads are not met, more cells (if available) will operate to meet
! the loads. Each cell operates in same way - same fan speed etc.
!
! REFERENCES:
! ASHRAE HVAC1KIT: A Toolkit for Primary HVAC System Energy Calculation. 1999.
! USE STATEMENTS:
USE DataPlant, ONLY: PlantLoop, SingleSetPoint, DualSetpointDeadband
USE DataBranchAirLoopPlant, ONLY: MassFlowTolerance
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER :: TowerNum
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: AirFlowRate
REAL(r64) :: UAdesign ! UA value at design conditions (entered by user) [W/C]
REAL(r64) :: OutletWaterTempOFF
REAL(r64) :: OutletWaterTemp1stStage
REAL(r64) :: OutletWaterTemp2ndStage
REAL(r64) :: FanModeFrac
REAL(r64) :: designWaterFlowRate
REAL(r64) :: FanPowerLow
REAL(r64) :: FanPowerHigh
REAL(r64) :: CpWater
REAL(r64) :: TempSetPoint
INTEGER :: LoopNum
INTEGER :: LoopSideNum
INTEGER :: SpeedSel = 0
!Added variables for multicell
REAL(r64) :: WaterMassFlowRatePerCellMin
REAL(r64) :: WaterMassFlowRatePerCellMax
INTEGER :: NumCellMin = 0
INTEGER :: NumCellMax = 0
INTEGER :: NumCellON = 0
REAL(r64) :: WaterMassFlowRatePerCell
LOGICAL :: IncrNumCellFlag ! determine if yes or no we increase the number of cells
!set inlet and outlet nodes
WaterInletNode = SimpleTower(TowerNum)%WaterInletNodeNum
WaterOutletNode = SimpleTower(TowerNum)%WaterOutletNodeNum
Qactual = 0.0d0
CTFanPower = 0.0d0
OutletWaterTemp = Node(WaterInletNode)%Temp
LoopNum = SimpleTower(TowerNum)%LoopNum
LoopSideNum = SimpleTower(TowerNum)%LoopSideNum
SELECT CASE (PlantLoop(LoopNum)%LoopDemandCalcScheme)
CASE (SingleSetPoint)
IF (SimpleTower(TowerNum)%SetpointIsOnOutlet) THEN
TempSetPoint = Node(WaterOutletNode)%TempSetpoint
ELSE
TempSetPoint = PlantLoop(LoopNum)%LoopSide(LoopSideNum)%TempSetpoint
ENDIF
CASE (DualSetPointDeadBand)
IF (SimpleTower(TowerNum)%SetpointIsOnOutlet) THEN
TempSetPoint = Node(WaterOutletNode)%TempSetpointHi
ELSE
TempSetPoint = PlantLoop(LoopNum)%LoopSide(LoopSideNum)%TempSetpointHi
ENDIF
END SELECT
! Do not RETURN here if flow rate is less than SmallMassFlow. Check basin heater and then RETURN.
IF(PlantLoop(LoopNum)%Loopside(LoopSideNum)%FlowLock .EQ. 0)RETURN
! MassFlowTolerance is a parameter to indicate a no flow condition
IF(WaterMassFlowRate.LE.MassFlowTolerance)THEN
CALL CalcBasinHeaterPower(SimpleTower(TowerNum)%BasinHeaterPowerFTempDiff,&
SimpleTower(TowerNum)%BasinHeaterSchedulePtr,&
SimpleTower(TowerNum)%BasinHeaterSetPointTemp,BasinHeaterPower)
RETURN
ENDIF
! Added for multi-cell. Determine the number of cells operating
IF (SimpleTower(TowerNum)%DesWaterMassFlowRate > 0.0D0) THEN
WaterMassFlowRatePerCellMin = SimpleTower(TowerNum)%DesWaterMassFlowRate * SimpleTower(TowerNum)%MinFracFlowRate / &
SimpleTower(TowerNum)%NumCell
WaterMassFlowRatePerCellMax = SimpleTower(TowerNum)%DesWaterMassFlowRate * SimpleTower(TowerNum)%MaxFracFlowRate / &
SimpleTower(TowerNum)%NumCell
!round it up to the nearest integer
NumCellMin = MIN(INT((WaterMassFlowRate / WaterMassFlowRatePerCellMax)+.9999d0),SimpleTower(TowerNum)%NumCell)
NumCellMax = MIN(INT((WaterMassFlowRate / WaterMassFlowRatePerCellMin)+.9999d0),SimpleTower(TowerNum)%NumCell)
ENDIF
! cap min at 1
IF(NumCellMin <= 0)NumCellMin = 1
IF(NumCellMax <= 0)NumCellMax = 1
IF(SimpleTower(TowerNum)%CellCtrl_Num == CellCtrl_MinCell)THEN
NumCellON = NumCellMin
ELSE
NumCellON = NumCellMax
END IF
SimpleTower(TowerNum)%NumCellON = NumCellON
WaterMassFlowRatePerCell = WaterMassFlowRate / NumCellON
IncrNumCellFlag = .true.
DO WHILE (IncrNumCellFlag)
IncrNumCellFlag = .false.
!set local variable for tower
UAdesign = SimpleTower(TowerNum)%FreeConvTowerUA / SimpleTower(TowerNum)%NumCell ! where is NumCellOn?
AirFlowRate = SimpleTower(TowerNum)%FreeConvAirFlowRate / SimpleTower(TowerNum)%NumCell
DesignWaterFlowRate = SimpleTower(TowerNum)%DesignWaterFlowRate ! ??useless subroutine variable??
OutletWaterTempOFF = Node(WaterInletNode)%Temp
WaterMassFlowRate = Node(WaterInletNode)%MassFlowRate
OutletWaterTemp1stStage = OutletWaterTemp
OutletWaterTemp2ndStage = OutletWaterTemp
FanModeFrac = 0.0d0
Call SimSimpleTower(TowerNum,WaterMassFlowRatePerCell,AirFlowRate,UAdesign,OutletWaterTempOFF)
! Setpoint was met using free convection regime (pump ON and fan OFF)
CTFanPower = 0.0d0
OutletWaterTemp = OutletWaterTempOFF
SpeedSel = 0
IF(OutletWaterTempOFF .GT. TempSetPoint)THEN
! Setpoint was not met (or free conv. not used),turn on cooling tower 1st stage fan
UAdesign = SimpleTower(TowerNum)%LowSpeedTowerUA / SimpleTower(TowerNum)%NumCell
AirFlowRate = SimpleTower(TowerNum)%LowSpeedAirFlowRate / SimpleTower(TowerNum)%NumCell
FanPowerLow = SimpleTower(TowerNum)%LowSpeedFanPower * NumCellON / SimpleTower(TowerNum)%NumCell
Call SimSimpleTower(TowerNum,WaterMassFlowRatePerCell,AirFlowRate,UAdesign,OutletWaterTemp1stStage)
IF(OutletWaterTemp1stStage .LE. TempSetPoint)THEN
! Setpoint was met with pump ON and fan ON 1st stage, calculate fan mode fraction
FanModeFrac = (TempSetPoint-OutletWaterTempOFF)/(OutletWaterTemp1stStage-OutletWaterTempOFF)
CTFanPower = FanModeFrac * FanPowerLow
OutletWaterTemp = TempSetPoint
Qactual = Qactual * FanModeFrac
SpeedSel = 1
ELSE
! Setpoint was not met, turn on cooling tower 2nd stage fan
UAdesign = SimpleTower(TowerNum)%HighSpeedTowerUA / SimpleTower(TowerNum)%NumCell
AirFlowRate = SimpleTower(TowerNum)%HighSpeedAirFlowRate / SimpleTower(TowerNum)%NumCell
FanPowerHigh = SimpleTower(TowerNum)%HighSpeedFanPower * NumCellON / SimpleTower(TowerNum)%NumCell
Call SimSimpleTower(TowerNum,WaterMassFlowRatePerCell,AirFlowRate,UAdesign,OutletWaterTemp2ndStage)
IF((OutletWaterTemp2ndStage .LE. TempSetPoint).AND. UAdesign .GT. 0.0d0)THEN
! Setpoint was met with pump ON and fan ON 2nd stage, calculate fan mode fraction
FanModeFrac = (TempSetPoint-OutletWaterTemp1stStage)/(OutletWaterTemp2ndStage-OutletWaterTemp1stStage)
CTFanPower = (FanModeFrac * FanPowerHigh) + (1.d0-FanModeFrac)*FanPowerLow
OutletWaterTemp = TempSetPoint
SpeedSel = 2
ELSE
! Setpoint was not met, cooling tower ran at full capacity
OutletWaterTemp = OutletWaterTemp2ndStage
CTFanPower = FanPowerHigh
SpeedSel = 2
FanModeFrac = 1.0d0
! if possible increase the number of cells and do the calculations again with the new water mass flow rate per cell
IF (NumCellON .lt. SimpleTower(TowerNum)%NumCell .and. &
(WaterMassFlowRate/(NumCellON+1)) .ge. WaterMassFlowRatePerCellMin)THEN
NumCellON = NumCellON + 1
WaterMassFlowRatePerCell = WaterMassFlowRate / NumCellON
IncrNumCellFlag = .true.
END IF
END IF
END IF
END IF
END DO
!output the fraction of the time step the fan is ON
FanCyclingRatio = FanModeFrac
SimpleTower(TowerNum)%SpeedSelected = SpeedSel
SimpleTower(TowerNum)%NumCellON = NumCellON
CpWater = GetSpecificHeatGlycol(PlantLoop(SimpleTower(TowerNum)%LoopNum)%FluidName, &
Node(WaterInletNode)%Temp, &
PlantLoop(SimpleTower(TowerNum)%LoopNum)%FluidIndex, &
'CalcTwoSpeedTower')
Qactual = WaterMassFlowRate * CpWater * (Node(WaterInletNode)%Temp - OutletWaterTemp)
AirFlowRateRatio = (AirFlowRate * SimpleTower(TowerNum)%NumCell) / SimpleTower(TowerNum)%HighSpeedAirFlowRate
RETURN
END SUBROUTINE CalcTwoSpeedTower