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) | :: | LoopNum | |||
integer, | intent(in) | :: | PumpNum |
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 SetupPumpMinMaxFlows(LoopNum, PumpNum)
! SUBROUTINE INFORMATION:
! AUTHOR: Edwin Lee
! DATE WRITTEN: Aug 2010
! MODIFIED Based on the Flow control portion of what was previously Pumps::InitSimVars, by:
! Dan Fisher October 1998
! Richard Liesen July 2001
! July 2001, Rick Strand (implemented new pump controls)
! May 2009, Brent Griffith (added EMS override capability)
! B. Griffith, Nov 2011 Pump control: Intermittent vs Continuous
! RE-ENGINEERED
! PURPOSE OF THIS SUBROUTINE:
! This subroutine initializes the pump minAvail and maxAvail flow rates, and assigns them to the
! outlet min/max avail according to inlet min/max constraints and zero flow request
! The loop solver then uses this information to set up the flow bounds for the loop side
! for the current iteration.
! METHODOLOGY EMPLOYED:
! Design flow rate and user specified minimum flow rate is compared in the inlet node
! min/maxavail. The pump output is appropriately constrained.
!
! Design flow is rated flow times schedule fraction
! Inlet node max will represent the rated flow rate according to pump init routines.
! These values are bounded by hardware min constraints on the inlet node, which is likely zero.
! These values are also bounded by EMS overridable limit of max flow rate.
! USE STATEMENTS:
USE ScheduleManager, ONLY: GetCurrentScheduleValue
USE FluidProperties, ONLY: GetDensityGlycol
USE DataPlant, ONLY: PlantLoop, Press_FlowCorrection, PlantAvailMgr
USE PlantPressureSystem, ONLY: ResolveLoopFlowVsPressure
USE PlantUtilities, ONLY: BoundValueToWithinTwoValues
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: LoopNum
INTEGER, INTENT(IN) :: PumpNum
! SUBROUTINE PARAMETER DEFINITIONS:
CHARACTER(len=*), PARAMETER :: RoutineName = 'PlantPumps:SetupPumpMinMaxFlows: '
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: InletNode !pump inlet node number
INTEGER :: OutletNode !pump outlet node number
REAL(r64) :: InletNodeMax
REAL(r64) :: InletNodeMin
REAL(r64) :: PumpMassFlowRateMax !max allowable flow rate at the pump
REAL(r64) :: PumpMassFlowRateMin !min allowable flow rate at the pump
REAL(r64) :: PumpSchedFraction
REAL(r64) :: PumpOverridableMaxLimit
REAL(r64) :: PumpMassFlowRateMinLimit
REAL(r64) :: PumpSchedRPM !Pump RPM Optional Input
!Inlet/Outlet Node Numbers
InletNode = PumpEquip(PumpNum)%InletNodeNum
OutletNode = PumpEquip(PumpNum)%OutletNodeNum
!Inlet node Min/MaxAvail
InletNodeMax = Node(InletNode)%MassFlowRateMaxAvail
InletNodeMin = Node(InletNode)%MassFlowRateMinAvail
!Retrive the pump speed fraction from the pump schedule
IF (PumpEquip(PumpNum)%PumpScheduleIndex .NE. 0) THEN
PumpSchedFraction = GetCurrentScheduleValue(PumpEquip(PumpNum)%PumpScheduleIndex)
PumpSchedFraction = BoundValueToWithinTwoValues(PumpSchedFraction, 0.0d0, 1.0d0)
ELSE
PumpSchedFraction = 1.0d0
END IF
!User specified min/max mass flow rates for pump
PumpOverridableMaxLimit = PumpEquip(PumpNum)%MassFlowRateMax
PumpMassFlowRateMinLimit = PumpEquip(PumpNum)%MassFlowRateMin
!The pump outlet node Min/MaxAvail
PumpMassFlowRateMin = MAX(InletNodeMin, PumpMassFlowRateMinLimit)
PumpMassFlowRateMax = MIN(InletNodeMax, PumpOverridableMaxLimit * PumpSchedFraction)
!Check for conflicts (MaxAvail < MinAvail)
IF(PumpMassFlowRateMin > PumpMassFlowRateMax)THEN !the demand side wants to operate outside of the pump range
!shut the pump (and the loop) down
PumpMassFlowRateMin = 0.0d0
PumpMassFlowRateMax = 0.0d0
!Let the user know that his input file is overconstrained
!DSU? Call one-time warning...with a counter
ENDIF
!DSU? IF (EMS ACTIVE) THEN...
!DSU? PumpMassFlowRateMax = MIN(PumpMassFlowRateMax, PumpOverridableMaxLimit) !Allow override by EMS
SELECT CASE (PumpEquip(PumpNum)%PumpType)
CASE (Pump_VarSpeed)
IF (PumpEquip(PumpNum)%HasVFD) THEN
SELECT CASE (PumpEquip(PumpNum)%VFD%VFDControlType)
CASE (VFDManual)
!Evaluate the schedule if it exists and put the fraction into a local variable
PumpSchedRPM = GetCurrentScheduleValue(PumpEquip(PumpNum)%VFD%ManualRPMSchedIndex)
!Convert the RPM to rot/sec for calculation routine
PumpEquip(PumpNum)%RotSpeed = PumpSchedRPM / 60.0d0
!Resolve the new mass flow rate based on current pressure characteristics
IF (PlantLoop(PumpEquip(PumpNum)%LoopNum)%UsePressureForPumpCalcs .AND. &
PlantLoop(PumpEquip(PumpNum)%LoopNum)%PressureSimType == Press_FlowCorrection .AND. &
PlantLoop(PumpEquip(PumpNum)%LoopNum)%PressureDrop.GT.0.0d0) THEN
PumpMassFlowRate = ResolveLoopFlowVsPressure(PumpEquip(PumpNum)%LoopNum, &
Node(PumpEquip(PumpNum)%InletNodeNum)%MassFlowRate, &
PumpEquip(PumpNum)%PressureCurve_Index, &
PumpEquip(PumpNum)%RotSpeed, &
PumpEquip(PumpNum)%ImpellerDiameter, &
PumpEquip(PumpNum)%MinPhiValue, &
PumpEquip(PumpNum)%MaxPhiValue)
PumpMassFlowRateMax = PumpMassFlowRate
PumpMassFlowRateMin = PumpMassFlowRate
END IF
CASE (VFDAutomatic)
IF (PlantLoop(PumpEquip(PumpNum)%LoopNum)%UsePressureForPumpCalcs .AND. &
PlantLoop(PumpEquip(PumpNum)%LoopNum)%PressureSimType == Press_FlowCorrection .AND. &
PlantLoop(PumpEquip(PumpNum)%LoopNum)%PressureDrop.GT.0.0d0) THEN
Call GetRequiredMassFlowRate(LoopNum, PumpNum, Node(PumpEquip(PumpNum)%InletNodeNum)%MassFlowRate, &
PumpMassFlowRate, PumpMassFlowRateMin, PumpMassFlowRateMax)
END IF
END SELECT !VFDControlType
END IF
IF (PumpEquip(PumpNum)%PumpControl == Continuous) THEN
Node(InletNode)%MassFlowRateRequest = PumpMassFlowRateMin
ENDIF
CASE (Pump_ConSpeed)
IF (PumpEquip(PumpNum)%PumpControl == Continuous) THEN
PumpMassFlowRateMin = PumpMassFlowRateMax
Node(InletNode)%MassFlowRateRequest = PumpMassFlowRateMin
ENDIF
! Override (lock down flow) for pressure drop if applicable
IF (PumpEquip(PumpNum)%LoopNum .GT. 0) THEN
IF (PlantLoop(PumpEquip(PumpNum)%LoopNum)%UsePressureForPumpCalcs .AND. &
PlantLoop(PumpEquip(PumpNum)%LoopNum)%PressureSimType == Press_FlowCorrection .AND. &
PlantLoop(PumpEquip(PumpNum)%LoopNum)%PressureDrop.GT.0.0d0) THEN
PumpMassFlowRate = ResolveLoopFlowVsPressure(PumpEquip(PumpNum)%LoopNum, &
Node(PumpEquip(PumpNum)%InletNodeNum)%MassFlowRate, & !DSU? Is this still valid?
PumpEquip(PumpNum)%PressureCurve_Index, &
PumpEquip(PumpNum)%RotSpeed, &
PumpEquip(PumpNum)%ImpellerDiameter, &
PumpEquip(PumpNum)%MinPhiValue, &
PumpEquip(PumpNum)%MaxPhiValue)
PumpMassFlowRateMax = PumpMassFlowRate
PumpMassFlowRateMin = PumpMassFlowRate
END IF
END IF
END SELECT
! Override pump operation based on System Availability Managers, should be done elsewhere? I suppose this should be OK though
IF(ALLOCATED(PlantAvailMgr))THEN
IF (PlantAvailMgr(LoopNum)%AvailStatus == ForceOff) THEN
PumpMassFlowRateMax = 0.0d0
PumpMassFlowRateMin = 0.0d0
END IF
END IF
! Check if EMS is overriding flow
IF (PumpEquip(PumpNum)%EMSMassFlowOverrideOn) THEN
PumpMassFlowRateMax = PumpEquip(PumpNum)%EMSMassFlowValue
PumpMassFlowRateMin = PumpEquip(PumpNum)%EMSMassFlowValue
ENDIF
! Update outlet node to allow loop solver to get data
!DSU? could avoid this by passing data in/out to avoid putting things on nodes
Node(OutletNode)%MassFlowRateMinAvail = PumpMassFlowRateMin
Node(OUtletNode)%MassFlowRateMaxAvail = PumpMassFlowRateMax
RETURN
END SUBROUTINE SetupPumpMinMaxFlows