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 | :: | BoilerNum | ||||
real(kind=r64) | :: | MyLoad | ||||
logical | :: | RunFlag | ||||
integer, | intent(in) | :: | EquipFlowCtrl |
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 CalcBoilerModel(BoilerNum,MyLoad,Runflag,EquipFlowCtrl)
! SUBROUTINE INFORMATION:
! AUTHOR Rahul Chillar
! DATE WRITTEN Dec 2004
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine calculates the boiler fuel consumption and the associated
! hot water demand met by the boiler
! METHODOLOGY EMPLOYED:
! The model is based on a single combustion efficiency (=1 for electric)
! and a second order polynomial fit of performance data to obtain part
! load performance
! REFERENCES:
! na
! USE STATEMENTS:
USE General, ONLY: RoundSigDigits
USE FluidProperties, ONLY: GetSatPressureRefrig, GetSatSpecificHeatRefrig, GetSatEnthalpyRefrig
USE DataPlant, ONLY: PlantLoop, SingleSetpoint, DualSetpointDeadband
USE DataBranchAirLoopPlant, ONLY : ControlType_SeriesActive
USE PlantUtilities, ONLY: SetComponentFlowRate
IMPLICIT NONE
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER :: BoilerNum ! boiler identifier
REAL(r64) :: MyLoad ! W - hot water demand to be met by boiler
LOGICAL :: RunFlag ! TRUE if boiler operating
INTEGER, INTENT(IN) :: EquipFlowCtrl ! Flow control mode for the equipment
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: BoilerEFF ! boiler efficiency
REAL(r64) :: BoilerNomCap ! W - boiler nominal capacity
REAL(r64) :: BoilerMaxPLR ! boiler maximum part load ratio
REAL(r64) :: BoilerMinPLR ! boiler minimum part load ratio
REAL(r64) :: TheorFuelUse ! Theoretical (stoichiometric) fuel use
REAL(r64) :: OperPLR ! operating part load ratio
REAL(r64) :: BoilerDeltaTemp ! C - boiler inlet to outlet temperature difference
REAL(r64) :: TempUpLimitBout ! C - boiler high temperature limit
REAL(r64) :: BoilerMassFlowRateMax ! Max Design Boiler Mass Flow Rate converted from Volume Flow Rate
REAL(r64) :: EnthSteamOutDry !
REAL(r64) :: EnthSteamOutWet !
REAL(r64) :: LatentEnthSteam !
REAL(r64) :: QualitySteam !
REAL(r64), DIMENSION(3) :: LoadCoef ! coefficients of the fuel use/part load curve
REAL(r64) :: CpWater ! Heat capacity of condensed steam
INTEGER :: BoilerInletNode ! Boiler inlet node number
INTEGER :: BoilerOutletNode ! Boiler outlet node number
! CHARACTER(len=25) CErrCount !
! INTEGER,SAVE :: PressErrCount=0 !
INTEGER :: LoopNum
INTEGER :: LoopSideNum
!Loading the variables derived type in to local variables
BoilerLoad = 0.0d0
BoilerMassFlowRate = 0.0d0
BoilerInletNode = Boiler(BoilerNum)%BoilerInletNodeNum
BoilerOutletNode = Boiler(BoilerNum)%BoilerOutletNodeNum
BoilerNomCap = Boiler(BoilerNum)%NomCap
BoilerMaxPLR = Boiler(BoilerNum)%MaxPartLoadRat
BoilerMinPLR = Boiler(BoilerNum)%MinPartLoadRat
LoadCoef = Boiler(BoilerNum)%FullLoadCoef
TempUpLimitBout = Boiler(BoilerNum)%TempUpLimitBoilerOut
BoilerMassFlowRateMax = Boiler(BoilerNum)%DesMassFlowRate
BoilerMaxPress = Boiler(BoilerNum)%BoilerMaxOperPress
BoilerEff = Boiler(BoilerNum)%Effic
QualitySteam = Node(BoilerInletNode)%Quality
LoopNum = Boiler(BoilerNum)%LoopNum
LoopSideNum = Boiler(BoilerNum)%LoopSideNum
SELECT CASE (PlantLoop(LoopNum)%LoopDemandCalcScheme)
CASE (SingleSetPoint)
BoilerOutletTemp = Node(BoilerOutletNode)%TempSetPoint
CASE (DualSetPointDeadBand)
BoilerOutletTemp = Node(BoilerOutletNode)%TempSetPointLo
END SELECT
!If the specified load is 0.0 or the boiler should not run then we leave this subroutine.Before leaving
!if the component control is SERIESACTIVE we set the component flow to inlet flow so that flow resolver
!will not shut down the branch
IF(MyLoad <= 0.0d0 .OR. .NOT. RunFlag) THEN
IF(EquipFlowCtrl == ControlType_SeriesActive) BoilerMassFlowRate = Node(BoilerInletNode)%MassFlowrate
RETURN
END IF
!Set the current load equal to the boiler load
BoilerLoad = MyLoad
Boiler(BoilerNum)%BoilerPressCheck= &
GetSatPressureRefrig('STEAM',BoilerOutletTemp,Boiler(BoilerNum)%FluidIndex,'CalcBoilerModel')
IF((Boiler(BoilerNum)%BoilerPressCheck).GT.BoilerMaxPress)THEN
IF (Boiler(BoilerNum)%PressErrIndex == 0) THEN
CALL ShowSevereError('Boiler:Steam="'//TRIM(Boiler(BoilerNum)%Name)// &
'", Saturation Pressure is greater than Maximum Operating Pressure,')
CALL ShowContinueError('Lower Input Temperature')
CALL ShowContinueError('Steam temperature=['//TRIM(RoundSigDigits(BoilerOutletTemp,2))//'] C')
CALL ShowContinueError('Refrigerant Saturation Pressure =['// &
trim(RoundSigDigits(Boiler(BoilerNum)%BoilerPressCheck,0))//'] Pa')
ENDIF
CALL ShowRecurringSevereErrorAtEnd('Boiler:Steam="'//TRIM(Boiler(BoilerNum)%Name)// &
'", Saturation Pressure is greater than Maximum Operating Pressure..continues',Boiler(BoilerNum)%PressErrIndex, &
ReportMinOf=Boiler(BoilerNum)%BoilerPressCheck,ReportMinUnits='[Pa]', &
ReportMaxOf=Boiler(BoilerNum)%BoilerPressCheck,ReportMaxUnits='[Pa]')
END IF
CpWater = GetSatSpecificHeatRefrig('STEAM',Node(BoilerInletNode)%Temp,0.0d0,Boiler(BoilerNum)%FluidIndex,'CalcBoilerModel')
IF (PlantLoop(LoopNum)%Loopside(LoopSideNum)%FlowLock==0) THEN
! Calculate the flow for the boiler
SELECT CASE (PlantLoop(Boiler(BoilerNum)%LoopNum)%LoopDemandCalcScheme)
CASE (SingleSetPoint)
BoilerDeltaTemp = Node(BoilerOutletNode)%TempSetPoint-Node(BoilerInletNode)%Temp
CASE (DualSetPointDeadBand)
BoilerDeltaTemp = Node(BoilerOutletNode)%TempSetPointLo-Node(BoilerInletNode)%Temp
END SELECT
BoilerOutletTemp = BoilerDeltaTemp + Node(BoilerInletNode)%Temp
EnthSteamOutDry=GetSatEnthalpyRefrig('STEAM',BoilerOutletTemp,1.0d0,Boiler(BoilerNum)%FluidIndex,'CalcBoilerModel')
EnthSteamOutWet=GetSatEnthalpyRefrig('STEAM',BoilerOutletTemp,0.0d0,Boiler(BoilerNum)%FluidIndex,'CalcBoilerModel')
LatentEnthSteam=EnthSteamOutDry-EnthSteamOutWet
BoilerMassFlowRate =BoilerLoad/(LatentEnthSteam+(CpWater*BoilerDeltaTemp))
!Check to see if the Maximum is exceeded, if so set to maximum
! BoilerMassFlowRate = MIN(BoilerMassFlowRateMax, BoilerMassFlowRate)
! BoilerMassFlowRate = MIN(BoilerMassFlowRate,Node(BoilerInletNode)%MassFlowRateMaxAvail) !CRBranchPump
! BoilerMassFlowRate = MAX(BoilerMassFlowRate,Node(BoilerInletNode)%MassFlowRateMinAvail) !CRBranchPump
CALL SetComponentFlowRate(BoilerMassFlowRate, BoilerInletNode, BoilerOutletNode, &
Boiler(BoilerNum)%LoopNum, &
Boiler(BoilerNum)%LoopSideNum, &
Boiler(BoilerNum)%BranchNum, &
Boiler(BoilerNum)%CompNum)
ELSE ! If FlowLock is True
! Set the boiler flow rate from inlet node and then check performance
BoilerMassFlowRate = Node(BoilerInletNode)%MassFlowRate
! Assume that it can meet the setpoint
SELECT CASE (PlantLoop(Boiler(BoilerNum)%LoopNum)%LoopDemandCalcScheme)
CASE (SingleSetPoint)
BoilerDeltaTemp = Node(BoilerOutletNode)%TempSetPoint-Node(BoilerInletNode)%Temp
CASE (DualSetPointDeadBand)
BoilerDeltaTemp = Node(BoilerOutletNode)%TempSetPointLo-Node(BoilerInletNode)%Temp
END SELECT
!If boiler outlet temp is already greater than setpoint than it does not need to operate this iteration
IF(BoilerDeltaTemp < 0.0d0) THEN
SELECT CASE (PlantLoop(Boiler(BoilerNum)%LoopNum)%LoopDemandCalcScheme)
CASE (SingleSetPoint)
BoilerOutletTemp=Node(BoilerOutletNode)%TempSetPoint
CASE (DualSetPointDeadBand)
BoilerOutletTemp=Node(BoilerOutletNode)%TempSetPointLo
END SELECT
EnthSteamOutDry=GetSatEnthalpyRefrig('STEAM',BoilerOutletTemp,1.0d0,Boiler(BoilerNum)%FluidIndex,'CalcBoilerModel')
EnthSteamOutWet=GetSatEnthalpyRefrig('STEAM',BoilerOutletTemp,0.0d0,Boiler(BoilerNum)%FluidIndex,'CalcBoilerModel')
LatentEnthSteam=EnthSteamOutDry-EnthSteamOutWet
BoilerLoad = (BoilerMassFlowRate*LatentEnthSteam)
ELSE
SELECT CASE (PlantLoop(Boiler(BoilerNum)%LoopNum)%LoopDemandCalcScheme)
CASE (SingleSetPoint)
BoilerOutletTemp=Node(BoilerOutletNode)%TempSetPoint
CASE (DualSetPointDeadBand)
BoilerOutletTemp=Node(BoilerOutletNode)%TempSetPointLo
END SELECT
EnthSteamOutDry=GetSatEnthalpyRefrig('STEAM',BoilerOutletTemp,1.0d0,Boiler(BoilerNum)%FluidIndex,'CalcBoilerModel')
EnthSteamOutWet=GetSatEnthalpyRefrig('STEAM',BoilerOutletTemp,0.0d0,Boiler(BoilerNum)%FluidIndex,'CalcBoilerModel')
LatentEnthSteam=EnthSteamOutDry-EnthSteamOutWet
! Calculate the boiler load with the specified flow rate.
BoilerLoad = ABS(BoilerMassFlowRate*LatentEnthSteam)+ &
ABS(BoilerMassFlowRate*CpWater*BoilerDeltaTemp)
END IF
! If load exceeds the distributed load set to the distributed load
IF(BoilerLoad > MyLoad) THEN
BoilerLoad = MyLoad
! Reset later , here just for calculating latent heat
SELECT CASE (PlantLoop(Boiler(BoilerNum)%LoopNum)%LoopDemandCalcScheme)
CASE (SingleSetPoint)
BoilerOutletTemp=Node(BoilerOutletNode)%TempSetPoint
CASE (DualSetPointDeadBand)
BoilerOutletTemp=Node(BoilerOutletNode)%TempSetPointLo
END SELECT
EnthSteamOutDry=GetSatEnthalpyRefrig('STEAM',BoilerOutletTemp,1.0d0,Boiler(BoilerNum)%FluidIndex,'CalcBoilerModel')
EnthSteamOutWet=GetSatEnthalpyRefrig('STEAM',BoilerOutletTemp,0.0d0,Boiler(BoilerNum)%FluidIndex,'CalcBoilerModel')
LatentEnthSteam=EnthSteamOutDry-EnthSteamOutWet
BoilerDeltaTemp =BoilerOutletTemp-Node(BoilerInletNode)%Temp
BoilerMassFlowRate=BoilerLoad/(LatentEnthSteam+CpWater*BoilerDeltaTemp)
CALL SetComponentFlowRate(BoilerMassFlowRate, BoilerInletNode, BoilerOutletNode, &
Boiler(BoilerNum)%LoopNum, &
Boiler(BoilerNum)%LoopSideNum, &
Boiler(BoilerNum)%BranchNum, &
Boiler(BoilerNum)%CompNum)
END IF
! Checks Boiler Load on the basis of the machine limits.
IF(BoilerLoad > BoilerNomCap)THEN
IF(BoilerMassFlowRate > MassFlowTolerance) THEN
BoilerLoad = BoilerNomCap
EnthSteamOutDry=GetSatEnthalpyRefrig('STEAM',BoilerOutletTemp,1.0d0,Boiler(BoilerNum)%FluidIndex,'CalcBoilerModel')
EnthSteamOutWet=GetSatEnthalpyRefrig('STEAM',BoilerOutletTemp,0.0d0,Boiler(BoilerNum)%FluidIndex,'CalcBoilerModel')
LatentEnthSteam=EnthSteamOutDry-EnthSteamOutWet
BoilerDeltaTemp = BoilerOutletTemp-Node(BoilerInletNode)%Temp
BoilerMassFlowRate=BoilerLoad/(LatentEnthSteam+CpWater*BoilerDeltaTemp)
CALL SetComponentFlowRate(BoilerMassFlowRate, BoilerInletNode, BoilerOutletNode, &
Boiler(BoilerNum)%LoopNum, &
Boiler(BoilerNum)%LoopSideNum, &
Boiler(BoilerNum)%BranchNum, &
Boiler(BoilerNum)%CompNum)
ELSE
BoilerLoad = 0.0d0
BoilerOutletTemp = Node(BoilerInletNode)%Temp
END IF
END IF
END IF !End of the FlowLock If block
! Limit BoilerOutletTemp. If > max temp, trip boiler.
IF(BoilerOutletTemp > TempUpLimitBout) THEN
BoilerDeltaTemp = 0.0d0
BoilerLoad = 0.0d0
BoilerOutletTemp = Node(BoilerInletNode)%Temp
! Does BoilerMassFlowRate need to be set????
END IF
OperPLR = BoilerLoad/BoilerNomCap
OperPLR = MIN(OperPLR,BoilerMaxPLR)
OperPLR = MAX(OperPLR,BoilerMinPLR)
TheorFuelUse = BoilerLoad/BoilerEff
! Calculate fuel used
FuelUsed=TheorFuelUse/(LoadCoef(1) + LoadCoef(2)*OperPLR + LoadCoef(3)*OperPLR**2)
RETURN
END SUBROUTINE CalcBoilerModel