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 | |||
logical, | intent(in) | :: | RunFlag | |||
real(kind=r64), | intent(in) | :: | MyLoad |
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 InitElecReformEIRChiller(EIRChillNum, RunFlag, MyLoad)
! SUBROUTINE INFORMATION:
! AUTHOR Lixing Gu, FSEC
! DATE WRITTEN July 2006
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine is for initializations of the Reformulated Electric EIR Chiller variables
! METHODOLOGY EMPLOYED:
! Uses the status flags to trigger initializations.
! REFERENCES:
! na
! USE STATEMENTS:
USE DataGlobals, ONLY : BeginEnvrnFlag, AnyEnergyManagementSystemInModel
USE DataPlant, ONLY : PlantLoop, TypeOf_Chiller_ElectricReformEIR, ScanPlantLoopsForObject, &
PlantSizesOkayToFinalize, PlantSizeNotComplete, LoopFlowStatus_NeedyIfLoopOn
USE PlantUtilities, ONLY : InterConnectTwoPlantLoopSides, InitComponentNodes, SetComponentFlowRate
USE DataEnvironment, ONLY : StdBaroPress
USE EMSManager, ONLY : iTemperatureSetpoint, CheckIfNodeSetpointManagedByEMS
USE DataInterfaces, ONLY : ShowFatalError, ShowSevereError, ShowContinueError
USE ScheduleManager, ONLY : GetCurrentScheduleValue
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT (IN) :: EIRChillNum ! Number of the current electric EIR chiller being simulated
LOGICAL, INTENT(IN) :: RunFlag ! TRUE when chiller operating
REAL(r64),INTENT(IN) :: MyLoad ! Current load put on chiller
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
LOGICAL,SAVE :: MyOneTimeFlag = .true. ! One time logic flag for allocating MyEnvrnFlag array
LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: MyFlag
LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: MyEnvrnFlag ! Logical array to initialize when appropriate
INTEGER :: EvapInletNode ! Node number for evaporator water inlet node
INTEGER :: EvapOutletNode ! Node number for evaporator water outlet node
INTEGER :: CondInletNode ! Node number for condenser water inlet node
INTEGER :: CondOutletNode ! Node number for condenser water outlet node
INTEGER :: HeatRecInNode ! Node number for heat recovery water inlet node
INTEGER :: HeatRecOutNode ! Node number for heat recovery water outlet node
REAL(r64) :: rho ! local fluid density
REAL(r64) :: mdot ! local fluid mass flow rate
REAL(r64) :: mdotCond ! local fluid mass flow rate for condenser
INTEGER :: LoopNum
INTEGER :: LoopSideNum
INTEGER :: BranchIndex
INTEGER :: CompIndex
LOGICAL :: FatalError
LOGICAL :: errFlag
LOGICAL :: HeatRecRunFlag
REAL(r64) :: HeatRecHighInletLimit
! FLOW:
! Do the one time initializations
IF (MyOneTimeFlag) THEN
ALLOCATE(MyEnvrnFlag(NumElecReformEIRChillers))
ALLOCATE(MyFlag(NumElecReformEIRChillers))
MyEnvrnFlag = .TRUE.
MyFlag=.TRUE.
MyOneTimeFlag = .false.
END IF
! Initialize condenser nodes
EvapInletNode = ElecReformEIRChiller(EIRChillNum)%EvapInletNodeNum
EvapOutletNode = ElecReformEIRChiller(EIRChillNum)%EvapOutletNodeNum
CondInletNode = ElecReformEIRChiller(EIRChillNum)%CondInletNodeNum
CondOutletNode = ElecReformEIRChiller(EIRChillNum)%CondOutletNodeNum
IF (ElecReformEIRChiller(EIRChillNum)%HeatRecActive ) THEN
HeatRecInNode = ElecReformEIRChiller(EIRChillNum)%HeatRecInletNodeNum
HeatRecOutNode = ElecReformEIRChiller(EIRChillNum)%HeatRecOutletNodeNum
ENDIF
! Init more variables
IF (MyFlag(EIRChillNum)) THEN
! Locate the chillers on the plant loops for later usage
errFlag = .FALSE.
CALL ScanPlantLoopsForObject(ElecReformEIRChiller(EIRChillNum)%Name, &
TypeOf_Chiller_ElectricReformEIR, &
ElecReformEIRChiller(EIRChillNum)%CWLoopNum, &
ElecReformEIRChiller(EIRChillNum)%CWLoopSideNum, &
ElecReformEIRChiller(EIRChillNum)%CWBranchNum,&
ElecReformEIRChiller(EIRChillNum)%CWCompNum, &
LowLimitTemp = ElecReformEIRChiller(EIRChillNum)%TempLowLimitEvapOut, &
InletNodeNumber = ElecReformEIRChiller(EIRChillNum)%EvapInletNodeNum, &
errFlag=errFlag)
IF (ElecReformEIRChiller(EIRChillNum)%CondenserType /= AirCooled) THEN
CALL ScanPlantLoopsForObject(ElecReformEIRChiller(EIRChillNum)%Name, &
TypeOf_Chiller_ElectricReformEIR, &
ElecReformEIRChiller(EIRChillNum)%CDLoopNum, &
ElecReformEIRChiller(EIRChillNum)%CDLoopSideNum, &
ElecReformEIRChiller(EIRChillNum)%CDBranchNum,&
ElecReformEIRChiller(EIRChillNum)%CDCompNum, &
InletNodeNumber = ElecReformEIRChiller(EIRChillNum)%CondInletNodeNum, &
errFlag=errFlag)
CALL InterConnectTwoPlantLoopSides( ElecReformEIRChiller(EIRChillNum)%CWLoopNum, &
ElecReformEIRChiller(EIRChillNum)%CWLoopSideNum, &
ElecReformEIRChiller(EIRChillNum)%CDLoopNum, &
ElecReformEIRChiller(EIRChillNum)%CDLoopSideNum, &
TypeOf_Chiller_ElectricReformEIR, .TRUE. )
ENDIF
IF (ElecReformEIRChiller(EIRChillNum)%HeatRecActive) THEN
CALL ScanPlantLoopsForObject(ElecReformEIRChiller(EIRChillNum)%Name, &
TypeOf_Chiller_ElectricReformEIR, &
ElecReformEIRChiller(EIRChillNum)%HRLoopNum, &
ElecReformEIRChiller(EIRChillNum)%HRLoopSideNum, &
ElecReformEIRChiller(EIRChillNum)%HRBranchNum,&
ElecReformEIRChiller(EIRChillNum)%HRCompNum, &
InletNodeNumber = ElecReformEIRChiller(EIRChillNum)%HeatRecInletNodeNum, &
errFlag=errFlag)
CALL InterConnectTwoPlantLoopSides( ElecReformEIRChiller(EIRChillNum)%CWLoopNum, &
ElecReformEIRChiller(EIRChillNum)%CWLoopSideNum, &
ElecReformEIRChiller(EIRChillNum)%HRLoopNum, &
ElecReformEIRChiller(EIRChillNum)%HRLoopSideNum, &
TypeOf_Chiller_ElectricReformEIR , .TRUE.)
ENDIF
IF ((ElecReformEIRChiller(EIRChillNum)%CondenserType /= AirCooled) .AND. &
(ElecReformEIRChiller(EIRChillNum)%HeatRecActive) ) THEN
CALL InterConnectTwoPlantLoopSides( ElecReformEIRChiller(EIRChillNum)%CDLoopNum, &
ElecReformEIRChiller(EIRChillNum)%CDLoopSideNum, &
ElecReformEIRChiller(EIRChillNum)%HRLoopNum, &
ElecReformEIRChiller(EIRChillNum)%HRLoopSideNum, &
TypeOf_Chiller_ElectricReformEIR , .FALSE. )
ENDIF
IF (errFlag) THEN
CALL ShowFatalError('InitElecReformEIRChiller: Program terminated due to previous condition(s).')
ENDIF
IF (ElecReformEIRChiller(EIRChillNum)%FlowMode == ConstantFlow) Then
! reset flow priority
PlantLoop(ElecReformEIRChiller(EIRChillNum)%CWLoopNum)%LoopSide(ElecReformEIRChiller(EIRChillNum)%CWLoopSideNum)% &
Branch(ElecReformEIRChiller(EIRChillNum)%CWBranchNum)%Comp(ElecReformEIRChiller(EIRChillNum)%CWCompNum)%FlowPriority &
= LoopFlowStatus_NeedyIfLoopOn
ENDIF
IF (ElecReformEIRChiller(EIRChillNum)%FlowMode == LeavingSetpointModulated) Then
! reset flow priority
PlantLoop(ElecReformEIRChiller(EIRChillNum)%CWLoopNum)%LoopSide(ElecReformEIRChiller(EIRChillNum)%CWLoopSideNum)% &
Branch(ElecReformEIRChiller(EIRChillNum)%CWBranchNum)%Comp(ElecReformEIRChiller(EIRChillNum)%CWCompNum)%FlowPriority &
= LoopFlowStatus_NeedyIfLoopOn
! check if setpoint on outlet node
IF ((Node(ElecReformEIRChiller(EIRChillNum)%EvapOutletNodeNum)%TempSetPoint == SensedNodeFlagValue) .AND. &
(Node(ElecReformEIRChiller(EIRChillNum)%EvapOutletNodeNum)%TempSetPointHi == SensedNodeFlagValue)) THEN
IF (.NOT. AnyEnergyManagementSystemInModel) THEN
IF (.NOT. ElecReformEIRChiller(EIRChillNum)%ModulatedFlowErrDone) THEN
CALL ShowWarningError('Missing temperature setpoint for LeavingSetpointModulated mode chiller named ' // &
TRIM(ElecReformEIRChiller(EIRChillNum)%Name) )
CALL ShowContinueError(' A temperature setpoint is needed at the outlet node of a chiller ' // &
'in variable flow mode, use a SetpointManager')
CALL ShowContinueError(' The overall loop setpoint will be assumed for chiller. The simulation continues ... ')
ElecReformEIRChiller(EIRChillNum)%ModulatedFlowErrDone = .TRUE.
ENDIF
ELSE
! need call to EMS to check node
FatalError = .FALSE. ! but not really fatal yet, but should be.
CALL CheckIfNodeSetpointManagedByEMS(ElecReformEIRChiller(EIRChillNum)%EvapOutletNodeNum,iTemperatureSetpoint, FatalError)
IF (FatalError) THEN
IF (.NOT. ElecReformEIRChiller(EIRChillNum)%ModulatedFlowErrDone) THEN
CALL ShowWarningError('Missing temperature setpoint for LeavingSetpointModulated mode chiller named ' // &
TRIM(ElecReformEIRChiller(EIRChillNum)%Name) )
CALL ShowContinueError(' A temperature setpoint is needed at the outlet node of a chiller evaporator ' // &
'in variable flow mode')
CALL ShowContinueError(' use a Setpoint Manager to establish a setpoint at the chiller evaporator outlet node ')
CALL ShowContinueError(' or use an EMS actuator to establish a setpoint at the outlet node ')
CALL ShowContinueError(' The overall loop setpoint will be assumed for chiller. The simulation continues ... ')
ElecReformEIRChiller(EIRChillNum)%ModulatedFlowErrDone = .TRUE.
ENDIF
ENDIF
ENDIF
ElecReformEIRChiller(EIRChillNum)%ModulatedFlowSetToLoop = .TRUE.
Node(ElecReformEIRChiller(EIRChillNum)%EvapOutletNodeNum)%TempSetPoint = &
Node(PlantLoop(ElecReformEIRChiller(EIRChillNum)%CWLoopNum)%TempSetPointNodeNum)%TempSetPoint
Node(ElecReformEIRChiller(EIRChillNum)%EvapOutletNodeNum)%TempSetPointHi = &
Node(PlantLoop(ElecReformEIRChiller(EIRChillNum)%CWLoopNum)%TempSetPointNodeNum)%TempSetPointHi
ENDIF
ENDIF
MyFlag(EIRChillNum)=.FALSE.
ENDIF
! Initialize Demand Side Variables
! IF((MyEnvrnFlag(EIRChillNum) .and. BeginEnvrnFlag) &
! .OR. (Node(CondInletNode)%MassFlowrate <= 0.0 .AND. RunFlag)) THEN
IF(MyEnvrnFlag(EIRChillNum) .and. BeginEnvrnFlag .AND. (PlantSizesOkayToFinalize)) THEN
IF (PlantSizeNotComplete) CALL SizeElecReformEIRChiller(EIRChillNum)
rho = GetDensityGlycol(PlantLoop(ElecReformEIRChiller(EIRChillNum)%CWLoopNum)%FluidName, &
InitConvTemp, &
PlantLoop(ElecReformEIRChiller(EIRChillNum)%CWLoopNum)%FluidIndex,&
'InitElecReformEIRChiller')
ElecReformEIRChiller(EIRChillNum)%EvapMassFlowRateMax = ElecReformEIRChiller(EIRChillNum)%EvapVolFlowRate * rho
CALL InitComponentNodes(0.d0, ElecReformEIRChiller(EIRChillNum)%EvapMassFlowRateMax, &
EvapInletNode, &
EvapOutletNode, &
ElecReformEIRChiller(EIRChillNum)%CWLoopNum, &
ElecReformEIRChiller(EIRChillNum)%CWLoopSideNum, &
ElecReformEIRChiller(EIRChillNum)%CWBranchNum, &
ElecReformEIRChiller(EIRChillNum)%CWCompNum)
IF (ElecReformEIRChiller(EIRChillNum)%CondenserType == WaterCooled) THEN
rho = GetDensityGlycol(PlantLoop(ElecReformEIRChiller(EIRChillNum)%CDLoopNum)%FluidName, &
ElecReformEIRChiller(EIRChillNum)%TempRefCondIn, &
PlantLoop(ElecReformEIRChiller(EIRChillNum)%CDLoopNum)%FluidIndex,&
'InitElecReformEIRChiller')
ElecReformEIRChiller(EIRChillNum)%CondMassFlowRateMax = rho * ElecReformEIRChiller(EIRChillNum)%CondVolFlowRate
CALL InitComponentNodes(0.d0, ElecReformEIRChiller(EIRChillNum)%CondMassFlowRateMax ,&
CondInletNode, &
CondOutletNode, &
ElecReformEIRChiller(EIRChillNum)%CDLoopNum, &
ElecReformEIRChiller(EIRChillNum)%CDLoopSideNum, &
ElecReformEIRChiller(EIRChillNum)%CDBranchNum, &
ElecReformEIRChiller(EIRChillNum)%CDCompNum)
Node(CondInletNode)%Temp = ElecReformEIRChiller(EIRChillNum)%TempRefCondIn
ELSE ! air or evap air condenser
! Initialize maximum available condenser flow rate
Node(CondInletNode)%MassFlowRate = ElecReformEIRChiller(EIRChillNum)%CondVolFlowRate * &
PsyRhoAirFnPbTdbW(StdBaroPress,ElecReformEIRChiller(EIRChillNum)%TempRefCondIn,0.0D0,'InitElecReformEIRChiller')
Node(CondOutletNode)%MassFlowRate = Node(CondInletNode)%MassFlowrate
Node(CondInletNode)%MassFlowRateMaxAvail = Node(CondInletNode)%MassFlowrate
Node(CondInletNode)%MassFlowRateMax = Node(CondInletNode)%MassFlowrate
Node(CondOutletNode)%MassFlowRateMax = Node(CondInletNode)%MassFlowrate
Node(CondInletNode)%MassFlowRateMinAvail = 0.0d0
Node(CondInletNode)%MassFlowRateMin = 0.0d0
Node(CondOutletNode)%MassFlowRateMinAvail = 0.0d0
Node(CondOutletNode)%MassFlowRateMin = 0.0d0
Node(CondInletNode)%Temp = ElecReformEIRChiller(EIRChillNum)%TempRefCondIn
ENDIF
IF (ElecReformEIRChiller(EIRChillNum)%HeatRecActive) THEN
rho = GetDensityGlycol(PlantLoop(ElecReformEIRChiller(EIRChillNum)%HRLoopNum)%FluidName, &
InitConvTemp, &
PlantLoop(ElecReformEIRChiller(EIRChillNum)%HRLoopNum)%FluidIndex,&
'InitElecReformEIRChiller')
ElecReformEIRChiller(EIRChillNum)%DesignHeatRecMassFlowRate = rho * &
ElecReformEIRChiller(EIRChillNum)%DesignHeatRecVolFlowRate
CALL InitComponentNodes(0.0D0, ElecReformEIRChiller(EIRChillNum)%DesignHeatRecMassFlowRate , &
ElecReformEIRChiller(EIRChillNum)%HeatRecInletNodeNum, &
ElecReformEIRChiller(EIRChillNum)%HeatRecOutletNodeNum, &
ElecReformEIRChiller(EIRChillNum)%HRLoopNum, &
ElecReformEIRChiller(EIRChillNum)%HRLoopSideNum, &
ElecReformEIRChiller(EIRChillNum)%HRBranchNum, &
ElecReformEIRChiller(EIRChillNum)%HRCompNum)
! overall capacity limit
ElecReformEIRChiller(EIRChillNum)%HeatRecMaxCapacityLimit = ElecReformEIRChiller(EIRChillNum)%HeatRecCapacityFraction &
* (ElecReformEIRChiller(EIRChillNum)%RefCap + ElecReformEIRChiller(EIRChillNum)%RefCap &
/ElecReformEIRChiller(EIRChillNum)%RefCOP)
ENDIF
MyEnvrnFlag(EIRChillNum) = .FALSE.
END IF
IF (.not. BeginEnvrnFlag) THEN
MyEnvrnFlag(EIRChillNum)=.true.
END IF
IF ((ElecReformEIRChiller(EIRChillNum)%FlowMode == LeavingSetpointModulated) &
.AND. ElecReformEIRChiller(EIRChillNum)%ModulatedFlowSetToLoop) THEN
! fix for clumsy old input that worked because loop setpoint was spread.
! could be removed with transition, testing , model change, period of being obsolete.
Node(ElecReformEIRChiller(EIRChillNum)%EvapOutletNodeNum)%TempSetPoint = &
Node(PlantLoop(ElecReformEIRChiller(EIRChillNum)%CWLoopNum)%TempSetPointNodeNum)%TempSetPoint
Node(ElecReformEIRChiller(EIRChillNum)%EvapOutletNodeNum)%TempSetPointHi = &
Node(PlantLoop(ElecReformEIRChiller(EIRChillNum)%CWLoopNum)%TempSetPointNodeNum)%TempSetPointHi
ENDIF
IF ((ABS(MyLoad) > 0.d0) .AND. RunFlag) THEN
mdot = ElecReformEIRChiller(EIRChillNum)%EvapMassFlowRateMax
mdotCond = ElecReformEIRChiller(EIRChillNum)%CondMassFlowRateMax
ELSE
mdot = 0.d0
mdotCond = 0.d0
ENDIF
CALL SetComponentFlowRate( mdot, EvapInletNode, EvapOutletNode, &
ElecReformEIRChiller(EIRChillNum)%CWLoopNum, &
ElecReformEIRChiller(EIRChillNum)%CWLoopSideNum, &
ElecReformEIRChiller(EIRChillNum)%CWBranchNum, &
ElecReformEIRChiller(EIRChillNum)%CWCompNum)
IF (ElecReformEIRChiller(EIRChillNum)%CondenserType == WaterCooled) THEN
CALL SetComponentFlowRate( mdotCond, CondInletNode, CondOutletNode, &
ElecReformEIRChiller(EIRChillNum)%CDLoopNum, &
ElecReformEIRChiller(EIRChillNum)%CDLoopSideNum, &
ElecReformEIRChiller(EIRChillNum)%CDBranchNum, &
ElecReformEIRChiller(EIRChillNum)%CDCompNum)
ENDIF
! Initialize heat recovery flow rates at node
IF (ElecReformEIRChiller(EIRChillNum)%HeatRecActive ) THEN
LoopNum = ElecReformEIRChiller(EIRChillNum)%HRLoopNum
LoopSideNum = ElecReformEIRChiller(EIRChillNum)%HRLoopSideNum
BranchIndex = ElecReformEIRChiller(EIRChillNum)%HRBranchNum
CompIndex = ElecReformEIRChiller(EIRChillNum)%HRCompNum
! check if inlet limit active and if exceeded.
IF (ElecReformEIRChiller(EIRChillNum)%HeatRecInletLimitSchedNum > 0) THEN
HeatRecHighInletLimit = GetCurrentScheduleValue(ElecReformEIRChiller(EIRChillNum)%HeatRecInletLimitSchedNum)
IF ( Node(HeatRecInNode)%Temp > HeatRecHighInletLimit) THEN ! shut down heat recovery
HeatRecRunFlag = .FALSE.
ELSE
HeatRecRunFlag = RunFlag
ENDIF
ELSE
HeatRecRunFlag = RunFlag
ENDIF
If ( HeatRecRunFlag) Then
mdot = ElecReformEIRChiller(EIRChillNum)%DesignHeatRecMassFlowRate
ELSE
mdot = 0.d0
ENDIF
CALL SetComponentFlowRate(mdot,HeatRecInNode,HeatRecOutNode,LoopNum,LoopSideNum,BranchIndex,CompIndex)
END IF
RETURN
END SUBROUTINE InitElecReformEIRChiller