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 | :: | ChillNum | ||||
| real(kind=r64) | :: | MyLoad | ||||
| logical, | intent(in) | :: | RunFlag | 
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 CalcExhaustAbsorberHeaterModel(ChillNum,MyLoad,Runflag)
          ! SUBROUTINE INFORMATION:
          !       AUTHOR         Jason Glazer and Michael J. Witte
          !       DATE WRITTEN   March 2001
          !       MODIFIED       Mahabir Bhandari, ORNL, Aug 2011, modified to accomodate exhaust fired double effect absorption chiller
          !       RE-ENGINEERED  na
          ! PURPOSE OF THIS SUBROUTINE:
          ! Simulate a Exhaust fired (Exhaust consuming) absorption chiller using
          ! curves and inputs similar to DOE-2.1e
          ! METHODOLOGY EMPLOYED:
          ! Curve fit of performance data
          ! REFERENCES:
          ! 1.  DOE-2.1e Supplement and source code
          ! 2.  CoolTools GasMod work
          ! USE STATEMENTS:
  USE DataGlobals,     ONLY : BeginFullSimFlag
  USE DataEnvironment, ONLY : OutDryBulbTemp
  USE DataHVACGlobals, ONLY : FirstTimeStepSysFlag, TimeStepSys
  USE CurveManager,    ONLY : CurveValue
  USE DataPlant,       ONLY : PlantLoop, SingleSetpoint, DualSetpointDeadband
  USE DataBranchAirLoopPlant, ONLY: MassFlowTolerance
  USE FluidProperties, ONLY : GetSpecificHeatGlycol, GetDensityGlycol
  USE PlantUtilities,  ONLY : SetComponentFlowRate
  USE Psychrometrics, ONLY:PsyCpAirFnWTdb
  USE MicroturbineElectricGenerator, ONLY: SimMTGenerator
  IMPLICIT NONE
          ! SUBROUTINE ARGUMENT DEFINITIONS:
  INTEGER              :: ChillNum        ! Absorber number
  REAL(r64)            :: MyLoad          ! operating load
  LOGICAL, INTENT(IN)  :: RunFlag         ! TRUE when Absorber operating
! FlowLock = 0  if mass flow rates may be changed by loop components
! FlowLock = 1  if mass flow rates may not be changed by loop components
! FlowLock = 2  if overloaded and mass flow rates has changed to a small amount and Tout drops
!                 below Setpoint
          ! SUBROUTINE PARAMETER DEFINITIONS:
 REAL(r64), parameter        :: WaterMassFlowTol=0.001d0 ! kg/s - minimum significan mass flow rate
 REAL(r64), parameter        :: AbsLeavingTemp = 176.667d0     ! C - Minimum temperature leaving the Chiller absorber (350 F)
 !INTEGER    :: ExhTempLTAbsLeavingTempCount      = 0        ! Counter for exhaust temp < absorber leaving air temp warning messages
          ! INTERFACE BLOCK SPECIFICATIONS
          ! na
          ! DERIVED TYPE DEFINITIONS
          ! na
          ! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
          ! Local copies of ExhaustAbsorberSpecs Type
          ! all variables that are local copies of data structure
          ! variables are prefaced with an "l" for local.
  REAL(r64)         :: lNomCoolingCap      ! W - design nominal capacity of Absorber
  REAL(r64)         :: lNomHeatCoolRatio   ! ratio of heating to cooling capacity
  REAL(r64)         :: lThermalEnergyHeatRatio      ! ratio of ThermalEnergy input to heating output
  REAL(r64)         :: lElecHeatRatio      ! ratio of electricity input to heating output
  INTEGER           :: lHeatReturnNodeNum  ! absorber hot water inlet node number, water side
  INTEGER           :: lHeatSupplyNodeNum  ! absorber hot water outlet node number, water side
  REAL(r64)         :: lMinPartLoadRat     ! min allowed operating frac full load
  REAL(r64)         :: lMaxPartLoadRat     ! max allowed operating frac full load
  REAL(r64)         :: lOptPartLoadRat     ! optimal operating frac full load
  INTEGER           :: lHeatCapFCoolCurve  ! Heating Capacity Function of Cooling Capacity Curve
  INTEGER           :: lThermalEnergyHeatFHPLRCurve ! ThermalEnergy Input to heat output ratio during heating only function
  ! Local copies of ExhaustAbsorberReportVars Type
  REAL(r64)    :: lHeatingLoad        ! heating load on the chiller
  REAL(r64)    :: lHeatingEnergy      ! heating energy
  REAL(r64)    :: lThermalEnergyUseRate        ! instantaneous use of Thermal Energy for period
  REAL(r64)    :: lThermalEnergy         ! variable to track total Thermal Energy used for a period (reference only)
  REAL(r64)    :: lCoolThermalEnergyUseRate    ! instantaneous use of thermal energy for period for cooling
  REAL(r64)    :: lHeatThermalEnergyUseRate    ! instantaneous use of thermal energy for period for heating
  REAL(r64)    :: lHeatThermalEnergy     ! variable to track total ThermalEnergy used for a period for heating
  REAL(r64)    :: lElectricPower      ! parasitic electric power used (was PumpingPower)
  REAL(r64)    :: lElectricEnergy     ! track the total electricity used for a period (was PumpingEnergy)
  REAL(r64)    :: lCoolElectricPower  ! parasitic electric power used  for cooling
  REAL(r64)    :: lHeatElectricPower  ! parasitic electric power used  for heating
  REAL(r64)    :: lHeatElectricEnergy ! track the total electricity used for a period for heating
  REAL(r64)    :: lHotWaterReturnTemp ! reporting: hot water return (inlet) temperature
  REAL(r64)    :: lHotWaterSupplyTemp ! reporting: hot water supply (outlet) temperature
  REAL(r64)    :: lHotWaterMassFlowRate   ! reporting: hot water mass flow rate
  REAL(r64)    :: lCoolPartLoadRatio      ! operating part load ratio (load/capacity for cooling)
  REAL(r64)    :: lHeatPartLoadRatio      ! operating part load ratio (load/capacity for heating)
  REAL(r64)    :: lAvailableHeatingCapacity    ! current heating capacity
  REAL(r64)    :: lFractionOfPeriodRunning
  Real(r64)    :: lHotWaterMassFlowRateMax  ! Maximum flow rate through the evaporator
  Real(r64)    :: lExhaustInTemp   ! Exhaust inlet temperature
  Real(r64)    :: lExhaustInFlow   ! Exhaust inlet flow rate
  Real(r64)    :: lExhHeatRecPotentialHeat   ! Exhaust heat recovery potential
  Real(r64)    ::  lExhaustAirHumRat
  ! other local variables
  REAL(r64)              :: HeatDeltaTemp       ! hot water temperature difference
  REAL(r64)              :: HeatSupplySetPointTemp
  INTEGER      :: LoopNum
  INTEGER      :: LoopSideNum
  REAL(r64)    :: Cp_HW  ! local fluid specific heat for hot water
  INTEGER  :: GeneratorType
  INTEGER :: GenIndex1
  REAL(r64)       ::CpAir
  REAL(r64)    :: rhoHW  ! local fluid density for hot water
  INTEGER      :: lExhaustAirInletNodeNum       ! Combustion Air Inlet Node number
  CHARACTER(len=MaxNameLength) :: GeneratorName
!  INTEGER      :: lExhaustAirOutletNodeNum      ! Combustion Air Outlet (Exhaust) Node number
  !initialize all output variables to zero
  lHeatingLoad        = 0.0d0
  lHeatingEnergy      = 0.0d0
  lThermalEnergyUseRate        = 0.0d0
  lThermalEnergy         = 0.0d0
  lCoolThermalEnergyUseRate    = 0.0d0
  lHeatThermalEnergyUseRate    = 0.0d0
  lHeatThermalEnergy     = 0.0d0
  lElectricPower      = 0.0d0
  lElectricEnergy     = 0.0d0
  lCoolElectricPower  = 0.0d0
  lHeatElectricPower  = 0.0d0
  lHeatElectricEnergy = 0.0d0
  lHotWaterReturnTemp = 0.0d0
  lHotWaterSupplyTemp = 0.0d0
  lHotWaterMassFlowRate   = 0.0d0
  lCoolPartLoadRatio      = 0.0d0
  lHeatPartLoadRatio      = 0.0d0
  lAvailableHeatingCapacity    = 0.0d0
  lFractionOfPeriodRunning = 0.0d0
  lExhaustInTemp  = 0.0d0
   lExhaustInFlow  = 0.0d0
  lExhHeatRecPotentialHeat = 0.0d0
  lExhaustAirHumRat =0.0d0
  ! set node values to data structure values for nodes
  lHeatReturnNodeNum  = ExhaustAbsorber(ChillNum)%HeatReturnNodeNum
  lHeatSupplyNodeNum  = ExhaustAbsorber(ChillNum)%HeatSupplyNodeNum
  lExhaustAirInletNodeNum   = ExhaustAbsorber(ChillNum)%ExhaustAirInletNodeNum
  ! set local copies of data from rest of input structure
  lNomCoolingCap      = ExhaustAbsorber(ChillNum)%NomCoolingCap
  lNomHeatCoolRatio   = ExhaustAbsorber(ChillNum)%NomHeatCoolRatio
  lThermalEnergyHeatRatio      = ExhaustAbsorber(ChillNum)%ThermalEnergyHeatRatio
  lElecHeatRatio      = ExhaustAbsorber(ChillNum)%ElecHeatRatio
  lMinPartLoadRat     = ExhaustAbsorber(ChillNum)%MinPartLoadRat
  lMaxPartLoadRat     = ExhaustAbsorber(ChillNum)%MaxPartLoadRat
  lOptPartLoadRat     = ExhaustAbsorber(ChillNum)%OptPartLoadRat
  lHeatCapFCoolCurve  = ExhaustAbsorber(ChillNum)%HeatCapFCoolCurve
  lThermalEnergyHeatFHPLRCurve = ExhaustAbsorber(ChillNum)%ThermalEnergyHeatFHPLRCurve
  lHotWaterMassFlowRateMax = Exhaustabsorber(chillnum)%DesHeatMassFlowRate
  LoopNum             = ExhaustAbsorber(ChillNum)%HWLoopNum
  LoopSideNum         = ExhaustAbsorber(ChillNum)%HWLoopSideNum
  Cp_HW               = GetSpecificHeatGlycol(PlantLoop(LoopNum)%FluidName, &
                                               lHotWaterReturnTemp, &
                                               PlantLoop(LoopNum)%FluidIndex, &
                                               'CalcExhaustAbsorberHeaterModel')
  rhoHW               = GetDensityGlycol(PlantLoop(LoopNum)%FluidName, &
                                               lHotWaterReturnTemp, &
                                               PlantLoop(LoopNum)%FluidIndex, &
                                               'CalcExhaustAbsorberHeaterModel')
  lCoolElectricPower  = ExhaustAbsorberReport(ChillNum)%CoolElectricPower
  lCoolThermalEnergyUseRate    = ExhaustAbsorberReport(ChillNum)%CoolThermalEnergyUseRate
  lCoolPartLoadRatio  = ExhaustAbsorberReport(ChillNum)%CoolPartLoadRatio
! initialize entering conditions
  lHotWaterReturnTemp  = Node(lHeatReturnNodeNum)%Temp
  lHotWaterMassFlowRate  = Node(lHeatReturnNodeNum)%MassFlowRate
  SELECT CASE (PlantLoop(LoopNum)%LoopDemandCalcScheme)
  CASE (SingleSetpoint)
    HeatSupplySetPointTemp = Node(lHeatSupplyNodeNum)%TempSetPoint
  CASE (DualSetpointDeadband)
    HeatSupplySetPointTemp = Node(lHeatSupplyNodeNum)%TempSetPointLo
  END SELECT
  HeatDeltaTemp  = ABS(lHotWaterReturnTemp - HeatSupplySetPointTemp)
          !If no loop demand or Absorber OFF, return
          ! will need to modify when absorber can act as a boiler
 IF (MyLoad<=0 .OR. .NOT. Runflag) THEN
          !set node temperatures
    lHotWaterSupplyTemp = lHotWaterReturnTemp
    HeatDeltaTemp = 0.0d0
    lFractionOfPeriodRunning = MIN(1.0d0,MAX(lHeatPartLoadRatio,lCoolPartLoadRatio)/lMinPartLoadRat)
 ELSE
            !Determine available heating capacity using the current cooling load
         lAvailableHeatingCapacity = ExhaustAbsorber(ChillNum)%NomHeatCoolRatio * &
           ExhaustAbsorber(ChillNum)%NomCoolingCap * CurveValue(lHeatCapFCoolCurve, &
           (ExhaustAbsorberReport(ChillNum)%CoolingLoad / ExhaustAbsorber(ChillNum)%NomCoolingCap))
            !Calculate current load for heating
  MyLoad = SIGN(MAX(ABS(MyLoad), ExhaustAbsorberReport(ChillNum)%HeatingCapacity * lMinPartLoadRat), MyLoad)
  MyLoad = SIGN(MIN(ABS(MyLoad), ExhaustAbsorberReport(ChillNum)%HeatingCapacity * lMaxPartLoadRat), MyLoad)
            ! Determine the following variables depending on if the flow has been set in
            ! the nodes (flowlock=1 to 2) or if the amount of load is still be determined (flowlock=0)
            !    chilled water flow,
            !    cooling load taken by the chiller, and
            !    supply temperature
  SELECT CASE (PlantLoop(LoopNum)%Loopside(LoopSideNum)%FlowLock)
    CASE (0) ! mass flow rates may be changed by loop components
        lHeatingLoad = ABS(MyLoad)
      IF (HeatDeltaTemp /= 0) THEN
        lHotWaterMassFlowRate = ABS(lHeatingLoad / (Cp_HW * HeatDeltaTemp))
        CALL SetComponentFlowRate(lHotWaterMassFlowRate, &
                              ExhaustAbsorber(ChillNum)%HeatReturnNodeNum, &
                              ExhaustAbsorber(ChillNum)%HeatSupplyNodeNum, &
                              ExhaustAbsorber(ChillNum)%HWLoopNum, &
                              ExhaustAbsorber(ChillNum)%HWLoopSideNum, &
                              ExhaustAbsorber(ChillNum)%HWBranchNum, &
                              ExhaustAbsorber(ChillNum)%HWCompNum)
      ELSE
        lHotWaterMassFlowRate = 0.0d0
        CALL ShowRecurringWarningErrorAtEnd('ExhaustAbsorberChillerModel:Heating"'//TRIM(ExhaustAbsorber(ChillNum)%Name)//  &
             '", DeltaTemp = 0 in mass flow calculation',ExhaustAbsorber(ChillNum)%DeltaTempHeatErrCount)
      END IF
      lHotWaterSupplyTemp = HeatSupplySetPointTemp
    CASE (1) ! mass flow rates may not be changed by loop components
      lHotWaterSupplyTemp = HeatSupplySetPointTemp
      lHeatingLoad = ABS(lHotWaterMassFlowRate * Cp_HW * HeatDeltaTemp)
!DSU this "2" is not a real state for flowLock
    CASE (2) ! chiller is underloaded and mass flow rates has changed to a small amount and Tout drops below Setpoint
! MJW 07MAR01 Borrow logic from steam absorption module
            ! The following conditional statements are made to avoid extremely small EvapMdot
            ! & unreasonable EvapOutletTemp due to overloading.
                ! Avoid 'divide by zero' due to small EvapMdot
      IF(lHotWaterMassFlowRate < MassFlowTolerance) THEN
        HeatDeltaTemp = 0.0d0
      ELSE
        HeatDeltaTemp = ABS(MyLoad) / (Cp_HW * lHotWaterMassFlowRate)
      END IF
      lHotWaterSupplyTemp = lHotWaterReturnTemp + HeatDeltaTemp
      lHeatingLoad = ABS(lHotWaterMassFlowRate * Cp_HW * HeatDeltaTemp)
  END SELECT
            !Calculate operating part load ratio for cooling
  lHeatPartLoadRatio = lHeatingLoad / lAvailableHeatingCapacity
            !Calculate ThermalEnergy consumption for heating
            ! ThermalEnergy used for heating availCap * HIR * HIR-FT * HIR-FPLR
  lHeatThermalEnergyUseRate = lAvailableHeatingCapacity * lThermalEnergyHeatRatio  &
     * CurveValue(lThermalEnergyHeatFHPLRCurve,lHeatPartLoadRatio)
            ! calculate the fraction of the time period that the chiller would be running
            ! use maximum from heating and cooling sides
  lFractionOfPeriodRunning = MIN(1.0d0,MAX(lHeatPartLoadRatio,lCoolPartLoadRatio)/lMinPartLoadRat)
            !Calculate electric parasitics used
            ! for heating based on nominal capacity not available capacity
  lHeatElectricPower = lNomCoolingCap * lNomHeatCoolRatio * lElecHeatRatio * lFractionOfPeriodRunning
            ! Coodinate electric parasitics for heating and cooling to avoid double counting
            ! Total electric is the max of heating electric or cooling electric
            ! If heating electric is greater, leave cooling electric and subtract if off of heating elec
            ! If cooling electric is greater, set heating electric to zero
  lExhaustInTemp  = Node(lExhaustAirInletNodeNum)%Temp
  lExhaustInFlow  = Node(lExhaustAirInletNodeNum)%MassFlowRate
  CpAir = PsyCpAirFnWTdb(lExhaustAirHumRat,lExhaustInTemp)
  lExhHeatRecPotentialHeat =  lExhaustInFlow  * Cpair * (  lExhaustInTemp  - AbsLeavingTemp )
    IF (lExhHeatRecPotentialHeat .LT. lHeatThermalEnergyUseRate ) THEN
      IF(ExhaustAbsorber(ChillNum)%ExhTempLTAbsLeavingHeatingTempIndex  == 0)THEN
        CALL ShowWarningError('ChillerHeater:Absorption:DoubleEffect "'//TRIM(ExhaustAbsorber(ChillNum)%Name)//'"')
        CALL ShowContinueError('...Exhaust temperature and flow input from Micro Turbine is not sufficient '&
                          //'to run the chiller during heating .')
        CALL ShowContinueError('...Value of Exhaust air inlet temp ='//TRIM(TrimSigDigits(lExhaustInTemp,4))//' C.')
        CALL ShowContinueError('... and Exhaust air flow rate of '//TRIM(TrimSigDigits(lExhaustInFlow,2))//' kg/s.')
        CALL ShowContinueError('...Value of minimum absorber leaving temp ='//TRIM(TrimSigDigits(AbsLeavingTemp,4))//' C.')
        CALL ShowContinueError('...Either increase the Exhaust temperature (min required = 350 C  )  '&
                          //'or flow or both of Micro Turbine to meet the min available potential criteria.')
        CALL ShowContinueErrorTimeStamp('... Simulation will continue.')
      ENDIF
      CALL ShowRecurringWarningErrorAtEnd('ChillerHeater:Absorption:DoubleEffect "'//  &
           TRIM(ExhaustAbsorber(ChillNum)%Name)//'":'// &
           ' Exhaust temperature from Micro Turbine is not sufficient to run the chiller during '//  &
             'heating warning continues...', &
           ExhaustAbsorber(ChillNum)%ExhTempLTAbsLeavingHeatingTempIndex,  lExhaustInTemp, AbsLeavingTemp)
! If exhaust is not available, it means the avilable thermal energy is 0.0 and Chiller is not available
   lHeatThermalEnergyUseRate = 0.0d0
   lHeatElectricPower =0.0d0
    lHotWaterSupplyTemp = lHotWaterReturnTemp
    HeatDeltaTemp = 0.0d0
    lFractionOfPeriodRunning = MIN(1.0d0,MAX(lHeatPartLoadRatio,lCoolPartLoadRatio)/lMinPartLoadRat)
   END IF
  IF (lHeatElectricPower .LE. lCoolElectricPower) THEN
    lHeatElectricPower = 0.0d0
  ELSE
    lHeatElectricPower = lHeatElectricPower - lCoolElectricPower
  ENDIF
 ENDIF ! IF(MyLoad==0 .OR. .NOT. Runflag)
  ! Write into the Report Variables except for nodes
  ExhaustAbsorberReport(ChillNum)%HeatingLoad             = lHeatingLoad
  ExhaustAbsorberReport(ChillNum)%HeatThermalEnergyUseRate = lHeatThermalEnergyUseRate
  ExhaustAbsorberReport(ChillNum)%HeatElectricPower        = lHeatElectricPower
  ExhaustAbsorberReport(ChillNum)%HotWaterReturnTemp       = lHotWaterReturnTemp
  ExhaustAbsorberReport(ChillNum)%HotWaterSupplyTemp       = lHotWaterSupplyTemp
  ExhaustAbsorberReport(ChillNum)%HotWaterFlowRate         = lHotWaterMassFlowRate
  ExhaustAbsorberReport(ChillNum)%HeatPartLoadRatio        = lHeatPartLoadRatio
  ExhaustAbsorberReport(ChillNum)%HeatingCapacity          = lAvailableHeatingCapacity
  ExhaustAbsorberReport(ChillNum)%FractionOfPeriodRunning  = lFractionOfPeriodRunning
  ! write the combined heating and cooling ThermalEnergy used and electric used
  ExhaustAbsorberReport(ChillNum)%ThermalEnergyUseRate     = lCoolThermalEnergyUseRate + lHeatThermalEnergyUseRate
  ExhaustAbsorberReport(ChillNum)%ElectricPower            = lCoolElectricPower + lHeatElectricPower
  ExhaustAbsorberReport(ChillNum)%ExhaustInTemp            = lExhaustInTemp
  ExhaustAbsorberReport(ChillNum)%ExhaustInFlow            = lExhaustInFlow
  ExhaustAbsorberReport(ChillNum)%ExhHeatRecPotentialHeat  = lExhHeatRecPotentialHeat
END SUBROUTINE CalcExhaustAbsorberHeaterModel