Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | SysNum | |||
logical, | intent(inout) | :: | SysReSim |
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 ResolveSysFlow(SysNum,SysReSim)
! SUBROUTINE INFORMATION
! AUTHOR: Fred Buhl
! DATE WRITTEN: Dec 1999
! MODIFIED:
! RE-ENGINEERED: This is new code, not reengineered
! PURPOSE OF THIS SUBROUTINE:
! This subroutines checks for mass flow balance in all air system branches
! and across all connections. If there is a failure of mass flow
! balance, mass flows are imposed to achieve mass flow balance and
! the resimulate flag SysReSim is set to true.
! METHODOLOGY EMPLOYED:
! Node()%MassFlowRateMaxAvail for every node is set to the minimum
! Node()%MassFlowRateMaxAvail on each branch. Mass balance is imposed
! at the branch connections. System inlet mass flows are forced to
! be less than or equal to the resulting inlet MassFlowRateMaxAvails.
! REFERENCES: None
! USE STATEMENTS:none
IMPLICIT NONE
! SUBROUTINE ARGUMENTS:
INTEGER, INTENT(IN) :: SysNum ! the primary air system number
LOGICAL, INTENT(INOUT) :: SysReSim ! Set to TRUE if mass balance fails and resimulation is needed
! SUBROUTINE PARAMETER DEFINITIONS: None
! INTERFACE BLOCK DEFINITIONS: None
! DERIVED TYPE DEFINITIONS: None
! SUBROUTINE LOCAL VARIABLE DEFINITIONS
INTEGER :: BranchNum ! branch DO loop index
INTEGER :: NodeIndex ! node on branch DO loop index
REAL(r64) :: MassFlowRateOutSum ! sum of splitter outlet mass flow rates (imposed)
REAL(r64) :: BranchMassFlowMaxAvail ! branch level maximum flow rate possible
INTEGER :: OutletNum ! splitter outlet DO loop index
INTEGER :: OutletNodeNum ! a splitter outlet node number
INTEGER :: InletNodeNum ! splitter inlet node number
INTEGER :: NodeNum ! a node number
INTEGER :: NodeNumNext ! node number of next node on a branch
INTEGER :: InNodeNum ! air system inlet node
INTEGER :: InBranchNum ! air system inlet branch number
INTEGER :: InBranchIndex ! air sys inlet branch DO loop index
! FLOW
! Find the minimum MassFlowMaxAvail for each branch in the system and store it on the branch inlet node.
! Check for mass flow conservation on each branch. Set SysReSim to TRUE is mass flow not conserved.
DO BranchNum=1,PrimaryAirSystem(SysNum)%NumBranches ! loop over branches in system
! Initialize branch max avail mass flow to max avail mass flow at outlet node
BranchMassFlowMaxAvail = Node(PrimaryAirSystem(SysNum)%Branch(BranchNum)%NodeNumOut)%MassFlowRateMaxAvail
DO NodeIndex=1,PrimaryAirSystem(SysNum)%Branch(BranchNum)%TotalNodes ! loop over nodes on branch
! Get the new smallest max avail mass flow
NodeNum = PrimaryAirSystem(SysNum)%Branch(BranchNum)%NodeNum(NodeIndex)
BranchMassFlowMaxAvail = MIN(BranchMassFlowMaxAvail,Node(NodeNum)%MassFlowRateMaxAvail)
! Check for mass flow conservation on the branch
IF (NodeIndex.LT.PrimaryAirSystem(SysNum)%Branch(BranchNum)%TotalNodes) THEN
! Set ReSim flag to TRUE if mass flow not conserved on this branch
NodeNumNext = PrimaryAirSystem(SysNum)%Branch(BranchNum)%NodeNum(NodeIndex+1)
IF (NodeNum.EQ.PrimaryAirSystem(SysNum)%OASysInletNodeNum) CYCLE ! don't enforce mass balance across OA Sys
IF (ABS(Node(NodeNum)%MassFlowRate - Node(NodeNumNext)%MassFlowRate) .GT. SmallMassFlow) SysReSim = .TRUE.
END IF
END DO ! end node loop
! Store the minimum MassFlowMasAvail for this branch on the branch inlet node
Node(PrimaryAirSystem(SysNum)%Branch(BranchNum)%NodeNumIn)%MassFlowRateMaxAvail = BranchMassFlowMaxAvail
END DO ! end branch loop
! force resimulation for fan-cycling, nonsimple systems
IF ( .NOT. AirLoopControlInfo(SysNum)%Simple .AND. AirLoopControlInfo(SysNum)%CyclingFan) THEN
SysReSim = .TRUE.
END IF
! If mass flow conserved on each branch, check for mass balance across splitter
IF (.NOT.SysReSim .AND. PrimaryAirSystem(SysNum)%Splitter%Exists) THEN
MassFlowRateOutSum = 0.0d0
InletNodeNum = PrimaryAirSystem(SysNum)%Splitter%NodeNumIn
! Get sum of splitter outlet mass flows
DO OutletNum=1,PrimaryAirSystem(SysNum)%Splitter%TotalOutletNodes
OutletNodeNum = PrimaryAirSystem(SysNum)%Splitter%NodeNumOut(OutletNum)
MassFlowRateOutSum = MassFlowRateOutSum + Node(OutletNodeNum)%MassFlowRate
END DO
! Check whether sum of splitter outlet mass flows equals splitter inlet flow.
IF (ABS(MassFlowRateOutSum-Node(InletNodeNum)%MassFlowRate) .GT. SmallMassFlow) SysReSim = .TRUE.
END IF
! If mass balance failed, resimulation is needed. Impose a mass balance for the new simulation.
IF (SysReSim) THEN
! Set the MassFlowRateMaxAvail on each node to the minimum MassFlowRateMaxAvail for the branch.
DO BranchNum=1,PrimaryAirSystem(SysNum)%NumBranches ! loop over branches in system
DO NodeIndex=2,PrimaryAirSystem(SysNum)%Branch(BranchNum)%TotalNodes ! loop over nodes on branch
NodeNum = PrimaryAirSystem(SysNum)%Branch(BranchNum)%NodeNum(NodeIndex)
Node(NodeNum)%MassFlowRateMaxAvail = Node(PrimaryAirSystem(SysNum)%Branch(BranchNum)%NodeNumIn)%MassFlowRateMaxAvail
END DO
END DO
! Impose mass balance at splitter
IF (PrimaryAirSystem(SysNum)%Splitter%Exists) THEN
InBranchNum = PrimaryAirSystem(SysNum)%Splitter%BranchNumIn
MassFlowRateOutSum = 0.0d0
InletNodeNum = PrimaryAirSystem(SysNum)%Splitter%NodeNumIn
DO OutletNum=1,PrimaryAirSystem(SysNum)%Splitter%TotalOutletNodes
OutletNodeNum = PrimaryAirSystem(SysNum)%Splitter%NodeNumOut(OutletNum)
MassFlowRateOutSum = MassFlowRateOutSum + MIN(Node(OutletNodeNum)%MassFlowRateMaxAvail,&
Node(OutletNodeNum)%MassFlowRateSetPoint)
END DO
! set the splitter inlet Max Avail mass flow rate
IF (Node(InletNodeNum)%MassFlowRateMaxAvail .GT. MassFlowRateOutSum+SmallMassFlow) THEN
Node(InletNodeNum)%MassFlowRateMaxAvail = MassFlowRateOutSum
END IF
! Pass the splitter inlet Max Avail mass flow rate upstream to the mixed air node
DO NodeIndex=PrimaryAirSystem(SysNum)%Branch(InBranchNum)%TotalNodes-1,1,-1
NodeNum = PrimaryAirSystem(SysNum)%Branch(InBranchNum)%NodeNum(NodeIndex)
Node(NodeNum)%MassFlowRateMaxAvail = Node(InletNodeNum)%MassFlowRateMaxAvail
IF (NodeNum .EQ. PrimaryAirSystem(SysNum)%OASysOutletNodeNum) EXIT
END DO
END IF
! Make sure air system inlet nodes have flow consistent with MassFlowRateMaxAvail
DO InBranchIndex=1,PrimaryAirSystem(SysNum)%NumInletBranches
InBranchNum = PrimaryAirSystem(SysNum)%InletBranchNum(InBranchIndex)
InNodeNum = PrimaryAirSystem(SysNum)%Branch(InBranchNum)%NodeNumIn
Node(InNodeNum)%MassFlowRate = MIN(Node(InNodeNum)%MassFlowRate,Node(InNodeNum)%MassFlowRateMaxAvail)
END DO
END IF
END SUBROUTINE ResolveSysFlow