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, | intent(in) | :: | EIRChillNum |
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 SizeElecReformEIRChiller(EIRChillNum)
! SUBROUTINE INFORMATION:
! AUTHOR Richard Raustad, FSEC
! DATE WRITTEN June 2004
! MODIFIED July 2006, L. Gu, modified for reformulated EIR chiller
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine is for sizing Reformulated Electric EIR Chiller Components for which capacities and flow rates
! have not been specified in the input.
! METHODOLOGY EMPLOYED:
! Obtains evaporator flow rate from the plant sizing array. Calculates reference capacity from
! the evaporator flow rate and the chilled water loop design delta T. The condenser flow rate
! is calculated from the reference capacity, the COP, and the condenser loop design delta T.
! REFERENCES:
! na
! USE STATEMENTS:
USE DataSizing
USE DataPlant, ONLY: PlantLoop, PlantSizesOkayToFinalize, TypeOf_Chiller_ElectricReformEIR
USE PlantUtilities, ONLY: RegisterPlantCompDesignFlow
USE ReportSizingManager, ONLY: ReportSizingOutput
USE CurveManager, ONLY: CurveValue, GetCurveMinMaxValues
USE OutputReportPredefined
USE ReportSizingManager, ONLY: ReportSizingOutput
USE StandardRatings, ONLY: CalcChillerIPLV
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: EIRChillNum
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: PltSizNum ! Plant Sizing index corresponding to CurLoopNum
INTEGER :: PltSizCondNum ! Plant Sizing index for condenser loop
LOGICAL :: ErrorsFound ! If errors detected in input
LOGICAL :: LoopErrorsFound ! Plant loop errors found
REAL(r64) :: SizingEvapOutletTemp ! Plant Sizing outlet temperature for CurLoopNum [C]
REAL(r64) :: SizingCondOutletTemp ! Plant Sizing outlet temperature for condenser loop [C]
REAL(r64) :: RefCAPFT ! Capacity as a function of temperature curve output used for sizing
CHARACTER(len=MaxNameLength) :: equipName ! Name of chiller
REAL(r64) :: CurveVal ! Used to verify EIR-FT/CAP-FT curves = 1 at reference conditions
REAL(r64) :: CondTemp ! Used to verify EIRFPLR curve is > than 0 at reference conditions
LOGICAL :: FoundNegValue = .FALSE. ! Used to evaluate EIRFPLR curve objects
INTEGER :: CurveCheck = 0 ! Used to evaluate EIRFPLR curve objects
REAL(r64), DIMENSION(11) :: CurveValArray ! Used to evaluate EIRFPLR curve objects
REAL(r64), DIMENSION(11) :: CondTempArray ! Used to evaluate EIRFPLR curve objects
REAL(r64) :: CurveValTmp ! Used to evaluate EIRFPLR curve objects
REAL(r64) :: Density ! Density of condenser water used in warning messages
REAL(r64) :: SpecificHeat ! Specific heat of condenser water used in warning messages
REAL(r64) :: CondenserCapacity ! Full load (reference) condenser capacity used in warning messages
CHARACTER(len=132) :: StringVar ! Used for EIRFPLR warning messages
INTEGER :: CurveValPtr ! Index to EIRFPLR curve output
REAL(r64) :: DeltaTCond ! Full load delta T at condenser, used for checking curve objects
REAL(r64) :: PLRTemp ! Temporary variable used for warning messages
REAL(r64) :: rho
REAL(r64) :: Cp
REAL(r64) :: tmpNomCap ! local nominal capacity cooling power
REAL(r64) :: tmpEvapVolFlowRate ! local evaporator design volume flow rate
REAL(r64) :: tmpCondVolFlowRate ! local condenser design volume flow rate
REAL(r64) :: tmpHeatRecVolFlowRate ! local heat recovery design volume flow rate
LOGICAL, SAVE :: MyOneTimeFlag = .TRUE.
LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: MyFlag ! TRUE in order to calculate IPLV
IF (MyOneTimeFlag) THEN
ALLOCATE(MyFlag(NumElecReformEIRChillers))
MyFlag = .TRUE.
MyOneTimeFlag = .FALSE.
END IF
PltSizNum = 0
PltSizCondNum = 0
ErrorsFound = .FALSE.
tmpNomCap = ElecReformEIRChiller(EIRChillNum)%RefCap
tmpEvapVolFlowRate = ElecReformEIRChiller(EIRChillNum)%EvapVolFlowRate
tmpCondVolFlowRate = ElecReformEIRChiller(EIRChillNum)%CondVolFlowRate
IF (ElecReformEIRChiller(EIRChillNum)%CondVolFlowRate == AutoSize) THEN
PltSizCondNum = PlantLoop(ElecReformEIRChiller(EIRChillNum)%CDLoopNum)%PlantSizNum
END IF
! find the appropriate Plant Sizing object
PltSizNum = PlantLoop(ElecReformEIRChiller(EIRChillNum)%CWLoopNum)%PlantSizNum
IF (ElecReformEIRChiller(EIRChillNum)%EvapVolFlowRate == AutoSize) THEN
IF (PltSizNum > 0) THEN
IF (PlantSizData(PltSizNum)%DesVolFlowRate >= SmallWaterVolFlow) THEN
tmpEvapVolFlowRate = PlantSizData(PltSizNum)%DesVolFlowRate * &
ElecReformEIRChiller(EIRChillNum)%SizFac
IF (PlantSizesOkayToFinalize) ElecReformEIRChiller(EIRChillNum)%EvapVolFlowRate = tmpEvapVolFlowRate
ELSE
tmpEvapVolFlowRate = 0.d0
IF (PlantSizesOkayToFinalize) ElecReformEIRChiller(EIRChillNum)%EvapVolFlowRate = tmpEvapVolFlowRate
END IF
IF (PlantSizesOkayToFinalize) CALL ReportSizingOutput('Chiller:Electric:ReformulatedEIR', &
ElecReformEIRChiller(EIRChillNum)%Name, &
'Reference Chilled Water Flow Rate [m3/s]', &
ElecReformEIRChiller(EIRChillNum)%EvapVolFlowRate)
ELSE
CALL ShowSevereError('Autosizing of Reformulated Electric Chiller evap flow rate requires a loop Sizing:Plant object')
CALL ShowContinueError('Occurs in Reformulated Electric Chiller object='//TRIM(ElecReformEIRChiller(EIRChillNum)%Name))
ErrorsFound = .TRUE.
END IF
END IF
CALL RegisterPlantCompDesignFlow(ElecReformEIRChiller(EIRChillNum)%EvapInletNodeNum,tmpEvapVolFlowRate)
IF (ElecReformEIRChiller(EIRChillNum)%RefCap == AutoSize) THEN
IF (PltSizNum > 0) THEN
IF (PlantSizData(PltSizNum)%DesVolFlowRate >= SmallWaterVolFlow) THEN
IF(PltSizCondNum > 0)THEN
SizingEvapOutletTemp = PlantSizData(PltSizNum)%ExitTemp
SizingCondOutletTemp = PlantSizData(PltSizCondNum)%ExitTemp + PlantSizData(PltSizCondNum)%DeltaT
ELSE
SizingEvapOutletTemp = ElecReformEIRChiller(EIRChillNum)%TempRefEvapOut
SizingCondOutletTemp = ElecReformEIRChiller(EIRChillNum)%TempRefCondOut
END IF
Cp = GetSpecificHeatGlycol(PlantLoop(ElecReformEIRChiller(EIRChillNum)%CWLoopNum)%FluidName, &
InitConvTemp, &
PlantLoop(ElecReformEIRChiller(EIRChillNum)%CWLoopNum)%FluidIndex, &
'SizeElecReformEIRChiller')
rho = GetDensityGlycol(PlantLoop(ElecReformEIRChiller(EIRChillNum)%CWLoopNum)%FluidName, &
InitConvTemp, &
PlantLoop(ElecReformEIRChiller(EIRChillNum)%CWLoopNum)%FluidIndex,&
'SizeElecReformEIRChiller')
RefCapFT = CurveValue(ElecReformEIRChiller(EIRChillNum)%ChillerCapFT, SizingEvapOutletTemp,SizingCondOutletTemp)
tmpNomCap = (Cp * rho * PlantSizData(PltSizNum)%DeltaT * tmpEvapVolFlowRate) / RefCapFT
IF (PlantSizesOkayToFinalize) ElecReformEIRChiller(EIRChillNum)%RefCap = tmpNomCap
ELSE
tmpNomCap = 0.d0
IF (PlantSizesOkayToFinalize) ElecReformEIRChiller(EIRChillNum)%RefCap = tmpNomCap
END IF
IF (PlantSizesOkayToFinalize) &
CALL ReportSizingOutput('Chiller:Electric:ReformulatedEIR', ElecReformEIRChiller(EIRChillNum)%Name, &
'Reference Capacity [W]', ElecReformEIRChiller(EIRChillNum)%RefCap)
ELSE
CALL ShowSevereError('Autosizing of Reformulated Electric Chiller reference capacity requires a loop Sizing:Plant object')
CALL ShowContinueError('Occurs in Reformulated Electric Chiller object='//TRIM(ElecReformEIRChiller(EIRChillNum)%Name))
ErrorsFound = .TRUE.
END IF
END IF
IF (ElecReformEIRChiller(EIRChillNum)%CondVolFlowRate == AutoSize) THEN
IF (PltSizCondNum > 0) THEN
IF (PlantSizData(PltSizNum)%DesVolFlowRate >= SmallWaterVolFlow) THEN
rho = GetDensityGlycol(PlantLoop(ElecReformEIRChiller(EIRChillNum)%CDLoopNum)%FluidName, &
InitConvTemp, &
PlantLoop(ElecReformEIRChiller(EIRChillNum)%CDLoopNum)%FluidIndex, &
'SizeElecReformEIRChiller')
Cp = GetSpecificHeatGlycol(PlantLoop(ElecReformEIRChiller(EIRChillNum)%CDLoopNum)%FluidName, &
ElecReformEIRChiller(EIRChillNum)%TempRefCondIn, &
PlantLoop(ElecReformEIRChiller(EIRChillNum)%CDLoopNum)%FluidIndex, &
'SizeElecReformEIRChiller')
tmpCondVolFlowRate = tmpNomCap * &
(1.0d0 + (1.0d0/ElecReformEIRChiller(EIRChillNum)%RefCOP) * &
ElecReformEIRChiller(EIRChillNum)%CompPowerToCondenserFrac) / &
( PlantSizData(PltSizCondNum)%DeltaT * Cp * rho)
IF (PlantSizesOkayToFinalize) ElecReformEIRChiller(EIRChillNum)%CondVolFlowRate = tmpCondVolFlowRate
ELSE
tmpCondVolFlowRate = 0.d0
IF (PlantSizesOkayToFinalize) ElecReformEIRChiller(EIRChillNum)%CondVolFlowRate = tmpCondVolFlowRate
END IF
IF (PlantSizesOkayToFinalize) &
CALL ReportSizingOutput('Chiller:Electric:ReformulatedEIR', ElecReformEIRChiller(EIRChillNum)%Name, &
'Reference Condenser Water Flow Rate [m3/s]', &
ElecReformEIRChiller(EIRChillNum)%CondVolFlowRate)
ELSE
CALL ShowSevereError('Autosizing of Reformulated Electric EIR Chiller condenser flow rate requires a condenser')
CALL ShowContinueError('loop Sizing:Plant object')
CALL ShowContinueError('Occurs in Reformulated Electric EIR Chiller object='//TRIM(ElecReformEIRChiller(EIRChillNum)%Name))
ErrorsFound = .TRUE.
END IF
END IF
! save the reference condenser water volumetric flow rate for use by the condenser water loop sizing algorithms
CALL RegisterPlantCompDesignFlow(ElecReformEIRChiller(EIRChillNum)%CondInletNodeNum,tmpCondVolFlowRate)
IF (ElecReformEIRChiller(EIRChillNum)%HeatRecActive) THEN
tmpHeatRecVolFlowRate = ElecReformEIRChiller(EIRChillNum)%DesignHeatRecVolFlowRate
IF (ElecReformEIRChiller(EIRChillNum)%DesignHeatRecVolFlowRate == Autosize) THEN
tmpHeatRecVolFlowRate = tmpCondVolFlowRate * ElecReformEIRChiller(EIRChillNum)%HeatRecCapacityFraction
IF (PlantSizesOkayToFinalize) THEN
ElecReformEIRChiller(EIRChillNum)%DesignHeatRecVolFlowRate = tmpHeatRecVolFlowRate
CALL ReportSizingOutput('Chiller:Electric:ReformulatedEIR', ElecReformEIRChiller(EIRChillNum)%Name, &
'Design Heat Recovery Fluid Flow Rate [m3/s]', &
ElecReformEIRChiller(EIRChillNum)%DesignHeatRecVolFlowRate)
ENDIF
ENDIF
! save the reference heat recovery fluid volumetric flow rate
CALL RegisterPlantCompDesignFlow(ElecReformEIRChiller(EIRChillNum)%HeatRecInletNodeNum,tmpHeatRecVolFlowRate)
ENDIF
IF (PlantSizesOkayToFinalize) THEN
IF (MyFlag(EIRChillNum)) THEN
CALL CalcChillerIPLV(ElecReformEIRChiller(EIRChillNum)%Name, &
TypeOf_Chiller_ElectricReformEIR, &
ElecReformEIRChiller(EIRChillNum)%RefCap, &
ElecReformEIRChiller(EIRChillNum)%RefCOP, &
ElecReformEIRChiller(EIRChillNum)%CondenserType, &
ElecReformEIRChiller(EIRChillNum)%ChillerCapFT, &
ElecReformEIRChiller(EIRChillNum)%ChillerEIRFT, &
ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLR, &
ElecReformEIRChiller(EIRChillNum)%MinUnLoadRat, &
ElecReformEIRChiller(EIRChillNum)%EvapVolFlowRate, &
ElecReformEIRChiller(EIRChillNum)%CDLoopNum, &
ElecReformEIRChiller(EIRChillNum)%CompPowerToCondenserFrac)
MyFlag(EIRChillNum) = .FALSE.
ENDIF
!create predefined report
equipName = ElecReformEIRChiller(EIRChillNum)%Name
CALL PreDefTableEntry(pdchMechType,equipName,'Chiller:Electric:ReformulatedEIR')
CALL PreDefTableEntry(pdchMechNomEff,equipName,ElecReformEIRChiller(EIRChillNum)%RefCOP)
CALL PreDefTableEntry(pdchMechNomCap,equipName,ElecReformEIRChiller(EIRChillNum)%RefCap)
ENDIF
! Only check performance curves if Capacity and volumetric flow rate are greater than 0
IF(ElecReformEIRChiller(EIRChillNum)%RefCap .GT. 0.0D0 .AND. &
ElecReformEIRChiller(EIRChillNum)%CondVolFlowRate .GT. 0.0D0) THEN
! Check the CAP-FT, EIR-FT, and PLR curves at reference conditions and warn user if different from 1.0 by more than +-10%
IF (ElecReformEIRChiller(EIRChillNum)%ChillerCAPFT > 0)THEN
CurveVal = CurveValue(ElecReformEIRChiller(EIRChillNum)%ChillerCAPFT, &
ElecReformEIRChiller(EIRChillNum)%TempRefEvapOut,ElecReformEIRChiller(EIRChillNum)%TempRefCondOut)
IF(CurveVal .GT. 1.10d0 .OR. CurveVal .LT. 0.90d0) THEN
CALL ShowWarningError('Capacity ratio as a function of temperature curve output is not equal to 1.0')
CALL ShowContinueError('(+ or - 10%) at reference conditions for Chiller:Electric:ReformulatedEIR = ' &
//TRIM(equipName))
CALL ShowContinueError('Curve output at reference conditions = '//TRIM(TrimSigDigits(CurveVal,3)))
END IF
CALL GetCurveMinMaxValues(ElecReformEIRChiller(EIRChillNum)%ChillerCAPFT, &
ElecReformEIRChiller(EIRChillNum)%ChillerCAPFTXTempMin,ElecReformEIRChiller(EIRChillNum)%ChillerCAPFTXTempMax, &
ElecReformEIRChiller(EIRChillNum)%ChillerCAPFTYTempMin,ElecReformEIRChiller(EIRChillNum)%ChillerCAPFTYTempMax)
END IF
IF (ElecReformEIRChiller(EIRChillNum)%ChillerEIRFT > 0) THEN
CurveVal = CurveValue(ElecReformEIRChiller(EIRChillNum)%ChillerEIRFT, &
ElecReformEIRChiller(EIRChillNum)%TempRefEvapOut,ElecReformEIRChiller(EIRChillNum)%TempRefCondOut)
IF(CurveVal .GT. 1.10d0 .OR. CurveVal .LT. 0.90d0)THEN
CALL ShowWarningError('Energy input ratio as a function of temperature curve output is not equal to 1.0')
CALL ShowContinueError('(+ or - 10%) at reference conditions for Chiller:Electric:ReformulatedEIR = ' &
//TRIM(equipName))
CALL ShowContinueError('Curve output at reference conditions = '//TRIM(TrimSigDigits(CurveVal,3)))
END IF
CALL GetCurveMinMaxValues(ElecReformEIRChiller(EIRChillNum)%ChillerEIRFT, &
ElecReformEIRChiller(EIRChillNum)%ChillerEIRFTXTempMin,ElecReformEIRChiller(EIRChillNum)%ChillerEIRFTXTempMax, &
ElecReformEIRChiller(EIRChillNum)%ChillerEIRFTYTempMin,ElecReformEIRChiller(EIRChillNum)%ChillerEIRFTYTempMax)
END IF
IF (ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLR > 0) THEN
CurveVal = CurveValue(ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLR, &
ElecReformEIRChiller(EIRChillNum)%TempRefCondOut,1.0d0)
IF(CurveVal .GT. 1.10d0 .OR. CurveVal .LT. 0.90d0)THEN
CALL ShowWarningError('Energy input ratio as a function of part-load ratio curve output is not equal to 1.0')
CALL ShowContinueError('(+ or - 10%) at reference conditions for Chiller:Electric:ReformulatedEIR = ' &
//TRIM(equipName))
CALL ShowContinueError('Curve output at reference conditions = '//TRIM(TrimSigDigits(CurveVal,3)))
END IF
CALL GetCurveMinMaxValues(ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLR, &
ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLRTempMin,ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLRTempMax, &
ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLRPLRMin,ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLRPLRMax)
IF (ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLRPLRMin < 0 .OR. &
ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLRPLRMin .GE. &
ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLRPLRMax .OR. &
ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLRPLRMin > 1) THEN
CALL ShowSevereError('Invalid minimum value of PLR = ' &
//TRIM(TrimSigDigits(ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLRPLRMin,3)) &
//' in bicubic curve = '//TRIM(ElecReformEIRChiller(EIRChillNum)%EIRFPLRName)//' which is used')
CALL ShowContinueError('by Chiller:Electric:ReformulatedEIR = '// TRIM(equipName)//'.')
CALL ShowContinueError('The minimum value of PLR [y] must be from zero to 1, and less than the maximum value of PLR.')
ErrorsFound=.True.
END IF
IF (ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLRPLRMax > 1.1 .OR. &
ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLRPLRMax .LE. &
ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLRPLRMin .OR. &
ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLRPLRMax < 0) THEN
CALL ShowSevereError('Invalid maximum value of PLR = ' &
//TRIM(TrimSigDigits(ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLRPLRMax,3)) &
//' in bicubic curve = '//TRIM(ElecReformEIRChiller(EIRChillNum)%EIRFPLRName)//' which is used')
CALL ShowContinueError('by Chiller:Electric:ReformulatedEIR = '//TRIM(equipName)//'.')
CALL ShowContinueError('The maximum value of PLR [y] must be from zero to 1.1, and greater than the minimum value ' &
//'of PLR.')
ErrorsFound=.True.
END IF
END IF
! Initialize condenser reference inlet temperature (not a user input)
Density = GetDensityGlycol(PlantLoop(ElecReformEIRChiller(EIRChillNum)%CDLoopNum)%FluidName, &
ElecReformEIRChiller(EIRChillNum)%TempRefCondOut, &
PlantLoop(ElecReformEIRChiller(EIRChillNum)%CDLoopNum)%FluidIndex,&
'SizeElecReformEIRChiller')
SpecificHeat = GetSpecificHeatGlycol(PlantLoop(ElecReformEIRChiller(EIRChillNum)%CDLoopNum)%FluidName, &
ElecReformEIRChiller(EIRChillNum)%TempRefCondOut, &
PlantLoop(ElecReformEIRChiller(EIRChillNum)%CDLoopNum)%FluidIndex, &
'SizeElecReformEIRChiller')
CondenserCapacity = ElecReformEIRChiller(EIRChillNum)%RefCap * &
(1.0d0 + (1.0d0/ElecReformEIRChiller(EIRChillNum)%RefCOP)*ElecReformEIRChiller(EIRChillNum)%CompPowerToCondenserFrac)
DeltaTCond = (CondenserCapacity) / &
(ElecReformEIRChiller(EIRChillNum)%CondVolFlowRate * Density * SpecificHeat)
ElecReformEIRChiller(EIRChillNum)%TempRefCondIn = ElecReformEIRChiller(EIRChillNum)%TempRefCondOut - DeltaTCond
! Check EIRFPLR curve output. Calculate condenser inlet temp based on reference condenser outlet temp,
! chiller capacity, and mass flow rate. Starting with the calculated condenser inlet temp and PLR = 0,
! calculate the condenser outlet temp proportional to PLR and test the EIRFPLR curve output for negative numbers.
FoundNegValue = .FALSE.
IF (ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLR > 0) THEN
CurveValArray = 0.0d0
CondTempArray = 0.0d0
DO CurveCheck = 0, 10, 1
PLRTemp = CurveCheck/10.0d0
CondTemp = ElecReformEIRChiller(EIRChillNum)%TempRefCondIn + (DeltaTCond*PLRTemp)
CondTemp = MIN(CondTemp, ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLRTempMax)
CondTemp = MAX(CondTemp, ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLRTempMin)
IF(PLRTemp .LT. ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLRPLRMin)THEN
CurveValTmp = CurveValue(ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLR, &
CondTemp, ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLRPLRMin)
ELSE
CurveValTmp = CurveValue(ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLR, CondTemp, PLRTemp)
END IF
IF(CurveValTmp .LT. 0.0d0) FoundNegValue = .TRUE.
CurveValArray(CurveCheck+1) = INT(CurveValTmp*100.0d0)/100.0d0
CondTempArray(CurveCheck+1) = INT(CondTemp*100.0d0)/100.0d0
END DO
END IF
! Output warning message if negative values are found in the EIRFPLR curve output. Results in Fatal error.
IF(FoundNegValue)THEN
CALL ShowWarningError('Energy input to cooing output ratio function of part-load ratio curve shows negative values ')
CALL ShowContinueError('for Chiller:Electric:ReformulatedEIR = '// TRIM(equipName)//'.')
CALL ShowContinueError('EIR as a function of PLR curve output at various part-load ratios and condenser '// &
'water temperatures shown below:')
CALL ShowContinueError('PLR = 0.00 0.10 0.20 0.30 0.40 0.50 0.60 0.70 0.80 0.90 1.00')
WRITE(StringVar,530)(CondTempArray(CurveValPtr), CurveValPtr = 1, 11)
530 FORMAT('Cond Temp (C) = ',11(F7.2))
CALL ShowContinueError(TRIM(StringVar))
WRITE(StringVar,531)(CurveValArray(CurveValPtr), CurveValPtr = 1, 11)
531 FORMAT('Curve Output = ',11(F7.2))
CALL ShowContinueError(TRIM(StringVar))
ErrorsFound = .TRUE.
END IF
ELSE ! just get curve min/max values if capacity or cond volume flow rate = 0
CALL GetCurveMinMaxValues(ElecReformEIRChiller(EIRChillNum)%ChillerCAPFT, &
ElecReformEIRChiller(EIRChillNum)%ChillerCAPFTXTempMin,ElecReformEIRChiller(EIRChillNum)%ChillerCAPFTXTempMax, &
ElecReformEIRChiller(EIRChillNum)%ChillerCAPFTYTempMin,ElecReformEIRChiller(EIRChillNum)%ChillerCAPFTYTempMax)
CALL GetCurveMinMaxValues(ElecReformEIRChiller(EIRChillNum)%ChillerEIRFT, &
ElecReformEIRChiller(EIRChillNum)%ChillerEIRFTXTempMin,ElecReformEIRChiller(EIRChillNum)%ChillerEIRFTXTempMax, &
ElecReformEIRChiller(EIRChillNum)%ChillerEIRFTYTempMin,ElecReformEIRChiller(EIRChillNum)%ChillerEIRFTYTempMax)
CALL GetCurveMinMaxValues(ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLR, &
ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLRTempMin,ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLRTempMax, &
ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLRPLRMin,ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLRPLRMax)
END IF
IF (ErrorsFound) THEN
CALL ShowFatalError('Preceding sizing errors cause program termination')
END IF
RETURN
END SUBROUTINE SizeElecReformEIRChiller