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 | ||
---|---|---|---|---|---|---|
real(kind=r64), | intent(inout) | :: | CompFlow | |||
integer, | intent(in) | :: | InletNode | |||
integer, | intent(in) | :: | OutletNode | |||
integer, | intent(in) | :: | LoopNum | |||
integer, | intent(in) | :: | LoopSideNum | |||
integer, | intent(in) | :: | BranchIndex | |||
integer, | intent(in) | :: | CompIndex |
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 SetComponentFlowRate(CompFlow,InletNode,OutletNode,LoopNum,LoopSideNum,BranchIndex,CompIndex)
! SUBROUTINE INFORMATION:
! AUTHOR Dan Fisher
! DATE WRITTEN August 2009
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! General purpose worker routine to set flows for a component model
!
! METHODOLOGY EMPLOYED:
! na
! REFERENCES:
! na
! USE STATEMENTS:
! na
USE DataLoopNode, ONLY : Node, NodeID, NumOfNodes
USE DataPlant, ONLY : PlantLoop, DemandOpSchemeType, FlowUnlocked, &
FlowLocked, PlantSizesOkayToFinalize
USE DataBranchAirLoopPlant, ONLY : ControlType_SeriesActive, MassFlowTolerance
USE DataInterfaces, ONLY : ShowFatalError, ShowContinueError, ShowSevereError,ShowContinueErrorTimeStamp
USE General, ONLY : RoundSigDigits
USE DataSizing, ONLY : AutoSize
USE DataGlobals, ONLY : SysSizingCalc
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
REAL(r64), INTENT(INOUT) :: CompFlow ![kg/s]
INTEGER, INTENT(IN) :: LoopNum ! plant loop index for PlantLoop structure
INTEGER, INTENT(IN) :: LoopSideNum ! Loop side index for PlantLoop structure
INTEGER, INTENT(IN) :: BranchIndex ! branch index for PlantLoop
INTEGER, INTENT(IN) :: CompIndex ! component index for PlantLoop
INTEGER, INTENT(IN) :: InletNode ! component's inlet node index in node structure
INTEGER, INTENT(IN) :: OutletNode ! component's outlet node index in node structure
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
LOGICAL, SAVE :: OneTimeDiagSetup = .TRUE.
LOGICAL, DIMENSION(:), ALLOCATABLE, SAVE :: NodeErrorMsgIssued
LOGICAL, SAVE :: NullPlantErrorMsgIssued
REAL(r64) :: MdotOldRequest ! initial value of mass flow
INTEGER :: CompInletNodeNum
INTEGER :: CompOutletNodeNum
INTEGER :: CompNum
REAL(r64) :: SeriesBranchHighFlowRequest ! local temporary used for sweeping across components on a branch
REAL(r64) :: SeriesBranchHardwareMaxLim
REAL(r64) :: SeriesBranchHardwareMinLim
REAL(r64) :: SeriesBranchMaxAvail
REAL(r64) :: SeriesBranchMinAvail
IF (OneTimeDiagSetup) THEN
ALLOCATE(NodeErrorMsgIssued(NumOfNodes) )
NodeErrorMsgIssued = .FALSE.
NullPlantErrorMsgIssued = .FALSE.
OneTimeDiagSetup = .FALSE.
ENDIF
IF (LoopNum == 0) THEN ! protect from hard crash below
IF (.NOT. NullPlantErrorMsgIssued ) THEN ! throw one dev error message
IF (InletNode > 0) THEN
CALL ShowSevereError('SetComponentFlowRate: trapped plant loop index = 0, check component with inlet node named=' &
//TRIM(NodeID(InletNode)) )
ELSE
CALL ShowSevereError('SetComponentFlowRate: trapped plant loop node id = 0')
ENDIF
NullPlantErrorMsgIssued = .TRUE.
ENDIF
RETURN
ENDIF
! FLOW:
MdotOldRequest = Node(InletNode)%MassFlowRateRequest
IF (PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchIndex)%Comp(CompIndex)%CurOpSchemeType == DemandOpSchemeType) THEN
! store flow request on inlet node
Node(InletNode)%MassFlowRateRequest = CompFlow
Node(OutletNode)%MassFlowRateMinAvail = MAX(Node(InletNode)%MassFlowRateMinAvail ,Node(InletNode)%MassFlowRateMin)
!virtual 2-way valve (was tried but it clamps down demand side component's flow options so they can't find proper solutions)
! Node(OutletNode)%MassFlowRateMinAvail = MAX(Node(InletNode)%MassFlowRateMinAvail , CompFlow)
Node(OutletNode)%MassFlowRateMaxAvail = MIN(Node(InletNode)%MassFlowRateMaxAvail,Node(InletNode)%MassFlowRateMax)
! Node(OutletNode)%MassFlowRateMaxAvail = MIN(Node(InletNode)%MassFlowRateMaxAvail , CompFlow)
ELSE
!DSU lodge the original request for all types
Node(InletNode)%MassFlowRateRequest = CompFlow
ENDIF
!Update Min/Max Avail
Node(OutletNode)%MassFlowRateMinAvail = MAX(Node(InletNode)%MassFlowRateMinAvail ,Node(InletNode)%MassFlowRateMin)
IF (Node(InletNode)%MassFlowRateMax >= 0.d0) THEN
Node(OutletNode)%MassFlowRateMaxAvail = MIN(Node(InletNode)%MassFlowRateMaxAvail,Node(InletNode)%MassFlowRateMax)
ELSE
IF (.NOT. SysSizingCalc .and. PlantSizesOkayToFinalize ) THEN
! throw error for developers, need to change a componennt model to set hardware limits on inlet
If ( .NOT. NodeErrorMsgIssued(InletNode)) THEN
CALL ShowSevereError('SetComponentFlowRate: check component model implementation for component with inlet node named=' &
//TRIM(NodeID(InletNode)) )
CALL ShowContinueError('Inlet node MassFlowRatMax = '//TRIM(RoundSigDigits(Node(InletNode)%MassFlowRateMax,8)) )
NodeErrorMsgIssued(InletNode) = .TRUE.
ENDIF
ENDIF
ENDIF
!Set loop flow rate
IF (PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Flowlock == FlowUnlocked)THEN
IF (PlantLoop(LoopNum)%MaxVolFlowRate == AutoSize)THEN !still haven't sized the plant loop
Node(OutletNode)%MassFlowRate = CompFlow
Node(InletNode)%MassFlowRate = Node(OutletNode)%MassFlowRate
ELSE !bound the flow by Min/Max available and hardware limits
IF (PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchIndex)%Comp(CompIndex)%FlowCtrl == ControlType_SeriesActive) THEN
! determine highest flow request for all the components on the branch
SeriesBranchHighFlowRequest = 0.d0
SeriesBranchHardwareMaxLim = Node(InletNode)%MassFlowRateMax
SeriesBranchHardwareMinLim = 0.d0
SeriesBranchMaxAvail = Node(InletNode)%MassFlowRateMaxAvail
SeriesBranchMinAvail = 0.d0
DO CompNum = 1, PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchIndex)%TotalComponents
CompInletNodeNum = PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchIndex)%Comp(CompNum)%NodeNumIn
SeriesBranchHighFlowRequest = MAX(Node(CompInletNodeNum)%MassFlowRateRequest, SeriesBranchHighFlowRequest)
SeriesBranchHardwareMaxLim = MIN(Node(CompInletNodeNum)%MassFlowRateMax, SeriesBranchHardwareMaxLim)
SeriesBranchHardwareMinLim = MAX(Node(CompInletNodeNum)%MassFlowRateMin, SeriesBranchHardwareMinLim)
SeriesBranchMaxAvail = MIN(Node(CompInletNodeNum)%MassFlowRateMaxAvail, SeriesBranchMaxAvail)
SeriesBranchMinAvail = MAX(Node(CompInletNodeNum)%MassFlowRateMinAvail, SeriesBranchMinAvail)
ENDDO
!take higher of branch max flow request and this new flow request
CompFlow = MAX(CompFlow, SeriesBranchHighFlowRequest)
! apply constraints on component flow
CompFlow = MAX(CompFlow, SeriesBranchHardwareMinLim)
CompFlow = MAX(CompFlow, SeriesBranchMinAvail)
CompFlow = MIN(CompFlow, SeriesBranchHardwareMaxLim)
CompFlow = MIN(CompFlow, SeriesBranchMaxAvail)
IF (CompFlow < MassFlowTolerance) CompFlow = 0.d0
Node(OutletNode)%MassFlowRate = CompFlow
Node(InletNode)%MassFlowRate = Node(OutletNode)%MassFlowRate
DO CompNum = 1, PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchIndex)%TotalComponents
CompInletNodeNum = PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchIndex)%Comp(CompNum)%NodeNumIn
CompOutletNodeNum = PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchIndex)%Comp(CompNum)%NodeNumOut
Node(CompInletNodeNum)%MassFlowRate = Node(OutletNode)%MassFlowRate
Node(CompOutletNodeNum)%MassFlowRate = Node(OutletNode)%MassFlowRate
ENDDO
ELSE ! not series active
Node(OutletNode)%MassFlowRate = MAX(Node(OutletNode)%MassFlowRateMinAvail, CompFlow)
Node(OutletNode)%MassFlowRate = MAX(Node(InletNode)%MassFlowRateMin, Node(OutletNode)%MassFlowRate)
Node(OutletNode)%MassFlowRate = MIN(Node(OutletNode)%MassFlowRateMaxAvail, Node(OutletNode)%MassFlowRate)
Node(OutletNode)%MassFlowRate = MIN(Node(InletNode)%MassFlowRateMax, Node(OutletNode)%MassFlowRate)
IF (Node(OutletNode)%MassFlowRate < MassFlowTolerance) Node(OutletNode)%MassFlowRate = 0.d0
CompFlow = Node(OutletNode)%MassFlowRate
Node(InletNode)%MassFlowRate = Node(OutletNode)%MassFlowRate
ENDIF
END IF
ELSEIF (PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Flowlock == FlowLocked)THEN
Node(OutletNode)%MassFlowRate = Node(InletNode)%MassFlowRate
CompFlow = Node(OutletNode)%MassFlowRate
! IF (((CompFlow - Node(OutletNode)%MassFlowRateMaxAvail) > MassFlowTol) .OR. &
! ((Node(OutletNode)%MassFlowRateMinAvail - CompFlow) > MassFlowTol)) THEN
! IF ( .NOT. NodeErrorMsgIssued(InletNode)) THEN
! CALL ShowSevereError('SetComponentFlowRate: Flow rate is out of range') !DEBUG error...should never get here
! CALL ShowContinueErrorTimeStamp(' ')
! CALL ShowContinueError('Component flow rate [kg/s] = '//TRIM(RoundSigDigits(CompFlow,8)) )
! CALL ShowContinueError('Node maximum flow rate available [kg/s] = ' &
! //TRIM(RoundSigDigits(Node(OutletNode)%MassFlowRateMaxAvail,8)) )
! CALL ShowContinueError('Node minimum flow rate available [kg/s] = '&
! //TRIM(RoundSigDigits(Node(OutletNode)%MassFlowRateMinAvail,8)) )
! CALL ShowContinueError('Component named = ' &
! //TRIM(PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchIndex)%Comp(CompIndex)%Name) )
! NodeErrorMsgIssued(InletNode) = .TRUE.
! ENDIF
! ! CALL ShowFatalError('SetComponentFlowRate: out of range flow rate problem caused termination')
! ENDIF
ELSE
CALL ShowFatalError('SetComponentFlowRate: Flow lock out of range') !DEBUG error...should never get here
ENDIF
IF (PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchIndex)%Comp(CompIndex)%CurOpSchemeType == DemandOpSchemeType) THEN
IF ((MdotOldRequest > 0.d0) .AND. (CompFlow > 0.d0)) THEN ! sure that not coming back from a no flow reset
IF (ABS(MdotOldRequest - Node(InletNode)%MassFlowRateRequest) > MassFlowTolerance) THEN !demand comp changed its flow request
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%SimLoopSideNeeded = .TRUE.
ENDIF
ENDIF
ENDIF
RETURN
END SUBROUTINE SetComponentFlowRate !DSU2