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 CalcGasAbsorberHeaterModel(ChillNum,MyLoad,Runflag)
! SUBROUTINE INFORMATION:
! AUTHOR Jason Glazer and Michael J. Witte
! DATE WRITTEN March 2001
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Simulate a direct fired (gas 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
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:
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
! Local copies of GasAbsorberSpecs 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) :: lFuelHeatRatio ! ratio of fuel input to heating output
REAL(r64) :: lElecHeatRatio ! ratio of electricity input to heating output
INTEGER :: lHeatReturnNodeNum ! absorber steam inlet node number, water side
INTEGER :: lHeatSupplyNodeNum ! absorber steam 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 :: lFuelHeatFHPLRCurve ! Fuel Input to heat output ratio during heating only function
REAL(r64) :: lFuelHeatingValue
! Local copies of GasAbsorberReportVars Type
REAL(r64) :: lHeatingLoad ! heating load on the chiller
REAL(r64) :: lHeatingEnergy ! heating energy
REAL(r64) :: lFuelUseRate ! instantaneous use of gas for period
REAL(r64) :: lFuelEnergy ! variable to track total fuel used for a period
REAL(r64) :: lCoolFuelUseRate ! instantaneous use of gas for period for cooling
REAL(r64) :: lHeatFuelUseRate ! instantaneous use of gas for period for heating
REAL(r64) :: lHeatFuelEnergy ! variable to track total fuel 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
! 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
REAL(r64) :: rhoHW ! local fluid density for hot water
! INTEGER, SAVE :: ErrCount ! error counter
!initialize all output variables to zero
lHeatingLoad = 0.0d0
lHeatingEnergy = 0.0d0
lFuelUseRate = 0.0d0
lFuelEnergy = 0.0d0
lCoolFuelUseRate = 0.0d0
lHeatFuelUseRate = 0.0d0
lHeatFuelEnergy = 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
! set node values to data structure values for nodes
lHeatReturnNodeNum = GasAbsorber(ChillNum)%HeatReturnNodeNum
lHeatSupplyNodeNum = GasAbsorber(ChillNum)%HeatSupplyNodeNum
! set local copies of data from rest of input structure
lNomCoolingCap = GasAbsorber(ChillNum)%NomCoolingCap
lNomHeatCoolRatio = GasAbsorber(ChillNum)%NomHeatCoolRatio
lFuelHeatRatio = GasAbsorber(ChillNum)%FuelHeatRatio
lElecHeatRatio = GasAbsorber(ChillNum)%ElecHeatRatio
lMinPartLoadRat = GasAbsorber(ChillNum)%MinPartLoadRat
lMaxPartLoadRat = GasAbsorber(ChillNum)%MaxPartLoadRat
lOptPartLoadRat = GasAbsorber(ChillNum)%OptPartLoadRat
lHeatCapFCoolCurve = GasAbsorber(ChillNum)%HeatCapFCoolCurve
lFuelHeatFHPLRCurve = GasAbsorber(ChillNum)%FuelHeatFHPLRCurve
lFuelHeatingValue = GasAbsorber(ChillNum)%FuelHeatingValue
lHotWaterMassFlowRateMax = Gasabsorber(chillnum)%DesHeatMassFlowRate
LoopNum = GasAbsorber(ChillNum)%HWLoopNum
LoopSideNum = GasAbsorber(ChillNum)%HWLoopSideNum
Cp_HW = GetSpecificHeatGlycol(PlantLoop(LoopNum)%FluidName, &
lHotWaterReturnTemp, &
PlantLoop(LoopNum)%FluidIndex, &
'CalcGasAbsorberHeaterModel')
rhoHW = GetDensityGlycol(PlantLoop(LoopNum)%FluidName, &
lHotWaterReturnTemp, &
PlantLoop(LoopNum)%FluidIndex, &
'CalcGasAbsorberHeaterModel')
lCoolElectricPower = GasAbsorberReport(ChillNum)%CoolElectricPower
lCoolFuelUseRate = GasAbsorberReport(ChillNum)%CoolFuelUseRate
lCoolPartLoadRatio = GasAbsorberReport(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 = GasAbsorber(ChillNum)%NomHeatCoolRatio * &
GasAbsorber(ChillNum)%NomCoolingCap * CurveValue(lHeatCapFCoolCurve, &
(GasAbsorberReport(ChillNum)%CoolingLoad / GasAbsorber(ChillNum)%NomCoolingCap))
!Calculate current load for heating
MyLoad = SIGN(MAX(ABS(MyLoad), GasAbsorberReport(ChillNum)%HeatingCapacity * lMinPartLoadRat), MyLoad)
MyLoad = SIGN(MIN(ABS(MyLoad), GasAbsorberReport(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, &
GasAbsorber(ChillNum)%HeatReturnNodeNum, &
GasAbsorber(ChillNum)%HeatSupplyNodeNum, &
GasAbsorber(ChillNum)%HWLoopNum, &
GasAbsorber(ChillNum)%HWLoopSideNum, &
GasAbsorber(ChillNum)%HWBranchNum, &
GasAbsorber(ChillNum)%HWCompNum)
ELSE
lHotWaterMassFlowRate = 0.0d0
CALL ShowRecurringWarningErrorAtEnd('GasAbsorberChillerModel:Heating"'//TRIM(GasAbsorber(ChillNum)%Name)// &
'", DeltaTemp = 0 in mass flow calculation',GasAbsorber(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
!DSU? this component model needs a lot of work, does not honor limits, incomplete ...
! MJW Not sure what to do with this now
! Must make adjustment to supply temperature since load is greater than available capacity
! this also affects the available capacity itself since it is a function of supply temperature
! Since these curves are generally fairly flat just use an estimate (done above) and correction
! approach instead of iterating to a solution.
! MJW 07MAR01 Logic seems wrong here, because of misunderstanding of what "overload" means
! "overload" means the chiller is overcooling the branch. See SUBROUTINE DistributeLoad
! IF (lChillWaterMassFlowRate > MassFlowTol) THEN
! ChillDeltaTemp = MyLoad / (CPCW(lChillReturnTemp) * lChillWaterMassFlowRate)
! lChillSupplyTemp = lChillReturnTemp - ChillDeltaTemp
! lAvailableCoolingCapacity = lNomCoolingCap * CurveValue(lCoolCapFTCurve,lChillSupplyTemp,calcCondTemp)
! ELSE
! ErrCount = ErrCount + 1
! IF (ErrCount < 10) THEN
! CALL ShowWarningError('GasAbsorberModel:lChillWaterMassFlowRate near 0 in available capacity calculation')
! END IF
! END IF
! 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 fuel consumption for cooling
! fuel used for cooling availCap * HIR * HIR-FT * HIR-FPLR
lHeatFuelUseRate = lAvailableHeatingCapacity * lFuelHeatRatio &
* CurveValue(lFuelHeatFHPLRCurve,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
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
GasAbsorberReport(ChillNum)%HeatingLoad = lHeatingLoad
GasAbsorberReport(ChillNum)%HeatFuelUseRate = lHeatFuelUseRate
GasAbsorberReport(ChillNum)%HeatElectricPower = lHeatElectricPower
GasAbsorberReport(ChillNum)%HotWaterReturnTemp = lHotWaterReturnTemp
GasAbsorberReport(ChillNum)%HotWaterSupplyTemp = lHotWaterSupplyTemp
GasAbsorberReport(ChillNum)%HotWaterFlowRate = lHotWaterMassFlowRate
GasAbsorberReport(ChillNum)%HeatPartLoadRatio = lHeatPartLoadRatio
GasAbsorberReport(ChillNum)%HeatingCapacity = lAvailableHeatingCapacity
GasAbsorberReport(ChillNum)%FractionOfPeriodRunning = lFractionOfPeriodRunning
! write the combined heating and cooling fuel used and electric used
GasAbsorberReport(ChillNum)%FuelUseRate = lCoolFuelUseRate + lHeatFuelUseRate
GasAbsorberReport(ChillNum)%ElectricPower = lCoolElectricPower + lHeatElectricPower
END SUBROUTINE CalcGasAbsorberHeaterModel