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.
calculate end time of current time step
Print warning messages only when valid and only for the first ocurrance. Let summary provide statistics. Wait for next time step to print warnings. If simulation iterates, print out the warning for the last iteration only. Must wait for next time step to accomplish this. If a warning occurs and the simulation down shifts, the warning is not valid.
Show single warning and pass additional info to ShowRecurringWarningErrorAtEnd
save last system time step and last end time of current time step (used to determine if warning is valid)
Some other component set the flow to 0. No reason to continue with calculations.
ElecReformEIRChiller(EIRChillNum)%PrintMessage = .FALSE.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer | :: | EIRChillNum | ||||
real(kind=r64) | :: | MyLoad | ||||
logical, | intent(in) | :: | RunFlag | |||
logical | :: | FirstIteration | ||||
integer, | intent(in) | :: | EquipFlowCtrl | |||
real(kind=r64), | intent(in) | :: | FalsiCondOutTemp |
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 CalcReformEIRChillerModel(EIRChillNum,MyLoad,Runflag,FirstIteration,EquipFlowCtrl,FalsiCondOutTemp)
! SUBROUTINE INFORMATION:
! AUTHOR Lixing Gu, FSEC
! DATE WRITTEN July 2006
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Simulate a vapor compression chiller using the reformulated model developed by Mark Hydeman
! METHODOLOGY EMPLOYED:
! Use empirical curve fits to model performance at off-design conditions
! REFERENCES:
! 1. Hydeman, M., P. Sreedharan, N. Webb, and S. Blanc. 2002. "Development and Testing of a Reformulated
! Regression-Based Electric Chiller Model". ASHRAE Transactions, HI-02-18-2, Vol 108, Part 2, pp. 1118-1127.
! USE STATEMENTS:
USE DataGlobals, ONLY : WarmupFlag, CurrentTime
USE DataInterfaces, ONLY : ShowFatalError, ShowSevereError, ShowWarningError, ShowContinueErrorTimeStamp, &
ShowRecurringWarningErrorAtEnd, ShowContinueError
USE DataHVACGlobals, ONLY : SmallLoad, SysTimeElapsed, TimeStepSys
USE General, ONLY : RoundSigDigits, CreateSysTimeIntervalString
USE CurveManager, ONLY : CurveValue
USE DataPlant, ONLY : DeltaTemptol,PlantLoop, SimPlantEquipTypes, TypeOf_Chiller_ElectricReformEIR, &
CompSetPtBasedSchemeType, CriteriaType_MassFlowRate, SingleSetpoint, DualSetpointDeadband
USE DataBranchAirLoopPlant, ONLY: ControlType_SeriesActive, MassFlowTolerance
USE DataEnvironment, ONLY : EnvironmentName, CurMnDy
USE PlantUtilities, ONLY : SetComponentFlowRate, PullCompInterconnectTrigger
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER :: EIRChillNum ! Chiller number
REAL(r64) :: MyLoad ! Operating load [W]
LOGICAL :: FirstIteration ! TRUE when first iteration of timestep !unused1208
LOGICAL, INTENT(IN) :: RunFlag ! TRUE when chiller operating
INTEGER, INTENT(IN) :: EquipFlowCtrl ! Flow control mode for the equipment
REAL(r64), INTENT(IN) :: FalsiCondOutTemp ! RegulaFalsi condenser outlet temperature result [C]
! SUBROUTINE PARAMETER DEFINITIONS:
CHARACTER(len=*), PARAMETER :: OutputFormat ='(F6.2)'
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: FRAC ! Chiller cycling ratio
REAL(r64) :: MinPartLoadRat ! Minimum allowed operating fraction of full load
REAL(r64) :: MinUnloadRat ! Minimum allowed unloading fraction of full load
REAL(r64) :: MaxPartLoadRat ! Maximum allowed operating fraction of full load
REAL(r64) :: EvapInletTemp ! Evaporator inlet temperature [C]
REAL(r64) :: CondInletTemp ! Condenser inlet temperature [C]
REAL(r64) :: EvapOutletTempSetpoint ! Evaporator outlet temperature setpoint [C]
REAL(r64) :: AvailChillerCap ! Chiller available capacity [W]
REAL(r64) :: ChillerRefCap ! Chiller reference capacity [W]
REAL(r64) :: EvapDeltaTemp ! Evaporator temperature difference [C]
REAL(r64) :: ReferenceCOP ! Reference coefficient of performance, from user input
REAL(r64) :: PartLoadRat ! Operating part load ratio
REAL(r64) :: TempLowLimitEout ! Evaporator low temp. limit cut off [C]
REAL(r64) :: EvapMassFlowRateMax ! Maximum evaporator mass flow rate converted from volume flow rate [kg/s]
INTEGER :: EvapInletNode ! evaporator inlet node number
INTEGER :: EvapOutletNode ! evaporator outlet node number
INTEGER :: CondInletNode ! condenser inlet node number
INTEGER :: CondOutletNode ! condenser outlet node number
! LOGICAL, SAVE :: PossibleSubCooling
REAL(r64) :: TempLoad ! actual load to be met by chiller. This value is compared to MyLoad
! and reset when necessary since this chiller can cycle, the load passed
! should be the actual load. Instead the minimum PLR * RefCap is
! passed in.
INTEGER :: PlantLoopNum ! Plant loop which contains the current chiller
INTEGER :: LoopSideNum ! Plant loop side which contains the current chiller (usually supply side)
INTEGER :: BranchNum
INTEGER :: CompNum
REAL(r64) :: Cp ! Local fluid specific heat
! REAL(r64),SAVE :: TimeStepSysLast=0.0 ! last system time step (used to check for downshifting)
! REAL(r64) :: CurrentEndTime ! end time of time step for current simulation time step
! REAL(r64),SAVE :: CurrentEndTimeLast=0.0 ! end time of time step for last simulation time step
! CHARACTER(len=6) :: OutputChar = ' ' ! character string for warning messages
! Set module level inlet and outlet nodes and initialize other local variables
ChillerPartLoadRatio = 0.0d0
ChillerCyclingRatio = 0.0d0
ChillerFalseLoadRate = 0.0d0
EvapMassFlowRate = 0.0d0
CondMassFlowRate = 0.0d0
Power = 0.0d0
QCondenser = 0.0d0
QEvaporator = 0.0d0
QHeatRecovered = 0.0d0
! CondenserFanPower = 0.0
EvapInletNode = ElecReformEIRChiller(EIRChillNum)%EvapInletNodeNum
EvapOutletNode = ElecReformEIRChiller(EIRChillNum)%EvapOutletNodeNum
CondInletNode = ElecReformEIRChiller(EIRChillNum)%CondInletNodeNum
CondOutletNode = ElecReformEIRChiller(EIRChillNum)%CondOutletNodeNum
PlantLoopNum = ElecReformEIRChiller(EIRChillNum)%CWLoopNum
LoopSideNum = ElecReformEIRChiller(EIRChillNum)%CWLoopSideNum
BranchNum = ElecReformEIRChiller(EIRChillNum)%CWBranchNum
CompNum = ElecReformEIRChiller(EIRChillNum)%CWCompNum
! Set performance curve outputs to 0.0 when chiller is off
ChillerCapFT = 0.0d0
ChillerEIRFT = 0.0d0
ChillerEIRFPLR = 0.0d0
! Set module-level chiller evap and condenser inlet temperature variables
EvapInletTemp = Node(EvapInletNode)%Temp
CondInletTemp = Node(CondInletNode)%Temp
! This chiller is currenlty has only a water-cooled condenser
!
!! calculate end time of current time step
! CurrentEndTime = CurrentTime + SysTimeElapsed
!
!! Print warning messages only when valid and only for the first ocurrance. Let summary provide statistics.
!! Wait for next time step to print warnings. If simulation iterates, print out
!! the warning for the last iteration only. Must wait for next time step to accomplish this.
!! If a warning occurs and the simulation down shifts, the warning is not valid.
! IF(CurrentEndTime .GT. CurrentEndTimeLast .AND. TimeStepSys .GE. TimeStepSysLast)THEN
! IF(ElecReformEIRChiller(EIRChillNum)%PrintMessage)THEN
! ElecReformEIRChiller(EIRChillNum)%MsgErrorCount = &
! ElecReformEIRChiller(EIRChillNum)%MsgErrorCount + 1
!! Show single warning and pass additional info to ShowRecurringWarningErrorAtEnd
! IF (ElecReformEIRChiller(EIRChillNum)%MsgErrorCount < 2) THEN
! CALL ShowWarningError(TRIM(ElecReformEIRChiller(EIRChillNum)%MsgBuffer1)//'.')
! CALL ShowContinueError(TRIM(ElecReformEIRChiller(EIRChillNum)%MsgBuffer2))
! ELSE
! CALL ShowRecurringWarningErrorAtEnd(TRIM(ElecReformEIRChiller(EIRChillNum)%MsgBuffer1)//' error continues.', &
! ElecReformEIRChiller(EIRChillNum)%ErrCount1,ReportMaxOf=ElecReformEIRChiller(EIRChillNum)%MsgDataLast, &
! ReportMinOf=ElecReformEIRChiller(EIRChillNum)%MsgDataLast,ReportMaxUnits='[C]',ReportMinUnits='[C]')
! END IF
! END IF
! END IF
!
!! save last system time step and last end time of current time step (used to determine if warning is valid)
! TimeStepSysLast = TimeStepSys
! CurrentEndTimeLast = CurrentEndTime
! If no loop demand or chiller OFF, return
! If chiller load is 0 or chiller is not running then leave the subroutine. Before leaving
! if the component control is SERIESACTIVE we set the component flow to inlet flow so that
! flow resolver will not shut down the branch
IF(MyLoad >= 0 .OR. .NOT. RunFlag) THEN
IF(EquipFlowCtrl == ControlType_SeriesActive .OR. PlantLoop(PlantLoopNum)%LoopSide(LoopSideNum)%FlowLock==1) THEN
EvapMassFlowRate = Node(EvapInletNode)%MassFlowrate
END IF
IF (ElecReformEIRChiller(EIRChillNum)%CondenserType == WaterCooled) THEN
IF (PlantLoop(ElecReformEIRChiller(EIRChillNum)%CDLoopNum)% &
LoopSide(ElecReformEIRChiller(EIRChillNum)%CDLoopSideNum)% &
Branch(ElecReformEIRChiller(EIRChillNum)%CDBranchNum)% &
Comp(ElecReformEIRChiller(EIRChillNum)%CDCompNum)%FlowCtrl == ControlType_SeriesActive) THEN
CondMassFlowRate = Node(CondInletNode)%MassFlowrate
ENDIF
ENDIF
RETURN
END IF
! LOAD LOCAL VARIABLES FROM DATA STRUCTURE (for code readability)
MinPartLoadRat = ElecReformEIRChiller(EIRChillNum)%MinPartLoadRat
MaxPartLoadRat = ElecReformEIRChiller(EIRChillNum)%MaxPartLoadRat
MinUnloadRat = ElecReformEIRChiller(EIRChillNum)%MinUnLoadRat
ChillerRefCap = ElecReformEIRChiller(EIRChillNum)%RefCap
ReferenceCOP = ElecReformEIRChiller(EIRChillNum)%RefCOP
EvapOutletTemp = Node(ElecReformEIRChiller(EIRChillNum)%EvapOutletNodeNum)%Temp
TempLowLimitEout = ElecReformEIRChiller(EIRChillNum)%TempLowLimitEvapOut
EvapMassFlowRateMax = ElecReformEIRChiller(EIRChillNum)%EvapMassFlowRateMax
! Set mass flow rates
IF (ElecReformEIRChiller(EIRChillNum)%CondenserType == WaterCooled) THEN
CondMassFlowRate = ElecReformEIRChiller(EIRChillNum)%CondMassFlowRateMax
CALL SetComponentFlowRate(CondMassFlowRate, CondInletNode, CondOutletNode, &
ElecReformEIRChiller(EIRChillNum)%CDLoopNum, &
ElecReformEIRChiller(EIRChillNum)%CDLoopSideNum, &
ElecReformEIRChiller(EIRChillNum)%CDBranchNum, &
ElecReformEIRChiller(EIRChillNum)%CDCompNum)
CALL PullCompInterconnectTrigger(ElecReformEIRChiller(EIRChillNum)%CWLoopNum, &
ElecReformEIRChiller(EIRChillNum)%CWLoopSideNum, &
ElecReformEIRChiller(EIRChillNum)%CWBranchNum, &
ElecReformEIRChiller(EIRChillNum)%CWCompNum, &
ElecReformEIRChiller(EIRChillNum)%CondMassFlowIndex, &
ElecReformEIRChiller(EIRChillNum)%CDLoopNum, &
ElecReformEIRChiller(EIRChillNum)%CDLoopSideNum, &
CriteriaType_MassFlowRate, &
CondMassFlowRate)
IF (CondMassFlowRate < MassFlowTolerance) RETURN
END IF
FRAC = 1.0d0
SELECT CASE (PlantLoop(PlantLoopNum)%LoopDemandCalcScheme)
CASE (SingleSetpoint)
IF ((ElecReformEIRChiller(EIRChillNum)%FlowMode == LeavingSetpointModulated) .OR. &
(PlantLoop(PlantLoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%CurOpSchemeType &
== CompSetPtBasedSchemeType) .OR. &
(Node(ElecReformEIRChiller(EIRChillNum)%EvapOutletNodeNum)%TempSetPoint /= SensedNodeFlagValue) ) THEN
! there will be a valid setpoint on outlet
EvapOutletTempSetpoint = Node(EvapOutletNode)%TempSetPoint
ELSE ! use plant loop overall setpoint
EvapOutletTempSetpoint= Node(PlantLoop(PlantLoopNum)%TempSetPointNodeNum)%TempSetPoint
ENDIF
CASE (DualSetpointDeadband)
IF ((ElecReformEIRChiller(EIRChillNum)%FlowMode == LeavingSetpointModulated) .OR. &
(PlantLoop(PlantLoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%CurOpSchemeType &
== CompSetPtBasedSchemeType) .OR. &
(Node(ElecReformEIRChiller(EIRChillNum)%EvapOutletNodeNum)%TempSetPointHi /= SensedNodeFlagValue) ) THEN
! there will be a valid setpoint on outlet
EvapOutletTempSetpoint = Node(EvapOutletNode)%TempSetPointHi
ELSE ! use plant loop overall setpoint
EvapOutletTempSetpoint= Node(PlantLoop(PlantLoopNum)%TempSetPointNodeNum)%TempSetPointHi
ENDIF
END SELECT
! correct temperature if using heat recovery
! use report values for latest valid calculation, lagged somewhat
IF ( ElecReformEIRChiller(EIRChillNum)%HeatRecActive ) THEN
If ( (ElecReformEIRChillerReport(EIRChillNum)%QHeatRecovery &
+ ElecReformEIRChillerReport(EIRChillNum)%QCond) > 0.d0) THEN ! protect div by zero
AvgCondSinkTemp = (ElecReformEIRChillerReport(EIRChillNum)%QHeatRecovery &
* ElecReformEIRChillerReport(EIRChillNum)%HeatRecOutletTemp &
+ ElecReformEIRChillerReport(EIRChillNum)%QCond &
* ElecReformEIRChillerReport(EIRChillNum)%CondOutletTemp) &
/ (ElecReformEIRChillerReport(EIRChillNum)%QHeatRecovery &
+ ElecReformEIRChillerReport(EIRChillNum)%QCond)
ELSE
AvgCondSinkTemp = FalsiCondOutTemp
ENDIF
ELSE
AvgCondSinkTemp = FalsiCondOutTemp
ENDIF
! Get capacity curve info with respect to CW setpoint and leaving condenser water temps
ChillerCapFT = MAX(0.0d0, CurveValue(ElecReformEIRChiller(EIRChillNum)%ChillerCapFT, &
EvapOutletTempSetpoint,AvgCondSinkTemp))
! Available chiller capacity as a function of temperature
AvailChillerCap = ChillerRefCap*ChillerCapFT
! IF (PlantLoop(PlantLoopNum)%Loopside(LoopSideNum)%FlowLock .EQ. 0) THEN
! EvapMassFlowRate = MIN(EvapMassFlowRateMax,Node(EvapInletNode)%MassFlowRateMaxAvail) !CRBranchPump
! EvapMassFlowRate = MAX(EvapMassFlowRate,Node(EvapInletNode)%MassFlowRateMinAvail) !CRBranchPump
!! Some other component set the flow to 0. No reason to continue with calculations.
! IF(EvapMassFlowRate == 0.0d0)THEN
! MyLoad = 0.0d0
!! ElecReformEIRChiller(EIRChillNum)%PrintMessage = .FALSE.
! RETURN
! END IF
! ELSE
EvapMassFlowRate = Node(EvapInletNode)%MassFlowRate
! Some other component set the flow to 0. No reason to continue with calculations.
IF(EvapMassFlowRate == 0.0d0)THEN
MyLoad = 0.0d0
! ElecReformEIRChiller(EIRChillNum)%PrintMessage = .FALSE.
RETURN
END IF
! END IF
! This chiller is currenlty has only a water-cooled condenser
! Calculate water side load
Cp = GetSpecificHeatGlycol(PlantLoop(ElecReformEIRChiller(EIRChillNum)%CWLoopNum)%FluidName, &
Node(EvapInletNode)%Temp, &
PlantLoop(ElecReformEIRChiller(EIRChillNum)%CWLoopNum)%FluidIndex, &
'CalcElecReformEIRChillerModel')
! problem here if no setpoint on outlet
! CR 9132 changed from actual node flow rate to maximum available to avoid issue of limiting capacity
TempLoad = Node(EvapInletNode)%MassFlowRateMaxAvail * Cp * (Node(EvapInletNode)%Temp - EvapOutletTempSetpoint)
TempLoad = MAX(0.0d0,TempLoad)
! MyLoad is capped at minimum PLR * RefCap, adjust load to actual water side load because this chiller can cycle
IF (ABS(MyLoad) .GT. TempLoad) THEN
MyLoad = SIGN(TempLoad, MyLoad)
END IF
! Part load ratio based on load and available chiller capacity, cap at max part load ratio
IF(AvailChillerCap .GT. 0)THEN
PartLoadRat = MAX(0.0d0, MIN(ABS(MyLoad)/AvailChillerCap,MaxPartLoadRat))
ELSE
PartLoadRat = 0.0d0
END IF
! Set evaporator heat transfer rate
QEvaporator = AvailChillerCap * PartLoadRat
ChillerPartLoadRatio = PartLoadRat
! If FlowLock is False (0), the chiller sets the plant loop mdot
! If FlowLock is True (1), the new resolved plant loop mdot is used
IF (PlantLoop(PlantLoopNum)%Loopside(LoopSideNum)%FlowLock==0) THEN
IF (PlantLoop(PlantLoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%CurOpSchemeType == &
CompSetPtBasedSchemeType) THEN
ElecReformEIRChiller(EIRChillNum)%PossibleSubCooling = .FALSE.
ELSE
ElecReformEIRChiller(EIRChillNum)%PossibleSubCooling = .TRUE.
ENDIF
! Either set the flow to the Constant value or caluclate the flow for the variable volume case
IF( (ElecReformEIRChiller(EIRChillNum)%FlowMode == ConstantFlow) &
.OR. (ElecReformEIRChiller(EIRChillNum)%FlowMode == NotModulated )) THEN
! Set the evaporator mass flow rate to design
! Start by assuming max (design) flow
EvapMassFlowRate = EvapMassFlowRateMax
! Use SetComponentFlowRate to decide actual flow
Call SetComponentFlowRate( EvapMassFlowRate, &
EvapInletNode , EvapOutletNode , &
ElecReformEIRChiller(EIRChillNum)%CWLoopNum, &
ElecReformEIRChiller(EIRChillNum)%CWLoopSideNum, &
ElecReformEIRChiller(EIRChillNum)%CWBranchNum, &
ElecReformEIRChiller(EIRChillNum)%CWCompNum)
IF (EvapMassFlowRate /= 0.0D0) THEN
EvapDeltaTemp = QEvaporator/EvapMassFlowRate/Cp
ELSE
EvapDeltaTemp = 0.0D0
ENDIF
EvapOutletTemp = Node(EvapInletNode)%Temp - EvapDeltaTemp
ELSEIF (ElecReformEIRChiller(EIRChillNum)%FlowMode == LeavingSetpointModulated) THEN
SELECT CASE (PlantLoop(PlantLoopNum)%LoopDemandCalcScheme)
CASE (SingleSetpoint)
! Calculate the Delta Temp from the inlet temp to the chiller outlet setpoint
EvapDeltaTemp = Node(EvapInletNode)%Temp - Node(EvapOutletNode)%TempSetPoint
CASE (DualSetpointDeadband)
EvapDeltaTemp = Node(EvapInletNode)%Temp - Node(EvapOutletNode)%TempSetPointHi
END SELECT
IF (EvapDeltaTemp /= 0) THEN
EvapMassFlowRate = MAX(0.0d0,(QEvaporator/Cp/EvapDeltaTemp))
IF((EvapMassFlowRate - EvapMassFlowRateMax) .GT. MassFlowTolerance) &
ElecReformEIRChiller(EIRChillNum)%PossibleSubCooling = .TRUE.
!Check to see if the Maximum is exceeded, if so set to maximum
EvapMassFlowRate = MIN(EvapMassFlowRateMax, EvapMassFlowRate)
! Use SetComponentFlowRate to decide actual flow
Call SetComponentFlowRate( EvapMassFlowRate, &
EvapInletNode , EvapOutletNode , &
ElecReformEIRChiller(EIRChillNum)%CWLoopNum, &
ElecReformEIRChiller(EIRChillNum)%CWLoopSideNum, &
ElecReformEIRChiller(EIRChillNum)%CWBranchNum, &
ElecReformEIRChiller(EIRChillNum)%CWCompNum)
! Should we recalculate this with the corrected setpoint?
SELECT CASE (PlantLoop(PlantLoopNum)%LoopDemandCalcScheme)
CASE (SingleSetpoint)
EvapOutletTemp = Node(EvapOutletNode)%TempSetPoint
CASE (DualSetpointDeadband)
EvapOutletTemp = Node(EvapOutletNode)%TempSetPointHi
END SELECT
QEvaporator = MAX(0.0d0,(EvapMassFlowRate*Cp*EvapDeltaTemp))
ELSE
! Try to request zero flow
EvapMassFlowRate=0.0d0
! Use SetComponentFlowRate to decide actual flow
CALL SetComponentFlowRate( EvapMassFlowRate, &
EvapInletNode , EvapOutletNode , &
ElecReformEIRChiller(EIRChillNum)%CWLoopNum, &
ElecReformEIRChiller(EIRChillNum)%CWLoopSideNum, &
ElecReformEIRChiller(EIRChillNum)%CWBranchNum, &
ElecReformEIRChiller(EIRChillNum)%CWCompNum)
! No deltaT since component is not running
EvapOutletTemp = Node(EvapInletNode)%Temp
QEvaporator = 0.0d0
PartLoadRat = 0.0d0
ChillerPartLoadRatio = PartLoadRat
IF (ElecReformEIRChiller(EIRChillNum)%DeltaTErrCount < 1 .AND. .NOT. WarmupFlag) THEN
ElecReformEIRChiller(EIRChillNum)%DeltaTErrCount=ElecReformEIRChiller(EIRChillNum)%DeltaTErrCount+1
CALL ShowWarningError('Evaporator DeltaTemp = 0 in mass flow calculation (Tevapin = Tevapout setpoint temp).')
CALL ShowContinueErrorTimeStamp(' ')
ELSE IF (.NOT. WarmupFlag) THEN
ElecReformEIRChiller(EIRChillNum)%ChillerCapFTError = ElecReformEIRChiller(EIRChillNum)%ChillerCapFTError + 1
CALL ShowRecurringWarningErrorAtEnd('CHILLER:ELECTRIC:REFORMULATEDEIR "' &
//TRIM(ElecReformEIRChiller(EIRChillNum)%Name)//'":'//&
' Evaporator DeltaTemp = 0 in mass flow calculation warning continues...' &
, ElecReformEIRChiller(EIRChillNum)%DeltaTErrCountIndex, EvapDeltaTemp, EvapDeltaTemp)
END IF
END IF
END IF !End of Constant Variable Flow If Block
ELSE ! If FlowLock is True
EvapMassFlowRate = Node(EvapInletNode)%MassFlowRate
Call SetComponentFlowRate( EvapMassFlowRate, &
EvapInletNode , EvapOutletNode , &
ElecReformEIRChiller(EIRChillNum)%CWLoopNum, &
ElecReformEIRChiller(EIRChillNum)%CWLoopSideNum, &
ElecReformEIRChiller(EIRChillNum)%CWBranchNum, &
ElecReformEIRChiller(EIRChillNum)%CWCompNum)
! Some other component set the flow to 0. No reason to continue with calculations.
IF(EvapMassFlowRate == 0.0d0)THEN
MyLoad = 0.0d0
! ElecReformEIRChiller(EIRChillNum)%PrintMessage = .FALSE.
RETURN
END IF
IF(ElecReformEIRChiller(EIRChillNum)%PossibleSubCooling) THEN
QEvaporator = ABS(MyLoad)
EvapDeltaTemp = QEvaporator/EvapMassFlowRate/Cp
EvapOutletTemp = Node(EvapInletNode)%Temp - EvapDeltaTemp
ELSE
EvapDeltaTemp = Node(EvapInletNode)%Temp - EvapOutletTempSetpoint
QEvaporator = MAX(0.0d0,(EvapMassFlowRate*Cp*EvapDeltaTemp))
EvapOutletTemp = EvapOutletTempSetpoint
END IF
IF(EvapOutletTemp .LT. TempLowLimitEout) THEN
IF((Node(EvapInletNode)%Temp - TempLowLimitEout) .GT. DeltaTemptol) THEN
EvapOutletTemp = TempLowLimitEout
EvapDeltaTemp = Node(EvapInletNode)%Temp - EvapOutletTemp
QEvaporator = EvapMassFlowRate*Cp*EvapDeltaTemp
ELSE
EvapOutletTemp = Node(EvapInletNode)%Temp
EvapDeltaTemp = Node(EvapInletNode)%Temp - EvapOutletTemp
QEvaporator = EvapMassFlowRate*Cp*EvapDeltaTemp
END IF
END IF
IF(EvapOutletTemp .LT. Node(EvapOutletNode)%TempMin) THEN
IF((Node(EvapInletNode)%Temp - Node(EvapOutletNode)%TempMin) .GT. DeltaTemptol) THEN
EvapOutletTemp = Node(EvapOutletNode)%TempMin
EvapDeltaTemp = Node(EvapInletNode)%Temp - EvapOutletTemp
QEvaporator = EvapMassFlowRate*Cp*EvapDeltaTemp
ELSE
EvapOutletTemp = Node(EvapInletNode)%Temp
EvapDeltaTemp = Node(EvapInletNode)%Temp - EvapOutletTemp
QEvaporator = EvapMassFlowRate*Cp*EvapDeltaTemp
END IF
END IF
! If load exceeds the distributed load set to the distributed load
IF(QEvaporator > ABS(MyLoad)) THEN
IF(EvapMassFlowRate > MassFlowTolerance) THEN
QEvaporator = ABS(MyLoad)
EvapDeltaTemp = QEvaporator/EvapMassFlowRate/Cp
EvapOutletTemp = Node(EvapInletNode)%Temp - EvapDeltaTemp
ELSE
QEvaporator = 0.0d0
EvapOutletTemp = Node(EvapInletNode)%Temp
END IF
END IF
! Checks QEvaporator on the basis of the machine limits.
IF(QEvaporator > (AvailChillerCap * MaxPartLoadRat))THEN
IF(EvapMassFlowRate > MassFlowTolerance) THEN
QEvaporator = AvailChillerCap * MaxPartLoadRat
EvapDeltaTemp = QEvaporator/EvapMassFlowRate/Cp
! evaporator outlet temperature is allowed to float upwards (recalculate AvailChillerCap? iterate?)
EvapOutletTemp = Node(EvapInletNode)%Temp - EvapDeltaTemp
ELSE
QEvaporator = 0.0d0
EvapOutletTemp = Node(EvapInletNode)%Temp
! ElecReformEIRChiller(EIRChillNum)%PrintMessage = .FALSE.
END IF
END IF
IF(AvailChillerCap .GT. 0.0d0)THEN
PartLoadRat = MAX(0.0d0,MIN((QEvaporator/AvailChillerCap),MaxPartLoadRat))
ELSE
PartLoadRat = 0.0d0
END IF
! Chiller cycles below minimum part load ratio, FRAC = amount of time chiller is ON during this time step
IF (PartLoadRat .LT. MinPartLoadRat) FRAC = MIN(1.0d0,(PartLoadRat/MinPartLoadRat))
! set the module level variable used for reporting FRAC
ChillerCyclingRatio = FRAC
! Chiller is false loading below PLR = minimum unloading ratio, find PLR used for energy calculation
IF(AvailChillerCap .GT. 0.0d0)THEN
PartLoadRat = MAX(PartLoadRat,MinUnLoadRat)
ELSE
PartLoadRat = 0.0d0
END IF
! set the module level variable used for reporting PLR
ChillerPartLoadRatio = PartLoadRat
! calculate the load due to false loading on chiller over and above water side load
ChillerFalseLoadRate = (AvailChillerCap * PartLoadRat * FRAC) - QEvaporator
IF(ChillerFalseLoadRate .LT. SmallLoad) THEN
ChillerFalseLoadRate = 0.0d0
END IF
END IF !This is the end of the FlowLock Block
ChillerEIRFT = MAX(0.0d0, CurveValue(ElecReformEIRChiller(EIRChillNum)%ChillerEIRFT,EvapOutletTemp,AvgCondSinkTemp))
ChillerEIRFPLR = MAX(0.0d0, CurveValue(ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLR,AvgCondSinkTemp,PartLoadRat))
Power = (AvailChillerCap/ReferenceCOP) * ChillerEIRFPLR * ChillerEIRFT * FRAC
QCondenser = Power*ElecReformEIRChiller(EIRChillNum)%CompPowerToCondenserFrac + QEvaporator + ChillerFalseLoadRate
! Currently only water cooled chillers are allowed for the reformulated EIR chiller model
IF (CondMassFlowRate > MassFlowTolerance) THEN
! If Heat Recovery specified for this vapor compression chiller, then Qcondenser will be adjusted by this subroutine
IF(ElecReformEIRChiller(EIRChillNum)%HeatRecActive) CALL ReformEIRChillerHeatRecovery(EIRChillNum,QCondenser, &
CondMassFlowRate,CondInletTemp,QHeatRecovered)
Cp = GetSpecificHeatGlycol(PlantLoop(ElecReformEIRChiller(EIRChillNum)%CDLoopNum)%FluidName, &
CondInletTemp, &
PlantLoop(ElecReformEIRChiller(EIRChillNum)%CDLoopNum)%FluidIndex, &
'CalcElecReformEIRChillerModel')
CondOutletTemp = QCondenser/CondMassFlowRate/Cp + CondInletTemp
ELSE
CALL ShowSevereError('ControlReformEIRChillerModel: Condenser flow = 0, for ElecReformEIRChiller='// &
TRIM(ElecReformEIRChiller(EIRChillNum)%Name))
CALL ShowContinueErrorTimeStamp(' ')
END IF
RETURN
END SUBROUTINE CalcReformEIRChillerModel