Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | TowerNum | |||
real(kind=r64), | intent(in) | :: | WaterMassFlowRate | |||
real(kind=r64), | intent(in) | :: | AirFlowRate | |||
real(kind=r64), | intent(in) | :: | UAdesign | |||
real(kind=r64), | intent(out) | :: | OutletWaterTemp |
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 SimSimpleTower(TowerNum,WaterMassFlowRate,AirFlowRate,UAdesign,OutletWaterTemp)
! SUBROUTINE INFORMATION:
! AUTHOR Dan Fisher
! DATE WRITTEN Sept. 1998
! MODIFIED na
! RE-ENGINEERED Shirey, Raustad, Jan 2001
! PURPOSE OF THIS SUBROUTINE:
!
! See purpose for Single Speed or Two Speed tower model
! METHODOLOGY EMPLOYED:
!
! See methodology for Single Speed or Two Speed tower model
! REFERENCES:
!
! Merkel, F. 1925. Verduftungskuhlung. VDI Forschungsarbeiten, Nr 275, Berlin.
! ASHRAE 1999. HVAC1KIT: A Toolkit for Primary HVAC System Energy Calculations.
! USE STATEMENTS:
! na
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER , INTENT(IN) :: TowerNum
REAL(r64), INTENT(IN) :: WaterMassFlowRate
REAL(r64), INTENT(IN) :: AirFlowRate
REAL(r64), INTENT(IN) :: UAdesign
REAL(r64), INTENT(OUT) :: OutletWaterTemp
! SUBROUTINE PARAMETER DEFINITIONS:
INTEGER, PARAMETER :: IterMax = 50 ! Maximum number of iterations allowed
REAL(r64), PARAMETER :: WetBulbTolerance = 0.00001d0 ! Maximum error for exiting wet-bulb temperature between iterations
! [delta K/K]
REAL(r64), PARAMETER :: DeltaTwbTolerance = 0.001d0 ! Maximum error (tolerance) in DeltaTwb for iteration convergence [C]
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: Iter ! Number of iterations completed
REAL(r64) :: MdotCpWater ! Water mass flow rate times the heat capacity [W/K]
REAL(r64) :: InletAirTemp ! Dry-bulb temperature of air entering the tower [C]
REAL(r64) :: CpWater ! Heat capacity of water [J/kg/K]
REAL(r64) :: CpAir ! Heat capacity of air [J/kg/K]
REAL(r64) :: AirDensity ! Density of air [kg/m3]
REAL(r64) :: AirMassFlowRate ! Mass flow rate of air [kg/s]
REAL(r64) :: effectiveness ! Effectiveness of the heat exchanger [-]
REAL(r64) :: UAactual ! UA value at actual conditions [W/C]
REAL(r64) :: InletAirEnthalpy ! Enthalpy of entering moist air [J/kg]
REAL(r64) :: InletAirWetBulb ! Wetbulb temp of entering moist air [C]
REAL(r64) :: OutletAirEnthalpy ! Enthalpy of exiting moist air [J/kg]
REAL(r64) :: OutletAirWetBulb ! Wetbulb temp of exiting moist air [C]
REAL(r64) :: OutletAirWetBulbLast ! temporary Wetbulb temp of exiting moist air [C]
REAL(r64) :: AirCapacity ! MdotCp of air through the tower
REAL(r64) :: CapacityRatioMin ! Minimum capacity of airside and waterside
REAL(r64) :: CapacityRatioMax ! Maximum capacity of airside and waterside
REAL(r64) :: CapacityRatio ! Ratio of minimum to maximum capacity
REAL(r64) :: NumTransferUnits ! Number of transfer Units [NTU]
REAL(r64) :: WetBulbError ! Calculated error for exiting wet-bulb temperature between iterations [delta K/K]
REAL(r64) :: CpAirside ! Delta enthalpy of the tower air divides by delta air wet-bulb temp [J/kg/K]
REAL(r64) :: Qactual ! Actual heat transfer rate between tower water and air [W]
REAL(r64) :: DeltaTwb ! Absolute value of difference between inlet and outlet air wet-bulb temp [C]
! set inlet and outlet node numbers, and initialize some local variables
WaterInletNode = SimpleTower(TowerNum)%WaterInletNodeNum
WaterOutletNode = SimpleTower(TowerNum)%WaterOutletNodeNum
Qactual = 0.0d0
! WetBulbTolerance = 0.00001
WetBulbError = 1.0d0
! IterMax = 50
DeltaTwb = 1.0d0
! DeltaTwbTolerance = 0.001
! set local tower inlet and outlet temperature variables
InletWaterTemp = SimpleTowerInlet(TowerNum)%WaterTemp
OutletWaterTemp = InletWaterTemp
InletAirTemp = SimpleTowerInlet(TowerNum)%AirTemp
InletAirWetBulb = SimpleTowerInlet(TowerNum)%AirWetBulb
IF(UAdesign.EQ.0.0d0)RETURN
! set water and air properties
AirDensity = PsyRhoAirFnPbTdbW(SimpleTowerInlet(TowerNum)%AirPress,InletAirTemp,SimpleTowerInlet(TowerNum)%AirHumRat)
AirMassFlowRate = AirFlowRate*AirDensity
CpAir = PsyCpAirFnWTdb(SimpleTowerInlet(TowerNum)%AirHumRat,InletAirTemp)
CpWater = GetSpecificHeatGlycol(PlantLoop(SimpleTower(TowerNum)%LoopNum)%FluidName, &
SimpleTowerInlet(TowerNum)%WaterTemp, &
PlantLoop(SimpleTower(TowerNum)%LoopNum)%FluidIndex, &
'SimSimpleTower')
InletAirEnthalpy = &
PsyHFnTdbRhPb(SimpleTowerInlet(TowerNum)%AirWetBulb, &
1.0d0, &
SimpleTowerInlet(TowerNum)%AirPress)
! initialize exiting wet bulb temperature before iterating on final solution
OutletAirWetBulb = InletAirWetBulb + 6.0d0
! Calcluate mass flow rates
IF (WaterMassFlowRate > 0.d0) THEN
MdotCpWater = WaterMassFlowRate * CpWater
ELSE
OutletWaterTemp = InletWaterTemp
RETURN
ENDIF
Iter = 0
DO WHILE ((WetBulbError.GT.WetBulbTolerance) .AND. (Iter.LE.IterMax) .AND. (DeltaTwb.gt.DeltaTwbTolerance))
Iter = Iter + 1
! OutletAirEnthalpy = PsyHFnTdbRhPb(OutletAirWetBulb,1.0,OutBaroPress)
OutletAirEnthalpy = PsyHFnTdbRhPb(OutletAirWetBulb,1.0d0,SimpleTowerInlet(TowerNum)%AirPress)
! calculate the airside specific heat and capacity
CpAirside = (OutletAirEnthalpy - InletAirEnthalpy)/(OutletAirWetBulb-InletAirWetBulb)
AirCapacity = AirMassFlowRate * CpAirside
! calculate the minimum to maximum capacity ratios of airside and waterside
CapacityRatioMin = MIN(AirCapacity,MdotCpWater)
CapacityRatioMax = MAX(AirCapacity,MdotCpWater)
CapacityRatio = CapacityRatioMin/CapacityRatioMax
! Calculate heat transfer coefficient and number of transfer units (NTU)
UAactual = UAdesign*CpAirside/CpAir
NumTransferUnits = UAactual/CapacityRatioMin
! calculate heat exchanger effectiveness
IF (CapacityRatio.LE.0.995d0)THEN
effectiveness = (1.d0-EXP(-1.0d0*NumTransferUnits*(1.0d0-CapacityRatio)))/ &
(1.0d0-CapacityRatio*EXP(-1.0d0*NumTransferUnits*(1.0d0-CapacityRatio)))
ELSE
effectiveness = NumTransferUnits/(1.d0+NumTransferUnits)
ENDIF
! calculate water to air heat transfer and store last exiting WB temp of air
Qactual = effectiveness * CapacityRatioMin * (InletWaterTemp-InletAirWetBulb)
OutletAirWetBulbLast = OutletAirWetBulb
! calculate new exiting wet bulb temperature of airstream
OutletAirWetBulb = InletAirWetBulb + Qactual/AirCapacity
! Check error tolerance and exit if satisfied
DeltaTwb = ABS(OutletAirWetBulb - InletAirWetBulb)
! Add KelvinConv to denominator below convert OutletAirWetBulbLast to Kelvin to avoid divide by zero.
! Wet bulb error units are delta K/K
WetBulbError = ABS((OutletAirWetBulb - OutletAirWetBulbLast)/(OutletAirWetBulbLast+KelvinConv))
END DO
IF(Qactual .GE. 0.0d0)THEN
OutletWaterTemp = InletWaterTemp - Qactual/ MdotCpWater
ELSE
OutletWaterTemp = InletWaterTemp
END IF
RETURN
END SUBROUTINE SimSimpleTower