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) | :: | CoilNum | |||
logical, | intent(in) | :: | FirstHVACIteration | |||
real(kind=r64), | intent(in) | :: | InletWaterTemp | |||
real(kind=r64), | intent(in) | :: | InletAirTemp | |||
real(kind=r64), | intent(in) | :: | AirDewPointTemp | |||
real(kind=r64) | :: | OutletWaterTemp | ||||
real(kind=r64) | :: | OutletAirTemp | ||||
real(kind=r64) | :: | OutletAirHumRat | ||||
real(kind=r64) | :: | TotWaterCoilLoad | ||||
real(kind=r64) | :: | SenWaterCoilLoad | ||||
real(kind=r64) | :: | SurfAreaWetFraction | ||||
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 CoilPartWetPartDry(CoilNum,FirstHVACIteration,InletWaterTemp, InletAirTemp, AirDewPointTemp, &
OutletWaterTemp,OutletAirTemp,OutletAirHumRat,TotWaterCoilLoad, &
SenWaterCoilLoad,SurfAreaWetFraction, 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 cooling coil when the external fin surface is
! part wet and part dry. Results include outlet air temperature and humidity,
! outlet liquid temperature, sensible and total cooling capacities, and the wet
! fraction of the air-side surface area.
! METHODOLOGY EMPLOYED:
! Models coil using effectiveness NTU model
! REFERENCES:
! Elmahdy, A.H. and Mitalas, G.P. 1977. "A Simple Model for Cooling and
! Dehumidifying Coils for Use In Calculating Energy Requirements for Buildings,"
! ASHRAE Transactions,Vol.83 Part 2, pp. 103-117.
! TRNSYS. 1990. A Transient System Simulation Program: Reference Manual.
! Solar Energy Laboratory, Univ. Wisconsin- Madison, pp. 4.6.8-1 - 4.6.8-12.
! Threlkeld, J.L. 1970. Thermal Environmental Engineering, 2nd Edition,
! Englewood Cliffs: Prentice-Hall,Inc. pp. 254-270.
! USE STATEMENTS:
USE General, ONLY: Iterate
! Enforce explicit typing of all variables in this routine
Implicit None
! FUNCTION ARGUMENT DEFINITIONS:
Integer, intent(in) :: CoilNum ! Number of Coil
REAL(r64), intent(in) :: InletWaterTemp ! Entering liquid temperature(C)
REAL(r64), intent(in) :: InletAirTemp ! Entering air dry bulb temperature(C)
REAL(r64), intent(in) :: AirDewPointTemp ! Entering air dew point(C)
Logical, intent(in) :: FirstHVACIteration ! Saving Old values
INTEGER, INTENT(IN) :: FanOpMode ! fan operating mode
REAL(r64), INTENT(IN) :: PartLoadRatio ! part-load ratio of heating coil
REAL(r64) :: OutletWaterTemp ! Leaving liquid temperature(C)
REAL(r64) :: OutletAirTemp ! Leaving air dry bulb temperature(C)
REAL(r64) :: OutletAirHumRat ! Leaving air humidity ratio
REAL(r64) :: TotWaterCoilLoad ! Total heat transfer rate (W)
REAL(r64) :: SenWaterCoilLoad ! Sensible heat transfer rate (W)
REAL(r64) :: SurfAreaWetFraction ! Fraction of surface area wet
! FUNCTION PARAMETER DEFINITIONS:
Integer, Parameter:: itmax = 60
real(r64), parameter :: smalltempdiff=1.0d-9
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! FUNCTION LOCAL VARIABLE DECLARATIONS:
REAL(r64) DryCoilHeatTranfer ! Heat transfer rate for dry coil(W)
REAL(r64) WetCoilTotalHeatTransfer ! Total heat transfer rate for wet coil(W)
REAL(r64) WetCoilSensibleHeatTransfer ! Sensible heat transfer rate for wet coil(W)
REAL(r64) SurfAreaWet ! Air-side area of wet coil(m2)
REAL(r64) SurfAreaDry ! Air-side area of dry coil(m2)
REAL(r64) DryCoilUA ! Overall heat transfer coefficient for dry coil(W/C)
REAL(r64) WetDryInterfcWaterTemp ! Liquid temperature at wet/dry boundary(C)
REAL(r64) WetDryInterfcAirTemp ! Air temperature at wet/dry boundary(C)
REAL(r64) WetDryInterfcSurfTemp ! Surface temperature at wet/dry boundary(C)
REAL(r64) EstimateWetDryInterfcWaterTemp ! Estimated liquid temperature at wet/dry boundary(C)
REAL(r64) EstimateSurfAreaWetFraction ! Initial Estimate for Fraction of Surface Wet with condensation
REAL(r64) WetPartUAInternal ! UA of Wet Coil Internal
REAL(r64) WetPartUAExternal ! UA of Dry Coil External
REAL(r64) WetDryInterfcHumRat ! Humidity Ratio at interface of the wet dry transition
REAL(r64) X1T ! Variables used in the two iteration in this subroutine.
REAL(r64) NewSurfAreaWetFrac ! Variables used in the two iteration in this subroutine.
REAL(r64) ResultXT ! Variables used in the two iteration in this subroutine.
REAL(r64) Y1T ! Variables used in the two iterations in this subroutine.
REAL(r64) errorT ! Error in interation for First If loop
REAL(r64) error ! Deviation of dependent variable in iteration
REAL(r64) SurfAreaFracPrevious, ErrorPrevious,SurfAreaFracLast,ErrorLast
Integer iter ! Iteration counter
Integer icvg ! Iteration convergence flag
INTEGER icvgT ! Iteration Convergence Flag for First If loop
INTEGER itT ! Iteration Counter for First If Loop
! Iterates on SurfAreaWetFraction to converge on surface temperature equal to
! entering air dewpoint at wet/dry boundary.
! Preliminary estimates of coil performance to begin iteration
OutletWaterTemp = InletAirTemp
DryCoilHeatTranfer = 0.0d0
WetCoilTotalHeatTransfer = 0.0d0
WetCoilSensibleHeatTransfer = 0.0d0
If(FirstHVACIteration)Then
! Estimate liquid temperature at boundary as entering air dew point
WetDryInterfcWaterTemp = AirDewPointTemp
! Estimate fraction wet surface area based on liquid temperatures
IF (ABS(OutletWaterTemp-InletWaterTemp) > smalltempdiff) then
SurfAreaWetFraction = (WetDryInterfcWaterTemp-InletWaterTemp)/(OutletWaterTemp-InletWaterTemp)
ELSE
SurfAreaWetFraction = 0.0d0
ENDIF
Else
SurfAreaWetFraction = WaterCoil(CoilNum)%SurfAreaWetFractionSaved
End IF
! BEGIN LOOP to converge on SurfAreaWetFraction
! The method employed in this loop is as follows: The coil is partially wet and partially dry,
! we calculate the temperature of the coil at the interface, (the point at which the moisture begins
! to condense) temperature of the water at interface and air temp is dew point at that location.
! This is done by Iterating between the Completely Dry and Completely Wet Coil until the outlet
! water temperature of one coil equals the inlet water temperature of another.
! Using this value of interface temperature we now iterate to calculate Surface Fraction Wet, Iterate
! function perturbs the value of Surface Fraction Wet and based on this new value the entire loop is
! repeated to get a new interface water temperature and then surface fraction wet is again calculated.
! This process continues till the error between the Wet Dry Interface Temp and Air Dew Point becomes
! very negligible and in 95% of the cases its is a complete convergence to give the exact surface Wet
! fraction.
NewSurfAreaWetFrac=SurfAreaWetFraction
error=0.0d0
SurfAreaFracPrevious=SurfAreaWetFraction
ErrorPrevious=0.0d0
SurfAreaFracLast=SurfAreaWetFraction
ErrorLast=0.0d0
DO iter = 1,itmax
! Calculating Surface Area Wet and Surface Area Dry
SurfAreaWet = SurfAreaWetFraction*WaterCoil(CoilNum)%TotCoilOutsideSurfArea
SurfAreaDry = WaterCoil(CoilNum)%TotCoilOutsideSurfArea-SurfAreaWet
! Calculating UA values for the Dry Part of the Coil
DryCoilUA = SurfAreaDry/(1.d0/WaterCoil(CoilNum)%UACoilInternalPerUnitArea+1.0d0/WaterCoil(CoilNum)%UADryExtPerUnitArea)
! Calculating UA Value for the Wet part of the Coil
WetPartUAExternal = WaterCoil(CoilNum)%UAWetExtPerUnitArea*SurfAreaWet
WetPartUAInternal = WaterCoil(CoilNum)%UACoilInternalPerUnitArea*SurfAreaWet
! Calculating Water Temperature at Wet Dry Interface of the coil
WetDryInterfcWaterTemp = InletWaterTemp+SurfAreaWetFraction*(OutletWaterTemp-InletWaterTemp)
! BEGIN LOOP to converge on liquid temperature at wet/dry boundary
DO itT = 1,itmax
! Calculate dry coil performance with estimated liquid temperature at the boundary.
CALL CoilCompletelyDry(CoilNum,WetDryInterfcWaterTemp, InletAirTemp,DryCoilUA, &
OutletWaterTemp,WetDryInterfcAirTemp,WetDryInterfcHumRat, &
DryCoilHeatTranfer,FanOpMode,PartLoadRatio)
! Calculate wet coil performance with calculated air temperature at the boundary.
CALL CoilCompletelyWet (CoilNum,InletWaterTemp,WetDryInterfcAirTemp,WetDryInterfcHumRat, &
WetPartUAInternal,WetPartUAExternal, &
EstimateWetDryInterfcWaterTemp,OutletAirTemp,OutletAirHumRat, &
WetCoilTotalHeatTransfer,WetCoilSensibleHeatTransfer, &
EstimateSurfAreaWetFraction,WetDryInterfcSurfTemp,FanOpMode,PartLoadRatio)
! Iterating to calculate the actual wet dry interface water temperature.
errorT = EstimateWetDryInterfcWaterTemp - WetDryInterfcWaterTemp
Call ITERATE (ResultXT,0.001d0, WetDryInterfcWaterTemp,errorT,X1T,Y1T,itT,icvgT)
WetDryInterfcWaterTemp = ResultXT
! IF convergence is achieved then exit the itT to itmax Do loop.
IF(icvgT .EQ. 1) Exit
End Do ! End Do for Liq Boundary temp Convergence
! Wet Dry Interface temperature not converged after maximum specified iterations.
! Print error message, set return error flag
IF ((itT > itmax).AND.(.NOT.WarmUpFlag)) THEN
CALL ShowWarningError('For Coil:Cooling:Water '//TRIM(WaterCoil(CoilNum)%Name))
CALL ShowContinueError ('CoilPartWetPartDry: Maximum iterations exceeded for Liq Temp, at Interface')
END IF
! If Following condition prevails then surface is dry, calculate dry coil performance and return
IF(SurfAreaWetFraction .LE. 0.0d0 .AND. WetDryInterfcSurfTemp .GE. AirDewPointTemp) THEN
! Calculating Value of Dry UA for the coil
DryCoilUA = WaterCoil(CoilNum)%TotCoilOutsideSurfArea/(1.0d0/WaterCoil(CoilNum)%UACoilInternalPerUnitArea+ &
1.0d0/WaterCoil(CoilNum)%UADryExtPerUnitArea)
! Calling the Completely Dry Coil for outputs
CALL CoilCompletelyDry(CoilNum,InletWaterTemp, InletAirTemp,DryCoilUA, &
OutletWaterTemp,OutletAirTemp,OutletAirHumRat,TotWaterCoilLoad,FanOpMode,PartLoadRatio)
! Sensible load = Total load in a Completely Dry Coil
SenWaterCoilLoad = TotWaterCoilLoad
! All coil is Dry so fraction wet is ofcourse =0
SurfAreaWetFraction = 0.0d0
RETURN
ENDIF
! IF the coil is not Dry then iterate to calculate Fraction of surface area that is wet.
error = WetDryInterfcSurfTemp - AirDewPointTemp
Call CoilAreaFracIter (NewSurfAreaWetFrac,SurfAreaWetFraction,error,SurfAreaFracPrevious, &
ErrorPrevious,SurfAreaFracLast,ErrorLast,iter,icvg)
SurfAreaWetFraction = NewSurfAreaWetFrac
!If converged, leave iteration loop
IF (icvg .EQ. 1) Exit
! Surface temperature not converged. Repeat calculations with new
! estimate of fraction wet surface area.
IF(SurfAreaWetFraction > 1.0d0) SurfAreaWetFraction = 1.0d0
IF(SurfAreaWetFraction <= 0.0d0) SurfAreaWetFraction = 0.0098d0
End Do ! End do for the overall iteration
! Calculate sum of total and sensible heat transfer from dry and wet parts.
TotWaterCoilLoad = DryCoilHeatTranfer+WetCoilTotalHeatTransfer
SenWaterCoilLoad = DryCoilHeatTranfer+WetCoilSensibleHeatTransfer
! Save last iterations values for this current time step
WaterCoil(CoilNum)%SurfAreaWetFractionSaved = SurfAreaWetFraction
RETURN
END SUBROUTINE CoilPartWetPartDry