Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | CoilNum | |||
real(kind=r64), | intent(in) | :: | WaterTempIn | |||
real(kind=r64), | intent(in) | :: | AirTempIn | |||
real(kind=r64), | intent(in) | :: | CoilUA | |||
real(kind=r64) | :: | OutletWaterTemp | ||||
real(kind=r64) | :: | OutletAirTemp | ||||
real(kind=r64) | :: | OutletAirHumRat | ||||
real(kind=r64) | :: | Q | ||||
integer, | intent(in) | :: | FanOpMode | |||
real(kind=r64), | intent(in) | :: | PartLoadRatio |
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 CoilCompletelyDry (CoilNum,WaterTempIn, AirTempIn,CoilUA, &
OutletWaterTemp,OutletAirTemp,OutletAirHumRat,Q,FanOpMode,PartLoadRatio)
! FUNCTION INFORMATION:
! AUTHOR Rahul Chillar
! DATE WRITTEN March 2004
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS FUNCTION:
! Calculate the performance of a sensible air-liquid heat exchanger. Calculated
! results include outlet air temperature and humidity, outlet water temperature,
! and heat transfer rate.
! METHODOLOGY EMPLOYED:
! Models coil using effectiveness-NTU model.
! REFERENCES:
! Kays, W.M. and A.L. London. 1964,Compact Heat Exchangers, 2nd Edition,
! New York: McGraw-Hill.
! USE STATEMENTS:
! na
! Enforce explicit typing of all variables in this routine
Implicit None
! FUNCTION ARGUMENT DEFINITIONS:
Integer, intent(in) :: CoilNum !
REAL(r64), intent(in) :: WaterTempIn ! Entering water temperature
REAL(r64), intent(in) :: AirTempIn ! Entering air dry bulb temperature
REAL(r64), intent(in) :: CoilUA ! Overall heat transfer coefficient
INTEGER, INTENT(IN) :: FanOpMode ! fan operating mode
REAL(r64), INTENT(IN) :: PartLoadRatio ! part-load ratio of heating coil
! FUNCTION PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! FUNCTION LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: OutletWaterTemp ! Leaving water temperature
REAL(r64) :: OutletAirTemp ! Leaving air dry bulb temperature
REAL(r64) :: OutletAirHumRat ! Leaving air humidity ratio
REAL(r64) :: Q ! Heat transfer rate
REAL(r64) :: CapacitanceAir ! Air-side capacity rate(W/C)
REAL(r64) :: CapacitanceWater ! Water-side capacity rate(W/C)
REAL(r64) :: AirMassFlow
REAL(r64) :: WaterMassFlowRate
REAL(r64) :: Cp
! adjust mass flow rates for cycling fan cycling coil operation
IF(FanOpMode .EQ. CycFanCycCoil)THEN
IF(PartLoadRatio .GT. 0.0d0)THEN
AirMassFlow = WaterCoil(CoilNum)%InletAirMassFlowRate/PartLoadRatio
WaterMassFlowRate = MIN(WaterCoil(CoilNum)%InletWaterMassFlowRate/PartLoadRatio, &
WaterCoil(CoilNum)%MaxWaterMassFlowRate)
ELSE
AirMassFlow = 0.0d0
WaterMassFlowRate = 0.0d0
END IF
ELSE
AirMassFlow = WaterCoil(CoilNum)%InletAirMassFlowRate
WaterMassFlowRate = WaterCoil(CoilNum)%InletWaterMassFlowRate
END IF
! Calculate air and water capacity rates
CapacitanceAir = AirMassFlow* &
PsyCpAirFnWTdb(WaterCoil(CoilNum)%InletAirHumRat,WaterCoil(CoilNum)%InletAirTemp)
! Water Capacity Rate
Cp = GetSpecificHeatGlycol(PlantLoop(WaterCoil(CoilNum)%WaterLoopNum)%FluidName, &
WaterTempIn, &
PlantLoop(WaterCoil(CoilNum)%WaterLoopNum)%FluidIndex, &
'CoilCompletelyDry')
CapacitanceWater = WaterMassFlowRate* Cp
! Determine the air and water outlet conditions
CALL CoilOutletStreamCondition(CoilNum, CapacitanceWater,WaterTempIn,CapacitanceAir,AirTempIn,CoilUA, &
OutletWaterTemp,OutletAirTemp)
! Calculate the total and sensible heat transfer rate both are equal in case of Dry Coil
Q=CapacitanceAir*(AirTempIn-OutletAirTemp)
! Outlet humidity is equal to Inlet Humidity because its a dry coil
OutletAirHumRat = WaterCoil(CoilNum)%InletAirHumRat
RETURN
END SUBROUTINE CoilCompletelyDry