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) | :: | BranchNum | |||
integer, | intent(in) | :: | CompNum | |||
logical, | intent(inout) | :: | LoopShutdownFlag |
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 ActivateEMSControls(LoopNum,LoopSideNum, BranchNum, CompNum, LoopShutDownFlag)
! SUBROUTINE INFORMATION:
! AUTHOR D.E. Fisher
! DATE WRITTEN Feb 2007
! MODIFIED
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine loads the plant EMS actuators
! METHODOLOGY EMPLOYED: The EMS flags are evaluated in hierarchical order:
! LOOP flags override branch and component flags
! BRANCH flags override component flags
! If the loop flag (EMSCtrl) is true, then
! IF EMSValue <= 0, shut down the entire loop including the pumps
! IF EMSValue > 0, no action
! If the LoopSide flag (EMSCtrl) is true, then:
! IF EMSValue <=0, shut down all components on the loopside except the pumps
! IF EMSValue > 0, no action
! If a component flag (EMSCtrl) is true, then:
! EMSValue <=0, shut down the component
! EMSValue > 0, calc. component load: MyLoad=MIN(MaxCompLoad,MaxCompLoad*EMSValue)
! REFERENCES:
! na
! USE STATEMENTS:
USE DataLoopNode
! SUBROUTINE ARGUMENT DEFINITIONS
INTEGER,INTENT(IN) :: LoopNum
INTEGER,INTENT(IN) :: LoopSideNum
INTEGER,INTENT(IN) :: BranchNum
INTEGER,INTENT(IN) :: CompNum
LOGICAL,INTENT(INOUT) :: LoopShutdownFlag
! SUBROUTINE PARAMETER DEFINITIONS
! na
! SUBROUTINE VARIABLE DEFINITIONS
REAL(r64) :: CurMassFlowRate
REAL(r64) :: ToutLowLimit
REAL(r64) :: Tinlet
REAL(r64) :: CurSpecHeat
REAL(r64) :: QTemporary
!unused REAL(r64) :: ChangeInLoad
!MODULE VARIABLE DECLARATIONS:
!Loop Control
IF(PlantLoop(LoopNum)%EMSCtrl)THEN
IF(PlantLoop(LoopNum)%EMSValue <= 0.0d0)THEN
LoopShutdownFlag = .TRUE.
CALL TurnOffLoopEquipment(LoopNum)
RETURN
ELSE
LoopShutdownFlag = .FALSE.
ENDIF
ELSE
LoopShutdownFlag = .FALSE.
ENDIF
!Half-loop control
IF( PlantLoop(LoopNum)%LoopSide(LoopSideNum)%EMSCtrl)THEN
IF(PlantLoop(LoopNum)%LoopSide(LoopSideNum)%EMSValue <= 0.0d0)THEN
CALL TurnOffLoopSideEquipment(LoopNum,LoopSideNum)
RETURN
ELSE
!do nothing: can't turn all loopside equip. ON with loop switch
ENDIF
ENDIF
IF(PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%EMSLoadOverrideOn)THEN
!EMSValue <= 0 turn component OFF
IF(PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%EMSLoadOverrideValue <= 0.0d0)THEN
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%ON = .FALSE.
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Available = .FALSE.
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MyLoad =0.0d0
RETURN
ELSE
!EMSValue > 0 Set Component Load and Turn component ON
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%ON = .TRUE.
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Available = .FALSE.
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MyLoad = &
MIN(PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Maxload, &
(PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Maxload * &
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%EMSLoadOverrideValue))
! Check lower/upper temperature limit for chillers
SELECT CASE(PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%TypeOf_Num)
CASE(TypeOf_Chiller_ElectricEIR,TypeOf_Chiller_Electric,TypeOf_Chiller_ElectricReformEIR)
!- Retrieve data from the plant loop data structure
CurMassFlowRate = Node(PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%NodeNumIn)%MassFlowRate
ToutLowLimit = PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MinOutletTemp
Tinlet = Node(PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%NodeNumIn)%Temp
CurSpecHeat = GetSpecificHeatGlycol(PlantLoop(loopNum)%FluidName,Tinlet,PlantLoop(loopNum)%FluidIndex, &
'ActivateEMSControls')
QTemporary = CurMassFlowRate*CurSpecHeat*(Tinlet-ToutLowLimit)
!- Don't correct if Q is zero, as this could indicate a component which this hasn't been implemented
IF(QTemporary.GT.0.0d0)THEN
!unused ChangeInLoad = MIN(ChangeInLoad,QTemporary)
! DSU? weird ems thing here?
IF ( ABS(PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MyLoad) > &
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Maxload ) THEN
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MyLoad = SIGN( &
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Maxload, &
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MyLoad )
ENDIF
IF ( ABS(PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MyLoad) > &
QTemporary ) THEN
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MyLoad = SIGN( &
QTemporary, &
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MyLoad )
ENDIF
! PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MyLoad = &
! MIN((PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%Maxload * &
! PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%EMSValue),Qtemporary)
ENDIF
CASE DEFAULT
!Nothing Changes for now, could add in case statements for boilers, which would use upper limit temp check
END SELECT
RETURN
ENDIF !EMSValue <=> 0
ENDIF !EMSFlag
RETURN
END SUBROUTINE ActivateEMSControls