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 GetEngineDrivenChillerInput
! SUBROUTINE INFORMATION:
! AUTHOR: Dan Fisher / Brandon Anderson
! DATE WRITTEN: September 2000
!
! PURPOSE OF THIS SUBROUTINE:
! This routine will get the input
! required by the EngineDriven Chiller model.
! METHODOLOGY EMPLOYED:
! REFERENCES: na
! USE STATEMENTS:
USE InputProcessor, ONLY : GetNumObjectsFound, GetObjectItem, VerifyName
USE DataIPShortCuts ! Data for field names, blank numerics
USE CurveManager, ONLY : GetCurveIndex
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 DataGlobals, ONLY: AnyEnergyManagementSystemInModel
IMPLICIT NONE !
! PARAMETERS
CHARACTER(len=*), PARAMETER :: RoutineName='GetEngineDrivenChillerInput: ' ! 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
LOGICAL, SAVE :: ErrorsFound=.false.
LOGICAL :: IsNotOK ! Flag to verify name
LOGICAL :: IsBlank ! Flag for blank name
LOGICAL :: errflag
LOGICAL :: Okay
!FLOW
cCurrentModuleObject = 'Chiller:EngineDriven'
NumEngineDrivenChillers = GetNumObjectsFound(cCurrentModuleObject)
IF (NumEngineDrivenChillers <= 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(EngineDrivenChiller))RETURN
!ALLOCATE ARRAYS
ALLOCATE (EngineDrivenChiller(NumEngineDrivenChillers))
ALLOCATE (EngineDrivenChillerReport(NumEngineDrivenChillers))
!LOAD ARRAYS WITH EngineDriven CURVE FIT CHILLER DATA
DO ChillerNum = 1 , NumEngineDrivenChillers
CALL GetObjectItem(cCurrentModuleObject,ChillerNum,cAlphaArgs,NumAlphas, &
rNumericArgs,NumNums,IOSTAT,AlphaBlank=lAlphaFieldBlanks, &
AlphaFieldnames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
IsNotOK=.false.
IsBlank=.false.
CALL VerifyName(cAlphaArgs(1),EngineDrivenChiller%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
EngineDrivenChiller(ChillerNum)%Base%Name = cAlphaArgs(1)
EngineDrivenChiller(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
EngineDrivenChiller(ChillerNum)%Base%COP = rNumericArgs(2)
IF (rNumericArgs(2) == 0.0d0) THEN
CALL ShowSevereError('Invalid '//TRIM(cNumericFieldNames(2))//'='//TRIM(RoundSigDigits(rNumericArgs(2),2)))
CALL ShowContinueError('Entered in '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
ErrorsFound=.true.
ENDIF
IF (cAlphaArgs(2) == 'AIRCOOLED' ) THEN
EngineDrivenChiller(ChillerNum)%Base%CondenserType = AirCooled
ELSEIF (cAlphaArgs(2) == 'WATERCOOLED' ) THEN
EngineDrivenChiller(ChillerNum)%Base%CondenserType = WaterCooled
ELSEIF (cAlphaArgs(2) == 'EVAPORATIVELYCOOLED' ) THEN
EngineDrivenChiller(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
EngineDrivenChiller(ChillerNum)%Base%EvapInletNodeNum = &
GetOnlySingleNode(cAlphaArgs(3),ErrorsFound,TRIM(cCurrentModuleObject),cAlphaArgs(1), &
NodeType_Water,NodeConnectionType_Inlet, 1, ObjectIsNotParent)
EngineDrivenChiller(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 (EngineDrivenChiller(ChillerNum)%Base%CondenserType == AirCooled .or. &
EngineDrivenChiller(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
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
EngineDrivenChiller(ChillerNum)%Base%CondInletNodeNum = &
GetOnlySingleNode(cAlphaArgs(5),ErrorsFound,TRIM(cCurrentModuleObject),cAlphaArgs(1), &
NodeType_Air,NodeConnectionType_OutsideAirReference, 2, ObjectIsNotParent)
CALL CheckAndAddAirNodeNumber(EngineDrivenChiller(ChillerNum)%Base%CondInletNodeNum,Okay)
IF (.not. Okay) THEN
CALL ShowWarningError(TRIM(cCurrentModuleObject)//', Adding OutdoorAir:Node='//TRIM(cAlphaArgs(5)))
ENDIF
EngineDrivenChiller(ChillerNum)%Base%CondOutletNodeNum = &
GetOnlySingleNode(cAlphaArgs(6),ErrorsFound,TRIM(cCurrentModuleObject),cAlphaArgs(1), &
NodeType_Air,NodeConnectionType_Outlet, 2, ObjectIsNotParent)
!CALL TestCompSet(TRIM(cCurrentModuleObject),cAlphaArgs(1),cAlphaArgs(5),cAlphaArgs(6),'Condenser (Air) Nodes')
ELSEIF (EngineDrivenChiller(ChillerNum)%Base%CondenserType == WaterCooled) THEN
EngineDrivenChiller(ChillerNum)%Base%CondInletNodeNum = &
GetOnlySingleNode(cAlphaArgs(5),ErrorsFound,TRIM(cCurrentModuleObject),cAlphaArgs(1), &
NodeType_Water,NodeConnectionType_Inlet, 2, ObjectIsNotParent)
EngineDrivenChiller(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
EngineDrivenChiller(ChillerNum)%Base%CondInletNodeNum = &
GetOnlySingleNode(cAlphaArgs(5),ErrorsFound,TRIM(cCurrentModuleObject),cAlphaArgs(1), &
NodeType_Unknown,NodeConnectionType_Inlet, 2, ObjectIsNotParent)
EngineDrivenChiller(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 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
ENDIF
EngineDrivenChiller(ChillerNum)%MinPartLoadRat = rNumericArgs(3)
EngineDrivenChiller(ChillerNum)%MaxPartLoadRat = rNumericArgs(4)
EngineDrivenChiller(ChillerNum)%OptPartLoadRat = rNumericArgs(5)
EngineDrivenChiller(ChillerNum)%TempDesCondIn = rNumericArgs(6)
EngineDrivenChiller(ChillerNum)%TempRiseCoef = rNumericArgs(7)
EngineDrivenChiller(ChillerNum)%TempDesEvapOut = rNumericArgs(8)
EngineDrivenChiller(ChillerNum)%Base%EvapVolFlowRate = rNumericArgs(9)
EngineDrivenChiller(ChillerNum)%Base%CondVolFlowRate = rNumericArgs(10)
EngineDrivenChiller(ChillerNum)%CapRatCoef(1) = rNumericArgs(11)
EngineDrivenChiller(ChillerNum)%CapRatCoef(2) = rNumericArgs(12)
EngineDrivenChiller(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
EngineDrivenChiller(ChillerNum)%PowerRatCoef(1) = rNumericArgs(14)
EngineDrivenChiller(ChillerNum)%PowerRatCoef(2) = rNumericArgs(15)
EngineDrivenChiller(ChillerNum)%PowerRatCoef(3) = rNumericArgs(16)
EngineDrivenChiller(ChillerNum)%FullLoadCoef(1) = rNumericArgs(17)
EngineDrivenChiller(ChillerNum)%FullLoadCoef(2) = rNumericArgs(18)
EngineDrivenChiller(ChillerNum)%FullLoadCoef(3) = rNumericArgs(19)
EngineDrivenChiller(ChillerNum)%TempLowLimitEvapOut = rNumericArgs(20)
!Load Special EngineDriven Chiller Curve Fit Inputs
EngineDrivenChiller(ChillerNum)%ClngLoadtoFuelCurve = GetCurveIndex(cAlphaArgs(7)) ! convert curve name to number
IF (EngineDrivenChiller(ChillerNum)%ClngLoadtoFuelCurve .EQ. 0) THEN
CALL ShowSevereError('Invalid '//TRIM(cAlphaFieldNames(7))//'='//TRIM(cAlphaArgs(7)))
CALL ShowContinueError('Entered in '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
ErrorsFound = .TRUE.
END IF
EngineDrivenChiller(ChillerNum)%RecJacHeattoFuelCurve = GetCurveIndex(cAlphaArgs(8)) ! convert curve name to number
IF (EngineDrivenChiller(ChillerNum)%RecJacHeattoFuelCurve .EQ. 0) THEN
CALL ShowSevereError('Invalid '//TRIM(cAlphaFieldNames(8))//'='//TRIM(cAlphaArgs(8)))
CALL ShowContinueError('Entered in '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
ErrorsFound = .TRUE.
END IF
EngineDrivenChiller(ChillerNum)%RecLubeHeattoFuelCurve = GetCurveIndex(cAlphaArgs(9)) ! convert curve name to number
IF (EngineDrivenChiller(ChillerNum)%RecLubeHeattoFuelCurve .EQ. 0) THEN
CALL ShowSevereError('Invalid '//TRIM(cAlphaFieldNames(9))//'='//TRIM(cAlphaArgs(9)))
CALL ShowContinueError('Entered in '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
ErrorsFound = .TRUE.
END IF
EngineDrivenChiller(ChillerNum)%TotExhausttoFuelCurve = GetCurveIndex(cAlphaArgs(10)) ! convert curve name to number
IF (EngineDrivenChiller(ChillerNum)%TotExhausttoFuelCurve .EQ. 0) THEN
CALL ShowSevereError('Invalid '//TRIM(cAlphaFieldNames(10))//'='//TRIM(cAlphaArgs(10)))
CALL ShowContinueError('Entered in '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
ErrorsFound = .TRUE.
END IF
EngineDrivenChiller(ChillerNum)%ExhaustTempCurve = GetCurveIndex(cAlphaArgs(11)) ! convert curve name to number
IF (EngineDrivenChiller(ChillerNum)%ExhaustTempCurve .EQ. 0) THEN
CALL ShowSevereError('Invalid '//TRIM(cAlphaFieldNames(11))//'='//TRIM(cAlphaArgs(11)))
CALL ShowContinueError('Entered in '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
ErrorsFound = .TRUE.
END IF
EngineDrivenChiller(ChillerNum)%UACoef(1) = rNumericArgs(21)
EngineDrivenChiller(ChillerNum)%UACoef(2) = rNumericArgs(22)
EngineDrivenChiller(ChillerNum)%MaxExhaustperPowerOutput = rNumericArgs(23)
EngineDrivenChiller(ChillerNum)%DesignMinExitGasTemp = rNumericArgs(24)
EngineDrivenChiller(ChillerNum)%FuelType = TRIM(cAlphaArgs(12))
SELECT CASE (cAlphaArgs(12))
CASE ('Gas','NATURALGAS','NATURAL GAS')
EngineDrivenChiller(ChillerNum)%FuelType = 'Gas'
CASE ('DIESEL')
EngineDrivenChiller(ChillerNum)%FuelType = 'Diesel'
CASE ('GASOLINE')
EngineDrivenChiller(ChillerNum)%FuelType = 'Gasoline'
CASE ('FUEL OIL #1','FUELOIL#1','FUEL OIL','DISTILLATE OIL')
EngineDrivenChiller(ChillerNum)%FuelType = 'FuelOil#1'
CASE ('FUEL OIL #2','FUELOIL#2','RESIDUAL OIL')
EngineDrivenChiller(ChillerNum)%FuelType = 'FuelOil#2'
CASE ('Propane','LPG','PROPANEGAS','PROPANE GAS')
EngineDrivenChiller(ChillerNum)%FuelType = 'Propane'
CASE ('OTHERFUEL1')
EngineDrivenChiller(ChillerNum)%FuelType = 'OtherFuel1'
CASE ('OTHERFUEL2')
EngineDrivenChiller(ChillerNum)%FuelType = 'OtherFuel2'
CASE DEFAULT
CALL ShowSevereError('Invalid '//TRIM(cAlphaFieldNames(12))//'='//TRIM(cAlphaArgs(12)))
CALL ShowContinueError('Entered in '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
CALL ShowContinueError('Valid choices are Electricity, NaturalGas, PropaneGas, Diesel, Gasoline, FuelOil#1, FuelOil#2,'// &
'OtherFuel1 or OtherFuel2')
ErrorsFound=.true.
END SELECT
EngineDrivenChiller(ChillerNum)%FuelHeatingValue = rNumericArgs(25)
EngineDrivenChiller(ChillerNum)%DesignHeatRecVolFlowRate = rNumericArgs(26)
IF (EngineDrivenChiller(ChillerNum)%DesignHeatRecVolFlowRate > 0.0d0) THEN
EngineDrivenChiller(ChillerNum)%HeatRecActive=.true.
EngineDrivenChiller(ChillerNum)%HeatRecInletNodeNum = &
GetOnlySingleNode(cAlphaArgs(13),ErrorsFound,TRIM(cCurrentModuleObject),cAlphaArgs(1), &
NodeType_Water,NodeConnectionType_Inlet, 3, ObjectIsNotParent)
IF (EngineDrivenChiller(ChillerNum)%HeatRecInletNodeNum == 0) THEN
CALL ShowSevereError('Invalid '//TRIM(cAlphaFieldNames(13))//'='//TRIM(cAlphaArgs(13)))
CALL ShowContinueError('Entered in '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
ErrorsFound=.true.
ENDIF
EngineDrivenChiller(ChillerNum)%HeatRecOutletNodeNum = &
GetOnlySingleNode(cAlphaArgs(14),ErrorsFound,TRIM(cCurrentModuleObject),cAlphaArgs(1), &
NodeType_Water,NodeConnectionType_Outlet, 3, ObjectIsNotParent)
IF (EngineDrivenChiller(ChillerNum)%HeatRecOutletNodeNum == 0) THEN
CALL ShowSevereError('Invalid '//TRIM(cAlphaFieldNames(14))//'='//TRIM(cAlphaArgs(14)))
CALL ShowContinueError('Entered in '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
ErrorsFound=.true.
ENDIF
CALL TestCompSet(TRIM(cCurrentModuleObject),cAlphaArgs(1),cAlphaArgs(13),cAlphaArgs(14),'Heat Recovery Nodes')
CALL RegisterPlantCompDesignFlow(EngineDrivenChiller(ChillerNum)%HeatRecInletNodeNum, &
EngineDrivenChiller(ChillerNum)%DesignHeatRecVolFlowRate)
! Condenser flow rate must be specified for heat reclaim
IF (EngineDrivenChiller(ChillerNum)%Base%CondenserType == AirCooled .OR. &
EngineDrivenChiller(ChillerNum)%Base%CondenserType == EvapCooled) THEN
IF(EngineDrivenChiller(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
ELSE
EngineDrivenChiller(ChillerNum)%HeatRecActive=.false.
EngineDrivenChiller(ChillerNum)%DesignHeatRecMassFlowRate = 0.0d0
EngineDrivenChiller(ChillerNum)%HeatRecInletNodeNum = 0
EngineDrivenChiller(ChillerNum)%HeatRecOutletNodeNum = 0
! if heat recovery is not used, don't care about condenser flow rate for air/evap-cooled equip.
IF (EngineDrivenChiller(ChillerNum)%Base%CondenserType == AirCooled .OR. &
EngineDrivenChiller(ChillerNum)%Base%CondenserType == EvapCooled) THEN
EngineDrivenChiller(ChillerNum)%Base%CondVolFlowRate = 0.0011d0 ! set to avoid errors in calc routine
END IF
IF ((.NOT. lAlphaFieldBlanks(13)) .OR. (.NOT. lAlphaFieldBlanks(14))) 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')
ENDIF
ENDIF
SELECT CASE (TRIM(cAlphaArgs(15)))
CASE ( 'CONSTANTFLOW' )
EngineDrivenChiller(ChillerNum)%Base%FlowMode = ConstantFlow
CASE ( 'VARIABLEFLOW' )
EngineDrivenChiller(ChillerNum)%Base%FlowMode = LeavingSetpointModulated
CALL ShowWarningError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//'",')
CALL ShowContinueError('Invalid '//TRIM(cAlphaFieldNames(15))//'='//TRIM(cAlphaArgs(15)))
CALL ShowContinueError('Key choice is now called "LeavingSetpointModulated" and the simulation continues')
CASE ('LEAVINGSETPOINTMODULATED')
EngineDrivenChiller(ChillerNum)%Base%FlowMode = LeavingSetpointModulated
CASE ('NOTMODULATED')
EngineDrivenChiller(ChillerNum)%Base%FlowMode = NotModulated
CASE DEFAULT
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//'",')
CALL ShowContinueError('Invalid '//TRIM(cAlphaFieldNames(15))//'='//TRIM(cAlphaArgs(15)))
CALL ShowContinueError('Available choices are ConstantFlow, NotModulated, or LeavingSetpointModulated')
CALL ShowContinueError('Flow mode NotModulated is assumed and the simulation continues.')
EngineDrivenChiller(ChillerNum)%Base%FlowMode = NotModulated
END SELECT
EngineDrivenChiller(ChillerNum)%HeatRecMaxTemp = rNumericArgs(27)
EngineDrivenChiller(ChillerNum)%Base%SizFac = rNumericArgs(28)
IF (EngineDrivenChiller(ChillerNum)%Base%SizFac <= 0.0d0) EngineDrivenChiller(ChillerNum)%Base%SizFac = 1.0d0
! Basin heater power as a function of temperature must be greater than or equal to 0
EngineDrivenChiller(ChillerNum)%Base%BasinHeaterPowerFTempDiff = rNumericArgs(29)
IF(rNumericArgs(29) .LT. 0.0d0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//', "'//TRIM(EngineDrivenChiller(ChillerNum)%Base%Name)//&
'" TRIM(cNumericFieldNames(29)) must be >= 0')
ErrorsFound = .TRUE.
END IF
EngineDrivenChiller(ChillerNum)%Base%BasinHeaterSetPointTemp = rNumericArgs(30)
IF(EngineDrivenChiller(ChillerNum)%Base%BasinHeaterPowerFTempDiff .GT. 0.0d0) THEN
IF(NumNums .LT. 30) THEN
EngineDrivenChiller(ChillerNum)%Base%BasinHeaterSetPointTemp = 2.0d0
ENDIF
IF(EngineDrivenChiller(ChillerNum)%Base%BasinHeaterSetPointTemp < 2.0d0) THEN
CALL ShowWarningError(TRIM(cCurrentModuleObject)//':"'//TRIM(EngineDrivenChiller(ChillerNum)%Base%Name)//&
'", '//TRIM(cNumericFieldNames(30))//' is less than 2 deg C. Freezing could occur.')
END IF
END IF
IF(.NOT. lAlphaFieldBlanks(16))THEN
EngineDrivenChiller(ChillerNum)%Base%BasinHeaterSchedulePtr = GetScheduleIndex(cAlphaArgs(16))
IF(EngineDrivenChiller(ChillerNum)%Base%BasinHeaterSchedulePtr .EQ. 0)THEN
CALL ShowWarningError(TRIM(cCurrentModuleObject)//', "'//TRIM(EngineDrivenChiller(ChillerNum)%Base%Name)//&
'" TRIM(cAlphaFieldNames(16)) "'//TRIM(cAlphaArgs(16)) &
//'" 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, NumEngineDrivenChillers
CALL SetupOutputVariable('Chiller Drive Shaft Power [W]', &
EngineDrivenChillerReport(ChillerNum)%Base%Power,'System','Average',EngineDrivenChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Drive Shaft Energy [J]', &
EngineDrivenChillerReport(ChillerNum)%Base%Energy,'System','Sum',EngineDrivenChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Evaporator Cooling Rate [W]', &
EngineDrivenChillerReport(ChillerNum)%Base%QEvap,'System','Average',EngineDrivenChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Evaporator Cooling Energy [J]', &
EngineDrivenChillerReport(ChillerNum)%Base%EvapEnergy,'System','Sum',EngineDrivenChiller(ChillerNum)%Base%Name, &
ResourceTypeKey='ENERGYTRANSFER',EndUseKey='CHILLERS',GroupKey='Plant')
CALL SetupOutputVariable('Chiller Evaporator Inlet Temperature [C]', &
EngineDrivenChillerReport(ChillerNum)%Base%EvapInletTemp,'System','Average',EngineDrivenChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Evaporator Outlet Temperature [C]', &
EngineDrivenChillerReport(ChillerNum)%Base%EvapOutletTemp,'System','Average',EngineDrivenChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Evaporator Mass Flow Rate [kg/s]', &
EngineDrivenChillerReport(ChillerNum)%Base%Evapmdot,'System','Average',EngineDrivenChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Condenser Heat Transfer Rate [W]', &
EngineDrivenChillerReport(ChillerNum)%Base%QCond,'System','Average',EngineDrivenChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Condenser Heat Transfer Energy [J]', &
EngineDrivenChillerReport(ChillerNum)%Base%CondEnergy,'System','Sum',EngineDrivenChiller(ChillerNum)%Base%Name, &
ResourceTypeKey='ENERGYTRANSFER',EndUseKey='HEATREJECTION',GroupKey='Plant')
!Condenser mass flow and outlet temp are valid for Water Cooled
IF (EngineDrivenChiller(ChillerNum)%Base%CondenserType == WaterCooled)THEN
CALL SetupOutputVariable('Chiller Condenser Inlet Temperature [C]', &
EngineDrivenChillerReport(ChillerNum)%Base%CondInletTemp,'System','Average',EngineDrivenChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Condenser Outlet Temperature [C]', &
EngineDrivenChillerReport(ChillerNum)%Base%CondOutletTemp,'System','Average',EngineDrivenChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Condenser Mass Flow Rate [kg/s]', &
EngineDrivenChillerReport(ChillerNum)%Base%Condmdot,'System','Average',EngineDrivenChiller(ChillerNum)%Base%Name)
ELSEIF (EngineDrivenChiller(ChillerNum)%Base%CondenserType == AirCooled) THEN
CALL SetupOutputVariable('Chiller Condenser Inlet Temperature [C]', &
EngineDrivenChillerReport(ChillerNum)%Base%CondInletTemp,'System','Average',EngineDrivenChiller(ChillerNum)%Base%Name)
ELSEIF (EngineDrivenChiller(ChillerNum)%Base%CondenserType == EvapCooled) THEN
CALL SetupOutputVariable('Chiller Condenser Inlet Temperature [C]', &
EngineDrivenChillerReport(ChillerNum)%Base%CondInletTemp,'System','Average',EngineDrivenChiller(ChillerNum)%Base%Name)
IF(EngineDrivenChiller(ChillerNum)%Base%BasinHeaterPowerFTempDiff .GT. 0.0d0)THEN
CALL SetupOutputVariable('Chiller Basin Heater Electric Power [W]', &
EngineDrivenChillerReport(ChillerNum)%Base%BasinHeaterPower,'System','Average',EngineDrivenChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Basin Heater Electric Energy [J]', &
EngineDrivenChillerReport(ChillerNum)%Base%BasinHeaterConsumption,'System','Sum', &
EngineDrivenChiller(ChillerNum)%Base%Name, &
ResourceTypeKey='Electric',EndUseKey='CHILLERS',GroupKey='Plant')
END IF
End IF
CALL SetupOutputVariable('Chiller ' // TRIM(EngineDrivenChiller(ChillerNum)%FuelType) //' Rate [W]', &
EngineDrivenChillerReport(ChillerNum)%FuelEnergyUseRate,'System','Average',EngineDrivenChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller ' // TRIM(EngineDrivenChiller(ChillerNum)%FuelType) //' Energy [J]', &
EngineDrivenChillerReport(ChillerNum)%FuelEnergy,'System','Sum',EngineDrivenChiller(ChillerNum)%Base%Name, &
ResourceTypeKey=EngineDrivenChiller(ChillerNum)%FuelType,EndUseKey='Cooling',GroupKey='Plant')
CALL SetupOutputVariable('Chiller COP [W/W]', &
EngineDrivenChillerReport(ChillerNum)%FuelCOP,'System','Average',EngineDrivenChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller ' // TRIM(EngineDrivenChiller(ChillerNum)%FuelType) //' Mass Flow Rate [kg/s]', &
EngineDrivenChillerReport(ChillerNum)%FuelMdot,'System','Average',EngineDrivenChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Exhaust Temperature [C]', &
EngineDrivenChillerReport(ChillerNum)%ExhaustStackTemp,'System','Average',EngineDrivenChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Heat Recovery Mass Flow Rate [kg/s]', &
EngineDrivenChillerReport(ChillerNum)%HeatRecMdot,'System','Average',EngineDrivenChiller(ChillerNum)%Base%Name)
IF (EngineDrivenChiller(ChillerNum)%HeatRecActive) THEN
! need to only report if heat recovery active
CALL SetupOutputVariable('Chiller Jacket Recovered Heat Rate [W]', &
EngineDrivenChillerReport(ChillerNum)%QJacketRecovered,'System','Average',EngineDrivenChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Jacket Recovered Heat Energy [J]', &
EngineDrivenChillerReport(ChillerNum)%JacketEnergyRec,'System','Sum',EngineDrivenChiller(ChillerNum)%Base%Name, &
ResourceTypeKey='ENERGYTRANSFER',EndUseKey='HEATRECOVERY',GroupKey='Plant')
CALL SetupOutputVariable('Chiller Lube Recovered Heat Rate [W]', &
EngineDrivenChillerReport(ChillerNum)%QLubeOilRecovered,'System','Average',EngineDrivenChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Lube Recovered Heat Energy [J]', &
EngineDrivenChillerReport(ChillerNum)%LubeOilEnergyRec,'System','Sum',EngineDrivenChiller(ChillerNum)%Base%Name, &
ResourceTypeKey='ENERGYTRANSFER',EndUseKey='HEATRECOVERY',GroupKey='Plant')
CALL SetupOutputVariable('Chiller Exhaust Recovered Heat Rate [W]', &
EngineDrivenChillerReport(ChillerNum)%QExhaustRecovered,'System','Average',EngineDrivenChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Exhaust Recovered Heat Energy [J]', &
EngineDrivenChillerReport(ChillerNum)%ExhaustEnergyRec,'System','Sum',EngineDrivenChiller(ChillerNum)%Base%Name, &
ResourceTypeKey='ENERGYTRANSFER',EndUseKey='HEATRECOVERY',GroupKey='Plant')
CALL SetupOutputVariable('Chiller Total Recovered Heat Rate [W]', &
EngineDrivenChillerReport(ChillerNum)%QTotalHEatRecovered,'System','Average',EngineDrivenChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Total Recovered Heat Energy [J]', &
EngineDrivenChillerReport(ChillerNum)%TotalHeatEnergyRec,'System','Sum',EngineDrivenChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Heat Recovery Inlet Temperature [C]', &
EngineDrivenChillerReport(ChillerNum)%HeatRecInletTemp,'System','Average',EngineDrivenChiller(ChillerNum)%Base%Name)
CALL SetupOutputVariable('Chiller Heat Recovery Outlet Temperature [C]', &
EngineDrivenChillerReport(ChillerNum)%HeatRecOutletTemp,'System','Average',EngineDrivenChiller(ChillerNum)%Base%Name)
ENDIF
IF (AnyEnergyManagementSystemInModel) THEN
CALL SetupEMSInternalVariable('Chiller Nominal Capacity', EngineDrivenChiller(ChillerNum)%Base%Name, '[W]', &
EngineDrivenChiller(ChillerNum)%Base%NomCap )
ENDIF
END DO
RETURN
END SUBROUTINE GetEngineDrivenChillerInput