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 | |||
integer, | intent(in) | :: | OpNum |
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 FindCompSPLoad(LoopNum,LoopSideNum,BranchNum,CompNum,OpNum)
! SUBROUTINE INFORMATION:
! AUTHOR Sankaranarayanan K P
! DATE WRITTEN Jan 2005
! MODIFIED na
! RE-ENGINEERED Dan Fisher July 2010
! PURPOSE OF THIS SUBROUTINE:
! To calculate the load on a component controlled by
! Component SetPoint based scheme.
! USE STATEMENTS:
USE DataLoopNode, ONLY : Node, SensedNodeFlagValue
USE FluidProperties, ONLY: GetDensityGlycol
IMPLICIT NONE
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: LoopNum
INTEGER, INTENT(IN) :: LoopSideNum
INTEGER, INTENT(IN) :: BranchNum
INTEGER, INTENT(IN) :: CompNum
INTEGER, INTENT(IN) :: OpNum !index for Plant()%loopside()%branch()%comp()%opscheme()
! SUBROUTINE PARAMETER DEFINITIONS:
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: CompDemand
REAL(r64) :: DemandMdot
REAL(r64) :: ActualMdot
REAL(r64) :: TempIn
REAL(r64) :: CurSpecHeat
REAL(r64) :: TempSetPt
REAL(r64) :: CompMinLoad
REAL(r64) :: CompMaxLoad
REAL(r64) :: CompOptLoad
INTEGER :: DemandNode
INTEGER :: CompPtr
INTEGER :: OpSchemePtr
INTEGER :: ListPtr
INTEGER :: SetPtNode
INTEGER :: NumEquipLists
REAL(r64) :: rho
REAL(r64) :: CurrentDemandForCoolingOp
REAL(r64) :: CurrentDemandForHeatingOp
!find the pointer to the 'PlantLoop()%OpScheme()'...data structure
NumEquipLists = PlantLoop(LoopNum)%loopside(LoopSideNum)%branch(BranchNum)%comp(CompNum)%opscheme(OpNum)%NumEquipLists
IF(NumEquipLists /= 1)THEN
!CALL Severe error) there should be exactly one list associated with component setpoint scheme
ENDIF
OpSchemePtr = PlantLoop(LoopNum)%loopside(LoopSideNum)%branch(BranchNum)%comp(CompNum)%opscheme(OpNum)%OpSchemePtr
ListPtr = PlantLoop(LoopNum)%loopside(LoopSideNum)%branch(BranchNum)%comp(CompNum)%opscheme(OpNum)%EquipList(1)%ListPtr
CompPtr = PlantLoop(LoopNum)%loopside(LoopSideNum)%branch(BranchNum)%comp(CompNum)%opscheme(OpNum)%EquipList(1)%CompPtr
!load local variables from the data structures
CompMinLoad = PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MinLoad
CompMaxLoad = PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MaxLoad
CompOptLoad = PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%OptLoad
DemandMdot = PlantLoop(LoopNum)%OpScheme(OpSchemePtr)%EquipList(ListPtr)%Comp(CompPtr)%SetPointFlowRate
DemandNode = PlantLoop(LoopNum)%OpScheme(OpSchemePtr)%EquipList(ListPtr)%Comp(CompPtr)%DemandNodeNum
SetPtNode = PlantLoop(LoopNum)%OpScheme(OpSchemePtr)%EquipList(ListPtr)%Comp(CompPtr)%SetPointNodeNum
TempIn = Node(DemandNode)%Temp
rho = GetDensityGlycol(PlantLoop(LoopNum)%FluidName, &
TempIn, &
PlantLoop(LoopNum)%FluidIndex,&
'FindCompSPLoad')
DemandMdot = PlantLoop(LoopNum)%OpScheme(OpSchemePtr)%EquipList(ListPtr)%Comp(CompPtr)%SetPointFlowRate * rho
!DSU? DemandMDot is a constant design flow rate, next based on actual current flow rate for accurate current demand?
ActualMdot = Node(DemandNode)%MassFlowRate
CurSpecHeat = GetSpecificHeatGlycol(PlantLoop(loopNum)%FluidName,TempIn,PlantLoop(loopNum)%FluidIndex, &
'FindCompSPLoad')
IF ((ActualMdot > 0.d0) .AND. (ActualMdot /= DemandMdot)) THEN
DemandMdot = ActualMdot
ENDIF
SELECT CASE (PlantLoop(LoopNum)%LoopDemandCalcScheme)
CASE (SingleSetpoint)
TempSetPt = Node(SetPtNode)%TempSetPoint
CASE (DualSetpointDeadband)
IF (PlantLoop(LoopNum)%OpScheme(OpSchemePtr)%EquipList(ListPtr)%Comp(CompPtr)%CtrlTypeNum == CoolingOp) THEN
TempSetPt = Node(SetPtNode)%TempSetPointHi
ELSEIF(PlantLoop(LoopNum)%OpScheme(OpSchemePtr)%EquipList(ListPtr)%Comp(CompPtr)%CtrlTypeNum == HeatingOP) THEN
TempSetPt = Node(SetPtNode)%TempSetPointLo
ELSEIF(PlantLoop(LoopNum)%OpScheme(OpSchemePtr)%EquipList(ListPtr)%Comp(CompPtr)%CtrlTypeNum == DualOP) THEN
CurrentDemandForCoolingOp = DemandMdot*CurSpecHeat*(Node(SetPtNode)%TempSetPointHi - TempIn)
CurrentDemandForHeatingOp = DemandMdot*CurSpecHeat*(Node(SetPtNode)%TempSetPointLo - TempIn)
IF ((CurrentDemandForCoolingOp < 0.d0) .AND. (CurrentDemandForHeatingOp <= 0.d0)) THEN ! cooling
TempSetPt = Node(SetPtNode)%TempSetPointHi
ELSEIF ((CurrentDemandForCoolingOp >= 0.d0) .AND. (CurrentDemandForHeatingOp > 0.d0)) THEN ! heating
TempSetPt = Node(SetPtNode)%TempSetPointLo
ELSE ! deadband
TempSetPt = TempIn
ENDIF
ENDIF
END SELECT
IF(TempSetPt == SensedNodeFlagValue) THEN
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%ON = .FALSE.
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MyLoad = 0.d0
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%EquipDemand = 0.d0
ELSE
CompDemand = (DemandMdot*CurSpecHeat*(TempSetPt - TempIn))
IF(ABS(CompDemand) < LoopDemandTol) CompDemand = 0.d0
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%EquipDemand = CompDemand
!set MyLoad and runflag
IF(PlantLoop(LoopNum)%OpScheme(OpSchemePtr)%EquipList(ListPtr)%Comp(CompPtr)%CtrlTypeNum == CoolingOp)THEN
IF(CompDemand < (- LoopDemandTol))THEN
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%ON = .TRUE.
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MyLoad = CompDemand
ELSE
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%ON = .FALSE.
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MyLoad = 0.d0
ENDIF
ELSEIF(PlantLoop(LoopNum)%OpScheme(OpSchemePtr)%EquipList(ListPtr)%Comp(CompPtr)%CtrlTypeNum == HeatingOP)THEN
IF(CompDemand > LoopDemandTol)THEN
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%ON = .TRUE.
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MyLoad = CompDemand
ELSE
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%ON = .FALSE.
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MyLoad = 0.d0
ENDIF
ELSEIF(PlantLoop(LoopNum)%OpScheme(OpSchemePtr)%EquipList(ListPtr)%Comp(CompPtr)%CtrlTypeNum == DualOP)THEN
IF(CompDemand > LoopDemandTol .OR. CompDemand < (- LoopDemandTol) )THEN
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%ON = .TRUE.
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MyLoad = CompDemand
ELSE
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%ON = .FALSE.
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MyLoad = 0.d0
ENDIF
ENDIF
!Check bounds on MyLoad
IF ( ABS(PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MyLoad) > CompMaxLoad) THEN
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MyLoad = SIGN(CompMaxLoad, &
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)%MyLoad,CompMaxLoad)
IF (ABS(PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MyLoad) < CompMinLoad) THEN
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MyLoad = SIGN( CompMinLoad, &
PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MyLoad )
ENDIF
! PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MyLoad = &
! MAX(PlantLoop(LoopNum)%LoopSide(LoopSideNum)%Branch(BranchNum)%Comp(CompNum)%MyLoad,CompMinLoad)
END IF !valid setpoint (TempSetPt /= SensedNodeFlagValue)
RETURN
END SUBROUTINE FindCompSPLoad