Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | PTUnitNum | |||
real(kind=r64), | intent(in) | :: | PLR | |||
logical, | intent(inout) | :: | errflag | |||
real(kind=r64), | intent(out) | :: | RuntimeFrac |
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 HeatPumpRunFrac(PTUnitNum,PLR,errflag,RuntimeFrac)
! SUBROUTINE INFORMATION:
! AUTHOR R. Raustad (based on subroutine by Kenneth Tang)
! DATE WRITTEN June 2009
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine calculates the PLF based on the PLR. Parameters required are
! thermostat cycling rate (Nmax), heat pump time constant (tau), and the fraction
! of on-cycle power use (pr)
! METHODOLOGY EMPLOYED:
! NA
! REFERENCES:
! (1) Henderson, H. I., K. Rengarajan.1996. A Model to predict the latent capacity
! of air conditioners and heat pumps at part-load conditions with constant fan
! operation. ASHRAE Transactions 102 (1): 266-274
! (2) Henderson, H.I. Jr., Y.J. Huang and Danny Parker. 1999. Residential Equipment
! Part Load Curves for Use in DOE-2. Environmental Energy Technologies Division,
! Ernest Orlando Lawrence Berkeley National Laboratory.
! USE STATEMENTS:
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: PTUnitNum ! PTAC Index Number
REAL(r64), INTENT(IN) :: PLR ! part load ratio
REAL(r64), INTENT(OUT) :: RuntimeFrac ! the required run time fraction to meet part load
LOGICAL, INTENT(INOUT) :: errflag ! part load factor out of range flag
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: PartLoadFactor ! Part load factor
REAL(r64) :: Nmax ! Maximum cycling rate [cycles/hr]
REAL(r64) :: tau ! Heat pump time constant [s]
REAL(r64) :: pr ! On-cycle power use fraction [~]
REAL(r64) :: error ! Calculation error
REAL(r64) :: PLF1 ! ith term of part load factor
REAL(r64) :: PLF2 ! (i+1)th term of part load factor
REAL(r64) :: A ! Variable for simplify equation
INTEGER :: NumIteration ! Iteration Counter
Nmax=PTUnit(PTUnitNum)%MaxONOFFCyclesperHour
tau=PTUnit(PTUnitNum)%HPTimeConstant
pr=PTUnit(PTUnitNum)%OnCyclePowerFraction
!Initialize
errflag = .FALSE.
error = 1.0d0
NumIteration = 0
!Initial guess for part load fraction
PLF1 = 1.0d0
!Calculate PLF using successive substitution until convergence
!is achieved
LOOPPLF: DO
NumIteration=NumIteration + 1
IF (PLR.EQ.1) THEN
! Set part load fraction, PLF1=1.0 if PLR=1.0 and exit loop
PLF1 = 1.0d0
EXIT LOOPPLF
END IF
IF (NumIteration.GT.100)THEN
! Exit loop if interation exceed 100
errflag = .TRUE.
PLF1 = 1.0d0
EXIT LOOPPLF
END IF
IF (error.LT.0.00001d0)THEN
! Exit loop if convergence is achieved
EXIT LOOPPLF
ELSE
! Calculate PLF
A = 4.d0 * tau * (Nmax/3600.d0) * (1 - PLR / PLF1)
IF (A.LT.1.5d-3) THEN
! A safety check to prevent PLF2 = 1 - A * (1 - Exp(-1 / A))
! from "float underflow error". Occurs when PLR is very close to 1.0,
! small A value, thus Exp(-1/A) = 0
PLF2 = 1 - A
ELSE
PLF2 = 1.0d0 - A * (1 - Exp(-1.d0 / A))
END IF
error = ABS((PLF2 - PLF1) / PLF1)
PLF1 = PLF2
END IF
END DO LOOPPLF
!Adjust PLF for the off cycle power consumption if
!on-cycle power use is specified by the user
IF (pr>0.0d0) THEN
PartLoadFactor = PLR / ((PLR / PLF1) + (1 - PLR / PLF1) * pr)
ELSE
PartLoadFactor=PLF1
END IF
IF (PartLoadFactor <= 0.0d0)THEN
PartLoadFactor = 0.0d0
RuntimeFrac = 0.0d0
errflag = .TRUE.
ELSE
RuntimeFrac = PLR / PartLoadFactor
ENDIF
IF (RuntimeFrac > 1.0d0 ) THEN
RuntimeFrac = 1.0d0
END IF
RETURN
END SUBROUTINE HeatPumpRunFrac