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.
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 GetElectricChillerInput
! SUBROUTINE INFORMATION:
! AUTHOR: Dan Fisher / Brandon Anderson
! DATE WRITTEN: September 2000
! PURPOSE OF THIS SUBROUTINE:
! This routine will get the input
! required by the Electric Chiller model.
! METHODOLOGY EMPLOYED:
! EnergyPlus input processor
! REFERENCES: na
! USE STATEMENTS:
USE InputProcessor, ONLY : GetNumObjectsFound, GetObjectItem, VerifyName
USE DataIPShortCuts ! Data for field names, blank numerics
USE BranchNodeConnections, ONLY: TestCompSet
USE NodeInputManager, ONLY: GetOnlySingleNode
USE GlobalNames, ONLY: VerifyUniqueChillerName
USE OutAirNodeManager, ONLY: CheckAndAddAirNodeNumber
USE General, ONLY: RoundSigDigits
USE PlantUtilities, ONLY: RegisterPlantCompDesignFlow
USE ScheduleManager, ONLY: GetScheduleIndex
USE DataSizing, ONLY: Autosize
USE DataGlobals, ONLY: AnyEnergyManagementSystemInModel
IMPLICIT NONE !
! PARAMETERS
CHARACTER(len=*), PARAMETER :: RoutineName='GetElectricChillerInput: ' ! include trailing blank space
!LOCAL VARIABLES
INTEGER :: ChillerNum !chiller counter
INTEGER :: NumAlphas ! Number of elements in the alpha array
INTEGER :: NumNums ! Number of elements in the numeric array
INTEGER :: IOStat ! IO Status when calling get input subroutine
! CHARACTER(len=MaxNameLength),DIMENSION(9) :: AlphArray !character string data
! REAL(r64), DIMENSION(22) :: NumArray !numeric data
LOGICAL, SAVE :: ErrorsFound=.false.
LOGICAL :: IsNotOK ! Flag to verify name
LOGICAL :: IsBlank ! Flag for blank name
LOGICAL :: errflag
LOGICAL :: Okay
! CHARACTER(len=MaxNameLength) :: cCurrentModuleObject ! for ease in renaming.
!FLOW
cCurrentModuleObject = 'Chiller:Electric'
NumElectricChillers = GetNumObjectsFound(cCurrentModuleObject)
IF (NumElectricChillers <= 0) THEN
CALL ShowSevereError('No '//TRIM(cCurrentModuleObject)//' Equipment specified in input file')
ErrorsFound=.true.
ENDIF
!See if load distribution manager has already gotten the input
IF (ALLOCATED(ElectricChiller))RETURN
!ALLOCATE ARRAYS
ALLOCATE (ElectricChiller(NumElectricChillers))
ALLOCATE (ElectricChillerReport(NumElectricChillers))
!LOAD ARRAYS WITH Electric CURVE FIT CHILLER DATA
DO ChillerNum = 1 , NumElectricChillers
CALL GetObjectItem(cCurrentModuleObject,ChillerNum,cAlphaArgs,NumAlphas, &
rNumericArgs,NumNums,IOSTAT,AlphaBlank=lAlphaFieldBlanks, NumBlank=lNumericFieldBlanks, &
NumericFieldNames=cNumericFieldNames,AlphaFieldnames=cAlphaFieldNames)
IsNotOK=.false.
IsBlank=.false.
CALL VerifyName(cAlphaArgs(1),ElectricChiller%Base%Name,ChillerNum-1,IsNotOK,IsBlank,TRIM(cCurrentModuleObject)//' Name')
IF (IsNotOK) THEN
ErrorsFound=.true.
IF (IsBlank) cAlphaArgs(1)='xxxxx'
ENDIF
CALL VerifyUniqueChillerName(TRIM(cCurrentModuleObject),cAlphaArgs(1),errflag,TRIM(cCurrentModuleObject)//' Name')
IF (errflag) THEN
ErrorsFound=.true.
ENDIF
ElectricChiller(ChillerNum)%Base%Name = cAlphaArgs(1)
IF (cAlphaArgs(2) == 'AIRCOOLED' ) THEN
ElectricChiller(ChillerNum)%Base%CondenserType = AirCooled
ELSEIF (cAlphaArgs(2) == 'WATERCOOLED' ) THEN
ElectricChiller(ChillerNum)%Base%CondenserType = WaterCooled
ELSEIF (cAlphaArgs(2) == 'EVAPORATIVELYCOOLED' ) THEN
ElectricChiller(ChillerNum)%Base%CondenserType = EvapCooled
ELSE
CALL ShowSevereError('Invalid '//TRIM(cAlphaFieldNames(2))//'='//TRIM(cAlphaArgs(2)))
CALL ShowContinueError('Entered in '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
ErrorsFound=.true.
ENDIF
ElectricChiller(ChillerNum)%Base%NomCap = rNumericArgs(1)
IF (rNumericArgs(1) == 0.0d0) THEN
CALL ShowSevereError('Invalid '//TRIM(cNumericFieldNames(1))//'='//TRIM(RoundSigDigits(rNumericArgs(1),2)))
CALL ShowContinueError('Entered in '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
ErrorsFound=.true.
ENDIF
ElectricChiller(ChillerNum)%Base%COP = rNumericArgs(2)
IF (rNumericArgs(2) == 0.0d0) THEN
CALL ShowSevereError('Invalid '//TRIM(cNumericFieldNames(2))//'='//TRIM(RoundSigDigits(rNumericArgs(2),3)))
CALL ShowContinueError('Entered in '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
ErrorsFound=.true.
ENDIF
ElectricChiller(ChillerNum)%Base%EvapInletNodeNum = GetOnlySingleNode(cAlphaArgs(3),ErrorsFound, &
TRIM(cCurrentModuleObject),cAlphaArgs(1), &
NodeType_Water,NodeConnectionType_Inlet, 1, ObjectIsNotParent)
ElectricChiller(ChillerNum)%Base%EvapOutletNodeNum = GetOnlySingleNode(cAlphaArgs(4),ErrorsFound, &
TRIM(cCurrentModuleObject),cAlphaArgs(1), &
NodeType_Water,NodeConnectionType_Outlet, 1, ObjectIsNotParent)
CALL TestCompSet(TRIM(cCurrentModuleObject),cAlphaArgs(1),cAlphaArgs(3),cAlphaArgs(4),'Chilled Water Nodes')
IF (ElectricChiller(ChillerNum)%Base%CondenserType == AirCooled .or. &
ElectricChiller(ChillerNum)%Base%CondenserType == EvapCooled) THEN
! Connection not required for air or evap cooled condenser
!If the condenser inlet is blank for air cooled and evap cooled condensers then supply a generic name
! since it is not used elsewhere for connection
! for transition purposes, add this node if not there.
IF(lAlphaFieldBlanks(5))THEN
IF (LEN_TRIM(cAlphaArgs(1)) < (MaxNameLength - 21) ) THEN ! protect against long name leading to > 100 chars
cAlphaArgs(5) = TRIM(cAlphaArgs(1))//' CONDENSER INLET NODE'
ELSE
cAlphaArgs(5) = TRIM(cAlphaArgs(1)(1:79))//' CONDENSER INLET NODE'
ENDIF
End If
IF(lAlphaFieldBlanks(6) )THEN
IF (LEN_TRIM(cAlphaArgs(1)) < (MaxNameLength - 22) ) THEN ! protect against long name leading to > 100 chars
cAlphaArgs(6) = TRIM(cAlphaArgs(1))//' CONDENSER OUTLET NODE'
ELSE
cAlphaArgs(6) = TRIM(cAlphaArgs(1)(1:78))//' CONDENSER OUTLET NODE'
ENDIF
END IF
ElectricChiller(ChillerNum)%Base%CondInletNodeNum = GetOnlySingleNode(cAlphaArgs(5),ErrorsFound, &
TRIM(cCurrentModuleObject),cAlphaArgs(1), &
NodeType_Air,NodeConnectionType_OutsideAirReference, 2, ObjectIsNotParent)
CALL CheckAndAddAirNodeNumber(ElectricChiller(ChillerNum)%Base%CondInletNodeNum,Okay)
IF (.not. Okay) THEN
CALL ShowWarningError(TRIM(cCurrentModuleObject)//', Adding OutdoorAir:Node='//TRIM(cAlphaArgs(5)))
ENDIF
ElectricChiller(ChillerNum)%Base%CondOutletNodeNum = GetOnlySingleNode(cAlphaArgs(6),ErrorsFound, &
TRIM(cCurrentModuleObject),cAlphaArgs(1), &
NodeType_Air,NodeConnectionType_Outlet, 2, ObjectIsNotParent)
ELSEIF (ElectricChiller(ChillerNum)%Base%CondenserType == WaterCooled) THEN
ElectricChiller(ChillerNum)%Base%CondInletNodeNum = GetOnlySingleNode(cAlphaArgs(5),ErrorsFound, &
TRIM(cCurrentModuleObject),cAlphaArgs(1), &
NodeType_Water,NodeConnectionType_Inlet, 2, ObjectIsNotParent)
ElectricChiller(ChillerNum)%Base%CondOutletNodeNum = GetOnlySingleNode(cAlphaArgs(6),ErrorsFound, &
TRIM(cCurrentModuleObject),cAlphaArgs(1), &
NodeType_Water,NodeConnectionType_Outlet, 2, ObjectIsNotParent)
CALL TestCompSet(TRIM(cCurrentModuleObject),cAlphaArgs(1),cAlphaArgs(5),cAlphaArgs(6),'Condenser Water Nodes')
!Condenser Inlet node name is necessary for Water Cooled
IF (lAlphaFieldBlanks(5) ) THEN
CALL ShowSevereError('Invalid, '//TRIM(cAlphaFieldNames(5))//'is blank ')
CALL ShowContinueError('Entered in '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
ErrorsFound=.true.
ElseIf ( lAlphaFieldBlanks(6) ) Then
CALL ShowSevereError('Invalid, '//TRIM(cAlphaFieldNames(6))//'is blank ')
CALL ShowContinueError('Entered in '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
ErrorsFound=.true.
ENDIF
ELSE
ElectricChiller(ChillerNum)%Base%CondInletNodeNum = GetOnlySingleNode(cAlphaArgs(5),ErrorsFound, &
TRIM(cCurrentModuleObject),cAlphaArgs(1), &
NodeType_Unknown,NodeConnectionType_Inlet, 2, ObjectIsNotParent)
ElectricChiller(ChillerNum)%Base%CondOutletNodeNum = GetOnlySingleNode(cAlphaArgs(6),ErrorsFound, &
TRIM(cCurrentModuleObject),cAlphaArgs(1), &
NodeType_Unknown,NodeConnectionType_Outlet, 2, ObjectIsNotParent)
CALL TestCompSet(TRIM(cCurrentModuleObject),cAlphaArgs(1),cAlphaArgs(5),cAlphaArgs(6),'Condenser (unknown?) Nodes')
!Condenser Inlet node name is necessary
IF (lAlphaFieldBlanks(5) ) THEN
CALL ShowSevereError('Invalid, '//TRIM(cAlphaFieldNames(5))//'is blank ')
CALL ShowContinueError('Entered in '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
ErrorsFound=.true.
ElseIf ( lAlphaFieldBlanks(6) ) Then
CALL ShowSevereError('Invalid, '//TRIM(cAlphaFieldNames(6))//'is blank ')
CALL ShowContinueError('Entered in '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
ErrorsFound=.true.
ENDIF
ENDIF
ElectricChiller(ChillerNum)%MinPartLoadRat = rNumericArgs(3)
ElectricChiller(ChillerNum)%MaxPartLoadRat = rNumericArgs(4)
ElectricChiller(ChillerNum)%OptPartLoadRat = rNumericArgs(5)
ElectricChiller(ChillerNum)%TempDesCondIn = rNumericArgs(6)
ElectricChiller(ChillerNum)%TempRiseCoef = rNumericArgs(7)
ElectricChiller(ChillerNum)%TempDesEvapOut = rNumericArgs(8)
ElectricChiller(ChillerNum)%Base%EvapVolFlowRate = rNumericArgs(9)
ElectricChiller(ChillerNum)%Base%CondVolFlowRate = rNumericArgs(10)
ElectricChiller(ChillerNum)%CapRatCoef(1) = rNumericArgs(11)
ElectricChiller(ChillerNum)%CapRatCoef(2) = rNumericArgs(12)
ElectricChiller(ChillerNum)%CapRatCoef(3) = rNumericArgs(13)
IF ((rNumericArgs(11)+rNumericArgs(12)+rNumericArgs(13)) == 0.0d0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//': Sum of Capacity Ratio Coef = 0.0, chiller='//TRIM(cAlphaArgs(1)))
ErrorsFound=.true.
ENDIF
ElectricChiller(ChillerNum)%PowerRatCoef(1) = rNumericArgs(14)
ElectricChiller(ChillerNum)%PowerRatCoef(2) = rNumericArgs(15)
ElectricChiller(ChillerNum)%PowerRatCoef(3) = rNumericArgs(16)
ElectricChiller(ChillerNum)%FullLoadCoef(1) = rNumericArgs(17)
ElectricChiller(ChillerNum)%FullLoadCoef(2) = rNumericArgs(18)
ElectricChiller(ChillerNum)%FullLoadCoef(3) = rNumericArgs(19)
ElectricChiller(ChillerNum)%TempLowLimitEvapOut = rNumericArgs(20)
ElectricChiller(ChillerNum)%Base%SizFac = rNumericArgs(22)
IF (ElectricChiller(ChillerNum)%Base%SizFac <= 0.0d0) ElectricChiller(ChillerNum)%Base%SizFac = 1.0d0
SELECT CASE (TRIM(cAlphaArgs(7)))
CASE ( 'CONSTANTFLOW' )
ElectricChiller(ChillerNum)%Base%FlowMode = ConstantFlow
CASE ( 'VARIABLEFLOW' )
ElectricChiller(ChillerNum)%Base%FlowMode = LeavingSetpointModulated
CALL ShowWarningError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//'",')
CALL ShowContinueError('Invalid '//TRIM(cAlphaFieldNames(7))//'='//TRIM(cAlphaArgs(7)))
CALL ShowContinueError('Key choice is now called "LeavingSetpointModulated" and the simulation continues')
CASE ('LEAVINGSETPOINTMODULATED')
ElectricChiller(ChillerNum)%Base%FlowMode = LeavingSetpointModulated
CASE ('NOTMODULATED')
ElectricChiller(ChillerNum)%Base%FlowMode = NotModulated
CASE DEFAULT
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//'",')
CALL ShowContinueError('Invalid '//TRIM(cAlphaFieldNames(7))//'='//TRIM(cAlphaArgs(7)))
CALL ShowContinueError('Available choices are ConstantFlow, NotModulated, or LeavingSetpointModulated')
CALL ShowContinueError('Flow mode NotModulated is assumed and the simulation continues.')
ElectricChiller(ChillerNum)%Base%FlowMode = NotModulated
END SELECT
! These are the Heat Recovery Inputs
ElectricChiller(ChillerNum)%DesignHeatRecVolFlowRate = rNumericArgs(21)
IF ((ElectricChiller(ChillerNum)%DesignHeatRecVolFlowRate > 0.0d0) &
.OR. (ElectricChiller(ChillerNum)%DesignHeatRecVolFlowRate == Autosize ) ) THEN
ElectricChiller(ChillerNum)%HeatRecActive=.true.
ElectricChiller(ChillerNum)%HeatRecInletNodeNum = &
GetOnlySingleNode(cAlphaArgs(8),ErrorsFound,TRIM(cCurrentModuleObject),cAlphaArgs(1), &
NodeType_Water,NodeConnectionType_Inlet, 3, ObjectIsNotParent)
IF (ElectricChiller(ChillerNum)%HeatRecInletNodeNum == 0) THEN
CALL ShowSevereError('Invalid '//TRIM(cAlphaFieldNames(8))//'='//TRIM(cAlphaArgs(8)))
CALL ShowContinueError('Entered in '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
ErrorsFound=.true.
ENDIF
ElectricChiller(ChillerNum)%HeatRecOutletNodeNum = &
GetOnlySingleNode(cAlphaArgs(9),ErrorsFound,TRIM(cCurrentModuleObject),cAlphaArgs(1), &
NodeType_Water,NodeConnectionType_Outlet, 3, ObjectIsNotParent)
IF (ElectricChiller(ChillerNum)%HeatRecOutletNodeNum == 0) THEN
CALL ShowSevereError('Invalid '//TRIM(cAlphaFieldNames(9))//'='//TRIM(cAlphaArgs(9)))
CALL ShowContinueError('Entered in '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
ErrorsFound=.true.
ENDIF
CALL TestCompSet(TRIM(cCurrentModuleObject),cAlphaArgs(1),cAlphaArgs(8),cAlphaArgs(9),'Heat Recovery Nodes')
IF ( ElectricChiller(ChillerNum)%DesignHeatRecVolFlowRate > 0.d0) THEN
CALL RegisterPlantCompDesignFlow(ElectricChiller(ChillerNum)%HeatRecInletNodeNum, &
ElectricChiller(ChillerNum)%DesignHeatRecVolFlowRate )
ENDIF
! Condenser flow rate must be specified for heat reclaim
IF (ElectricChiller(ChillerNum)%Base%CondenserType == AirCooled .OR. &
ElectricChiller(ChillerNum)%Base%CondenserType == EvapCooled) THEN
IF(ElectricChiller(ChillerNum)%Base%CondVolFlowRate .LE. 0.0d0)THEN
CALL ShowSevereError('Invalid '//TRIM(cNumericFieldNames(10))//'='//TRIM(RoundSigDigits(rNumericArgs(10),6)))
CALL ShowSevereError('Condenser fluid flow rate must be specified for Heat Reclaim applications.')
CALL ShowContinueError('Entered in '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
ErrorsFound=.true.
END IF
END IF
IF(NumNums > 24) THEN
IF ( .NOT. lNumericFieldBlanks(25)) THEN
ElectricChiller(ChillerNum)%HeatRecCapacityFraction = rNumericArgs(25)
ELSE
ElectricChiller(ChillerNum)%HeatRecCapacityFraction = 1.d0
ENDIF
ELSE
ElectricChiller(ChillerNum)%HeatRecCapacityFraction = 1.d0
ENDIF
IF (NumAlphas > 10) THEN
IF ( .NOT. lAlphaFieldBlanks(11)) THEN
ElectricChiller(ChillerNum)%HeatRecInletLimitSchedNum = GetScheduleIndex(cAlphaArgs(11))
IF (ElectricChiller(ChillerNum)%HeatRecInletLimitSchedNum == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//'"')
CALL ShowContinueError('Invalid '//TRIM(cAlphaFieldNames(11))//'='//TRIM(cAlphaArgs(11)))
ErrorsFound=.True.
ENDIF
ELSE
ElectricChiller(ChillerNum)%HeatRecInletLimitSchedNum = 0
ENDIF
ELSE
ElectricChiller(ChillerNum)%HeatRecInletLimitSchedNum = 0
ENDIF
IF (NumAlphas > 11) THEN
IF( .NOT. lAlphaFieldBlanks(12)) THEN
ElectricChiller(ChillerNum)%HeatRecSetpointNodeNum = &
GetOnlySingleNode(cAlphaArgs(12), ErrorsFound,TRIM(cCurrentModuleObject),cAlphaArgs(1), &
NodeType_Water,NodeConnectionType_Sensor, 1, ObjectIsNotParent)
ELSE
ElectricChiller(ChillerNum)%HeatRecSetpointNodeNum = 0
ENDIF
ELSE
ElectricChiller(ChillerNum)%HeatRecSetpointNodeNum = 0
ENDIf
ELSE
ElectricChiller(ChillerNum)%HeatRecActive=.false.
ElectricChiller(ChillerNum)%DesignHeatRecMassFlowRate = 0.0d0
ElectricChiller(ChillerNum)%HeatRecInletNodeNum = 0
ElectricChiller(ChillerNum)%HeatRecOutletNodeNum = 0
! if heat recovery is not used, don't care about condenser flow rate for air/evap-cooled equip.
IF (ElectricChiller(ChillerNum)%Base%CondenserType == AirCooled .OR. &
ElectricChiller(ChillerNum)%Base%CondenserType == EvapCooled) THEN
ElectricChiller(ChillerNum)%Base%CondVolFlowRate = 0.0011d0 ! set to avoid errors in calc routine
END IF
IF ((.NOT. lAlphaFieldBlanks(8)) .OR. (.NOT. lAlphaFieldBlanks(9))) THEN
CALL ShowWarningError('Since Design Heat Flow Rate = 0.0, Heat Recovery inactive for '// &
TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
CALL ShowContinueError('However, Node names were specified for Heat Recovery inlet or outlet nodes')
END IF
END IF
! Basin heater power as a function of temperature must be greater than or equal to 0
ElectricChiller(ChillerNum)%Base%BasinHeaterPowerFTempDiff = rNumericArgs(23)
IF(rNumericArgs(23) .LT. 0.0d0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//', "'//TRIM(ElectricChiller(ChillerNum)%Base%Name)//&
'" TRIM(cNumericFieldNames(23)) must be >= 0')
ErrorsFound = .TRUE.
END IF
ElectricChiller(ChillerNum)%Base%BasinHeaterSetPointTemp = rNumericArgs(24)
IF(ElectricChiller(ChillerNum)%Base%BasinHeaterPowerFTempDiff .GT. 0.0d0) THEN
IF(NumNums .LT. 24) THEN
ElectricChiller(ChillerNum)%Base%BasinHeaterSetPointTemp = 2.0d0
ENDIF
IF(ElectricChiller(ChillerNum)%Base%BasinHeaterSetPointTemp < 2.0d0) THEN
CALL ShowWarningError(TRIM(cCurrentModuleObject)//':"'//TRIM(ElectricChiller(ChillerNum)%Base%Name)//&
'", '//TRIM(cNumericFieldNames(24))//' is less than 2 deg C. Freezing could occur.')
END IF
END IF
IF(.NOT. lAlphaFieldBlanks(10))THEN
ElectricChiller(ChillerNum)%Base%BasinHeaterSchedulePtr = GetScheduleIndex(cAlphaArgs(10))
IF(ElectricChiller(ChillerNum)%Base%BasinHeaterSchedulePtr .EQ. 0)THEN
CALL ShowWarningError(TRIM(cCurrentModuleObject)//', "'//TRIM(ElectricChiller(ChillerNum)%Base%Name)//&
'" TRIM(cAlphaFieldNames(10)) "'//TRIM(cAlphaArgs(10)) &
//'" was not found. Basin heater operation will not be modeled and the simulation continues')
END IF
END IF
END DO
IF (ErrorsFound) THEN
CALL ShowFatalError('Errors found in processing input for '// TRIM(cCurrentModuleObject) )
ENDIF
DO ChillerNum = 1, NumElectricChillers
CALL SetupOutputVariable('Chiller Electric Power [W]', &
ElectricChillerReport(ChillerNum)%Base%Power,'System','Average',ElectricChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Electric Energy [J]', &
ElectricChillerReport(ChillerNum)%Base%Energy,'System','Sum',ElectricChiller(ChillerNum)%Base%Name, &
ResourceTypeKey='ELECTRICITY',EndUseKey='Cooling',GroupKey='Plant')
CALL SetupOutputVariable('Chiller Evaporator Cooling Rate [W]', &
ElectricChillerReport(ChillerNum)%Base%QEvap,'System','Average',ElectricChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Evaporator Cooling Energy [J]', &
ElectricChillerReport(ChillerNum)%Base%EvapEnergy,'System','Sum',ElectricChiller(ChillerNum)%Base%Name, &
ResourceTypeKey='ENERGYTRANSFER',EndUseKey='CHILLERS',GroupKey='Plant')
CALL SetupOutputVariable('Chiller Evaporator Inlet Temperature [C]', &
ElectricChillerReport(ChillerNum)%Base%EvapInletTemp,'System','Average',ElectricChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Evaporator Outlet Temperature [C]', &
ElectricChillerReport(ChillerNum)%Base%EvapOutletTemp,'System','Average',ElectricChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Evaporator Mass Flow Rate [kg/s]', &
ElectricChillerReport(ChillerNum)%Base%Evapmdot,'System','Average',ElectricChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Condenser Heat Transfer Rate [W]', &
ElectricChillerReport(ChillerNum)%Base%QCond,'System','Average',ElectricChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Condenser Heat Transfer Energy [J]', &
ElectricChillerReport(ChillerNum)%Base%CondEnergy,'System','Sum',ElectricChiller(ChillerNum)%Base%Name, &
ResourceTypeKey='ENERGYTRANSFER',EndUseKey='HEATREJECTION',GroupKey='Plant')
CALL SetupOutputVariable('Chiller COP [W/W]', &
ElectricChillerReport(ChillerNum)%ActualCOP,'System','Average',ElectricChiller(ChillerNum)%Base%Name)
!Condenser mass flow and outlet temp are valid for water cooled
IF (ElectricChiller(ChillerNum)%Base%CondenserType == WaterCooled)THEN
CALL SetupOutputVariable('Chiller Condenser Inlet Temperature [C]', &
ElectricChillerReport(ChillerNum)%Base%CondInletTemp,'System','Average',ElectricChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Condenser Outlet Temperature [C]', &
ElectricChillerReport(ChillerNum)%Base%CondOutletTemp,'System','Average',ElectricChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Condenser Mass Flow Rate [kg/s]', &
ElectricChillerReport(ChillerNum)%Base%Condmdot,'System','Average',ElectricChiller(ChillerNum)%Base%Name)
ELSEIF (ElectricChiller(ChillerNum)%Base%CondenserType == AirCooled) THEN
CALL SetupOutputVariable('Chiller Condenser Inlet Temperature [C]', &
ElectricChillerReport(ChillerNum)%Base%CondInletTemp,'System','Average',ElectricChiller(ChillerNum)%Base%Name)
ELSEIF (ElectricChiller(ChillerNum)%Base%CondenserType == EvapCooled) THEN
CALL SetupOutputVariable('Chiller Condenser Inlet Temperature [C]', &
ElectricChillerReport(ChillerNum)%Base%CondInletTemp,'System','Average',ElectricChiller(ChillerNum)%Base%Name)
IF(ElectricChiller(ChillerNum)%Base%BasinHeaterPowerFTempDiff .GT. 0.0d0)THEN
CALL SetupOutputVariable('Chiller Basin Heater Electric Power [W]', &
ElectricChillerReport(ChillerNum)%Base%BasinHeaterPower,'System','Average',ElectricChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Basin Heater Electric Energy [J]', &
ElectricChillerReport(ChillerNum)%Base%BasinHeaterConsumption,'System','Sum',ElectricChiller(ChillerNum)%Base%Name, &
ResourceTypeKey='Electric',EndUseKey='CHILLERS',GroupKey='Plant')
END IF
ENDIF
!If heat recovery is active then setup report variables
IF (ElectricChiller(ChillerNum)%HeatRecActive) THEN
CALL SetupOutputVariable('Chiller Total Recovered Heat Rate [W]', &
ElectricChillerReport(ChillerNum)%QHeatRecovery,'System','Average',ElectricChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Total Recovered Heat Energy [J]', &
ElectricChillerReport(ChillerNum)%EnergyHeatRecovery,'System','Sum',ElectricChiller(ChillerNum)%Base%Name, &
ResourceTypeKey='ENERGYTRANSFER',EndUseKey='HEATRECOVERY',GroupKey='Plant')
CALL SetupOutputVariable('Chiller Heat Recovery Inlet Temperature [C]', &
ElectricChillerReport(ChillerNum)%HeatRecInletTemp,'System','Average',ElectricChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Heat Recovery Outlet Temperature [C]', &
ElectricChillerReport(ChillerNum)%HeatRecOutletTemp,'System','Average',ElectricChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Heat Recovery Mass Flow Rate [kg/s]', &
ElectricChillerReport(ChillerNum)%HeatRecMassFlow,'System','Average',ElectricChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Effective Heat Rejection Temperature [C]', &
ElectricChillerReport(ChillerNum)%ChillerCondAvgTemp, 'System','Average',ElectricChiller(ChillerNum)%Base%Name)
ENDIF
IF (AnyEnergyManagementSystemInModel) THEN
CALL SetupEMSInternalVariable('Chiller Nominal Capacity', ElectricChiller(ChillerNum)%Base%Name, '[W]', &
ElectricChiller(ChillerNum)%Base%NomCap )
ENDIF
END DO
RETURN
END SUBROUTINE GetElectricChillerInput