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) | :: | CurSchemePtr | |||
integer, | intent(in) | :: | ListPtr | |||
real(kind=r64), | intent(in) | :: | LoopDemand | |||
real(kind=r64), | intent(inout) | :: | RemLoopDemand |
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 DistributePlantLoad(LoopNum, LoopSideNum, CurSchemePtr,ListPtr,LoopDemand,RemLoopDemand)
! SUBROUTINE INFORMATION:
! AUTHOR Dan Fisher
! DATE WRITTEN July 1998
! MODIFIED na
! RE-ENGINEERED July 2010
! Sept 2010 B. Griffith, retain actual sign of load values
! PURPOSE OF THIS SUBROUTINE: This subroutine distributes the load
! to plant equipment according to one of two distribution schemes:
! OPTIMAL = 1
! SEQUENTIAL = 2
! METHODOLOGY EMPLOYED:
! na
! REFERENCES:
! na
! USE STATEMENTS:
USE DataLoopNode
IMPLICIT NONE
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN ) :: LoopNum
INTEGER, INTENT(IN ) :: LoopSideNum
INTEGER, INTENT(IN ) :: CurSchemePtr !use as index in PlantLoop()Opscheme() data structure
INTEGER, INTENT(IN ) :: ListPtr !use as index in PlantLoop()Opscheme() data structure
REAL(r64), INTENT(IN) :: LoopDemand
REAL(r64), INTENT(INOUT) :: RemLoopDemand
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: ChangeInLoad
REAL(r64) :: DivideLoad
REAL(r64) :: UniformLoad
REAL(r64) :: NewLoad
INTEGER :: LoadFlag
INTEGER :: BranchNum
INTEGER :: CompNum
INTEGER :: CompIndex
! INTEGER :: EquipNum
INTEGER :: NumCompsOnList
! load local variables
NumCompsOnList = PlantLoop(LoopNum)%OpScheme(CurSchemePtr)%EquipList(ListPtr)%NumComps
RemLoopDemand = LoopDemand
IF (NumCompsOnList <= 0) RETURN
!set flag to specify optimal or sequential loading of equipment
LoadFlag = PlantLoop(LoopNum)%LoadDistribution
IF (ABS(RemLoopDemand) < SmallLoad) THEN
!no load to distribute
ELSE
SELECT CASE (LoadFlag)
CASE (OptimalLoading) ! LoadFlag=1 indicates "optimal" load distribution
!OPTIMAL DISTRIBUTION SCHEME
!step 1: load all machines to optimal PLR
DO CompIndex =1, NumCompsOnList
BranchNum = PlantLoop(LoopNum)%OpScheme(CurSchemePtr)%EquipList(ListPtr)%Comp(CompIndex)%BranchNumPtr
CompNum = PlantLoop(LoopNum)%OpScheme(CurSchemePtr)%EquipList(ListPtr)%Comp(CompIndex)%CompNumPtr
IF(.NOT. PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Available) CYCLE
IF (PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Optload > 0.d0) THEN
ChangeInLoad= MIN(PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Optload,ABS(RemLoopDemand))
ELSE
! this is for some components like cooling towers don't have well defined OptLoad
ChangeInLoad = ABS(RemLoopDemand)
ENDIF
CALL AdjustChangeInLoadForLastStageUpperRangeLimit(LoopNum, CurSchemePtr, ListPtr, ChangeInLoad)
CALL AdjustChangeInLoadByEMSControls(LoopNum, LoopSideNum, BranchNum, CompNum, ChangeInLoad)
CALL AdjustChangeInLoadByHowServed(LoopNum, LoopSideNum, BranchNum, CompNum, ChangeInLoad)
ChangeInLoad= MAX(0.0d0,ChangeInLoad)
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Myload = SIGN(ChangeInLoad, RemLoopDemand)
RemLoopDemand = RemLoopDemand - PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Myload
IF (ABS(RemLoopDemand) < SmallLoad) RemLoopDemand = 0.d0 !CR8631 don't just exit or %MyLoad on second device isn't reset
END DO
!step 2: Evenly distribute remaining loop demand
IF (ABS(RemLoopDemand) > SmallLoad)THEN
DivideLoad = ABS(RemLoopDemand)/NumCompsOnList
DO CompIndex =1, NumCompsOnList
BranchNum = PlantLoop(LoopNum)%OpScheme(CurSchemePtr)%EquipList(ListPtr)%Comp(CompIndex)%BranchNumPtr
CompNum = PlantLoop(LoopNum)%OpScheme(CurSchemePtr)%EquipList(ListPtr)%Comp(CompIndex)%CompNumPtr
IF(.NOT. PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Available)CYCLE
NewLoad = PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Myload
NewLoad = MIN(PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Maxload, &
ABS(NewLoad) + DivideLoad)
ChangeInLoad = NewLoad - ABS(PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Myload)
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Myload = SIGN(NewLoad, RemLoopDemand)
RemLoopDemand= RemLoopDemand - SIGN(ChangeInLoad, RemLoopDemand)
IF (ABS(RemLoopDemand) < SmallLoad) RemLoopDemand = 0.d0 !CR8631 don't just exit or %MyLoad on second device isn't reset
END DO
END IF
! step 3: If RemLoopDemand is still greater than zero, look for any machine
IF (ABS(RemLoopDemand) > SmallLoad)THEN
DO CompIndex =1, NumCompsOnList
BranchNum = PlantLoop(LoopNum)%OpScheme(CurSchemePtr)%EquipList(ListPtr)%Comp(CompIndex)%BranchNumPtr
CompNum = PlantLoop(LoopNum)%OpScheme(CurSchemePtr)%EquipList(ListPtr)%Comp(CompIndex)%CompNumPtr
IF(.NOT. PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Available)CYCLE
DivideLoad = PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Maxload &
- ABS(PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Myload)
ChangeInLoad = MIN(ABS(RemLoopDemand), DivideLoad)
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Myload = &
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Myload + SIGN(ChangeInLoad, RemLoopDemand)
RemLoopDemand= RemLoopDemand - SIGN(ChangeInLoad,RemLoopDemand)
IF (ABS(RemLoopDemand) < SmallLoad) RemLoopDemand = 0.d0 !CR8631 don't just exit or %MyLoad on second device isn't reset
END DO
END IF
!SEQUENTIAL DISTRIBUTION SCHEME
CASE (SequentialLoading)! LoadFlag=2 indicates "sequential" load distribution
! step 1: Load machines in list order
DO CompIndex =1, NumCompsOnList
BranchNum = PlantLoop(LoopNum)%OpScheme(CurSchemePtr)%EquipList(ListPtr)%Comp(CompIndex)%BranchNumPtr
CompNum = PlantLoop(LoopNum)%OpScheme(CurSchemePtr)%EquipList(ListPtr)%Comp(CompIndex)%CompNumPtr
IF(.NOT. PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Available)CYCLE
IF (PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Maxload > 0.d0) THEN ! apply known limit
ChangeInLoad = MIN(PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Maxload, &
ABS(RemLoopDemand))
ELSE
! this is for some components like cooling towers don't have well defined MaxLoad
ChangeInLoad = ABS(RemLoopDemand)
ENDIF
CALL AdjustChangeInLoadForLastStageUpperRangeLimit(LoopNum, CurSchemePtr, ListPtr, ChangeInLoad)
CALL AdjustChangeInLoadByEMSControls(LoopNum, LoopSideNum, BranchNum, CompNum, ChangeInLoad)
CALL AdjustChangeInLoadByHowServed(LoopNum, LoopSideNum, BranchNum, CompNum, ChangeInLoad)
ChangeInLoad = MAX(0.0d0, ChangeInLoad)
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Myload = SIGN(ChangeInLoad, RemLoopDemand)
RemLoopDemand= RemLoopDemand - SIGN(ChangeInLoad, RemLoopDemand)
IF (ABS(RemLoopDemand) < SmallLoad) RemLoopDemand = 0.d0 !CR8631 don't just exit or %MyLoad on second device isn't reset
END DO
!UNIFORM DISTRIBUTION SCHEME
CASE (UniformLoading)! LoadFlag=3 indicates "uniform" load distribution
! step 1: distribute load equally to all machines
UniformLoad = ABS(RemLoopDemand)/NumCompsOnList
DO CompIndex =1, NumCompsOnList
BranchNum = PlantLoop(LoopNum)%OpScheme(CurSchemePtr)%EquipList(ListPtr)%Comp(CompIndex)%BranchNumPtr
CompNum = PlantLoop(LoopNum)%OpScheme(CurSchemePtr)%EquipList(ListPtr)%Comp(CompIndex)%CompNumPtr
IF(.NOT. PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Available)CYCLE
IF (PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Maxload > 0.d0) THEN
ChangeInLoad = MIN(PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Maxload, &
UniformLoad)
ELSE
! this is for some components like cooling towers don't have well defined MaxLoad
ChangeInLoad = ABS(RemLoopDemand)
ENDIF
CALL AdjustChangeInLoadForLastStageUpperRangeLimit(LoopNum, CurSchemePtr, ListPtr, ChangeInLoad)
CALL AdjustChangeInLoadByEMSControls(LoopNum, LoopSideNum, BranchNum, CompNum, ChangeInLoad)
CALL AdjustChangeInLoadByHowServed(LoopNum, LoopSideNum, BranchNum, CompNum, ChangeInLoad)
ChangeInLoad = MAX(0.0d0, ChangeInLoad)
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Myload = SIGN(ChangeInLoad, RemLoopDemand)
RemLoopDemand = RemLoopDemand- SIGN(ChangeInLoad, RemLoopDemand)
IF (ABS(RemLoopDemand) < SmallLoad) RemLoopDemand = 0.d0
END DO
! step 2: If RemLoopDemand is not zero, then distribute remainder sequentially.
IF (ABS(RemLoopDemand) > SmallLoad )THEN
DO CompIndex =1, NumCompsOnList
BranchNum = PlantLoop(LoopNum)%OpScheme(CurSchemePtr)%EquipList(ListPtr)%Comp(CompIndex)%BranchNumPtr
CompNum = PlantLoop(LoopNum)%OpScheme(CurSchemePtr)%EquipList(ListPtr)%Comp(CompIndex)%CompNumPtr
IF(.NOT. PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Available)CYCLE
ChangeInLoad = MIN(PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Maxload - &
ABS(PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Myload), &
ABS(RemLoopDemand))
ChangeInLoad = MAX(0.0d0, ChangeInLoad)
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Myload = &
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Myload + SIGN(ChangeInLoad, RemLoopDemand)
RemLoopDemand= RemLoopDemand - SIGN(ChangeInLoad,RemLoopDemand)
IF (ABS(RemLoopDemand) < SmallLoad ) RemLoopDemand = 0.d0
END DO
END IF
END SELECT
ENDIF ! load is small check
! now update On flags according to result for MyLoad
DO CompIndex =1, NumCompsOnList
BranchNum = PlantLoop(LoopNum)%OpScheme(CurSchemePtr)%EquipList(ListPtr)%Comp(CompIndex)%BranchNumPtr
CompNum = PlantLoop(LoopNum)%OpScheme(CurSchemePtr)%EquipList(ListPtr)%Comp(CompIndex)%CompNumPtr
IF (ABS(PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Myload) < SmallLoad) THEN
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%On = .FALSE.
ELSE
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%On = .TRUE.
ENDIF
ENDDO
RETURN
END SUBROUTINE DistributePlantLoad