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) | :: | RatedTotalCapacity | |||
real(kind=r64), | intent(in) | :: | RatedCOP | |||
integer, | intent(in) | :: | CapFFlowCurveIndex | |||
integer, | intent(in) | :: | CapFTempCurveIndex | |||
integer, | intent(in) | :: | EIRFFlowCurveIndex | |||
integer, | intent(in) | :: | EIRFTempCurveIndex | |||
real(kind=r64), | intent(in) | :: | RatedAirVolFlowRate | |||
real(kind=r64), | intent(in) | :: | FanPowerPerEvapAirFlowRateFromInput | |||
integer, | intent(in), | optional | :: | RegionNum | ||
real(kind=r64), | intent(in), | optional | :: | MinOATCompressor | ||
real(kind=r64), | intent(in), | optional | :: | OATempCompressorOn | ||
logical, | intent(in), | optional | :: | OATempCompressorOnOffBlank | ||
integer, | intent(in), | optional | :: | DefrostControl | ||
real(kind=r64), | intent(out) | :: | NetHeatingCapRated | |||
real(kind=r64), | intent(out) | :: | NetHeatingCapH3Test | |||
real(kind=r64), | intent(out) | :: | HSPF |
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 SingleSpeedDXHeatingCoilStandardRatings(RatedTotalCapacity, RatedCOP, CapFFlowCurveIndex, CapFTempCurveIndex, &
EIRFFlowCurveIndex, EIRFTempCurveIndex, RatedAirVolFlowRate, &
FanPowerPerEvapAirFlowRateFromInput, RegionNum, MinOATCompressor, &
OATempCompressorOn, OATempCompressorOnOffBlank, DefrostControl, &
NetHeatingCapRated, NetHeatingCapH3Test, HSPF)
! SUBROUTINE INFORMATION:
! AUTHOR Chandan Sharma
! DATE WRITTEN February 2012
! MODIFIED B Nigusse, December 2012
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! na
! METHODOLOGY EMPLOYED:
! na
! REFERENCES:
! na
! USE STATEMENTS:
USE CurveManager, ONLY: CurveValue, GetCurveMinMaxValues, GetCurveType
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: CapFTempCurveIndex ! Index for the capacity as a function of temperature modifier curve
INTEGER, INTENT(IN) :: CapFFlowCurveIndex ! Index for the capacity as a function of flow fraction modifier curve
INTEGER, INTENT(IN) :: EIRFTempCurveIndex ! Index for the EIR as a function of temperature modifier curve
INTEGER, INTENT(IN) :: EIRFFlowCurveIndex ! Index for the EIR as a function of flow fraction modifier curve
REAL(r64), INTENT(IN) :: RatedTotalCapacity ! Reference capacity of DX coil [W]
REAL(r64), INTENT(IN) :: RatedCOP ! Reference coefficient of performance [W/W]
REAL(r64), INTENT(IN) :: RatedAirVolFlowRate ! Rated air volume flow rate [m3/s]
REAL(r64), INTENT(IN) :: FanPowerPerEvapAirFlowRateFromInput ! Fan power per air volume flow rate [W/(m3/s)]
INTEGER, OPTIONAL, INTENT(IN) :: RegionNum ! Region number for calculating HSPF of single speed DX heating coil
INTEGER, OPTIONAL, INTENT(IN) :: DefrostControl ! defrost control; 1=timed, 2=on-demand
REAL(r64), OPTIONAL, INTENT(IN) :: MinOATCompressor ! Minimum OAT for heat pump compressor operation [C]
REAL(r64), OPTIONAL, INTENT(IN) :: OATempCompressorOn ! The outdoor tempearture when the compressor is automatically turned
! back on, if applicable, following automatic shut off. This field is
! used only for HSPF calculation. [C]
LOGICAL, OPTIONAL, INTENT(IN) :: OATempCompressorOnOffBlank ! Flag used to determine low temperature cut out factor
REAL(r64), INTENT(OUT) :: NetHeatingCapRated ! Net Heating Coil capacity at Rated conditions,
! accounting for supply fan heat [W]
REAL(r64), INTENT(OUT) :: NetHeatingCapH3Test ! Net Heating Coil capacity at H3 test conditions
! accounting for supply fan heat [W]
REAL(r64), INTENT(OUT) :: HSPF ! seasonale energy efficiency ratio of multi speed DX cooling coil
! SUBROUTINE PARAMETER DEFINITIONS:
! na
!
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: TotalHeatingCapRated = 0.0d0 ! Heating Coil capacity at Rated conditions, without accounting supply fan heat [W]
REAL(r64) :: EIRRated = 0.0D0 ! EIR at Rated conditions [-]
REAL(r64) :: TotCapTempModFacRated = 0.0D0 ! Total capacity as a function of temerature modifier at rated conditions [-]
REAL(r64) :: EIRTempModFacRated = 0.0D0 ! EIR as a function of temerature modifier at rated conditions [-]
REAL(r64) :: TotalHeatingCapH2Test = 0.0d0 ! Heating Coil capacity at H2 test conditions, without accounting supply fan heat [W]
REAL(r64) :: TotalHeatingCapH3Test = 0.0d0 ! Heating Coil capacity at H3 test conditions, without accounting supply fan heat [W]
REAL(r64) :: CapTempModFacH2Test = 0.0D0 ! Total capacity as a function of temerature modifier at H2 test conditions [-]
REAL(r64) :: EIRTempModFacH2Test = 0.0d0 ! EIR as a function of temerature modifier at H2 test conditions [-]
REAL(r64) :: EIRH2Test = 0.0d0 ! EIR at H2 test conditions [-]
REAL(r64) :: CapTempModFacH3Test = 0.0d0 ! Total capacity as a function of temerature modifier at H3 test conditions [-]
REAL(r64) :: EIRTempModFacH3Test = 0.0d0 ! EIR as a function of temerature modifier at H3 test conditions [-]
REAL(r64) :: EIRH3Test = 0.0d0 ! EIR at H3 test conditions [-]
REAL(r64) :: TotCapFlowModFac = 0.0d0 ! Total capacity modifier (function of actual supply air flow vs rated flow)
REAL(r64) :: EIRFlowModFac = 0.0d0 ! EIR modifier (function of actual supply air flow vs rated flow)
REAL(r64) :: FanPowerPerEvapAirFlowRate = 0.0d0 ! Fan power per air volume flow rate [W/(m3/s)]
REAL(r64) :: ElecPowerRated ! Total system power at Rated conditions accounting for supply fan heat [W]
REAL(r64) :: ElecPowerH2Test ! Total system power at H2 test conditions accounting for supply fan heat [W]
REAL(r64) :: ElecPowerH3Test ! Total system power at H3 test conditions accounting for supply fan heat [W]
REAL(r64) :: NetHeatingCapH2Test ! Net Heating Coil capacity at H2 test conditions accounting for supply fan heat [W]
REAL(r64) :: PartLoadFactor
REAL(r64) :: LoadFactor ! Frac. "on" time for last stage at the desired reduced capacity, (dimensionless)
REAL(r64) :: LowTempCutOutFactor = 0.0d0 ! Factor which corresponds to compressor operation depending on outdoor temperature
REAL(r64) :: OATempCompressorOff = 0.0D0 ! Minimum outdoor air temperature to turn the commpressor off, [C]
REAL(r64) :: FractionalBinHours = 0.0d0 ! Fractional bin hours for the heating season [-]
REAL(r64) :: BuildingLoad = 0.0d0 ! Building space conditioning load corresponding to an outdoor bin temperature [W]
REAL(r64) :: HeatingModeLoadFactor = 0.0d0 ! Heating mode load factor corresponding to an outdoor bin temperature [-]
REAL(r64) :: NetHeatingCapReduced = 0.0d0 ! Net Heating Coil capacity corresponding to an outdoor bin temperature [W]
REAL(r64) :: TotalBuildingLoad = 0.0d0 ! Sum of building load over the entire heating season [W]
REAL(r64) :: TotalElectricalEnergy = 0.0d0 ! Sum of electrical energy consumed by the heatpump over the heating season [W]
REAL(r64) :: DemandDeforstCredit = 1.0d0 ! A factor to adjust HSPF if coil has demand defrost control [-]
REAL(r64) :: CheckCOP = 0.0d0 ! Checking COP at an outdoor bin temperature against unity [-]
REAL(r64) :: DesignHeatingRequirement = 0.0d0 ! The amount of heating required to maintain a given indoor temperature
! at a particular outdoor design temperature. [W]
REAL(r64) :: DesignHeatingRequirementMin = 0.0d0 ! minimum design heating requirement [W]
REAL(r64) :: DesignHeatingRequirementMax = 0.0d0 ! maximum design heating requirement [W]
REAL(r64) :: ElectricalPowerConsumption = 0.0d0 ! Electrical power corresponding to an outdoor bin temperature [W]
REAL(r64) :: HeatPumpElectricalEnergy = 0.0d0 ! Heatpump electrical energy corresponding to an outdoor bin temperature [W]
REAL(r64) :: TotalHeatPumpElectricalEnergy = 0.0d0 ! Sum of Heatpump electrical energy over the entire heating season [W]
REAL(r64) :: ResistiveSpaceHeatingElectricalEnergy = 0.0d0 ! resistance heating electrical energy corresponding to an
! outdoor bin temperature [W]
REAL(r64) :: TotalResistiveSpaceHeatingElectricalEnergy = 0.0d0 ! Sum of resistance heating electrical energy over the
! entire heating season [W]
INTEGER :: BinNum ! bin number counter
INTEGER :: spnum ! compressor speed number
INTEGER :: StandardDHRNum ! Integer counter for standardized DHRs
TotalBuildingLoad = 0.0d0
TotalHeatPumpElectricalEnergy = 0.0d0
TotalResistiveSpaceHeatingElectricalEnergy = 0.0d0
! Calculate the supply air fan electric power consumption. The electric power consumption is estimated
! using either user supplied or AHRI default value for fan power per air volume flow rate
IF( FanPowerPerEvapAirFlowRateFromInput <= 0.0D0) THEN
FanPowerPerEvapAirFlowRate=DefaultFanPowerPerEvapAirFlowRate
ELSE
FanPowerPerEvapAirFlowRate=FanPowerPerEvapAirFlowRateFromInput
ENDIF
TotCapFlowModFac = CurveValue(CapFFlowCurveIndex,AirMassFlowRatioRated)
EIRFlowModFac = CurveValue(EIRFFlowCurveIndex,AirMassFlowRatioRated)
SELECT CASE(GetCurveType(CapFTempCurveIndex))
CASE('QUADRATIC', 'CUBIC')
TotCapTempModFacRated = CurveValue(CapFTempCurveIndex,HeatingOutdoorCoilInletAirDBTempRated)
CapTempModFacH2Test = CurveValue(CapFTempCurveIndex,HeatingOutdoorCoilInletAirDBTempH2Test)
CapTempModFacH3Test = CurveValue(CapFTempCurveIndex,HeatingOutdoorCoilInletAirDBTempH3Test)
CASE('BIQUADRATIC')
TotCapTempModFacRated = CurveValue(CapFTempCurveIndex,HeatingIndoorCoilInletAirDBTempRated, &
HeatingOutdoorCoilInletAirDBTempRated)
CapTempModFacH2Test = CurveValue(CapFTempCurveIndex,HeatingIndoorCoilInletAirDBTempRated, &
HeatingOutdoorCoilInletAirDBTempH2Test)
CapTempModFacH3Test = CurveValue(CapFTempCurveIndex,HeatingIndoorCoilInletAirDBTempRated, &
HeatingOutdoorCoilInletAirDBTempH3Test)
END SELECT
SELECT CASE(GetCurveType(EIRFTempCurveIndex))
CASE('QUADRATIC', 'CUBIC')
EIRTempModFacRated = CurveValue(EIRFTempCurveIndex,HeatingOutdoorCoilInletAirDBTempRated)
EIRTempModFacH2Test = CurveValue(EIRFTempCurveIndex,HeatingOutdoorCoilInletAirDBTempH2Test)
EIRTempModFacH3Test = CurveValue(EIRFTempCurveIndex,HeatingOutdoorCoilInletAirDBTempH3Test)
CASE('BIQUADRATIC')
EIRTempModFacRated = CurveValue(EIRFTempCurveIndex,HeatingIndoorCoilInletAirDBTempRated, &
HeatingOutdoorCoilInletAirDBTempRated)
EIRTempModFacH2Test = CurveValue(EIRFTempCurveIndex,HeatingIndoorCoilInletAirDBTempRated, &
HeatingOutdoorCoilInletAirDBTempH2Test)
EIRTempModFacH3Test = CurveValue(EIRFTempCurveIndex,HeatingIndoorCoilInletAirDBTempRated, &
HeatingOutdoorCoilInletAirDBTempH3Test)
END SELECT
TotalHeatingCapRated = RatedTotalCapacity * TotCapTempModFacRated * TotCapFlowModFac
NetHeatingCapRated = TotalHeatingCapRated + FanPowerPerEvapAirFlowRate * RatedAirVolFlowRate
TotalHeatingCapH2Test = RatedTotalCapacity * CapTempModFacH2Test * TotCapFlowModFac
NetHeatingCapH2Test = TotalHeatingCapH2Test + FanPowerPerEvapAirFlowRate * RatedAirVolFlowRate
TotalHeatingCapH3Test = RatedTotalCapacity * CapTempModFacH3Test * TotCapFlowModFac
NetHeatingCapH3Test = TotalHeatingCapH3Test + FanPowerPerEvapAirFlowRate * RatedAirVolFlowRate
IF ( RatedCOP > 0.0D0 ) THEN ! RatedCOP <= 0.0 is trapped in GetInput, but keep this as "safety"
EIRRated = EIRTempModFacRated * EIRFlowModFac / RatedCOP
EIRH2Test = EIRTempModFacH2Test * EIRFlowModFac / RatedCOP
EIRH3Test = EIRTempModFacH3Test * EIRFlowModFac / RatedCOP
ENDIF
ElecPowerRated = EIRRated * TotalHeatingCapRated + FanPowerPerEvapAirFlowRate * RatedAirVolFlowRate
ElecPowerH2Test = EIRH2Test * TotalHeatingCapH2Test + FanPowerPerEvapAirFlowRate * RatedAirVolFlowRate
ElecPowerH3Test = EIRH3Test * TotalHeatingCapH3Test + FanPowerPerEvapAirFlowRate * RatedAirVolFlowRate
IF (RegionNum .EQ. 5) THEN
DesignHeatingRequirementMin = NetHeatingCapRated
ELSE
DesignHeatingRequirementMin = NetHeatingCapRated * 1.8D0* (18.33D0 - OutdoorDesignTemperature(RegionNum)) / (60.0D0)
ENDIF
DO StandardDHRNum = 1, TotalNumOfStandardDHRs - 1
IF (StandardDesignHeatingRequirement(StandardDHRNum) .LE. DesignHeatingRequirementMin .AND. &
StandardDesignHeatingRequirement(StandardDHRNum + 1) .GE. DesignHeatingRequirementMin) THEN
IF ((DesignHeatingRequirementMin - StandardDesignHeatingRequirement(StandardDHRNum)) .GT. &
(StandardDesignHeatingRequirement(StandardDHRNum + 1) - DesignHeatingRequirementMin)) THEN
DesignHeatingRequirementMin = StandardDesignHeatingRequirement(StandardDHRNum + 1)
ELSE
DesignHeatingRequirementMin = StandardDesignHeatingRequirement(StandardDHRNum)
ENDIF
ENDIF
END DO
IF (StandardDesignHeatingRequirement(1) .GE. DesignHeatingRequirementMin) THEN
DesignHeatingRequirement = StandardDesignHeatingRequirement(1)
ELSEIF (StandardDesignHeatingRequirement(TotalNumOfStandardDHRs) .LE. DesignHeatingRequirementMin) THEN
DesignHeatingRequirement = StandardDesignHeatingRequirement(TotalNumOfStandardDHRs)
ELSE
DesignHeatingRequirement = DesignHeatingRequirementMin
ENDIF
DO BinNum = 1, TotalNumOfTemperatureBins(RegionNum)
IF (RegionNum .EQ. 1) THEN
FractionalBinHours = RegionOneFracBinHoursAtOutdoorBinTemp(BinNum)
ELSEIF (RegionNum .EQ. 2) THEN
FractionalBinHours = RegionTwoFracBinHoursAtOutdoorBinTemp(BinNum)
ELSEIF (RegionNum .EQ. 3) THEN
FractionalBinHours = RegionThreeFracBinHoursAtOutdoorBinTemp(BinNum)
ELSEIF (RegionNum .EQ. 4) THEN
FractionalBinHours = RegionFourFracBinHoursAtOutdoorBinTemp(BinNum)
ELSEIF (RegionNum .EQ. 5) THEN
FractionalBinHours = RegionFiveFracBinHoursAtOutdoorBinTemp(BinNum)
ELSEIF (RegionNum .EQ. 6) THEN
FractionalBinHours = RegionSixFracBinHoursAtOutdoorBinTemp(BinNum)
ENDIF
BuildingLoad = (18.33D0 - OutdoorBinTemperature(BinNum)) / (18.33D0 - OutdoorDesignTemperature(RegionNum)) &
* CorrectionFactor * DesignHeatingRequirement
IF ((OutdoorBinTemperature(BinNum) .LE. -8.33D0) .OR. (OutdoorBinTemperature(BinNum) .GE. 7.22D0)) THEN
NetHeatingCapReduced = NetHeatingCapH3Test + (NetHeatingCapRated - NetHeatingCapH3Test) * &
(OutdoorBinTemperature(BinNum) + 8.33D0)/ (16.67D0)
ElectricalPowerConsumption = ElecPowerH3Test + (ElecPowerRated - ElecPowerH3Test) * &
(OutdoorBinTemperature(BinNum) + 8.33D0)/ (16.67D0)
ELSE
NetHeatingCapReduced = NetHeatingCapH3Test + (NetHeatingCapH2Test - NetHeatingCapH3Test) * &
(OutdoorBinTemperature(BinNum) + 8.33D0)/ (10.0D0)
ElectricalPowerConsumption = ElecPowerH3Test + (ElecPowerH2Test - ElecPowerH3Test) * &
(OutdoorBinTemperature(BinNum) + 8.33D0)/ (10.0D0)
ENDIF
IF (NetHeatingCapReduced .NE. 0.0D0) THEN
HeatingModeLoadFactor = BuildingLoad / NetHeatingCapReduced
ENDIF
IF (HeatingModeLoadFactor .GT. 1.0D0) THEN
HeatingModeLoadFactor = 1.0D0
ENDIF
PartLoadFactor = 1 - CyclicDegradationCoeff * (1 - HeatingModeLoadFactor)
IF (ElectricalPowerConsumption .NE. 0.0D0) THEN
CheckCOP = NetHeatingCapReduced/ElectricalPowerConsumption
ENDIF
OATempCompressorOff = MinOATCompressor
IF (CheckCOP .LT. 1.0D0) THEN
LowTempCutOutFactor = 0.0D0
ELSE
IF(.NOT. OATempCompressorOnOffBlank) THEN
IF (OutdoorBinTemperature(BinNum) .LE. OATempCompressorOff) THEN
LowTempCutOutFactor = 0.0D0
ELSEIF (OutdoorBinTemperature(BinNum) .GT. OATempCompressorOff .and. &
OutdoorBinTemperature(BinNum) .LE. OATempCompressorOn) THEN
LowTempCutOutFactor = 0.5D0
ELSE
LowTempCutOutFactor = 1.0D0
ENDIF
ELSE
LowTempCutOutFactor = 1.0D0
ENDIF
ENDIF
IF (PartLoadFactor .NE. 0.0D0) THEN
HeatPumpElectricalEnergy = (HeatingModeLoadFactor * ElectricalPowerConsumption * LowTempCutOutFactor) &
* FractionalBinHours / PartLoadFactor
ENDIF
ResistiveSpaceHeatingElectricalEnergy = (BuildingLoad - HeatingModeLoadFactor * NetHeatingCapReduced &
* LowTempCutOutFactor) * FractionalBinHours
TotalBuildingLoad = TotalBuildingLoad + (BuildingLoad * FractionalBinHours)
TotalHeatPumpElectricalEnergy = TotalHeatPumpElectricalEnergy + HeatPumpElectricalEnergy
TotalResistiveSpaceHeatingElectricalEnergy = TotalResistiveSpaceHeatingElectricalEnergy + &
ResistiveSpaceHeatingElectricalEnergy
END DO
TotalElectricalEnergy = TotalHeatPumpElectricalEnergy + TotalResistiveSpaceHeatingElectricalEnergy
IF (DefrostControl .EQ. Timed) THEN
DemandDeforstCredit = 1.0D0 ! Timed defrost control
ELSE
DemandDeforstCredit = 1.03D0 ! Demand defrost control
ENDIF
IF (TotalElectricalEnergy .NE. 0.0D0) THEN
HSPF = TotalBuildingLoad * DemandDeforstCredit / TotalElectricalEnergy
ENDIF
RETURN
END SUBROUTINE SingleSpeedDXHeatingCoilStandardRatings