CalcMinimalDXHeating Subroutine

public subroutine CalcMinimalDXHeating(OutdoorDryBulb, OutdoorHumRatio, OutdoorPressure, InletDryBulbTemp, InletAirHumRat, RatedCOP, RatedTotCap, PartLoadRatio, RatedAirMassFlowRate, OutletAirTemp, OutletAirHumRat, ElecHeatingPower, TotalHeatingEnergyRate, TotalSensibleHeatOut)

Uses

  • proc~~calcminimaldxheating~~UsesGraph proc~calcminimaldxheating CalcMinimalDXHeating module~psychrowrapper PsychroWrapper proc~calcminimaldxheating->module~psychrowrapper module~minimaldxfan MinimalDXFan proc~calcminimaldxheating->module~minimaldxfan module~psychrolib psychrolib module~psychrowrapper->module~psychrolib module~epluspsychro EPlusPsychro module~psychrowrapper->module~epluspsychro iso_fortran_env iso_fortran_env module~minimaldxfan->iso_fortran_env

Simplified EnergyPlus subroutine for calculating the performance of a DX heating coil. Adapted from EnergyPlus CalcDXHeatingCoil by D.Meyer and R. Raustad (2018).

ORIGINAL ENERGY PLUS SUBROUTINE INFORMATION:

   AUTHOR         Richard Raustad
   DATE WRITTEN   October 2001
   MODIFIED       Raustad/Shirey Mar 2004
                  Kenneth Tang 2004 (Sensitivity of TotCapTempModFac & EIRTempModFac  to indoor dry bulb temp)
                  Feb 2005 M. J. Witte, GARD Analytics, Inc.
                    Add new coil type COIL:DX:MultiMode:CoolingEmpirical:
   RE-ENGINEERED  na

PURPOSE OF THIS SUBROUTINE:

Calculates the air-side heating performance and electrical heating energy use of a direct-expansion, air-cooled heat pump unit.

METHODOLOGY EMPLOYED:

This routine simulates the performance of air-cooled DX heating equipment. The routine requires the user to enter the total heating capacity and COP for the unit at ARI 210/240 rating conditions (21.11C [70F] dry-bulb, 15.55C [60F] wet-bulb air entering the heating coil, 8.33C [47F] dry-bulb, 6.11C [43F] wet-bulb air entering the outdoor condenser. Since different manufacturer's rate their equipment at different air flow rates, the supply air flow rate corresponding to the rated capacities and rated COP must also be entered (should be between 300 cfm/ton and 450 cfm/ton). The rated information entered by the user should NOT include the thermal or electrical impacts of the supply air fan, as this is addressed by another module.

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 efficiency of the unit as a function of outdoor 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.

REFERENCES:

Winkelmann, F.C., Birdsall, B.E., Buhl W.F., Ellington, K.L., Erdem, A.E. 1993. DOE-2 Supplement Version 2.1E. Energy and Environment Division, Larwence Berkely Laboratory.

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.

1. https://bigladdersoftware.com/epx/docs/8-7/engineering-reference/coils.html#single-speed-dx-heating-coil-standard-ratings

2. https://github.com/NREL/EnergyPlusRelease/blob/1ba8474958dbac5a371362731b23310d40e0635d/SourceCode/DXCoil.f90#L10082-L10509

Arguments

Type IntentOptional AttributesName
real(kind=dp), intent(in) :: OutdoorDryBulb

Outdoor (environmental) air temperature [°C]

real(kind=dp), intent(in) :: OutdoorHumRatio

Outdoor (environmental) air humidity ratio [kg/kg]

real(kind=dp), intent(in) :: OutdoorPressure

Outdoor (environmental) pressure [Pa]

real(kind=dp), intent(in) :: InletDryBulbTemp

Actual inlet air temperature [°C]

real(kind=dp), intent(in) :: InletAirHumRat

Actual inlet air humidity ratio [kg kg-1]

real(kind=dp), intent(in) :: RatedCOP

Rated COP [1]

real(kind=dp), intent(in) :: RatedTotCap

Rated capacity [W]

real(kind=dp), intent(in) :: PartLoadRatio

Part load ratio (PLR). This is the actual heating produced by the AC unit divided by the maximum heatng available - i.e. PLR = (SensibleHeatingLoad / TotalHeatingEnergyRate) [1]

real(kind=dp), intent(in) :: RatedAirMassFlowRate

HVAC air mass flow rate [kg/s]

real(kind=dp), intent(out) :: OutletAirTemp

Actual outlet temperature [°C]

real(kind=dp), intent(out) :: OutletAirHumRat

Actual outlet humidity ratio [kg/kg]

real(kind=dp), intent(out) :: ElecHeatingPower

Electrical power consumed by the DX unit [W]

real(kind=dp), intent(out) :: TotalHeatingEnergyRate

Total energy supplied by the DX unit [W]

real(kind=dp), intent(out) :: TotalSensibleHeatOut

Total sensible heat removed by the evaporator[W]


Calls

proc~~calcminimaldxheating~~CallsGraph proc~calcminimaldxheating CalcMinimalDXHeating proc~gethumratiofromenthalpyandtdrybulb GetHumRatioFromEnthalpyAndTDryBulb proc~calcminimaldxheating->proc~gethumratiofromenthalpyandtdrybulb proc~initpsychrometrics InitPsychrometrics proc~calcminimaldxheating->proc~initpsychrometrics proc~gettdrybulbfromenthalpyandhumratio GetTDryBulbFromEnthalpyAndHumRatio proc~calcminimaldxheating->proc~gettdrybulbfromenthalpyandhumratio proc~getonofffan GetOnOffFan proc~calcminimaldxheating->proc~getonofffan proc~gethumratiofromtdewpoint GetHumRatioFromTDewPoint proc~calcminimaldxheating->proc~gethumratiofromtdewpoint proc~getrelhumfromhumratio GetRelHumFromHumRatio proc~calcminimaldxheating->proc~getrelhumfromhumratio proc~psytsatfnhpb PsyTsatFnHPb proc~calcminimaldxheating->proc~psytsatfnhpb proc~getmoistairenthalpy GetMoistAirEnthalpy proc~calcminimaldxheating->proc~getmoistairenthalpy proc~getmoistairdensity GetMoistAirDensity proc~calcminimaldxheating->proc~getmoistairdensity proc~gettwetbulbfromhumratio GetTWetBulbFromHumRatio proc~calcminimaldxheating->proc~gettwetbulbfromhumratio proc~isip isIP proc~gethumratiofromenthalpyandtdrybulb->proc~isip proc~setunitsystem SetUnitSystem proc~initpsychrometrics->proc~setunitsystem proc~gettdrybulbfromenthalpyandhumratio->proc~isip proc~gethumratiofromvappres GetHumRatioFromVapPres proc~gethumratiofromtdewpoint->proc~gethumratiofromvappres proc~getsatvappres GetSatVapPres proc~gethumratiofromtdewpoint->proc~getsatvappres proc~getvappresfromhumratio GetVapPresFromHumRatio proc~getrelhumfromhumratio->proc~getvappresfromhumratio proc~getrelhumfromvappres GetRelHumFromVapPres proc~getrelhumfromhumratio->proc~getrelhumfromvappres proc~getsatairenthalpy GetSatAirEnthalpy proc~psytsatfnhpb->proc~getsatairenthalpy proc~getmoistairenthalpy->proc~isip proc~getmoistairvolume GetMoistAirVolume proc~getmoistairdensity->proc~getmoistairvolume proc~gettdewpointfromhumratio GetTDewPointFromHumRatio proc~gettwetbulbfromhumratio->proc~gettdewpointfromhumratio proc~gethumratiofromtwetbulb GetHumRatioFromTWetBulb proc~gettwetbulbfromhumratio->proc~gethumratiofromtwetbulb proc~gettdewpointfromhumratio->proc~getvappresfromhumratio proc~gettdewpointfromvappres GetTDewPointFromVapPres proc~gettdewpointfromhumratio->proc~gettdewpointfromvappres proc~getmoistairvolume->proc~isip proc~gettrankinefromtfahrenheit GetTRankineFromTFahrenheit proc~getmoistairvolume->proc~gettrankinefromtfahrenheit proc~gettkelvinfromtcelsius GetTKelvinFromTCelsius proc~getmoistairvolume->proc~gettkelvinfromtcelsius proc~getrelhumfromvappres->proc~getsatvappres proc~getsatairenthalpy->proc~getmoistairenthalpy proc~getsathumratio GetSatHumRatio proc~getsatairenthalpy->proc~getsathumratio proc~gethumratiofromtwetbulb->proc~isip proc~gethumratiofromtwetbulb->proc~getsathumratio proc~getsatvappres->proc~isip proc~getsatvappres->proc~gettrankinefromtfahrenheit proc~getsatvappres->proc~gettkelvinfromtcelsius proc~gettdewpointfromvappres->proc~isip proc~gettdewpointfromvappres->proc~getsatvappres proc~dlnpws_ dLnPws_ proc~gettdewpointfromvappres->proc~dlnpws_ proc~getsathumratio->proc~getsatvappres proc~dlnpws_->proc~isip proc~dlnpws_->proc~gettrankinefromtfahrenheit proc~dlnpws_->proc~gettkelvinfromtcelsius

Called by

proc~~calcminimaldxheating~~CalledByGraph proc~calcminimaldxheating CalcMinimalDXHeating proc~simminimaldxheating SimMinimalDXHeating proc~simminimaldxheating->proc~calcminimaldxheating

Contents

Source Code


Source Code

  subroutine CalcMinimalDXHeating(OutdoorDryBulb, OutdoorHumRatio, OutdoorPressure,             & !I
                                  InletDryBulbTemp, InletAirHumRat,                             & !I
                                  RatedCOP, RatedTotCap, PartLoadRatio, RatedAirMassFlowRate,   & !I
                                  OutletAirTemp, OutletAirHumRat,                               & !O
                                  ElecHeatingPower, TotalHeatingEnergyRate, TotalSensibleHeatOut) !O

    !+ Simplified EnergyPlus subroutine for calculating the performance of a DX heating coil.
    !+ Adapted from EnergyPlus `CalcDXHeatingCoil` by D.Meyer and R. Raustad (2018).
    !+
    !+####ORIGINAL ENERGY PLUS SUBROUTINE INFORMATION:
    !+       AUTHOR         Richard Raustad
    !+       DATE WRITTEN   October 2001
    !+       MODIFIED       Raustad/Shirey Mar 2004
    !+                      Kenneth Tang 2004 (Sensitivity of TotCapTempModFac & EIRTempModFac  to indoor dry bulb temp)
    !+                      Feb 2005 M. J. Witte, GARD Analytics, Inc.
    !+                        Add new coil type COIL:DX:MultiMode:CoolingEmpirical:
    !+       RE-ENGINEERED  na
    !+
    !+####PURPOSE OF THIS SUBROUTINE:
    !+ Calculates the air-side heating performance and electrical heating energy
    !+ use of a direct-expansion, air-cooled heat pump unit.
    !+
    !+####METHODOLOGY EMPLOYED:
    !+ This routine simulates the performance of air-cooled DX heating equipment.
    !+ The routine requires the user to enter the total heating capacity
    !+ and COP for the unit at ARI 210/240 rating conditions (21.11C [70F] dry-bulb,
    !+ 15.55C [60F] wet-bulb air entering the heating coil, 8.33C [47F] dry-bulb,
    !+ 6.11C [43F] wet-bulb air entering the outdoor condenser. Since different
    !+ manufacturer's rate their equipment at different air flow rates, the supply
    !+ air flow rate corresponding to the rated capacities and rated COP must also
    !+ be entered (should be between 300 cfm/ton and 450 cfm/ton). The rated information
    !+ entered by the user should NOT include the thermal or electrical impacts of the
    !+ supply air fan, as this is addressed by another module.
    !+
    !+ 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 efficiency of the unit as a function
    !+ of outdoor 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.
    !+
    !+####REFERENCES:
    !+
    !+ Winkelmann, F.C., Birdsall, B.E., Buhl W.F., Ellington, K.L., Erdem, A.E. 1993.
    !+ DOE-2 Supplement Version 2.1E.  Energy and Environment Division, Larwence Berkely
    !+ Laboratory.
    !+
    !+ 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.
    !+
    !+####LINKS:
    !+
    !+ 1.
    !+ <https://bigladdersoftware.com/epx/docs/8-7/engineering-reference/coils.html#single-speed-dx-heating-coil-standard-ratings>
    !+
    !+ 2.
    !+ <https://github.com/NREL/EnergyPlusRelease/blob/1ba8474958dbac5a371362731b23310d40e0635d/SourceCode/DXCoil.f90#L10082-L10509>

    use PsychroWrapper, only: InitPsychrometrics, GetMoistAirDensity,           &
                              GetTWetBulbFromHumRatio, GetMoistAirEnthalpy,     &
                              GetHumRatioFromEnthalpyAndTDryBulb,               &
                              GetTDryBulbFromEnthalpyAndHumRatio,               &
                              GetRelHumFromHumRatio, GetHumRatioFromTDewPoint,  &
                              PsyTsatFnHPb

    use MinimalDXFan, only: GetOnOffFan

    ! Using fortran 2008 standard to represent double-precision floating-point format
    integer, parameter :: dp = REAL64

    ! Subroutine Arguments
    real(dp), intent(in)    :: OutdoorDryBulb
    !+ Outdoor (environmental) air temperature      [°C]
    real(dp), intent(in)    :: OutdoorHumRatio
    !+ Outdoor (environmental) air humidity ratio   [kg/kg]
    real(dp), intent(in)    :: OutdoorPressure
    !+ Outdoor (environmental) pressure             [Pa]
    real(dp), intent(in)    :: InletDryBulbTemp
    !+ Actual inlet air temperature                 [°C]
    real(dp), intent(in)    :: InletAirHumRat
    !+ Actual inlet air humidity ratio              [kg kg-1]
    real(dp), intent(in)    :: RatedCOP
    !+ Rated COP                                    [1]
    real(dp), intent(in)    :: RatedTotCap
    !+ Rated capacity                               [W]
    real(dp), intent(in)    :: PartLoadRatio
    !+ Part load ratio (PLR). This is the actual heating produced by the AC unit divided by the maximum
    !+ heatng  available - i.e. `PLR = (SensibleHeatingLoad / TotalHeatingEnergyRate)` `[1]`
    real(dp), intent(in)    :: RatedAirMassFlowRate
    !+ HVAC air mass flow rate                      [kg/s]
    real(dp), intent(out)   :: OutletAirTemp
    !+ Actual outlet temperature                    [°C]
    real(dp), intent(out)   :: OutletAirHumRat
    !+ Actual outlet humidity ratio                 [kg/kg]
    real(dp), intent(out)   :: ElecHeatingPower
    !+ Electrical power consumed by the DX unit     [W]
    real(dp), intent(out)   :: TotalHeatingEnergyRate
    !+ Total energy supplied by the DX unit         [W]
    real(dp), intent(out)   :: TotalSensibleHeatOut
    !+ Total sensible heat removed by the evaporator[W]

    ! Local variables
    real(dp)                :: TotCapTempModFac         ! Total heating capacity modifier curve function of both [1]
                                                        ! the outdoor and indoor air dry-bulb temperature
    real(dp)                :: ActualCOP                ! Actual COP                                   [1]
    real(dp)                :: TotCap                   ! Actual capacity                              [W]
    real(dp)                :: IndoorAirDensity
    real(dp)                :: InletAirDryBulbTemp
    !+ Actual inlet air temperature                                                                     [°C]
    real(dp)                :: InletAirEnthalpy
    real(dp)                :: FullLoadOutAirEnth
    real(dp)                :: FullLoadOutAirHumRat
    real(dp)                :: FullLoadOutAirTemp
    real(dp)                :: OutletAirEnthalpy
    real(dp)                :: TotCapFlowModFac
    real(dp)                :: RatedEIR
    real(dp)                :: EIRTempModFac
    real(dp)                :: EIR
    real(dp)                :: PLF
    real(dp)                :: OutdoorCoilT
    real(dp)                :: OutdoorCoildw
    real(dp)                :: LoadDueToDefrost
    real(dp)                :: HeatingCapacityMultiplier
    real(dp)                :: FractionalDefrostTime
    real(dp)                :: InputPowerMultiplier
    real(dp)                :: PLRHeating
    real(dp)                :: DefrostPower
    real(dp)                :: FullLoadOutAirRH
    real(dp)                :: HeatingCoilRuntimeFraction
    real(dp)                :: DefrostEIRTempModFac
    real(dp)                :: InletAirWetbulbC
    real(dp)                :: AirMassFlowRate
    real(dp)                :: FanPower
    ! Power of the fan to be simulated          [W]

    character (len=12)      :: DefrostStrategy = 'Resistive' ! TODO: ReverseCycle cannot be currently used due to missing DefrostEIRFT coefficients

    real(dp), parameter     :: MaxOATDefrost    = 0.0_dp
    real(dp), parameter     :: MinOATCompressor = -10.0_dp
    real(dp), parameter     :: DefrostCapacity  = 2000.0_dp ! For now set the heater to 2000 W
    real(dp), parameter     :: AirMassFlowRatio = 1.0_dp    ! Ratio of compressor on airflow to average timestep airflow    [1]
                                                            ! Set to 1. Used only by DX coils with different air flow during heating
                                                            ! and when no heating is required (constant fan, fan speed changes)
    integer,  parameter     :: FanMode = 0
        ! Mode of operation: 1 for on, 0 for off                            [1]
    real(dp), parameter     :: MotEff = 0.75_dp
        ! Fan motor efficiency                                              [1]
    real(dp), parameter     :: MotInAirFrac = 1.0_dp
        ! Fraction of motor heat entering air stream                        [1]

    ! Performance curves coefficients
    ! Reference:
    ! https://github.com/NREL/EnergyPlus/blob/develop/datasets/ResidentialACsAndHPsPerfCurves.idf#L444-L540

    ! Coefficients for HPHeatingCAPFTemp -- Total heating capacity function of temperature curve (bi-quadratic).
    ! Minimum and maximum values of x and y are 0 and 50 respectively with curve output in rage 0 to 5
    real(dp), parameter :: A1 =  0.876825_dp
        ! Coefficient1 Constant
    real(dp), parameter :: B1 =  -0.002955_dp
        ! Coefficient2 x
    real(dp), parameter :: C1 =  -0.000058_dp
        ! Coefficient3 x**2
    real(dp), parameter :: D1 =  0.025335_dp
        ! Coefficient4 y
    real(dp), parameter :: E1 =  0.000196_dp
        ! Coefficient5 y**2
    real(dp), parameter :: F1 =  -0.000043_dp
        ! Coefficient6 x*y
    real(dp), parameter :: HPHeatingCAPFTempMin = 0.0_dp !TODO: find curves Min Max 
        ! Minimum curve output value
    real(dp), parameter :: HPHeatingCAPFTempMax = 5.0_dp
        ! Maximum curve output value

    ! Coefficients for HPHeatingCAPFFF -- total heating capacity function of flow fraction curve (quadratic).
    ! Minimum and maximum values of x are 0 and 1.5 respectively with curve output in range 0 to 2
    real(dp), parameter :: A2 =  0.694045465_dp
        ! Coefficient1 Constant
    real(dp), parameter :: B2 =  0.474207981_dp
        ! Coefficient2 x
    real(dp), parameter :: C2 =  -0.168253446_dp
        ! Coefficient3 x**2
    real(dp), parameter :: HPHeatingCAPFFFMin = 0.0_dp
        ! Minimum curve output value
    real(dp), parameter :: HPHeatingCAPFFFMax = 2.0_dp
        ! Maximum curve output value

    ! Coefficients for HPHeatingEIRFTemp -- Energy input ratio function of temperature curve (bi-quadratic).
    ! Minimum and maximum values of x and y are 0 and 50 respectively with curve output in rage 0 to 5
    real(dp), parameter :: A3 =  0.704658_dp
        ! Coefficient1 Constant
    real(dp), parameter :: B3 =  0.008767_dp
        ! Coefficient2 x
    real(dp), parameter :: C3 =  0.000625_dp
        ! Coefficient3 x**2
    real(dp), parameter :: D3 =  -0.009037_dp
        ! Coefficient4 y
    real(dp), parameter :: E3 =  0.000738_dp
        ! Coefficient5 y**2
    real(dp), parameter :: F3 =  -0.001025_dp
        ! Coefficient6 x*y
    real(dp), parameter :: ACCoolingEIRFTempMin = 0.0_dp
        ! Minimum curve output value
    real(dp), parameter :: ACCoolingEIRFTempMax = 5.0_dp
        ! Maximum curve output value

    ! Coefficients for ACCoolingEIRFFF -- Energy input ratio function of flow fraction curve (quadratic).
    ! Minimum and maximum values of x are 0 and 1.5 respectively with curve output in range 0 to 2
    real(dp), parameter :: A4 =  2.185418751_dp
        ! Coefficient1 Constant
    real(dp), parameter :: B4 =  -1.942827919_dp
        ! Coefficient2 x
    real(dp), parameter :: C4 =  0.757409168_dp
        ! Coefficient3 x**2
    real(dp), parameter :: ACCoolingEIRFFFMin = 0.0_dp
        ! Minimum curve output value
    real(dp), parameter :: ACCoolingEIRFFFMax = 2.0_dp
        ! Maximum curve output value

    ! Part Load Fraction curve (quadratic) as a function of Part Load Ratio is default from
    ! Table 6. BEopt AC Rated Value Inputs of NREL report NREL/TP-5500-56354
    ! Minimum and maximum values of x are 0 and 1.5 respectively
    real(dp), parameter :: A5 = 0.90_dp            !- Coefficient1 Constant
    real(dp), parameter :: B5 = 0.10_dp            !- Coefficient2 x
    real(dp), parameter :: C5 = 0.0_dp             !- Coefficient3 x**2

    ! FIXME: the coefficients are set to zero as no data is available.
    ! the DefrostEIRTempModFac curve is only being used for testing purposes.
    ! TODO: find coefficients for DefrostEIRTempModFac
    real(dp), parameter     :: A6 = 1.0_dp          !- Coefficient1 Constant
    real(dp), parameter     :: B6 = 0.0_dp            !- Coefficient2 x
    real(dp), parameter     :: C6 = 0.0_dp            !- Coefficient3 x**2
    real(dp), parameter     :: D6 = 0.0_dp            !- Coefficient4 y
    real(dp), parameter     :: E6 = 0.0_dp            !- Coefficient5 y**2
    real(dp), parameter     :: F6 = 0.0_dp            !- Coefficient6 x*y

    call InitPsychrometrics()

    ! Calculate air density of indoor air using outdoor pressure. Assume indoor pressure = outdoor pressure
    IndoorAirDensity = GetMoistAirDensity(InletAirDryBulbTemp, InletAirHumRat, OutdoorPressure)

    ! Check that the part load ratio is greater than 0 (i.e. DX unit is off) else just pass through conditions.
    if ((PartLoadRatio > 0) .AND. (OutdoorDryBulb > MinOATCompressor)) then
      ! Set the rated mass flow rate equal the mass flow rate used in the subroutine then check
      ! that the air mass flow rate is within bounds else set air mass flow rate accordingly
      AirMassFlowRate = RatedAirMassFlowRate
      if (AirMassFlowRate / IndoorAirDensity / RatedTotCap < 0.00004027_dp) then
        AirMassFlowRate = 0.00004027_dp * RatedTotCap * IndoorAirDensity
        print *, 'Warning: air mass flow rate must be greater than 0.00004027m3/s/W'
        print *, 'Resetting the air mass flow rate to: ', AirMassFlowRate, ' kg/s'

      else if (AirMassFlowRate / IndoorAirDensity / RatedTotCap > 0.00006041_dp) then
        AirMassFlowRate = 0.00006041_dp * RatedTotCap * IndoorAirDensity
        print *, 'Warning: air mass flow rate must be lower than 0.00006041m3/s/W'
        print *, 'Resetting the air mass flow rate to: ', AirMassFlowRate, ' kg/s'
      end if

      ! Modify the inlet air temperature to account for heat added by the fan motor
      ! The fan power is assumed to be 0.04151 W/W of the rated capacity
      FanPower = 0.04151 * RatedTotCap
      ! GetOnOffFan returns enthaply therefore we calculate an updated value of InletAirDryBulbTemp that
      ! accounts for the added heat released by the fan.
      InletAirEnthalpy = GetMoistAirEnthalpy(InletDryBulbTemp, InletAirHumRat)
      InletAirEnthalpy = GetOnOffFan(FanMode, MotEff, FanPower, MotInAirFrac, InletAirEnthalpy, AirMassFlowRate)
      InletAirDryBulbTemp = GetTDryBulbFromEnthalpyAndHumRatio(InletAirEnthalpy, InletAirHumRat)
      InletAirWetbulbC = GetTWetBulbFromHumRatio(InletAirDryBulbTemp,InletAirHumRat,OutdoorPressure)

      ! Assuming no condensation -> no moisture being extracted from either the
      ! indoor or the outdoor environment -> sensible heating/heating only.
      ! InletAirDryBulbTemp is the dry bulb temperature of the air entering the indoor coil
      ! OutdoorDryBulb is the dry bulb temperature of the air entering the outdoor coil
      ! Total heating capacity modifier curve function of temperature for off-rated conditions
      TotCapTempModFac = A1 + B1 * InletAirDryBulbTemp + C1 * InletAirDryBulbTemp**2        &
                        + D1 * OutdoorDryBulb  + E1 * OutdoorDryBulb**2   &
                        + F1 * InletAirDryBulbTemp * OutdoorDryBulb

      ! Limit the heating capacity modifier curve function of temperature to the its set bounds
      if (TotCapTempModFac < HPHeatingCAPFTempMin) then
        TotCapTempModFac = HPHeatingCAPFTempMin
        print *, 'Warning: the total heating capacity modifier curve function of temperature exceeds its set bounds'
        print *, 'The curve has been reset to: ', HPHeatingCAPFTempMin
      else if (TotCapTempModFac > HPHeatingCAPFTempMax) then
        TotCapTempModFac = HPHeatingCAPFTempMax
        print *, 'Warning: the total heating capacity modifier curve function of temperature exceeds its set bounds'
        print *, 'The curve has been reset to: ', HPHeatingCAPFTempMax
      end if

      ! Get total capacity modifying factor (function of mass flow) for off-rated conditions
      ! AirMassFlowRatio = AirMassFlow / RatedAirMassFlowRate
      ! Total heating capacity modifier curve function of flow fraction
      TotCapFlowModFac = A2 + B2 * AirMassFlowRatio + C2 * AirMassFlowRatio**2

      ! Limit the heating capacity modifier curve to the its set bounds
      if (TotCapFlowModFac < HPHeatingCAPFFFMin) then
        TotCapFlowModFac = HPHeatingCAPFFFMin
        print *, 'Warning: the total heating capacity modifier curve function of flow fraction exceeds its set bounds'
        print *, 'The curve has been reset to: ', HPHeatingCAPFFFMin
      else if (TotCapFlowModFac > HPHeatingCAPFFFMax) then
        TotCapFlowModFac = HPHeatingCAPFFFMax
        print *, 'Warning: the total heating capacity modifier curve function of flow fraction exceeds its set bounds'
        print *, 'The curve has been reset to: ', HPHeatingCAPFFFMax
      end if

      ! Calculate total heating capacity for off-rated conditions
      TotCap = RatedTotCap * TotCapFlowModFac * TotCapTempModFac

      ! Calculating adjustment factors for defrost
      ! Calculate delta w through outdoor coil by assuming a coil temp of 0.82*DBT-9.7(F) per DOE2.1E
      OutdoorCoilT = 0.82_dp * OutdoorDryBulb - 8.589_dp
      OutdoorCoildw = max( 1.0d-6, &
                          (OutdoorHumRatio - GetHumRatioFromTDewPoint(OutdoorCoilT , OutdoorPressure)) )

      ! Initializing defrost adjustment factors
      LoadDueToDefrost            = 0.0_dp
      HeatingCapacityMultiplier   = 1.00_dp
      FractionalDefrostTime       = 0.00_dp
      InputPowerMultiplier        = 1.00_dp
      PLRHeating                  = 0.00_dp

      ! Check outdoor temperature to determine of defrost is active
      ! If the outdoor dry bulb temperature, defrost adjustment should be active (MaxOATDefrost = 0).
      if (OutdoorDryBulb <= MaxOATDefrost) then
        ! Calculate defrost adjustment factors assuming defrost control is on-demand
        FractionalDefrostTime = 1.00_dp / (1.00_dp + 0.014460_dp / OutdoorCoildw)
        HeatingCapacityMultiplier = 0.8750_dp * ( 1.00_dp - FractionalDefrostTime)
        InputPowerMultiplier = 0.9540_dp * ( 1.00_dp - FractionalDefrostTime)

        ! TODO: ReverseCycle is currently deactivated - will need to find DefrostEIRFT coefficients
        !       before using this option. This means that we will always imply resistive defrost below MaxOATDefrost
        if (FractionalDefrostTime > 0.00_dp) then
          if ( trim(adjustl(DefrostStrategy)) == 'ReverseCycle') then
              LoadDueToDefrost = ( 0.010_dp * FractionalDefrostTime) * (7.2220_dp - OutdoorDryBulb) * &
                                    (RatedTotCap/1.016670_dp )
              DefrostEIRTempModFac = A6 + max(15.5550_dp,InletAirWetbulbC) * (B6 + C6 * max(15.5550_dp,InletAirWetbulbC))   &
                                        + max(15.5550_dp,OutdoorDryBulb) * (D6 + E6 * max(15.5550_dp,OutdoorDryBulb))     &
                                        + max(15.5550_dp,InletAirWetbulbC) * max(15.5550_dp,OutdoorDryBulb) * F6
              DefrostPower =  DefrostEIRTempModFac * (RatedTotCap / 1.016670_dp) * FractionalDefrostTime

          else if ( trim(adjustl(DefrostStrategy)) == 'Resistive') then
            ! Calculate defrost adjustment factors - assume resistive defrost only
            DefrostPower = DefrostCapacity * FractionalDefrostTime

          else
            error stop 'Error: you must select a valid defrost strategy'
          end if

        else
          ! Defrost is not active because (FractionalDefrostTime == 0)
          DefrostPower =  0.0_dp
        end if
      end if

      ! Modify total heating capacity based on defrost heating capacity multiplier
      TotCap = TotCap * HeatingCapacityMultiplier

      ! TODO: the crankcase heater option has not been implemented as there is no current need.
      !       maybe done in the future if needed.

      ! Calculate coil condition
      FullLoadOutAirEnth = InletAirEnthalpy + TotCap / AirMassFlowRate

      ! Amount of moisture in/out unchanged as this is sensible heat process only
      FullLoadOutAirHumRat = InletAirHumRat
      FullLoadOutAirTemp = GetTDryBulbFromEnthalpyAndHumRatio(FullLoadOutAirEnth, FullLoadOutAirHumRat)
      FullLoadOutAirRH = GetRelHumFromHumRatio(FullLoadOutAirTemp,FullLoadOutAirHumRat,OutdoorPressure)
      ! Limit to saturated conditions at FullLoadOutAirEnth
      if (FullLoadOutAirRH > 1.00_dp) then
        FullLoadOutAirTemp = PsyTsatFnHPb(FullLoadOutAirEnth, OutdoorPressure)
        FullLoadOutAirHumRat  = GetHumRatioFromEnthalpyAndTDryBulb(FullLoadOutAirEnth, FullLoadOutAirTemp)
      end if

      ! Calculate actual outlet conditions for the input part load ratio
      ! Actual outlet conditions are "average" for time step
      ! Assume continuous fan, cycling compressor
      OutletAirEnthalpy = ( (PartLoadRatio * AirMassFlowRatio) * FullLoadOutAirEnth +  &
                              (1.00_dp - (PartLoadRatio * AirMassFlowRatio)) * InletAirEnthalpy)

      OutletAirHumRat   = ( PartLoadRatio * FullLoadOutAirHumRat + &
                          (1.00_dp - PartLoadRatio) * InletAirHumRat )

      OutletAirTemp     = GetTDryBulbFromEnthalpyAndHumRatio(OutletAirEnthalpy,OutletAirHumRat)

      ! Calculate electricity consumed. First, get EIR modifying factors for off-rated conditions
      ! Use biquadratic curve. This allows sensitivity of the EIR to the entering dry-bulb temperature
      ! as well as the outside dry-bulb temperature.

      ! Calculate EIR from COP
      RatedEIR = 1 / RatedCOP

      EIRTempModFac = A3 + InletAirDryBulbTemp * (B3 + C3 * InletAirDryBulbTemp)    &
                      + OutdoorDryBulb * (D3 + E3 * OutdoorDryBulb)  &
                      + InletAirDryBulbTemp * OutdoorDryBulb * F3

      ! Calculate actual EIR
      EIR = RatedEIR * EIRTempModFac

      ! Calculate modified PartLoadRatio due to defrost (reverse-cycle defrost only)
      ! TODO: Set LoadDueToDefrost = 0 for now as ReverseCycle to defrost options has not been added yet
      LoadDueToDefrost = 0.0_dp
      PLRHeating = min( 1.00_dp, (PartLoadRatio + LoadDueToDefrost / TotCap) )

      ! Calculate PLF (0.85, 0.15)
      PLF = A5 + B5 * PartLoadRatio + C5 * PartLoadRatio**2
      if (PLF < 0.70_dp) then
        PLF = 0.70_dp
      end if

      HeatingCoilRuntimeFraction = (PLRHeating / PLF)

      ! Adjust defrost power to correct for DOE-2 bug where defrost power is constant regardless of compressor runtime fraction
      ! Defrosts happen based on compressor run time (frost buildup on outdoor coil), not total elapsed time.
      DefrostPower = DefrostPower * HeatingCoilRuntimeFraction

      ElecHeatingPower = TotCap * EIR * HeatingCoilRuntimeFraction * InputPowerMultiplier

      ! Total heating power of the DX unit (energy rate moved from outdoor to indoor)
      TotalHeatingEnergyRate = AirMassFlowRate * (OutletAirEnthalpy - InletAirEnthalpy)

      ! This is the actual power 'removed' from the outdoor environment.
      ! We assume that all the electric power is dissipated as heat directly in the outdoor environment.
      TotalSensibleHeatOut = ElecHeatingPower - TotalHeatingEnergyRate

      ! If/when the fan is on, we add the power consumed by the fan to the electrical power consumed by the DX unit
      if (FanMode == 1) ElecHeatingPower = ElecHeatingPower + FanPower

    else
      ! The DX coil is off. Pass through conditions
      OutletAirTemp           = InletDryBulbTemp
      OutletAirHumRat         = InletAirHumRat
      ElecHeatingPower        = 0.0_dp
      TotalHeatingEnergyRate  = 0.0_dp
      TotalSensibleHeatOut    = 0.0_dp
    end if
  end subroutine CalcMinimalDXHeating