Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | DXCoilNum | |||
real(kind=r64), | intent(in) | :: | SHRss | |||
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 | |||
integer, | intent(in), | optional | :: | Mode | ||
real(kind=r64), | intent(in), | optional | :: | HeatingRTF |
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, RTF, QLatRated, QLatActual, EnteringDB, EnteringWB, Mode, HeatingRTF) RESULT(SHReff)
! FUNCTION INFORMATION:
! AUTHOR Richard Raustad, FSEC
! DATE WRITTEN September 2003
! Feb 2005 M. J. Witte, GARD Analytics, Inc.
! Add new coil type COIL:DX:MultiMode:CoolingEmpirical:
! Nov 2008 R. Raustad, FSEC
! Modified to allow latent degradation with cycling fan
! 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).
!
! REFERENCES:
! "A Model to Predict the Latent Capacity of Air Conditioners and
! Heat Pumps at Part-Load Conditions with Constant Fan Operation"
! 1996 ASHRAE Transactions, Volume 102, Part 1, Pp. 266 - 274,
! Hugh I. Henderson, Jr., P.E., Kannan Rengarajan, P.E.
! USE STATEMENTS:
! na
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! FUNCTION ARGUMENT DEFINITIONS:
INTEGER, INTENT (IN) :: DXCoilNum ! Index number for cooling coil
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
INTEGER, INTENT(IN), OPTIONAL :: Mode ! Performance mode for MultiMode DX coil; Always 1 for other coil types
REAL(r64), INTENT (IN), OPTIONAL :: HeatingRTF ! Used to recalculate Toff for cycling fan systems
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) :: Nmax ! Maximum ON/OFF cycles per hour for the compressor (cycles/hr)
REAL(r64) :: Tcl ! Time constant for latent capacity to reach steady state after startup (sec)
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
REAL(r64) :: Ton_heating
REAL(r64) :: Toff_heating
If (DXCoil(DXCoilNum)%DXCoilType_Num .NE. CoilDX_MultiSpeedCooling) Then
Twet_rated = DXCoil(DXCoilNum)%Twet_Rated(Mode)
Gamma_rated = DXCoil(DXCoilNum)%Gamma_Rated(Mode)
Nmax = DXCoil(DXCoilNum)%MaxONOFFCyclesperHour(Mode)
Tcl = DXCoil(DXCoilNum)%LatentCapacityTimeConstant(Mode)
Else
Twet_rated = DXCoil(DXCoilNum)%MSTwet_Rated(Mode)
Gamma_rated = DXCoil(DXCoilNum)%MSGamma_Rated(Mode)
Nmax = DXCoil(DXCoilNum)%MSMaxONOFFCyclesperHour(Mode)
Tcl = DXCoil(DXCoilNum)%MSLatentCapacityTimeConstant(Mode)
End If
! 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. Twet_rated .LE. 0.0d0 .OR. &
Gamma_rated .LE. 0.0d0 .OR. Nmax .LE. 0.0d0 .OR. Tcl .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*Nmax*(1.0d0-RTF)) ! duration of cooling coil on-cycle (sec)
Toff = 3600.d0/(4.d0*Nmax*RTF) ! duration of cooling coil off-cycle (sec)
! 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
! Need to include the reheat coil operation to account for actual fan run time. E+ uses a
! separate heating coil for heating and reheat (to separate the heating and reheat loads)
! and real world applications would use a single heating coil for both purposes, the actual
! fan operation is based on HeatingPLR + ReheatPLR. For cycling fan RH control, latent
! degradation only occurs when a heating load exists, in this case the reheat load is
! equal to and oposite in magnitude to the cooling coil sensible output but the reheat
! coil is not always active. This additional fan run time has not been accounted for at this time.
!
! Recalculate Toff for cycling fan systems when heating is active
IF (PRESENT(HeatingRTF)) THEN
IF (HeatingRTF .LT. 1.0d0 .AND. HeatingRTF .GT. RTF)THEN
Ton_heating = 3600.d0/(4.d0*Nmax*(1.d0-HeatingRTF))
Toff_heating = 3600.d0/(4.d0*Nmax*HeatingRTF)
! add additional heating coil operation during cooling coil off cycle (due to cycling rate difference of coils)
Ton_heating = Ton_heating + MAX(0.0d0,MIN(Ton_heating, (Ton+Toffa)-(Ton_heating+Toff_heating)))
Toffa = MIN(Toffa,Ton_heating - Ton)
END IF
END IF
! Use sucessive substitution to solve for To
aa = (Gamma*Toffa) - (0.25d0/Twet)*(Gamma**2)*(Toffa**2)
To1 = aa+Tcl
Error = 1.0d0
DO WHILE (Error .gt. 0.001d0)
To2 = aa-Tcl*(EXP(-To1/Tcl)-1.d0)
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/Tcl is a large negative number.
! Cap lower limit at -700 to avoid the underflow errors.
aa = EXP(MAX(-700.0d0,-Ton/Tcl))
! Calculate latent heat ratio multiplier
LHRmult = MAX(((Ton-To2)/(Ton+Tcl*(aa-1.0d0))),0.0d0)
! Calculate part-load or "effective" sensible heat ratio
SHReff = 1.0d0-(1.0d0-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