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 | ||
---|---|---|---|---|---|---|
real(kind=r64), | intent(in) | :: | InletDryBulb | |||
real(kind=r64), | intent(in) | :: | InletHumRat | |||
real(kind=r64), | intent(in) | :: | InletEnthalpy | |||
real(kind=r64), | intent(in) | :: | InletWetBulb | |||
real(kind=r64), | intent(in) | :: | AirMassFlowRatio | |||
real(kind=r64), | intent(in) | :: | AirMassFlow | |||
real(kind=r64), | intent(in) | :: | TotCapNom | |||
real(kind=r64), | intent(in) | :: | CBF | |||
integer, | intent(in) | :: | CCapFTemp | |||
integer, | intent(in) | :: | CCapFFlow | |||
real(kind=r64), | intent(out) | :: | TotCap | |||
real(kind=r64), | intent(out) | :: | SHR | |||
real(kind=r64), | intent(in) | :: | CondInletTemp | |||
real(kind=r64), | intent(in) | :: | Pressure |
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 CalcTotCapSHR(InletDryBulb,InletHumRat,InletEnthalpy,InletWetBulb,AirMassFlowRatio,&
AirMassFlow,TotCapNom,CBF,CCapFTemp,CCapFFlow,TotCap,SHR,CondInletTemp, Pressure)
! SUBROUTINE INFORMATION:
! AUTHOR Fred Buhl using Don Shirey's code
! DATE WRITTEN September 2002
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Calculates total capacity and sensible heat ratio of a DX coil at the specified conditions
! METHODOLOGY EMPLOYED:
! With the rated performance data entered by the user, the model employs some of the
! DOE-2.1E curve fits to adjust the capacity and SHR of the unit as a function
! of entering air temperatures and supply air flow rate (actual vs rated flow). The model
! does NOT employ the exact same methodology to calculate performance as DOE-2, although
! some of the DOE-2 curve fits are employed by this model.
! The model checks for coil dryout conditions, and adjusts the calculated performance
! appropriately.
! REFERENCES:
! ASHRAE HVAC 2 Toolkit page 4-81.
!
! Henderson, H.I. Jr., K. Rengarajan and D.B. Shirey, III. 1992.The impact of comfort
! control on air conditioner energy use in humid climates. ASHRAE Transactions 98(2):
! 104-113.
!
! Henderson, H.I. Jr., Danny Parker and Y.J. Huang. 2000.Improving DOE-2's RESYS routine:
! User Defined Functions to Provide More Accurate Part Load Energy Use and Humidity
! Predictions. Proceedings of ACEEE Conference.
! USE STATEMENTS:
USE CurveManager, ONLY: CurveValue
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
REAL(r64), INTENT (IN) :: InletDryBulb ! inlet air dry bulb temperature [C]
REAL(r64), INTENT (IN) :: InletHumRat ! inlet air humidity ratio [kg water / kg dry air]
REAL(r64), INTENT (IN) :: InletEnthalpy ! inlet air specific enthalpy [J/kg]
REAL(r64), INTENT (IN) :: InletWetBulb ! inlet air wet bulb temperature [C]
REAL(r64), INTENT (IN) :: AirMassFlowRatio ! Ratio of actual air mass flow to nominal air mass flow
REAL(r64), INTENT (IN) :: AirMassFlow ! actual mass flow for capacity and SHR calculation
REAL(r64), INTENT (IN) :: TotCapNom ! nominal total capacity [W]
REAL(r64), INTENT (IN) :: CBF ! coil bypass factor
INTEGER, INTENT (IN) :: CCapFTemp ! capacity modifier curve index, function of entering wetbulb
! and outside drybulb
INTEGER, INTENT (IN) :: CCapFFlow ! capacity modifier curve, function of actual flow vs rated flow
REAL(r64), INTENT (OUT) :: TotCap ! total capacity at the given conditions [W]
REAL(r64), INTENT (OUT) :: SHR ! sensible heat ratio at the given conditions
REAL(r64), INTENT (IN) :: CondInletTemp ! Condenser inlet temperature [C]
REAL(r64), INTENT (IN) :: Pressure ! air pressure [Pa]
! SUBROUTINE PARAMETER DEFINITIONS:
CHARACTER(len=*), PARAMETER :: RoutineName='CalcTotCapSHR'
INTEGER, PARAMETER :: MaxIter = 30 ! Maximum number of iterations for dry evaporator calculations
REAL(r64), PARAMETER :: RF = 0.4d0 ! Relaxation factor for dry evaporator iterations
REAL(r64), PARAMETER :: Tolerance = 0.01d0 ! Error tolerance for dry evaporator iterations
REAL(r64), PARAMETER :: MinHumRatCalc = 0.00001d0 ! Error tolerance for dry evaporator iterations
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: InletWetBulbCalc ! calculated inlet wetbulb temperature used for finding dry coil point [C]
REAL(r64) :: InletHumRatCalc ! calculated inlet humidity ratio used for finding dry coil point [kg water / kg dry air]
REAL(r64) :: TotCapTempModFac ! Total capacity modifier (function of entering wetbulb, outside drybulb)
REAL(r64) :: TotCapFlowModFac ! Total capacity modifier (function of actual supply air flow vs nominal flow)
REAL(r64) :: hDelta ! Change in air enthalpy across the cooling coil [J/kg]
REAL(r64) :: hADP ! Apparatus dew point enthalpy [J/kg]
REAL(r64) :: tADP ! Apparatus dew point temperature [C]
REAL(r64) :: wADP ! Apparatus dew point humidity ratio [kg/kg]
REAL(r64) :: hTinwADP ! Enthalpy at inlet dry-bulb and wADP [J/kg]
REAL(r64) :: SHRCalc ! temporary calculated value of SHR
REAL(r64) :: TotCapCalc ! temporary calculated value of total capacity [W]
INTEGER :: Counter ! Counter for dry evaporator iterations
REAL(r64) :: werror ! Deviation of humidity ratio in dry evaporator iteration loop
! MaxIter = 30
! RF = 0.4d0
Counter = 0
! Tolerance = 0.01d0
werror = 0.0d0
InletWetBulbCalc = InletWetBulb
InletHumRatCalc = InletHumRat
! DO WHILE (ABS(werror) .gt. Tolerance .OR. Counter == 0)
! Get capacity modifying factor (function of inlet wetbulb & outside drybulb) for off-rated conditions
DO
TotCapTempModFac = CurveValue(CCapFTemp,InletWetBulbCalc,CondInletTemp)
! Get capacity modifying factor (function of mass flow) for off-rated conditions
TotCapFlowModFac = CurveValue(CCapFFlow,AirMassFlowRatio)
! Get total capacity
TotCapCalc = TotCapNom * TotCapFlowModFac * TotCapTempModFac
! Calculate apparatus dew point conditions using TotCap and CBF
hDelta = TotCapCalc/AirMassFlow
hADP = InletEnthalpy - hDelta/(1.d0-CBF)
tADP = PsyTsatFnHPb(hADP,Pressure)
wADP = PsyWFnTdbH(tADP,hADP)
hTinwADP = PsyHFnTdbW(InletDryBulb,wADP)
IF ((InletEnthalpy-hADP) > 1.d-10) THEN
SHRCalc = MIN((hTinwADP-hADP)/(InletEnthalpy-hADP),1.d0)
ELSE
SHRCalc=1.0d0
ENDIF
!
! Check for dry evaporator conditions (win < wadp)
!
IF (wADP .gt. InletHumRatCalc .or. (Counter .ge. 1 .and. Counter .lt. MaxIter)) THEN
If(InletHumRatCalc == 0.0d0)InletHumRatCalc=MinHumRatCalc
! InletHumRatCalc=MAX(InletHumRatCalc,MinHumRatCalc) ! proposed.
werror = (InletHumRatCalc - wADP)/InletHumRatCalc
!
! Increase InletHumRatCalc at constant inlet air temp to find coil dry-out point. Then use the
! capacity at the dry-out point to determine exiting conditions from coil. This is required
! since the TotCapTempModFac doesn't work properly with dry-coil conditions.
!
InletHumRatCalc = RF*wADP + (1.d0-RF)*InletHumRatCalc
InletWetBulbCalc = PsyTwbFnTdbWPb(InletDryBulb,InletHumRatCalc,Pressure)
Counter = Counter + 1
IF (ABS(werror) .gt. Tolerance) CYCLE ! Recalculate with modified inlet conditions
EXIT ! conditions are satisfied
ELSE
EXIT ! conditions are satisfied
END IF
END DO
! END DO
! Calculate full load output conditions
IF (SHRCalc .gt. 1.d0 .OR. Counter .gt. 0) SHRCalc = 1.d0
SHR = SHRCalc
TotCap = TotCapCalc
RETURN
END SUBROUTINE CalcTotCapSHR