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 SizeElectricEIRChiller(EIRChillNum)
! SUBROUTINE INFORMATION:
! AUTHOR Richard Raustad, FSEC
! DATE WRITTEN June 2004
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine is for sizing 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_ElectricEIR
USE PlantUtilities, ONLY: RegisterPlantCompDesignFlow
USE ReportSizingManager, ONLY: ReportSizingOutput
USE OutputReportPredefined
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:
!unused1208 INTEGER :: PltSizIndex ! Plant Sizing Do loop index
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
CHARACTER(len=MaxNameLength) :: equipName
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
LOGICAL, SAVE :: MyOneTimeFlag = .TRUE.
LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: MyFlag ! TRUE in order to calculate IPLV
IF (MyOneTimeFlag) THEN
ALLOCATE(MyFlag(NumElectricEIRChillers))
MyFlag = .TRUE.
MyOneTimeFlag = .FALSE.
END IF
PltSizNum = 0
PltSizCondNum = 0
ErrorsFound = .FALSE.
tmpNomCap = ElectricEIRChiller(EIRChillNum)%RefCap
tmpEvapVolFlowRate = ElectricEIRChiller(EIRChillNum)%EvapVolFlowRate
tmpCondVolFlowRate = ElectricEIRChiller(EIRChillNum)%CondVolFlowRate
IF (ElectricEIRChiller(EIRChillNum)%CondenserType == WaterCooled) THEN
IF (ElectricEIRChiller(EIRChillNum)%CondVolFlowRate == AutoSize) THEN
PltSizCondNum = PlantLoop(ElectricEIRChiller(EIRChillNum)%CDLoopNum)%PlantSizNum
END IF
END IF
! find the appropriate Plant Sizing object
PltSizNum = PlantLoop(ElectricEIRChiller(EIRChillNum)%CWLoopNum)%PlantSizNum
IF (ElectricEIRChiller(EIRChillNum)%EvapVolFlowRate == AutoSize) THEN
IF (PltSizNum > 0) THEN
IF (PlantSizData(PltSizNum)%DesVolFlowRate >= SmallWaterVolFlow) THEN
tmpEvapVolFlowRate = PlantSizData(PltSizNum)%DesVolFlowRate * &
ElectricEIRChiller(EIRChillNum)%SizFac
IF (PlantSizesOkayToFinalize) ElectricEIRChiller(EIRChillNum)%EvapVolFlowRate = tmpEvapVolFlowRate
ELSE
tmpEvapVolFlowRate = 0.d0
IF (PlantSizesOkayToFinalize) ElectricEIRChiller(EIRChillNum)%EvapVolFlowRate = tmpEvapVolFlowRate
END IF
IF (PlantSizesOkayToFinalize) CALL ReportSizingOutput('Chiller:Electric:EIR', ElectricEIRChiller(EIRChillNum)%Name, &
'Reference Chilled Water Flow Rate [m3/s]', &
ElectricEIRChiller(EIRChillNum)%EvapVolFlowRate)
ELSE
CALL ShowSevereError('Autosizing of Electric Chiller evap flow rate requires a loop Sizing:Plant object')
CALL ShowContinueError('Occurs in Electric Chiller object='//TRIM(ElectricEIRChiller(EIRChillNum)%Name))
ErrorsFound = .TRUE.
END IF
END IF
CALL RegisterPlantCompDesignFlow(ElectricEIRChiller(EIRChillNum)%EvapInletNodeNum,tmpEvapVolFlowRate)
IF (ElectricEIRChiller(EIRChillNum)%RefCap == AutoSize) THEN
IF (PltSizNum > 0) THEN
IF (PlantSizData(PltSizNum)%DesVolFlowRate >= SmallWaterVolFlow) THEN
Cp = GetSpecificHeatGlycol(PlantLoop(ElectricEIRChiller(EIRChillNum)%CWLoopNum)%FluidName, &
InitConvTemp, &
PlantLoop(ElectricEIRChiller(EIRChillNum)%CWLoopNum)%FluidIndex, &
'SizeElectricEIRChiller')
rho = GetDensityGlycol(PlantLoop(ElectricEIRChiller(EIRChillNum)%CWLoopNum)%FluidName, &
InitConvTemp, &
PlantLoop(ElectricEIRChiller(EIRChillNum)%CWLoopNum)%FluidIndex,&
'SizeElectricEIRChiller')
tmpNomCap = Cp * rho * PlantSizData(PltSizNum)%DeltaT * tmpEvapVolFlowRate
IF (PlantSizesOkayToFinalize) ElectricEIRChiller(EIRChillNum)%RefCap = tmpNomCap
ELSE
tmpNomCap = 0.d0
IF (PlantSizesOkayToFinalize) ElectricEIRChiller(EIRChillNum)%RefCap = tmpNomCap
END IF
IF (PlantSizesOkayToFinalize) CALL ReportSizingOutput('Chiller:Electric:EIR', ElectricEIRChiller(EIRChillNum)%Name, &
'Reference Capacity [W]', ElectricEIRChiller(EIRChillNum)%RefCap)
ELSE
CALL ShowSevereError('Autosizing of Electric Chiller reference capacity requires a loop Sizing:Plant object')
CALL ShowContinueError('Occurs in Electric Chiller object='//TRIM(ElectricEIRChiller(EIRChillNum)%Name))
ErrorsFound = .TRUE.
END IF
END IF
IF (ElectricEIRChiller(EIRChillNum)%CondVolFlowRate == AutoSize) THEN
IF (PltSizCondNum > 0) THEN
IF (PlantSizData(PltSizNum)%DesVolFlowRate >= SmallWaterVolFlow) THEN
rho = GetDensityGlycol(PlantLoop(ElectricEIRChiller(EIRChillNum)%CDLoopNum)%FluidName, &
InitConvTemp, &
PlantLoop(ElectricEIRChiller(EIRChillNum)%CDLoopNum)%FluidIndex,&
'SizeElectricEIRChiller')
Cp = GetSpecificHeatGlycol(PlantLoop(ElectricEIRChiller(EIRChillNum)%CDLoopNum)%FluidName, &
ElectricEIRChiller(EIRChillNum)%TempRefCondIn, &
PlantLoop(ElectricEIRChiller(EIRChillNum)%CDLoopNum)%FluidIndex, &
'SizeElectricEIRChiller')
tmpCondVolFlowRate = tmpNomCap * &
(1.0d0 + (1.0d0/ElectricEIRChiller(EIRChillNum)%RefCOP) * ElectricEIRChiller(EIRChillNum)%CompPowerToCondenserFrac) / &
( PlantSizData(PltSizCondNum)%DeltaT * Cp * rho )
IF (PlantSizesOkayToFinalize) ElectricEIRChiller(EIRChillNum)%CondVolFlowRate = tmpCondVolFlowRate
ELSE
tmpCondVolFlowRate = 0.d0
IF (PlantSizesOkayToFinalize) ElectricEIRChiller(EIRChillNum)%CondVolFlowRate = tmpCondVolFlowRate
END IF
IF (PlantSizesOkayToFinalize) CALL ReportSizingOutput('Chiller:Electric:EIR', ElectricEIRChiller(EIRChillNum)%Name, &
'Reference Condenser Water Flow Rate [m3/s]', &
ElectricEIRChiller(EIRChillNum)%CondVolFlowRate)
ELSE
CALL ShowSevereError('Autosizing of Electric EIR Chiller condenser flow rate requires a condenser')
CALL ShowContinueError('loop Sizing:Plant object')
CALL ShowContinueError('Occurs in Electric EIR Chiller object='//TRIM(ElectricEIRChiller(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(ElectricEIRChiller(EIRChillNum)%CondInletNodeNum,tmpCondVolFlowRate)
IF (PlantSizesOkayToFinalize) THEN
IF (MyFlag(EIRChillNum)) THEN
CALL CalcChillerIPLV(ElectricEIRChiller(EIRChillNum)%Name, &
TypeOf_Chiller_ElectricEIR, &
ElectricEIRChiller(EIRChillNum)%RefCap, &
ElectricEIRChiller(EIRChillNum)%RefCOP, &
ElectricEIRChiller(EIRChillNum)%CondenserType, &
ElectricEIRChiller(EIRChillNum)%ChillerCapFT, &
ElectricEIRChiller(EIRChillNum)%ChillerEIRFT, &
ElectricEIRChiller(EIRChillNum)%ChillerEIRFPLR, &
ElectricEIRChiller(EIRChillNum)%MinUnLoadRat)
MyFlag(EIRChillNum) = .FALSE.
ENDIF
!create predefined report
equipName = ElectricEIRChiller(EIRChillNum)%Name
CALL PreDefTableEntry(pdchMechType,equipName,'Chiller:Electric:EIR')
CALL PreDefTableEntry(pdchMechNomEff,equipName,ElectricEIRChiller(EIRChillNum)%RefCOP)
CALL PreDefTableEntry(pdchMechNomCap,equipName,ElectricEIRChiller(EIRChillNum)%RefCap)
ENDIF
IF (ErrorsFound) THEN
CALL ShowFatalError('Preceding sizing errors cause program termination')
END IF
RETURN
END SUBROUTINE SizeElectricEIRChiller