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 | ||
|---|---|---|---|---|---|---|
| integer, | intent(in) | :: | HPNum | |||
| integer, | intent(in) | :: | CyclingScheme | |||
| real(kind=r64), | intent(in) | :: | RuntimeFrac | |||
| real(kind=r64), | intent(in) | :: | SensDemand | |||
| real(kind=r64), | intent(in) | :: | LatentDemand | |||
| integer, | intent(in) | :: | CompOp | |||
| real(kind=r64), | intent(in) | :: | PartLoadRatio | |||
| real(kind=r64), | intent(in) | :: | OnOffAirFlowRatio | |||
| real(kind=r64), | intent(in) | :: | WaterPartLoad | 
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 CalcHPCoolingSimple(HPNum,CyclingScheme,RuntimeFrac,SensDemand,LatentDemand,CompOp,PartLoadRatio,  &
                               OnOffAirFlowRatio,WaterPartLoad)
          !       AUTHOR         Arun Shenoy
          !       DATE WRITTEN   Jan 2004
          !       MODIFIED       na
          !       RE-ENGINEERED  Kenneth Tang (Jan 2005)
          ! PURPOSE OF THIS SUBROUTINE:
          ! This subroutine is for simulating the cooling mode of the Water to Air HP Simple
          ! METHODOLOGY EMPLOYED:
          ! Simulate the heat pump performance using the coefficients and rated conditions
          !
          ! If the LatDegradModelSimFlag is enabled, the coil will be simulated twice:
          ! (1)first simulation at the rated conditions (2) second simulation at the
          ! actual operating conditions. Then call CalcEffectiveSHR and the effective SHR
          ! is adjusted.
          !
          ! If the LatDegradModelSimFlag is disabled, the cooling coil is only simulated
          ! once at the actual operating conditions.
          !
          ! Finally, adjust the heat pump outlet conditions based on the PartLoadRatio
          ! and RuntimeFrac.
          ! REFERENCES:
          ! (1) Lash.T.A.,1992.Simulation and Analysis of a Water Loop Heat Pump System.
          ! M.S. Thesis, University of Illinois at Urbana Champaign.
          ! (2) Shenoy, Arun. 2004. Simulation, Modeling and Analysis of Water to Air Heat Pump.
          ! State Energy Simulation Program. M.S. Thesis, Department of Mechanical and Aerospace Engineering,
          ! Oklahoma State University. (downloadable from www.hvac.okstate.edu)
          ! (3) Tang,C.C.. 2005. Modeling Packaged Heat Pumps in a Quasi-Steady
          ! State Energy Simulation Program. M.S. Thesis, Department of Mechanical and Aerospace Engineering,
          ! Oklahoma State University. (downloadable from www.hvac.okstate.edu)
          ! (4) 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), pp. 266-274.
          ! USE STATEMENTS:
  USE DataHVACGlobals,      ONLY: TimeStepSys, DXElecCoolingPower
  USE Psychrometrics,       ONLY: PsyWFnTdbTwbPb,PsyCpAirFnWTdb,PsyHFnTdbW,PsyRhoAirFnPbTdbW,  &
                                  PsyTwbFnTdbWPb,PsyTdbFnHW,PsyWFnTdbH
  USE FluidProperties,      ONLY: GetSpecificHeatGlycol
  USE DataPlant,            ONLY: PlantLoop
  IMPLICIT NONE    ! Enforce explicit typing of all variables in this routine
          ! SUBROUTINE ARGUMENT DEFINITIONS:
  INTEGER,   INTENT(IN) :: HPNum              ! Heat Pump Number
  INTEGER,   INTENT(IN) :: CyclingScheme      ! Fan/Compressor cycling scheme indicator
  REAL(r64), INTENT(IN) :: RuntimeFrac        ! Runtime Fraction of compressor or percent on time (on-time/cycle time)
  REAL(r64), INTENT(IN) :: SensDemand         ! Cooling Sensible Demand [W] !unused1208
  REAL(r64), INTENT(IN) :: LatentDemand       ! Cooling Latent Demand [W]
  INTEGER,   INTENT(IN) :: CompOp             ! compressor operation flag
  REAL(r64), INTENT(IN) :: PartLoadRatio      ! compressor part load ratio
  REAL(r64), INTENT(IN) :: OnOffAirFlowRatio  ! ratio of compressor on flow to average flow over time step
  REAL(r64), INTENT(IN) :: WaterPartLoad      ! water part load ratio
          ! SUBROUTINE PARAMETER DEFINITIONS:
  REAL(r64), PARAMETER  :: Tref=283.15d0      ! Reference Temperature for performance curves,10C [K]
  CHARACTER(len=*), PARAMETER :: RoutineName='CalcHPCoolingSimple'
          ! INTERFACE BLOCK SPECIFICATIONS
          ! na
          ! DERIVED TYPE DEFINITIONS
          ! na
          ! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
  REAL(r64) :: TotalCapRated          ! Rated Total Cooling Capacity [W]
  REAL(r64) :: SensCapRated           ! Rated Sensible Cooling Capacity [W]
  REAL(r64) :: CoolPowerRated         ! Rated Cooling Power Input[W]
  REAL(r64) :: AirVolFlowRateRated    ! Rated Air Volumetric Flow Rate [m3/s]
  REAL(r64) :: WaterVolFlowRateRated  ! Rated Water Volumetric Flow Rate [m3/s]
  REAL(r64) :: TotalCapCoeff1         ! 1st coefficient of the total cooling capacity performance curve
  REAL(r64) :: TotalCapCoeff2         ! 2nd coefficient of the total cooling capacity performance curve
  REAL(r64) :: TotalCapCoeff3         ! 3rd coefficient of the total cooling capacity performance curve
  REAL(r64) :: TotalCapCoeff4         ! 4th coefficient of the total cooling capacity performance curve
  REAL(r64) :: TotalCapCoeff5         ! 5th coefficient of the total cooling capacity performance curve
  REAL(r64) :: SensCapCoeff1          ! 1st coefficient of the sensible cooling capacity performance curve
  REAL(r64) :: SensCapCoeff2          ! 2nd coefficient of the sensible cooling capacity performance curve
  REAL(r64) :: SensCapCoeff3          ! 3rd coefficient of the sensible cooling capacity performance curve
  REAL(r64) :: SensCapCoeff4          ! 4th coefficient of the sensible cooling capacity performance curve
  REAL(r64) :: SensCapCoeff5          ! 5th coefficient of the sensible cooling capacity performance curve
  REAL(r64) :: SensCapCoeff6          ! 6th coefficient of the sensible cooling capacity performance curve
  REAL(r64) :: CoolPowerCoeff1        ! 1st coefficient of the cooling power consumption curve
  REAL(r64) :: CoolPowerCoeff2        ! 2nd coefficient of the cooling power consumption curve
  REAL(r64) :: CoolPowerCoeff3        ! 3rd coefficient of the cooling power consumption curve
  REAL(r64) :: CoolPowerCoeff4        ! 4th coefficient of the cooling power consumption curve
  REAL(r64) :: CoolPowerCoeff5        ! 5th coefficient of the cooling power consumption curve
  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) :: SHRss                  ! Sensible heat ratio at steady state
  REAL(r64) :: SHReff                 ! Effective sensible heat ratio at part-load condition
!  REAL(r64) :: PartLoadRatio          ! Part load ratio
  REAL(r64) :: ratioTDB               ! Ratio of the inlet air dry bulb temperature to the rated conditions
  REAL(r64) :: ratioTWB               ! Ratio of the inlet air wet bulb temperature to the rated conditions
  REAL(r64) :: ratioTS                ! Ratio of the source side(water) inlet temperature to the rated conditions
  REAL(r64) :: ratioVL                ! Ratio of the air flow rate to the rated conditions
  REAL(r64) :: ratioVS                ! Ratio of the water flow rate to the rated conditions
  REAL(r64) :: CpWater                ! Specific heat of water [J/kg_C]
  REAL(r64) :: CpAir                  ! Specific heat of air [J/kg_C]
  REAL(r64) :: ReportingConstant
  LOGICAL :: LatDegradModelSimFlag  ! Latent degradation model simulation flag
  INTEGER :: NumIteration           ! Iteration Counter
  INTEGER, SAVE :: Count=0          ! No idea what this is for.
  LOGICAL, SAVE    :: FirstTime = .true.
  REAL(r64), SAVE  :: LoadSideInletDBTemp_Init ! rated conditions
  REAL(r64), SAVE  :: LoadSideInletWBTemp_Init ! rated conditions
  REAL(r64), SAVE  :: LoadSideInletHumRat_Init ! rated conditions
  REAL(r64), SAVE  :: LoadSideInletEnth_Init ! rated conditions
  REAL(r64), SAVE  :: CpAir_Init                ! rated conditions
  REAL(r64)        :: LoadSideInletDBTemp_Unit ! calc conditions for unit
  REAL(r64)        :: LoadSideInletWBTemp_Unit ! calc conditions for unit
  REAL(r64)        :: LoadSideInletHumRat_Unit ! calc conditions for unit
  REAL(r64)        :: LoadSideInletEnth_Unit ! calc conditions for unit
  REAL(r64)        :: CpAir_Unit                ! calc conditions for unit
  IF (FirstTime) THEN
    !Set indoor air conditions to the rated condition
    LoadSideInletDBTemp_Init = 26.7d0
    LoadSideInletHumRat_Init = 0.0111d0
    LoadSideInletEnth_Init = PsyHFnTdbW(LoadSideInletDBTemp_Init,LoadSideInletHumRat_Init,RoutineName//':Init')
    CpAir_Init = PsyCpAirFnWTdb(LoadSideInletHumRat_Init,LoadSideInletDBTemp_Init,RoutineName//':Init')
    FirstTime=.false.
  ENDIF
  LoadSideInletWBTemp_Init = PsyTwbFnTdbWPb(LoadSideInletDBTemp_Init,LoadSideInletHumRat_Init,OutBaroPress,RoutineName)
 !  LOAD LOCAL VARIABLES FROM DATA STRUCTURE (for code readability)
  TotalCapRated          = SimpleWatertoAirHP(HPNum)%RatedCapCoolTotal
  SensCapRated           = SimpleWatertoAirHP(HPNum)%RatedCapCoolSens
  CoolPowerRated         = SimpleWatertoAirHP(HPNum)%RatedPowerCool
  AirVolFlowRateRated    = SimpleWatertoAirHP(HPNum)%RatedAirVolFlowRate
  WaterVolFlowRateRated  = SimpleWatertoAirHP(HPNum)%RatedWaterVolFlowRate
  TotalCapCoeff1         = SimpleWatertoAirHP(HPNum)%TotalCoolCap1
  TotalCapCoeff2         = SimpleWatertoAirHP(HPNum)%TotalCoolCap2
  TotalCapCoeff3         = SimpleWatertoAirHP(HPNum)%TotalCoolCap3
  TotalCapCoeff4         = SimpleWatertoAirHP(HPNum)%TotalCoolCap4
  TotalCapCoeff5         = SimpleWatertoAirHP(HPNum)%TotalCoolCap5
  SensCapCoeff1          = SimpleWatertoAirHP(HPNum)%SensCoolCap1
  SensCapCoeff2          = SimpleWatertoAirHP(HPNum)%SensCoolCap2
  SensCapCoeff3          = SimpleWatertoAirHP(HPNum)%SensCoolCap3
  SensCapCoeff4          = SimpleWatertoAirHP(HPNum)%SensCoolCap4
  SensCapCoeff5          = SimpleWatertoAirHP(HPNum)%SensCoolCap5
  SensCapCoeff6          = SimpleWatertoAirHP(HPNum)%SensCoolCap6
  CoolPowerCoeff1        = SimpleWatertoAirHP(HPNum)%CoolPower1
  CoolPowerCoeff2        = SimpleWatertoAirHP(HPNum)%CoolPower2
  CoolPowerCoeff3        = SimpleWatertoAirHP(HPNum)%CoolPower3
  CoolPowerCoeff4        = SimpleWatertoAirHP(HPNum)%CoolPower4
  CoolPowerCoeff5        = SimpleWatertoAirHP(HPNum)%CoolPower5
  Twet_rated             = SimpleWatertoAirHP(HPNum)%Twet_rated
  Gamma_rated            = SimpleWatertoAirHP(HPNum)%Gamma_rated
  LoadSideMassFlowRate   = SimpleWatertoAirHP(HPNum)%AirMassFlowRate
  SourceSideMassFlowRate = SimpleWatertoAirHP(HPNum)%WaterMassFlowRate
  SourceSideInletTemp    = SimpleWatertoAirHP(HPNum)%InletWaterTemp
  SourceSideInletEnth    = SimpleWatertoAirHP(HPNum)%InletWaterEnthalpy
  CpWater = GetSpecificHeatGlycol(PlantLoop(SimpleWatertoAirHP(HPNum)%LoopNum)%FluidName, &
                                   SourceSideInletTemp, &
                                   PlantLoop(SimpleWatertoAirHP(HPNum)%LoopNum)%FluidIndex,  &
                                  'CalcHPCoolingSimple:SourceSideInletTemp')
   !Check for flows, do not perform simulation if no flow in load side or source side.
  IF (SourceSideMassFlowRate <= 0.0d0 .OR. LoadSideMassFlowRate <= 0.0d0)THEN
     SimpleWatertoAirHP(HPNum)%SimFlag = .FALSE.
     RETURN
  ELSE
     SimpleWatertoAirHP(HPNum)%SimFlag = .TRUE.
  ENDIF
  IF (CompOp .EQ. 0) THEN
     SimpleWaterToAirHP(HPNum)%SimFlag = .FALSE.
     RETURN
  ENDIF
  !Loop the calculation at least once depending whether the latent degradation model
  !is enabled. 1st iteration to calculate the QLatent(rated) at (TDB,TWB)indoorair=(26.7C,19.4C)
  !and 2nd iteration to calculate the  QLatent(actual)
  IF((RuntimeFrac .GE. 1.0d0) .OR. (Twet_rated .LE. 0.0d0) .OR. (Gamma_rated .LE. 0.0d0)) THEN
    LatDegradModelSimFlag = .FALSE.
    !Set NumIteration=1 so that latent model would quit after 1 simulation with the actual condition
    NumIteration=1
  ELSE
    LatDegradModelSimFlag = .TRUE.
    !Set NumIteration=0 so that latent model would simulate twice with rated and actual condition
    NumIteration=0
  END IF
  !Set indoor air conditions to the actual condition
  LoadSideInletDBTemp_Unit = SimpleWatertoAirHP(HPNum)%InletAirDBTemp
  LoadSideInletHumRat_Unit = SimpleWatertoAirHP(HPNum)%InletAirHumRat
  LoadSideInletWBTemp_Unit = PsyTwbFnTdbWPb(LoadSideInletDBTemp_Unit,LoadSideInletHumRat_Unit,OutBaroPress,RoutineName)
  LoadSideInletEnth_Unit = SimpleWatertoAirHP(HPNum)%InletAirEnthalpy
  CpAir_Unit = PsyCpAirFnWTdb(LoadSideInletHumRat_Unit,LoadSideInletDBTemp_Unit)
LOOP: DO
    NumIteration=NumIteration+1
    IF (NumIteration.EQ.1) THEN
    !Set indoor air conditions to the rated conditions
        LoadSideInletDBTemp = LoadSideInletDBTemp_Init
        LoadSideInletHumRat = LoadSideInletHumRat_Init
        LoadSideInletWBTemp = LoadSideInletWBTemp_Init
        LoadSideInletEnth = LoadSideInletEnth_Init
        CpAir = CpAir_Init
    ELSE
    !Set indoor air conditions to the actual condition
        LoadSideInletDBTemp = LoadSideInletDBTemp_Unit
        LoadSideInletHumRat = LoadSideInletHumRat_Unit
        LoadSideInletWBTemp = LoadSideInletWBTemp_Unit
        LoadSideInletEnth = LoadSideInletEnth_Unit
        CpAir = CpAir_Unit
    END IF
    ratioTDB = ((LoadSideInletDBTemp+CelsiustoKelvin)/Tref)
    ratioTWB = ((LoadSideInletWBTemp+CelsiustoKelvin)/Tref)
    ratioTS = ((SourceSideInletTemp+CelsiustoKelvin)/Tref)
    ratioVL = (LoadSideMassFlowRate/(AirVolFlowRateRated*PsyRhoAirFnPbTdbW(StdBaroPress,LoadSideInletDBTemp,LoadSideInletHumRat)))
    IF (WaterPartLoad > 0.0d0 .and. SimpleWatertoAirHP(HPNum)%DesignWaterMassFlowRate > 0.0d0) THEN
      ratioVS = (SourceSideMassFlowRate)/(SimpleWatertoAirHP(HPNum)%DesignWaterMassFlowRate*WaterPartLoad)
    ELSE
      ratioVS = 0.0d0
    ENDIF
    QLoadTotal = TotalCapRated*(TotalCapCoeff1 + (ratioTWB * TotalCapCoeff2) + (ratioTS * TotalCapCoeff3) +   &
                                (ratioVL * TotalCapCoeff4) + (ratioVS * TotalCapCoeff5))
    QSensible = SensCapRated*(SensCapCoeff1 + (ratioTDB * SensCapCoeff2) + (ratioTWB * SensCapCoeff3) +   &
                                (ratioTS * SensCapCoeff4) + (ratioVL * SensCapCoeff5) + (ratioVS * SensCapCoeff6))
    Winput = CoolPowerRated*(CoolPowerCoeff1 + (ratioTWB * CoolPowerCoeff2) + (ratioTS * CoolPowerCoeff3)+   &
                                (ratioVL * CoolPowerCoeff4) + (ratioVS * CoolPowerCoeff5))
    Qsource =  QLoadTotal + Winput
  !Check if the Sensible Load is greater than the Total Cooling Load
  IF(QSensible.GT.QLoadTotal) THEN
     QSensible = QLoadTotal
  END IF
  IF(LatDegradModelSimFlag) THEN
  !Calculate for SHReff using the Latent Degradation Model
    IF(NumIteration.EQ.1) THEN
        QLatRated=QLoadTotal-QSensible
    ELSEIF(NumIteration.EQ.2) THEN
        QLatActual=QLoadTotal-QSensible
        SHRss=QSensible/QLoadTotal
        SHReff = CalcEffectiveSHR(HPNum, SHRss,CyclingScheme, RuntimeFrac, &
                 QLatRated, QLatActual, LoadSideInletDBTemp, LoadSideInletWBTemp)
!       Update sensible capacity based on effective SHR
        QSensible = QLoadTotal * SHReff
        EXIT LOOP
    END IF
  ELSE
  !Assume SHReff=SHRss
    SHReff = QSensible/QLoadTotal
    EXIT LOOP
  END IF
  END DO LOOP
  !calculate coil outlet state variables
  LoadSideOutletEnth   = LoadSideInletEnth - QLoadTotal/LoadSideMassFlowRate
  LoadSideOutletDBTemp = LoadSideInletDBTemp - QSensible/(LoadSideMassFlowRate * CpAir)
  LoadsideOutletHumRat = PsyWFnTdbH(LoadSideOutletDBTemp,LoadSideOutletEnth,RoutineName)
  Count = Count + 1
  !Actual outlet conditions are "average" for time step
  IF (CyclingScheme .EQ. ContFanCycCoil) THEN
    ! continuous fan, cycling compressor
    SimpleWatertoAirHP(HPNum)%OutletAirEnthalpy = PartLoadRatio*LoadSideOutletEnth + &
                                                  (1.0d0-PartLoadRatio)*LoadSideInletEnth
    SimpleWatertoAirHP(HPNum)%OutletAirHumRat   = PartLoadRatio*LoadsideOutletHumRat + &
                                                  (1.0d0-PartLoadRatio)*LoadSideInletHumRat
    SimpleWatertoAirHP(HPNum)%OutletAirDBTemp   = PsyTdbFnHW(SimpleWatertoAirHP(HPNum)%OutletAirEnthalpy,  &
                                                             SimpleWatertoAirHP(HPNum)%OutletAirHumRat,    &
                                                             RoutineName)
    PLRCorrLoadSideMdot = LoadSideMassFlowRate
  ELSE
    ! default to cycling fan, cycling compressor
    SimpleWatertoAirHP(HPNum)%OutletAirEnthalpy = LoadSideOutletEnth
    SimpleWatertoAirHP(HPNum)%OutletAirHumRat   = LoadsideOutletHumRat
    SimpleWatertoAirHP(HPNum)%OutletAirDBTemp   = LoadSideOutletDBTemp
    PLRCorrLoadSideMdot = LoadSideMassFlowRate*PartLoadRatio
  END IF
   ! scale heat transfer rates to PLR and power to RTF
  QLoadTotal = QLoadTotal*PartLoadRatio
  QSensible  = QSensible*PartLoadRatio
  Winput     = Winput*RuntimeFrac
  QSource    = QSource*PartLoadRatio
!  Add power to global variable so power can be summed by parent object
  DXElecCoolingPower = Winput
  ReportingConstant=TimeStepSys*SecInHour
  !Update heat pump data structure
  SimpleWatertoAirHP(HPNum)%Power               = Winput
  SimpleWatertoAirHP(HPNum)%QLoadTotal          = QLoadTotal
  SimpleWatertoAirHP(HPNum)%QSensible           = QSensible
  SimpleWatertoAirHP(HPNum)%QLatent             = QLoadTotal - QSensible
  SimpleWatertoAirHP(HPNum)%QSource             = QSource
  SimpleWatertoAirHP(HPNum)%Energy=Winput*ReportingConstant
  SimpleWatertoAirHP(HPNum)%EnergyLoadTotal=QLoadTotal*ReportingConstant
  SimpleWatertoAirHP(HPNum)%EnergySensible=QSensible*ReportingConstant
  SimpleWatertoAirHP(HPNum)%EnergyLatent=(QLoadTotal - QSensible)*ReportingConstant
  SimpleWatertoAirHP(HPNum)%EnergySource=QSource*ReportingConstant
  IF(RunTimeFrac == 0.0d0) THEN
    SimpleWatertoAirHP(HPNum)%COP = 0.0d0
  ELSE
    SimpleWatertoAirHP(HPNum)%COP = QLoadTotal/Winput
  END IF
  SimpleWatertoAirHP(HPNum)%RunFrac             = RuntimeFrac
  SimpleWatertoAirHP(HPNum)%PartLoadRatio       = PartLoadRatio
  SimpleWatertoAirHP(HPNum)%AirMassFlowRate     = PLRCorrLoadSideMdot
  SimpleWatertoAirHP(HPNum)%WaterMassFlowRate   = SourceSideMassFlowRate
  SimpleWatertoAirHP(HPNum)%OutletWaterTemp     = SourceSideInletTemp + QSource/(SourceSideMassFlowRate * CpWater)
  SimpleWatertoAirHP(HPNum)%OutletWaterEnthalpy = SourceSideInletEnth + QSource/SourceSideMassFlowRate
END SUBROUTINE CalcHPCoolingSimple