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) | :: | LoopSideNum | |||
integer, | intent(in) | :: | MixNum |
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 UpdatePlantMixer(LoopNum,LoopSideNum,MixNum)
! SUBROUTINE INFORMATION:
! AUTHOR Brandon Anderson, Dan Fisher
! DATE WRITTEN October 1999
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! calculate the outlet conditions at the mixer
! METHODOLOGY EMPLOYED:
! na
! REFERENCES:
! na
! USE STATEMENTS:
! na
USE DataLoopNode, ONLY : Node
USE DataPlant, ONLY : PlantLoop, SupplySide, DemandSide
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: LoopNum
INTEGER, INTENT(IN) :: LoopSideNum
INTEGER, INTENT(IN) :: MixNum
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: InletNodeNum
INTEGER :: MixerInletNode
INTEGER :: MixerOutletNode
INTEGER :: SplitterNum
INTEGER :: SplitterInNode
REAL(r64) :: MixerOutletMassFlow ! local calculation of mixer outlet mass flow rate
REAL(r64) :: MixerOutletMassFlowMaxAvail ! branch contribution to MassFlowRateMaxAvail at outlet
REAL(r64) :: MixerOutletMassFlowMinAvail
REAL(r64) :: MixerOutletTemp
REAL(r64) :: MixerInletMassFlow
REAL(r64) :: MassFrac
REAL(r64) :: MixerOutletPress
REAL(r64) :: MixerOutletQuality
! FLOW:
IF (PlantLoop(LoopNum)%LoopSide(LoopSideNum)%MixerExists) THEN
!Find mixer outlet node number
MixerOutletNode = PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Mixer(MixNum)%NodeNumOut
! Find corresponding splitter inlet node number--correspondence, but currently
! hard code things to a single split/mix setting it to the mixer number
SplitterNum = MixNum
SplitterInNode = PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Splitter(SplitterNum)%NodeNumIn
!Initialize Mixer outlet temp and mass flow rate
MixerOutletTemp = 0.0d0
MixerOutletMassFlow = 0.0d0
MixerOutletMassFlowMaxAvail = 0.0d0
MixerOutletMassFlowMinAvail = 0.0d0
MixerOutletPress = 0.0d0
MixerOutletQuality = 0.0d0
!Calculate Mixer outlet mass flow rate
DO InletNodeNum = 1, PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Mixer(MixNum)%TotalInletNodes
MixerInletNode = PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Mixer(MixNum)%NodeNumIn(InletNodeNum)
MixerOutletMassFlow = MixerOutletMassFlow + Node(MixerInletNode)%MassFlowRate
END DO
!Calculate Mixer outlet temperature
DO InletNodeNum = 1, PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Mixer(MixNum)%TotalInletNodes
MixerInletNode = PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Mixer(MixNum)%NodeNumIn(InletNodeNum)
IF(MixerOutletMassFlow > 0.0d0) THEN
MixerInletMassFlow = Node(MixerInletNode)%MassFlowRate
MassFrac = MixerInletMassFlow / MixerOutletMassFlow
!mass flow weighted temp and enthalpy for each mixer inlet
MixerOutletTemp = MixerOutletTemp + MassFrac * Node(MixerInletNode)%Temp
MixerOutletQuality = MixerOutletQuality +MassFrac*Node(MixerInletNode)%Quality
MixerOutletMassFlowMaxAvail = MixerOutletMassFlowMaxAvail + Node(MixerInletNode)%MassFlowRateMaxAvail
MixerOutletMassFlowMinAvail = MixerOutletMassFlowMinAvail + Node(MixerInletNode)%MassFlowRateMinAvail
MixerOutletPress = MAX(MixerOutletPress,Node(MixerInletNode)%Press)
ELSE !MixerOutletMassFlow <=0, then perform the 'no flow' update.
MixerOutletTemp = Node(SplitterInNode)%Temp
MixerOutletQuality = Node(SplitterInNode)%Quality
MixerOutletMassFlowMaxAvail = Node(SplitterInNode)%MassFlowRateMaxAvail
MixerOutletMassFlowMinAvail = Node(SplitterInNode)%MassFlowRateMinAvail
MixerOutletPress = Node(SplitterInNode)%Press
EXIT
ENDIF
ENDDO
Node(MixerOutletNode)%MassFlowRate = MixerOutletMassFlow
Node(MixerOutletNode)%Temp = MixerOutletTemp
IF (PlantLoop(LoopNum)%HasPressureComponents) THEN
!Don't update pressure, let pressure system handle this...
ELSE
!Go ahead and update!
Node(MixerOutletNode)%Press = MixerOutletPress
END IF
Node(MixerOutletNode)%Quality = MixerOutletQuality
! set max/min avails on mixer outlet to be consistent with the following rules
! 1. limited by the max/min avails on splitter inlet
! 2. limited by the sum of max/min avails for each branch's mixer inlet node
Node(MixerOutletNode)%MassFlowRateMaxAvail = MIN(MixerOutletMassFlowMaxAvail,Node(SplitterInNode)%MassFlowRateMaxAvail)
Node(MixerOutletNode)%MassFlowRateMinAvail = MAX(MixerOutletMassFlowMinAvail,Node(SplitterInNode)%MassFlowRateMinAvail)
END IF
RETURN
END SUBROUTINE UpdatePlantMixer