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 CalcGasAbsorberChillerModel(ChillNum,MyLoad,Runflag)
! SUBROUTINE INFORMATION:
! AUTHOR Jason Glazer
! 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 DataHVACGlobals, ONLY : FirstTimeStepSysFlag, TimeStepSys
USE CurveManager, ONLY : CurveValue
USE DataPlant, ONLY : DeltaTemptol, PlantLoop, SingleSetpoint, DualSetpointDeadband
USE DataBranchAirLoopPlant, ONLY : MassFlowTolerance
USE FluidProperties, ONLY : GetDensityGlycol, GetSpecificHeatGlycol
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
! 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) :: lFuelCoolRatio ! ratio of fuel input to cooling output
REAL(r64) :: lFuelHeatRatio ! ratio of fuel input to heating output
REAL(r64) :: lElecCoolRatio ! ratio of electricity input to cooling output
INTEGER :: lChillReturnNodeNum ! Node number on the inlet side of the plant
INTEGER :: lChillSupplyNodeNum ! Node number on the outlet side of the plant
INTEGER :: lCondReturnNodeNum ! Node number on the inlet side of the condenser
INTEGER :: lCondSupplyNodeNum ! Node number on the outlet side of the condenser
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
REAL(r64) :: lTempDesCondReturn ! design secondary loop fluid temperature at the Absorber condenser side inlet
REAL(r64) :: lTempDesCHWSupply ! design chilled water supply temperature
REAL(r64) :: lCondVolFlowRate ! m**3/s - design nominal water volumetric flow rate through the condenser
INTEGER :: lCoolCapFTCurve ! cooling capacity as a function of temperature curve
INTEGER :: lFuelCoolFTCurve ! Fuel-Input-to cooling output Ratio Function of Temperature Curve
INTEGER :: lFuelCoolFPLRCurve ! Fuel-Input-to cooling output Ratio Function of Part Load Ratio Curve
INTEGER :: lElecCoolFTCurve ! Electric-Input-to cooling output Ratio Function of Temperature Curve
INTEGER :: lElecCoolFPLRCurve ! Electric-Input-to cooling output Ratio Function of Part Load Ratio Curve
LOGICAL :: lIsEnterCondensTemp ! if using entering conderser water temperature is TRUE, exiting is FALSE
LOGICAL :: lIsWaterCooled ! if water cooled it is TRUE
REAL(r64) :: lCHWLowLimitTemp ! Chilled Water Lower Limit Temperature
REAL(r64) :: lFuelHeatingValue
! Local copies of GasAbsorberReportVars Type
REAL(r64) :: lCoolingLoad ! cooling load on the chiller (previously called QEvap)
REAL(r64) :: lCoolingEnergy ! variable to track total cooling load for period (was EvapEnergy)
REAL(r64) :: lTowerLoad ! load on the cooling tower/condenser (previously called QCond)
REAL(r64) :: lTowerEnergy ! variable to track total tower load for a period (was CondEnergy)
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) :: lCoolFuelEnergy ! variable to track total fuel used for a period for cooling
REAL(r64) :: lHeatFuelUseRate ! instantaneous use of gas for 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) :: lCoolElectricEnergy ! track the total electricity used for a period for cooling
REAL(r64) :: lHeatElectricPower ! parasitic electric power used for heating
REAL(r64) :: lChillReturnTemp ! reporting: evaporator inlet temperature (was EvapInletTemp)
REAL(r64) :: lChillSupplyTemp ! reporting: evaporator outlet temperature (was EvapOutletTemp)
REAL(r64) :: lChillWaterMassFlowRate ! reporting: evaporator mass flow rate (was Evapmdot)
REAL(r64) :: lCondReturnTemp ! reporting: condenser inlet temperature (was CondInletTemp)
REAL(r64) :: lCondSupplyTemp ! reporting: condenser outlet temperature (was CondOutletTemp)
REAL(r64) :: lCondWaterMassFlowRate ! reporting: condenser mass flow rate (was Condmdot)
REAL(r64) :: lCoolPartLoadRatio ! operating part load ratio (load/capacity for cooling)
REAL(r64) :: lHeatPartLoadRatio ! operating part load ratio (load/capacity for heating)
REAL(r64) :: lAvailableCoolingCapacity ! current capacity after temperature adjustment
REAL(r64) :: lFractionOfPeriodRunning
REAL(r64) :: Partloadrat ! actual operating part load ratio of unit (ranges from minplr to 1)
Real(r64) :: lChillWaterMassflowratemax ! Maximum flow rate through the evaporator
! other local variables
REAL(r64) :: ChillDeltaTemp ! chilled water temperature difference
REAL(r64) :: ChillSupplySetPointTemp
REAL(r64) :: calcCondTemp ! the condenser temperature used for curve calculation
! either return or supply depending on user input
REAL(r64), SAVE :: oldCondSupplyTemp = 0.0d0 ! save the last iteration value of leaving condenser water temperature
REAL(r64) :: revisedEstimateAvailCap ! final estimate of available capacity if using leaving
! condenser water temperature
REAL(r64) :: errorAvailCap ! error fraction on final estimate of AvailableCoolingCapacity
INTEGER :: LoopNum
INTEGER :: LoopSideNum
REAL(r64) :: rhoCW ! local fluid density for chilled water
REAL(r64) :: Cp_CW ! local fluid specific heat for chilled water
REAL(r64) :: rhoCD ! local fluid density for condenser water
REAL(r64) :: Cp_CD ! local fluid specific heat for condenser water
!initialize all output variables to zero
lCoolingLoad = 0.0d0
lCoolingEnergy = 0.0d0
lTowerLoad = 0.0d0
lTowerEnergy = 0.0d0
lFuelUseRate = 0.0d0
lFuelEnergy = 0.0d0
lCoolFuelUseRate = 0.0d0
lCoolFuelEnergy = 0.0d0
lHeatFuelUseRate = 0.0d0
lElectricPower = 0.0d0
lElectricEnergy = 0.0d0
lCoolElectricPower = 0.0d0
lCoolElectricEnergy = 0.0d0
lHeatElectricPower = 0.0d0
lChillReturnTemp = 0.0d0
lChillSupplyTemp = 0.0d0
lChillWaterMassFlowRate = 0.0d0
lCondReturnTemp = 0.0d0
lCondSupplyTemp = 0.0d0
lCondWaterMassFlowRate = 0.0d0
lCoolPartLoadRatio = 0.0d0
lHeatPartLoadRatio = 0.0d0
lAvailableCoolingCapacity = 0.0d0
lFractionOfPeriodRunning = 0.0d0
PartloadRat = 0.0d0
! set node values to data structure values for nodes
lChillReturnNodeNum = GasAbsorber(ChillNum)%ChillReturnNodeNum
lChillSupplyNodeNum = GasAbsorber(ChillNum)%ChillSupplyNodeNum
lCondReturnNodeNum = GasAbsorber(ChillNum)%CondReturnNodeNum
lCondSupplyNodeNum = GasAbsorber(ChillNum)%CondSupplyNodeNum
! set local copies of data from rest of input structure
lNomCoolingCap = GasAbsorber(ChillNum)%NomCoolingCap
lFuelCoolRatio = GasAbsorber(ChillNum)%FuelCoolRatio
lFuelHeatRatio = GasAbsorber(ChillNum)%FuelHeatRatio
lElecCoolRatio = GasAbsorber(ChillNum)%ElecCoolRatio
lMinPartLoadRat = GasAbsorber(ChillNum)%MinPartLoadRat
lMaxPartLoadRat = GasAbsorber(ChillNum)%MaxPartLoadRat
lOptPartLoadRat = GasAbsorber(ChillNum)%OptPartLoadRat
lTempDesCondReturn = GasAbsorber(ChillNum)%TempDesCondReturn
lTempDesCHWSupply = GasAbsorber(ChillNum)%TempDesCHWSupply
lCondVolFlowRate = GasAbsorber(ChillNum)%CondVolFlowRate
lCoolCapFTCurve = GasAbsorber(ChillNum)%CoolCapFTCurve
lFuelCoolFTCurve = GasAbsorber(ChillNum)%FuelCoolFTCurve
lFuelCoolFPLRCurve = GasAbsorber(ChillNum)%FuelCoolFPLRCurve
lElecCoolFTCurve = GasAbsorber(ChillNum)%ElecCoolFTCurve
lElecCoolFPLRCurve = GasAbsorber(ChillNum)%ElecCoolFPLRCurve
lisEnterCondensTemp = GasAbsorber(ChillNum)%isEnterCondensTemp
lisWaterCooled = GasAbsorber(ChillNum)%isWaterCooled
lCHWLowLimitTemp = GasAbsorber(ChillNum)%CHWLowLimitTemp
lFuelHeatingValue = GasAbsorber(ChillNum)%FuelHeatingValue
lHeatElectricPower = GasAbsorberReport(ChillNum)%HeatElectricPower
lHeatFuelUseRate = GasAbsorberReport(ChillNum)%HeatFuelUseRate
lHeatPartLoadRatio = GasAbsorberReport(ChillNum)%HeatPartLoadRatio
! initialize entering conditions
lChillReturnTemp = Node(lChillReturnNodeNum)%Temp
lChillWaterMassFlowRate = Node(lChillReturnNodeNum)%MassFlowRate
lCondReturnTemp = Node(lCondReturnNodeNum)%Temp
lCondWaterMassFlowRate = Node(lCondReturnNodeNum)%MassFlowRate
SELECT CASE (PlantLoop(GasAbsorber(ChillNum)%CWLoopNum)%LoopDemandCalcScheme)
CASE (SingleSetpoint)
ChillSupplySetPointTemp = Node(lChillSupplyNodeNum)%TempSetPoint
CASE (DualSetpointDeadband)
ChillSupplySetPointTemp = Node(lChillSupplyNodeNum)%TempSetPointHi
END SELECT
ChillDeltaTemp = ABS(lChillReturnTemp - ChillSupplySetPointTemp)
rhoCW = GetDensityGlycol(PlantLoop(GasAbsorber(ChillNum)%CWLoopNum)%FluidName, &
lChillReturnTemp, &
PlantLoop(GasAbsorber(ChillNum)%CWLoopNum)%FluidIndex, &
'CalcGasAbsorberChillerModel')
Cp_CW = GetSpecificHeatGlycol(PlantLoop(GasAbsorber(ChillNum)%CWLoopNum)%FluidName, &
lChillReturnTemp, &
PlantLoop(GasAbsorber(ChillNum)%CWLoopNum)%FluidIndex, &
'CalcGasAbsorberChillerModel')
rhoCD = GetDensityGlycol(PlantLoop(GasAbsorber(ChillNum)%CDLoopNum)%FluidName, &
lChillReturnTemp, &
PlantLoop(GasAbsorber(ChillNum)%CDLoopNum)%FluidIndex, &
'CalcGasAbsorberChillerModel')
Cp_CD = GetSpecificHeatGlycol(PlantLoop(GasAbsorber(ChillNum)%CDLoopNum)%FluidName, &
lChillReturnTemp, &
PlantLoop(GasAbsorber(ChillNum)%CDLoopNum)%FluidIndex, &
'CalcGasAbsorberChillerModel')
!If no loop demand or Absorber OFF, return
! will need to modify when absorber can act as a boiler
IF (MyLoad>=0 .OR. .NOT. ((GasAbsorber(ChillNum)%InHeatingMode) .OR. (GasAbsorber(ChillNum)%InCoolingMode))) THEN
!set node temperatures
lChillSupplyTemp = lChillReturnTemp
lCondSupplyTemp = lCondReturnTemp
lCondWaterMassFlowRate = 0.0d0
IF (lisWaterCooled) THEN
CALL SetComponentFlowRate(lCondWaterMassFlowRate, &
GasAbsorber(ChillNum)%CondReturnNodeNum, &
GasAbsorber(ChillNum)%CondSupplyNodeNum, &
GasAbsorber(ChillNum)%CDLoopNum, &
GasAbsorber(ChillNum)%CDLoopSideNum, &
GasAbsorber(ChillNum)%CDBranchNum, &
GasAbsorber(ChillNum)%CDCompNum)
ENDIF
ChillDeltaTemp = 0.0d0
lFractionOfPeriodRunning = MIN(1.0d0,MAX(lHeatPartLoadRatio,lCoolPartLoadRatio)/lMinPartLoadRat)
ELSE
! if water cooled use the input node otherwise just use outside air temperature
IF (lIsWaterCooled) THEN
! most manufacturers rate have tables of entering condenser water temperature
! but a few use leaving condenser water temperature so we have a flag
! when leaving is used it uses the previous iterations value of the value
lCondReturnTemp = Node(lCondReturnNodeNum)%Temp
IF (lIsEnterCondensTemp) THEN
calcCondTemp = lCondReturnTemp
ELSE
IF (oldCondSupplyTemp == 0) THEN
oldCondSupplyTemp = lCondReturnTemp + 8.0d0 ! if not previously estimated assume 8C greater than return
END IF
calcCondTemp = oldCondSupplyTemp
END IF
!Set mass flow rates
lCondWaterMassFlowRate = GasAbsorber(ChillNum)%DesCondMassFlowRate
CALL SetComponentFlowRate(lCondWaterMassFlowRate, &
GasAbsorber(ChillNum)%CondReturnNodeNum, &
GasAbsorber(ChillNum)%CondSupplyNodeNum, &
GasAbsorber(ChillNum)%CDLoopNum, &
GasAbsorber(ChillNum)%CDLoopSideNum, &
GasAbsorber(ChillNum)%CDBranchNum, &
GasAbsorber(ChillNum)%CDCompNum)
ELSE
! air cooled
Node(lCondReturnNodeNum)%Temp=Node(lCondReturnNodeNum)%OutAirDryBulb
lCondReturnTemp = Node(lCondReturnNodeNum)%Temp
lCondWaterMassFlowRate = 0.d0
CALL SetComponentFlowRate(lCondWaterMassFlowRate, &
GasAbsorber(ChillNum)%CondReturnNodeNum, &
GasAbsorber(ChillNum)%CondSupplyNodeNum, &
GasAbsorber(ChillNum)%CDLoopNum, &
GasAbsorber(ChillNum)%CDLoopSideNum, &
GasAbsorber(ChillNum)%CDBranchNum, &
GasAbsorber(ChillNum)%CDCompNum)
END IF
!Determine available cooling capacity using the setpoint temperature
lAvailableCoolingCapacity = lNomCoolingCap * CurveValue(lCoolCapFTCurve,ChillSupplySetPointTemp,calcCondTemp)
!Calculate current load for cooling
MyLoad = SIGN(MAX(ABS(MyLoad), lAvailableCoolingCapacity * lMinPartLoadRat), MyLoad )
MyLoad = SIGN(MIN(ABS(MyLoad), lAvailableCoolingCapacity * 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
lChillWaterMassflowratemax = Gasabsorber(chillnum)%DesEvapMassFlowRate
LoopNum = GasAbsorber(ChillNum)%CWLoopNum
LoopSideNum = GasAbsorber(ChillNum)%CWLoopSideNum
SELECT CASE (PlantLoop(LoopNum)%Loopside(LoopSideNum)%FlowLock)
CASE (0) ! mass flow rates may be changed by loop components
GasAbsorber(ChillNum)%Possiblesubcooling = .FALSE.
lCoolingLoad = ABS(myLoad)
IF (ChillDeltaTemp /= 0.0d0) THEN
lChillWaterMassFlowRate = ABS(lCoolingLoad / (Cp_CW * ChillDeltaTemp))
If(lChillWaterMassFlowRate -lChillWaterMassflowratemax.GT.MassFlowTolerance) &
GasAbsorber(ChillNum)%Possiblesubcooling = .TRUE.
CALL SetComponentFlowRate(lChillWaterMassFlowRate, &
GasAbsorber(ChillNum)%ChillReturnNodeNum, &
GasAbsorber(ChillNum)%ChillSupplyNodeNum, &
GasAbsorber(ChillNum)%CWLoopNum, &
GasAbsorber(ChillNum)%CWLoopSideNum, &
GasAbsorber(ChillNum)%CWBranchNum, &
GasAbsorber(ChillNum)%CWCompNum)
lChillSupplyTemp = ChillSupplySetPointTemp
ELSE
lChillWaterMassFlowRate = 0.0d0
CALL ShowRecurringWarningErrorAtEnd('GasAbsorberChillerModel:Cooling"'//TRIM(GasAbsorber(ChillNum)%Name)// &
'", DeltaTemp = 0 in mass flow calculation',GasAbsorber(ChillNum)%DeltaTempCoolErrCount)
END IF
lChillSupplyTemp = ChillSupplySetPointTemp
CASE (1) ! mass flow rates may not be changed by loop components
lChillWatermassflowrate = Node(lChillreturnnodenum)%Massflowrate
If (GasAbsorber(ChillNum)%Possiblesubcooling) then
lCoolingload = ABS(myload)
ChillDeltaTemp = lCoolingload/lChillWatermassflowrate/Cp_CW
lChillSupplyTemp = Node(lChillReturnnodenum)%Temp - ChillDeltaTemp
ELSE
ChillDeltaTemp = Node(lChillReturnnodenum)%Temp - ChillSupplySetPointTemp
lCoolingload = ABS(lChillWatermassflowrate*Cp_CW*ChillDeltaTemp)
lChillSupplyTemp = ChillSupplySetPointTemp
END IF
!Check that the Chiller Supply outlet temp honors both plant loop temp low limit and also the chiller low limit
IF(lChillSupplyTemp .LT. lCHWLowLimitTemp ) THEN
IF((Node(lChillReturnnodenum)%Temp - lCHWLowLimitTemp ) .GT. DeltaTemptol) THEN
lChillSupplyTemp = lCHWLowLimitTemp
ChillDeltaTemp = Node(lChillReturnnodenum)%Temp - lChillSupplyTemp
lCoolingload = lChillWatermassflowrate * Cp_CW * ChillDeltaTemp
ELSE
lChillSupplyTemp = Node(lChillReturnnodenum)%Temp
ChillDeltaTemp = Node(lChillReturnnodenum)%Temp - lChillSupplyTemp
lCoolingload = lChillWatermassflowrate * Cp_CW * ChillDeltaTemp
END IF
END IF
IF(lChillSupplyTemp .LT. Node(lChillSupplyNodenum)%TempMin) THEN
IF((Node(lChillReturnnodenum)%Temp - Node(lChillSupplyNodenum)%TempMin) .GT. DeltaTemptol) THEN
lChillSupplyTemp = Node(lChillSupplyNodenum)%TempMin
ChillDeltaTemp = Node(lChillReturnnodenum)%Temp - lChillSupplyTemp
lCoolingload = lChillWatermassflowrate * Cp_CW * ChillDeltaTemp
ELSE
lChillSupplyTemp = Node(lChillReturnnodenum)%Temp
ChillDeltaTemp = Node(lChillReturnnodenum)%Temp - lChillSupplyTemp
lCoolingload = lChillWatermassflowrate * Cp_CW * ChillDeltaTemp
END IF
END IF
! Checks Coolingload on the basis of the machine limits.
If(lCoolingload > ABS(MyLoad)) Then
If(lChillwatermassflowrate > MassFlowTolerance) THEN
lCoolingload = ABS(MyLoad)
ChillDeltaTemp = lCoolingload/lChillwatermassflowrate/Cp_CW
lChillSupplyTemp = Node(lChillReturnnodenum)%Temp - ChillDeltaTemp
Else
lChillSupplyTemp = Node(lChillReturnnodenum)%Temp
ChillDeltaTemp = Node(lChillReturnnodenum)%Temp - lChillSupplyTemp
lCoolingload = lChillWatermassflowrate * Cp_CW * ChillDeltaTemp
End If
End If
END SELECT
!Calculate operating part load ratio for cooling
Partloadrat = MIN(ABS(MyLoad)/lAvailableCoolingCapacity,lMaxPartLoadRat)
Partloadrat = MAX(lMinPartLoadRat,Partloadrat)
IF(lAvailableCoolingCapacity > 0.0d0) THEN
IF(ABS(MyLoad)/lAvailableCoolingCapacity.LT.lMinPartLoadRat) THEN
lCoolPartLoadRatio = myload/lAvailableCoolingCapacity
ELSE
lCoolPartLoadRatio = PartLoadRat
ENDIF
ELSE !Else if AvailableCoolingCapacity < 0.0
lCoolPartLoadRatio = 0.0d0
ENDIF
! calculate the fraction of the time period that the chiller would be running
! use maximum from heating and cooling sides
IF(lCoolPartLoadRatio.LT.lMinPartLoadRat.OR.lHeatPartLoadRatio.LT.lMinPartLoadRat) THEN
lFractionOfPeriodRunning = MIN(1.0d0,MAX(lHeatPartLoadRatio,lCoolPartLoadRatio)/lMinPartLoadRat)
ELSE
lFractionOfPeriodRunning = 1.0d0
ENDIF
!Calculate fuel consumption for cooling
! fuel used for cooling availCap * HIR * HIR-FT * HIR-FPLR
lCoolFuelUseRate = lAvailableCoolingCapacity * lFuelCoolRatio &
* CurveValue(lFuelCoolFTCurve,lChillSupplyTemp,calcCondTemp) &
* CurveValue(lFuelCoolFPLRCurve,lCoolPartLoadRatio)*lFractionOfPeriodRunning
!Calculate electric parasitics used
! based on nominal capacity, not available capacity,
! electric used for cooling nomCap * %OP * EIR * EIR-FT * EIR-FPLR
lCoolElectricPower = lNomCoolingCap * lElecCoolRatio * lFractionOfPeriodRunning &
* CurveValue(lElecCoolFTCurve,lChillSupplyTemp,calcCondTemp) &
* CurveValue(lElecCoolFPLRCurve,lCoolPartLoadRatio)
! determine conderser load which is cooling load plus the
! fuel used for cooling times the burner efficiency plus
! the electricity used
lTowerLoad = lCoolingLoad + lCoolFuelUseRate / lFuelHeatRatio + lCoolElectricPower
! for water cooled condenser make sure enough flow rate
! for air cooled condenser just set supply to return temperature
IF (lIsWaterCooled) THEN
IF (lCondWaterMassFlowRate > MassFlowTolerance) THEN
lCondSupplyTemp = lCondReturnTemp + lTowerLoad / (lCondWaterMassFlowRate * Cp_CD )
ELSE
CALL ShowSevereError('CalcGasAbsorberChillerModel: Condenser flow = 0, for Gas Absorber Chiller='// &
TRIM(GasAbsorber(ChillNum)%Name))
CALL ShowContinueErrorTimeStamp(' ')
CALL ShowFatalError('Program Terminates due to previous error condition.')
END IF
ELSE
lCondSupplyTemp = lCondReturnTemp !if air cooled condenser just set supply and return to same temperature
END IF
! save the condenser water supply temperature for next iteration if that is used in lookup
! and if capacity is large enough error than report problem
oldCondSupplyTemp = lCondSupplyTemp
IF (.NOT. lIsEnterCondensTemp) THEN
! calculate the fraction of the estimated error between the capacity based on the previous
! iteration's value of condenser supply temperature and the actual calculated condenser supply
! temperature. If this becomes too common then may need to iterate a solution instead of
! relying on previous iteration method.
revisedEstimateAvailCap = lNomCoolingCap * CurveValue(lCoolCapFTCurve,ChillSupplySetPointTemp,lCondSupplyTemp)
IF (revisedEstimateAvailCap > 0.0d0) THEN
errorAvailCap = ABS((revisedEstimateAvailCap - lAvailableCoolingCapacity)/revisedEstimateAvailCap)
IF (errorAvailCap > 0.05d0) THEN ! if more than 5% error in estimate
CALL ShowRecurringWarningErrorAtEnd('GasAbsorberChillerModel:"'//TRIM(GasAbsorber(ChillNum)%Name)// &
'", poor Condenser Supply Estimate',GasAbsorber(ChillNum)%condErrCount,ReportMinOf=errorAvailCap, &
ReportMaxOf=errorAvailCap)
ENDIF
ENDIF
ENDIF
ENDIF ! IF(MyLoad>=0 .OR. .NOT. Runflag)
! Write into the Report Variables except for nodes
GasAbsorberReport(ChillNum)%CoolingLoad = lCoolingLoad
GasAbsorberReport(ChillNum)%TowerLoad = lTowerLoad
GasAbsorberReport(ChillNum)%CoolFuelUseRate = lCoolFuelUseRate
GasAbsorberReport(ChillNum)%CoolElectricPower = lCoolElectricPower
GasAbsorberReport(ChillNum)%CondReturnTemp = lCondReturnTemp
GasAbsorberReport(ChillNum)%ChillReturnTemp = lChillReturnTemp
GasAbsorberReport(ChillNum)%CondSupplyTemp = lCondSupplyTemp
GasAbsorberReport(ChillNum)%ChillSupplyTemp = lChillSupplyTemp
GasAbsorberReport(ChillNum)%ChillWaterFlowRate = lChillWaterMassFlowRate
GasAbsorberReport(ChillNum)%CondWaterFlowRate = lCondWaterMassFlowRate
GasAbsorberReport(ChillNum)%CoolPartLoadRatio = lCoolPartLoadRatio
GasAbsorberReport(ChillNum)%CoolingCapacity = lAvailableCoolingCapacity
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 CalcGasAbsorberChillerModel