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 GetChillerheaterInput
! SUBROUTINE INFORMATION:
! AUTHOR: Kyung Tae Yun, Mississippi State University
! DATE WRITTEN: Feb 2013
! PURPOSE OF THIS SUBROUTINE:
! This routine will get the input required by the ChillerHeaterPerformance:Electric:EIR model.
! METHODOLOGY EMPLOYED:
!
! REFERENCES: na
! USE STATEMENTS:
USE InputProcessor, ONLY: GetNumObjectsFound, GetObjectItem, VerifyName, SameString
USE DataIPShortCuts
USE BranchNodeConnections, ONLY: TestCompSet
USE NodeInputManager, ONLY: GetOnlySingleNode
USE CurveManager, ONLY: GetCurveIndex, GetCurveMinMaxValues
USE CurveManager, ONLY: CurveValue
USE PlantUtilities, ONLY: RegisterPlantCompDesignFlow
USE ScheduleManager, ONLY: GetScheduleIndex
USE General, ONLY: TrimSigDigits, RoundSigDigits
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! PARAMETERS
! na
! LOCAL VARIABLES
CHARACTER(len=MaxNameLength) :: EvapInletNodeName ! Evaporator inlet node name
CHARACTER(len=MaxNameLength) :: EvapOutletNodeName ! Evaporator outlet node name
CHARACTER(len=MaxNameLength) :: CondInletNodeName ! Condenser inlet node name
CHARACTER(len=MaxNameLength) :: CondOutletNodeName ! Condenser outlet node name
CHARACTER(len=MaxNameLength) :: temp_char ! temporary character variable
CHARACTER(len=MaxNameLength) :: StringVar ! Used for EIRFPLR warning messages
LOGICAL, SAVE :: CHErrorsFound=.false. ! True when input errors are found
LOGICAL, SAVE :: AllocatedFlag =.FALSE. ! True when arrays are allocated
LOGICAL :: IsNotOK ! Flag to verify name
LOGICAL :: IsBlank ! Flag for blank name
LOGICAL :: FoundNegValue = .FALSE. ! Used to evaluate PLFFPLR curve objects
LOGICAL :: errflag ! Used to tell if a unique chiller name has been specified
INTEGER :: CurveValPtr ! Index to EIRFPLR curve output
INTEGER :: CurveCheck = 0 ! Used to evaluate PLFFPLR curve objects
INTEGER :: ChillerHeaterNum ! 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
REAL(r64) :: CurveVal ! Used to verify EIR-FT and CAP-FT curves
REAL(r64), DIMENSION(11) :: CurveValArray ! Used to evaluate PLFFPLR curve objects
REAL(r64) :: CurveValTmp ! Used to evaluate PLFFPLR curve objects
cCurrentModuleObject = 'ChillerHeaterPerformance:Electric:EIR'
NumChillerheaters = GetNumObjectsFound(cCurrentModuleObject)
IF (NumChillerheaters <= 0) THEN
CALL ShowSevereError('No '//TRIM(cCurrentModuleObject)//' equipment specified in input file')
CHErrorsFound=.true.
END IF
! Allocate temporary Chillerheater and ChillerheaterReport arrays
IF (ALLOCATED(Chillerheater)) DEALLOCATE (Chillerheater)
IF (ALLOCATED(ChillerheaterReport)) DEALLOCATE (ChillerheaterReport)
ALLOCATE (Chillerheater(NumChillerheaters))
ALLOCATE (ChillerheaterReport(NumChillerheaters))
! Load arrays with electric EIR chiller data
DO ChillerHeaterNum = 1 , NumChillerheaters
CALL GetObjectItem(cCurrentModuleObject,ChillerHeaterNum,cAlphaArgs,NumAlphas, &
rNumericArgs,NumNums,IOSTAT,AlphaBlank=lAlphaFieldBlanks, &
AlphaFieldnames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
Chillerheater(ChillerHeaterNum)%Name = cAlphaArgs(1)
IsNotOK=.false.
IsBlank=.false.
CALL VerifyName(cAlphaArgs(1),Chillerheater%Name,ChillerHeaterNum-1,IsNotOK,IsBlank,TRIM(cCurrentModuleObject)//' Name')
IF (IsNotOK) THEN
CHErrorsFound=.true.
IF (IsBlank) cAlphaArgs(1)='xxxxx'
END IF
Chillerheater(ChillerHeaterNum)%CondModeCooling = cAlphaArgs(4)
! Performance curves
Chillerheater(ChillerHeaterNum)%ChillerCapFTCooling = GetCurveIndex(cAlphaArgs(5))
IF (Chillerheater(ChillerHeaterNum)%ChillerCapFTCooling == 0) THEN
CALL ShowSevereError('Invalid '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
CALL ShowContinueError('Entered in '//TRIM(cAlphaFieldNames(5))//'='//TRIM(cAlphaArgs(5)))
CHErrorsFound = .TRUE.
END IF
Chillerheater(ChillerHeaterNum)%ChillerEIRFTCooling = GetCurveIndex(cAlphaArgs(6))
IF (Chillerheater(ChillerHeaterNum)%ChillerEIRFTCooling == 0) THEN
CALL ShowSevereError('Invalid '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
CALL ShowContinueError('Entered in '//TRIM(cAlphaFieldNames(6))//'='//TRIM(cAlphaArgs(6)))
CHErrorsFound = .TRUE.
END IF
Chillerheater(ChillerHeaterNum)%ChillerEIRFPLRCooling = GetCurveIndex(cAlphaArgs(7))
IF (Chillerheater(ChillerHeaterNum)%ChillerEIRFPLRCooling == 0) THEN
CALL ShowSevereError('Invalid '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
CALL ShowContinueError('Entered in '//TRIM(cAlphaFieldNames(7))//'='//TRIM(cAlphaArgs(7)))
CHErrorsFound = .TRUE.
END IF
Chillerheater(ChillerHeaterNum)%CondModeHeating = cAlphaArgs(8)
! Performance curves
Chillerheater(ChillerHeaterNum)%ChillerCapFTHeating = GetCurveIndex(cAlphaArgs(9))
IF (Chillerheater(ChillerHeaterNum)%ChillerCapFTHeating .EQ. 0) THEN
CALL ShowSevereError('Invalid '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
CALL ShowContinueError('Entered in '//TRIM(cAlphaFieldNames(9))//'='//TRIM(cAlphaArgs(9)))
CHErrorsFound = .TRUE.
END IF
Chillerheater(ChillerHeaterNum)%ChillerEIRFTHeating = GetCurveIndex(cAlphaArgs(10))
IF (Chillerheater(ChillerHeaterNum)%ChillerEIRFTHeating .EQ. 0) THEN
CALL ShowSevereError('Invalid '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
CALL ShowContinueError('Entered in '//TRIM(cAlphaFieldNames(10))//'='//TRIM(cAlphaArgs(10)))
CHErrorsFound = .TRUE.
END IF
Chillerheater(ChillerHeaterNum)%ChillerEIRFPLRHeating = GetCurveIndex(cAlphaArgs(11))
IF (Chillerheater(ChillerHeaterNum)%ChillerEIRFPLRHeating .EQ. 0) THEN
CALL ShowSevereError('Invalid '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
CALL ShowContinueError('Entered in '//TRIM(cAlphaFieldNames(11))//'='//TRIM(cAlphaArgs(11)))
CHErrorsFound = .TRUE.
END IF
IF(cAlphaArgs(2) == 'CONSTANTFLOW') THEN
Chillerheater(ChillerHeaterNum)%ConstantFlow = .True.
Chillerheater(ChillerHeaterNum)%VariableFlow = .False.
ELSEIF(cAlphaArgs(2) == 'VARIABLEFLOW') THEN
Chillerheater(ChillerHeaterNum)%ConstantFlow = .False.
Chillerheater(ChillerHeaterNum)%VariableFlow = .True.
ELSE ! Assume a constant flow chiller if none is specified
Chillerheater(ChillerHeaterNum)%ConstantFlow = .True.
Chillerheater(ChillerHeaterNum)%VariableFlow = .False.
CALL ShowSevereError('Invalid '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
CALL ShowContinueError('Entered in '//TRIM(cAlphaFieldNames(2))//'='//TRIM(cAlphaArgs(2)))
CALL ShowContinueError('simulation assumes CONSTANTFLOW and continues..')
END IF
IF(ChillerHeaterNum > 1) THEN
IF(Chillerheater(ChillerHeaterNum)%ConstantFlow .NEQV. Chillerheater(ChillerHeaterNum-1)%ConstantFlow) THEN
Chillerheater(ChillerHeaterNum)%ConstantFlow = .True.
CALL ShowWarningError('Water flow mode is different from the other chiller heater(s) ' &
//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
CALL ShowContinueError('Entered in '//TRIM(cAlphaFieldNames(2))//'='//TRIM(cAlphaArgs(2)))
CALL ShowContinueError('Simulation assumes CONSTANTFLOW and continues..')
END IF
END IF
IF (SameString(cAlphaArgs(3),'WaterCooled')) THEN
Chillerheater(ChillerHeaterNum)%CondenserType = WaterCooled
ELSE
CALL ShowSevereError('Invalid '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
CALL ShowContinueError('Entered in '//TRIM(cAlphaFieldNames(3))//'='//TRIM(cAlphaArgs(3)))
CALL ShowContinueError('Valid entries is WaterCooled')
CHErrorsFound=.TRUE.
END IF
! Chiller rated performance data
Chillerheater(ChillerHeaterNum)%RefCapCooling = rNumericArgs(1)
IF (rNumericArgs(1) == 0.0d0) THEN
CALL ShowSevereError('Invalid '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
CALL ShowContinueError('Entered in '//TRIM(cNumericFieldNames(1))//'='//TRIM(RoundSigDigits(rNumericArgs(1),2)))
CHErrorsFound=.true.
END IF
Chillerheater(ChillerHeaterNum)%RefCOPCooling = rNumericArgs(2)
IF (rNumericArgs(2) == 0.0d0) THEN
CALL ShowSevereError('Invalid '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
CALL ShowContinueError('Entered in '//TRIM(cNumericFieldNames(2))//'='//TRIM(RoundSigDigits(rNumericArgs(2),2)))
CHErrorsFound=.true.
END IF
Chillerheater(ChillerHeaterNum)%TempRefEvapOutCooling = rNumericArgs(3)
Chillerheater(ChillerHeaterNum)%TempRefCondInCooling = rNumericArgs(4)
Chillerheater(ChillerHeaterNum)%TempRefCondOutCooling = rNumericArgs(5)
Chillerheater(ChillerHeaterNum)%ClgHtgToCoolingCapRatio = rNumericArgs(6)
Chillerheater(ChillerHeaterNum)%RefCapClgHtg = rNumericArgs(6) * Chillerheater(ChillerHeaterNum)%RefCapCooling
IF (rNumericArgs(6) == 0.0d0) THEN
CALL ShowSevereError('Invalid '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
CALL ShowContinueError('Entered in '//TRIM(cNumericFieldNames(6))//'='//TRIM(RoundSigDigits(rNumericArgs(6),2)))
CHErrorsFound=.true.
END IF
Chillerheater(ChillerHeaterNum)%ClgHtgtoCogPowerRatio = rNumericArgs(7)
Chillerheater(ChillerHeaterNum)%RefPowerClgHtg = Chillerheater(ChillerHeaterNum)%RefCapCooling / &
Chillerheater(ChillerHeaterNum)%RefCOPCooling * rNumericArgs(7)
Chillerheater(ChillerHeaterNum)%RefCOPClgHtg = Chillerheater(ChillerHeaterNum)%RefCapClgHtg / &
Chillerheater(ChillerHeaterNum)%RefPowerClgHtg
IF (rNumericArgs(7) == 0.0d0) THEN
CALL ShowSevereError('Invalid '//TRIM(cCurrentModuleObject)//'='//TRIM(cAlphaArgs(1)))
CALL ShowContinueError('Entered in '//TRIM(cNumericFieldNames(7))//'='//TRIM(RoundSigDigits(rNumericArgs(7),2)))
CHErrorsFound=.true.
END IF
Chillerheater(ChillerHeaterNum)%TempRefEvapOutClgHtg = rNumericArgs(8)
Chillerheater(ChillerHeaterNum)%TempRefCondOutClgHtg = rNumericArgs(9)
Chillerheater(ChillerHeaterNum)%TempRefCondInClgHtg = rNumericArgs(10)
Chillerheater(ChillerHeaterNum)%TempLowLimitEvapOut = rNumericArgs(11)
Chillerheater(ChillerHeaterNum)%EvapVolFlowRate = rNumericArgs(12)
Chillerheater(ChillerHeaterNum)%CondVolFlowRate = rNumericArgs(13)
Chillerheater(ChillerHeaterNum)%DesignHotWaterVolFlowRate = rNumericArgs(14)
Chillerheater(ChillerHeaterNum)%OpenMotorEff = rNumericArgs(15)
Chillerheater(ChillerHeaterNum)%OptPartLoadRatCooling = rNumericArgs(16)
Chillerheater(ChillerHeaterNum)%OptPartLoadRatClgHtg = rNumericArgs(17)
Chillerheater(ChillerHeaterNum)%SizFac = rNumericArgs(18)
IF (Chillerheater(ChillerHeaterNum)%SizFac <= 0.0d0) Chillerheater(ChillerHeaterNum)%SizFac = 1.0d0
IF(Chillerheater(ChillerHeaterNum)%OpenMotorEff .LT. 0.0d0 .OR. &
Chillerheater(ChillerHeaterNum)%OpenMotorEff .GT. 1.0d0) THEN
CALL ShowSevereError('GetCurveInput: For '//TRIM(cCurrentModuleObject)//': '//TRIM(cAlphaArgs(1)))
CALL ShowContinueError(TRIM(cNumericFieldNames(14))//' = '//TRIM(RoundSigDigits(rNumericArgs(14),3)) )
CALL ShowContinueError(TRIM(cNumericFieldNames(14))//' must be greater than or equal to zero' )
CALL ShowContinueError(TRIM(cNumericFieldNames(14))//' must be less than or equal to one' )
CHErrorsFound=.true.
END IF
! Check the CAP-FT, EIR-FT, and PLR curves and warn user if different from 1.0 by more than +-10%
IF (Chillerheater(ChillerHeaterNum)%ChillerCAPFTCooling > 0) THEN
CurveVal = CurveValue(Chillerheater(ChillerHeaterNum)%ChillerCAPFTCooling, &
Chillerheater(ChillerHeaterNum)%TempRefEvapOutCooling, &
Chillerheater(ChillerHeaterNum)%TempRefCondInCooling)
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 '//TRIM(cCurrentModuleObject)//'= '// &
TRIM(cAlphaArgs(1)))
CALL ShowContinueError('Curve output at reference conditions = '//TRIM(TrimSigDigits(CurveVal,3)))
END IF
END IF
IF (Chillerheater(ChillerHeaterNum)%ChillerEIRFTCooling > 0) THEN
CurveVal = CurveValue(Chillerheater(ChillerHeaterNum)%ChillerEIRFTCooling, &
Chillerheater(ChillerHeaterNum)%TempRefEvapOutCooling, &
Chillerheater(ChillerHeaterNum)%TempRefCondInCooling)
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 '//TRIM(cCurrentModuleObject)//'= '// &
TRIM(cAlphaArgs(1)))
CALL ShowContinueError('Curve output at reference conditions = '//TRIM(TrimSigDigits(CurveVal,3)))
END IF
END IF
IF (Chillerheater(ChillerHeaterNum)%ChillerEIRFPLRCooling > 0) THEN
CurveVal = CurveValue(Chillerheater(ChillerHeaterNum)%ChillerEIRFPLRCooling, 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 '//TRIM(cCurrentModuleObject)//'= '// &
TRIM(cAlphaArgs(1)))
CALL ShowContinueError('Curve output at reference conditions = '//TRIM(TrimSigDigits(CurveVal,3)))
END IF
END IF
IF (Chillerheater(ChillerHeaterNum)%ChillerEIRFPLRCooling > 0) THEN
FoundNegValue = .FALSE.
DO CurveCheck = 0, 10, 1
CurveValTmp = CurveValue(Chillerheater(ChillerHeaterNum)%ChillerEIRFPLRCooling, REAL(CurveCheck/10.0d0,r64))
IF(CurveValTmp .LT. 0.0d0) FoundNegValue = .TRUE.
CurveValArray(CurveCheck+1) = INT(CurveValTmp*100.0d0)/100.0d0
END DO
IF(FoundNegValue)THEN
CALL ShowWarningError('Energy input ratio as a function of part-load ratio curve shows negative values ')
CALL ShowContinueError('for '//TRIM(cCurrentModuleObject)//'= '//TRIM(cAlphaArgs(1)))
CALL ShowContinueError('EIR as a function of PLR curve output at various part-load ratios 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)(CurveValArray(CurveValPtr), CurveValPtr = 1, 11)
530 FORMAT('Curve Output = ',11(F7.2))
CALL ShowContinueError(TRIM(StringVar))
CHErrorsFound = .TRUE.
END IF
END IF
IF (Chillerheater(ChillerHeaterNum)%ChillerCAPFTHeating > 0) THEN
CurveVal = CurveValue(Chillerheater(ChillerHeaterNum)%ChillerCAPFTHeating, &
Chillerheater(ChillerHeaterNum)%TempRefEvapOutClgHtg,Chillerheater(ChillerHeaterNum)%TempRefCondInClgHtg)
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 '//TRIM(cCurrentModuleObject)//'= '//TRIM(cAlphaArgs(1)))
CALL ShowContinueError('Curve output at reference conditions = '//TRIM(TrimSigDigits(CurveVal,3)))
END IF
END IF
IF (Chillerheater(ChillerHeaterNum)%ChillerEIRFTHeating > 0) THEN
CurveVal = CurveValue(Chillerheater(ChillerHeaterNum)%ChillerEIRFTHeating, &
Chillerheater(ChillerHeaterNum)%TempRefEvapOutClgHtg,Chillerheater(ChillerHeaterNum)%TempRefCondInClgHtg)
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 '//TRIM(cCurrentModuleObject)//'= '//TRIM(cAlphaArgs(1)))
CALL ShowContinueError('Curve output at reference conditions = '//TRIM(TrimSigDigits(CurveVal,3)))
END IF
END IF
IF (Chillerheater(ChillerHeaterNum)%ChillerEIRFPLRHeating > 0) THEN
CurveVal = CurveValue(Chillerheater(ChillerHeaterNum)%ChillerEIRFPLRHeating, 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 '//TRIM(cCurrentModuleObject)//'= '//TRIM(cAlphaArgs(1)))
CALL ShowContinueError('Curve output at reference conditions = '//TRIM(TrimSigDigits(CurveVal,3)))
END IF
END IF
IF (Chillerheater(ChillerHeaterNum)%ChillerEIRFPLRHeating > 0) THEN
FoundNegValue = .FALSE.
DO CurveCheck = 0, 10, 1
CurveValTmp = CurveValue(Chillerheater(ChillerHeaterNum)%ChillerEIRFPLRHeating, REAL(CurveCheck/10.0d0,r64))
IF(CurveValTmp .LT. 0.0d0) FoundNegValue = .TRUE.
CurveValArray(CurveCheck+1) = INT(CurveValTmp*100.0d0)/100.0d0
END DO
IF(FoundNegValue)THEN
CALL ShowWarningError('Energy input ratio as a function of part-load ratio curve shows negative values ')
CALL ShowContinueError('for '//TRIM(cCurrentModuleObject)//'= '//TRIM(cAlphaArgs(1)))
CALL ShowContinueError('EIR as a function of PLR curve output at various part-load ratios 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,550)(CurveValArray(CurveValPtr), CurveValPtr = 1, 11)
550 FORMAT('Curve Output = ',11(F7.2))
CALL ShowContinueError(TRIM(StringVar))
CHErrorsFound = .TRUE.
END IF
END IF
CALL GetCurveMinMaxValues(Chillerheater(ChillerHeaterNum)%ChillerEIRFPLRHeating,&
Chillerheater(ChillerHeaterNum)%MinPartLoadRatClgHtg, &
Chillerheater(ChillerHeaterNum)%MaxPartLoadRatClgHtg)
CALL GetCurveMinMaxValues(Chillerheater(ChillerHeaterNum)%ChillerEIRFPLRCooling,&
Chillerheater(ChillerHeaterNum)%MinPartLoadRatCooling, &
Chillerheater(ChillerHeaterNum)%MaxPartLoadRatCooling)
END DO
IF (CHErrorsFound) THEN
CALL ShowFatalError('Errors found in processing input for '//TRIM(cCurrentModuleObject))
END IF
RETURN
END SUBROUTINE GetChillerheaterInput