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) | :: | 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 CalculateWaterUseage(TowerNum)
! SUBROUTINE INFORMATION:
! AUTHOR B. Griffith
! DATE WRITTEN August 2006
! MODIFIED T Hong, Aug. 2008. Added fluid bypass for single speed cooling tower
! A Flament, July 2010. Added multi-cell capability
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Collect tower water useage calculations for
! reuse by all the tower models.
! METHODOLOGY EMPLOYED:
! <description>
! REFERENCES:
! Code for this routine started from VariableSpeedTower
! USE STATEMENTS:
USE DataGlobals, ONLY: SecInHour, BeginTimeStepFlag
USE DataHVACGlobals, ONLY: TimeStepSys
USE ScheduleManager, ONLY: GetCurrentScheduleValue
USE DataWater , ONLY: WaterStorage
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: TowerNum
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: AirDensity
REAL(r64) :: AirMassFlowRate
REAL(r64) :: AvailTankVdot
REAL(r64) :: BlowDownVdot =0.0d0
REAL(r64) :: DriftVdot =0.0d0
REAL(r64) :: EvapVdot =0.0d0
REAL(r64) :: InletAirEnthalpy
REAL(r64) :: InSpecificHumRat
REAL(r64) :: OutSpecificHumRat
REAL(r64) :: TairAvg
REAL(r64) :: MakeUpVdot
REAL(r64) :: OutletAirEnthalpy
REAL(r64) :: OutletAirHumRatSat
REAL(r64) :: OutletAirTSat
REAL(r64) :: StarvedVdot
REAL(r64) :: TankSupplyVdot
REAL(r64) :: rho
REAL(r64) :: AverageWaterTemp
AverageWaterTemp = (InletWaterTemp + OutletWaterTemp) / 2.0d0
! Set water and air properties
If (SimpleTower(TowerNum)%EvapLossMode == EvapLossByMoistTheory) Then
AirDensity = PsyRhoAirFnPbTdbW(SimpleTowerInlet(TowerNum)%AirPress, &
SimpleTowerInlet(TowerNum)%AirTemp,SimpleTowerInlet(TowerNum)%AirHumRat)
AirMassFlowRate = AirFlowRateRatio*SimpleTower(TowerNum)%HighSpeedAirFlowRate*AirDensity&
* SimpleTower(TowerNum)%NumCellON / SimpleTower(TowerNum)%NumCell
InletAirEnthalpy = &
PsyHFnTdbRhPb(SimpleTowerInlet(TowerNum)%AirWetBulb, &
1.0d0, &
SimpleTowerInlet(TowerNum)%AirPress)
IF (AirMassFlowRate > 0.0d0) Then
! Calculate outlet air conditions for determining water usage
OutletAirEnthalpy = InletAirEnthalpy + Qactual/AirMassFlowRate
OutletAirTSat = PsyTsatFnHPb(OutletAirEnthalpy,SimpleTowerInlet(TowerNum)%AirPress)
OutletAirHumRatSat = PsyWFnTdbH(OutletAirTSat,OutletAirEnthalpy)
! calculate specific humidity ratios (HUMRAT to mass of moist air not dry air)
InSpecificHumRat = SimpleTowerInlet(TowerNum)%AirHumRat / ( 1 + SimpleTowerInlet(TowerNum)%AirHumRat)
OutSpecificHumRat = OutletAirHumRatSat / (1+ OutletAirHumRatSat)
! calculate average air temp for density call
TairAvg = (SimpleTowerInlet(TowerNum)%AirTemp + OutletAirTSat)/2.0d0
! Amount of water evaporated, get density water at air temp or 4 C if too cold
rho = GetDensityGlycol(PlantLoop(SimpleTower(TowerNum)%LoopNum)%FluidName, &
MAX(TairAvg,4.d0), &
PlantLoop(SimpleTower(TowerNum)%LoopNum)%FluidIndex,&
'CalculateWaterUseage')
EvapVdot = (AirMassFlowRate * (OutSpecificHumRat - InSpecificHumRat)) / rho ! [m3/s]
IF (EvapVdot < 0.0d0) EvapVdot = 0.0d0
ELSE
EvapVdot = 0.0d0
ENDIF
ElseIf (SimpleTower(TowerNum)%EvapLossMode == EvapLossByUserFactor) Then
! EvapVdot = SimpleTower(TowerNum)%UserEvapLossFactor * (InletWaterTemp - OutletWaterTemp) &
! * SimpleTower(TowerNum)%DesignWaterFlowRate
rho = GetDensityGlycol(PlantLoop(SimpleTower(TowerNum)%LoopNum)%FluidName, &
AverageWaterTemp, &
PlantLoop(SimpleTower(TowerNum)%LoopNum)%FluidIndex,&
'CalculateWaterUseage')
EvapVdot = SimpleTower(TowerNum)%UserEvapLossFactor * (InletWaterTemp - OutletWaterTemp) &
* (WaterMassFlowRate / rho )
IF (EvapVdot < 0.0d0) EvapVdot = 0.0d0
ELSE
! should never come here
ENDIF
! amount of water lost due to drift
DriftVdot = SimpleTower(TowerNum)%DesignWaterFlowRate * &
SimpleTower(TowerNum)%NumCellON / SimpleTower(TowerNum)%NumCell * &
SimpleTower(TowerNum)%DriftLossFraction * AirFlowRateRatio
If (SimpleTower(TowerNum)%BlowdownMode == BlowdownBySchedule) THEN
! Amount of water lost due to blow down (purging contaminants from tower basin)
IF(SimpleTower(TowerNum)%SchedIDBlowdown .GT. 0)THEN
BlowDownVdot = GetCurrentScheduleValue(SimpleTower(TowerNum)%SchedIDBlowdown)
ELSE
BlowDownVdot = 0.0d0
END IF
ELSEIF (SimpleTower(TowerNum)%BlowdownMode == BlowdownByConcentration) THEN
If (SimpleTower(TowerNum)%ConcentrationRatio > 2.0d0) Then ! protect divide by zero
BlowDownVdot = EvapVdot / (SimpleTower(TowerNum)%ConcentrationRatio - 1) - DriftVdot
ELSE
BlowDownVdot = EvapVdot - DriftVdot
ENDIF
If ( BlowDownVdot < 0.0d0 ) BlowDownVdot = 0.0d0
ELSE
!should never come here
ENDIF
! Added for fluid bypass
IF (SimpleTower(TowerNum)%CapacityControl == CapacityControl_FluidBypass) THEN
If (SimpleTower(TowerNum)%EvapLossMode == EvapLossByUserFactor) EvapVdot = EvapVdot * (1 - SimpleTower(TowerNum)%BypassFraction)
DriftVdot = DriftVdot * (1 - SimpleTower(TowerNum)%BypassFraction)
BlowDownVdot = BlowDownVdot * (1 - SimpleTower(TowerNum)%BypassFraction)
ENDIF
MakeUpVdot = EvapVdot + DriftVdot + BlowDownVdot
! set demand request in Water STorage if needed
StarvedVdot = 0.0d0
TankSupplyVdot = 0.0d0
If (SimpleTower(TowerNum)%SuppliedByWaterSystem) Then
! set demand request
WaterStorage(SimpleTower(TowerNum)%WaterTankID)%VdotRequestDemand(SimpleTower(TowerNum)%WaterTankDemandARRID) &
= MakeUpVdot
AvailTankVdot = & ! check what tank can currently provide
WaterStorage(SimpleTower(TowerNum)%WaterTankID)%VdotAvailDemand(SimpleTower(TowerNum)%WaterTankDemandARRID)
TankSupplyVdot = MakeUpVdot ! init
If (AvailTankVdot < MakeUpVdot) Then ! calculate starved flow
StarvedVdot = MakeUpVdot - AvailTankVdot
TankSupplyVdot = AvailTankVdot
ENDIF
ELSE ! supplied by mains
ENDIF
! total water usage
! update report variables
SimpleTowerReport(TowerNum)%EvaporationVdot = EvapVdot
SimpleTowerReport(TowerNum)%EvaporationVol = EvapVdot * (TimeStepSys * SecInHour)
SimpleTowerReport(TowerNum)%DriftVdot = DriftVdot
SimpleTowerReport(TowerNum)%DriftVol = DriftVdot * (TimeStepSys * SecInHour)
SimpleTowerReport(TowerNum)%BlowdownVdot = BlowDownVdot
SimpleTowerReport(TowerNum)%BlowdownVol = BlowDownVdot * (TimeStepSys * SecInHour)
SimpleTowerReport(TowerNum)%MakeUpVdot = MakeUpVdot
SimpleTowerReport(TowerNum)%MakeUpVol = MakeUpVdot * (TimeStepSys * SecInHour)
SimpleTowerReport(TowerNum)%TankSupplyVdot = TankSupplyVdot
SimpleTowerReport(TowerNum)%TankSupplyVol = TankSupplyVdot * (TimeStepSys * SecInHour)
SimpleTowerReport(TowerNum)%StarvedMakeUpVdot = StarvedVdot
SimpleTowerReport(TowerNum)%StarvedMakeUpVol = StarvedVdot * (TimeStepSys * SecInHour)
RETURN
END SUBROUTINE CalculateWaterUseage