Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | DXCoilNum | |||
real(kind=r64), | intent(in) | :: | SHRss | |||
integer, | intent(in) | :: | CyclingScheme | |||
real(kind=r64), | intent(in) | :: | RTF | |||
real(kind=r64), | intent(in) | :: | QLatRated | |||
real(kind=r64), | intent(in) | :: | QLatActual | |||
real(kind=r64), | intent(in) | :: | EnteringDB | |||
real(kind=r64), | intent(in) | :: | EnteringWB |
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.
FUNCTION CalcEffectiveSHR(DXCoilNum,SHRss, CyclingScheme, RTF, QLatRated, QLatActual, EnteringDB, EnteringWB) RESULT(SHReff)
! FUNCTION INFORMATION:
! AUTHOR Bo Shen, based on WatertoAirHeatPumpSimple:CalcEffectiveSHR
! DATE WRITTEN March 2012
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS FUNCTION:
! Adjust sensible heat ratio to account for degradation of DX coil latent
! capacity at part-load (cycling) conditions.
! METHODOLOGY EMPLOYED:
! With model parameters entered by the user, the part-load latent performance
! of a DX cooling coil is determined for a constant air flow system with
! a cooling coil that cycles on/off. The model calculates the time
! required for condensate to begin falling from the cooling coil.
! Runtimes greater than this are integrated to a "part-load" latent
! capacity which is used to determine the "part-load" sensible heat ratio.
! See reference below for additional details (linear decay model, Eq. 8b).
! For cycling fan operation, a modified version of Henderson and Rengarajan (1996)
! model is used by ultilizing the fan delay time as the time-off (or time duration
! for the re-evaporation of moisture from time coil). Refer to Tang, C.C. (2005)
! REFERENCES:
! na
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! FUNCTION ARGUMENT DEFINITIONS:
INTEGER, INTENT (IN) :: DXCoilNum ! Index number for cooling coil
INTEGER, INTENT (IN) :: CyclingScheme ! Fan/compressor cycling scheme indicator
REAL(r64), INTENT (IN) :: SHRss ! Steady-state sensible heat ratio
REAL(r64), INTENT (IN) :: RTF ! Compressor run-time fraction
REAL(r64), INTENT (IN) :: QLatRated ! Rated latent capacity
REAL(r64), INTENT (IN) :: QLatActual ! Actual latent capacity
REAL(r64), INTENT (IN) :: EnteringDB ! Entering air dry-bulb temperature
REAL(r64), INTENT (IN) :: EnteringWB ! Entering air wet-bulb temperature
REAL(r64) :: SHReff ! Effective sensible heat ratio, includes degradation due to cycling effects
! FUNCTION PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! FUNCTION LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: Twet ! Nominal time for condensate to begin leaving the coil's condensate drain line
! at the current operating conditions (sec)
REAL(r64) :: Gamma ! Initial moisture evaporation rate divided by steady-state AC latent capacity
! at the current operating conditions
REAL(r64) :: Twet_rated ! Twet at rated conditions (coil air flow rate and air temperatures), sec
REAL(r64) :: Gamma_rated ! Gamma at rated conditions (coil air flow rate and air temperatures)
REAL(r64) :: Twet_max ! Maximum allowed value for Twet
REAL(r64) :: MaxONOFFCyclesperHour ! Maximum cycling rate of heat pump [cycles/hr]
REAL(r64) :: HPTimeConstant ! Heat pump time constant [s]
REAL(r64) :: FanDelayTime ! Fan delay time, time delay for the HP's fan to
! shut off after compressor cycle off [s]
REAL(r64) :: Ton ! Coil on time (sec)
REAL(r64) :: Toff ! Coil off time (sec)
REAL(r64) :: Toffa ! Actual coil off time (sec). Equations valid for Toff <= (2.0 * Twet/Gamma)
REAL(r64) :: aa ! Intermediate variable
REAL(r64) :: To1 ! Intermediate variable (first guess at To). To = time to the start of moisture removal
REAL(r64) :: To2 ! Intermediate variable (second guess at To). To = time to the start of moisture removal
REAL(r64) :: Error ! Error for iteration (DO) loop
REAL(r64) :: LHRmult ! Latent Heat Ratio (LHR) multiplier. The effective latent heat ratio LHR = (1-SHRss)*LHRmult
Twet_rated = VarSpeedCoil(DXCoilNum)%Twet_Rated
Gamma_rated = VarSpeedCoil(DXCoilNum)%Gamma_Rated
MaxONOFFCyclesperHour = VarSpeedCoil(DXCoilNum)%MaxONOFFCyclesperHour
HPTimeConstant = VarSpeedCoil(DXCoilNum)%HPTimeConstant
FanDelayTime = VarSpeedCoil(DXCoilNum)%FanDelayTime
! No moisture evaporation (latent degradation) occurs for runtime fraction of 1.0
! All latent degradation model parameters cause divide by 0.0 if not greater than 0.0
! Latent degradation model parameters initialize to 0.0 meaning no evaporation model used.
IF((RTF.GE.1.0d0) .OR. (QLatRated.EQ.0.0d0) .OR. (QLatActual.EQ.0.0d0) .OR. (Twet_rated.LE.0.0d0) .OR. &
(Gamma_rated.LE.0.0d0) .OR. (MaxONOFFCyclesperHour.LE.0.0d0) .OR. (HPTimeConstant.LE.0.0d0) .OR. (RTF.LE. 0.0d0)) THEN
SHReff = SHRss
RETURN
ENDIF
Twet_max = 9999.0d0 ! high limit for Twet
! Calculate the model parameters at the actual operating conditions
Twet = MIN(Twet_rated*QLatRated /(QLatActual+1.d-10),Twet_max)
Gamma = Gamma_rated*QLatRated*(EnteringDB-EnteringWB)/((26.7d0-19.4d0)*QLatActual+1.d-10)
! Calculate the compressor on and off times using a converntional thermostat curve
Ton = 3600.d0/(4.d0*MaxONOFFCyclesperHour*(1.d0-RTF)) ! duration of cooling coil on-cycle (sec)
IF ((CyclingScheme .EQ. CycFanCycCoil).AND.(FanDelayTime.NE.0.0d0)) THEN
! For CycFanCycCoil, moisture is evaporated from the cooling coil back to the air stream
! until the fan cycle off. Assume no evaporation from the coil after the fan shuts off.
Toff = FanDelayTime
ELSE
! For ContFanCycCoil, moisture is evaporated from the cooling coil back to the air stream
! for the entire heat pump off-cycle.
Toff = 3600.d0/(4.d0*MaxONOFFCyclesperHour*RTF) ! duration of cooling coil off-cycle (sec)
END IF
! Cap Toff to meet the equation restriction
IF(Gamma .GT. 0.0d0)THEN
Toffa = MIN(Toff, 2.d0*Twet/Gamma)
ELSE
Toffa = Toff
END IF
! Use sucessive substitution to solve for To
aa = (Gamma*Toffa) - (0.25d0/Twet)*(Gamma**2)*(Toffa**2)
To1 = aa+HPTimeConstant
Error = 1.0d0
DO WHILE (Error .gt. 0.001d0)
To2 = aa-HPTimeConstant*(EXP(-To1/HPTimeConstant)-1.0d0)
Error = ABS((To2-To1)/To1)
To1 = To2
END DO
! Adjust Sensible Heat Ratio (SHR) using Latent Heat Ratio (LHR) multiplier
! Floating underflow errors occur when -Ton/HPTimeConstant is a large negative number.
! Cap lower limit at -700 to avoid the underflow errors.
aa = EXP(MAX(-700.0d0,-Ton/HPTimeConstant))
! Calculate latent heat ratio multiplier
LHRmult = MAX(((Ton-To2)/(Ton+HPTimeConstant*(aa-1.0d0))),0.0d0)
! Calculate part-load or "effective" sensible heat ratio
SHReff = 1.0-(1.0-SHRss)*LHRmult
IF (SHReff .LT. SHRss) SHReff = SHRss ! Effective SHR can be less than the steady-state SHR
IF (SHReff .GT. 1.0d0) SHReff=1.0d0 ! Effective sensible heat ratio can't be greater than 1.0
RETURN
END FUNCTION CalcEffectiveSHR