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 Dan Fisher
! DATE WRITTEN April 1999
! MODIFIED Taecheol Kim,May 2000
! R. Raustad - FSEC, June 2008: added boiler efficiency curve object
! B. Griffith - NREL, Aug 2011: added switch for temperature to use in curve
! 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:
! USE STATEMENTS:
USE DataGlobals, ONLY: BeginEnvrnFlag, WarmupFlag
USE FluidProperties, ONLY: GetSpecificHeatGlycol
USE DataBranchAirLoopPlant, ONLY: ControlType_SeriesActive
USE CurveManager, ONLY: CurveValue
USE General, ONLY: TrimSigDigits
USE PlantUtilities, ONLY: SetComponentFlowRate
USE DataPlant, ONLY: SingleSetpoint, DualSetpointDeadband
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
INTEGER :: BoilerInletNode ! Boiler inlet node number
INTEGER :: BoilerOutletNode ! Boiler outlet node number
INTEGER :: LoopNum ! Plant loop with boiler
INTEGER :: LoopSideNum ! Plant loop side with boiler (supply, demand)
REAL(r64) :: BoilerMassFlowRateMax ! Max Design Boiler Mass Flow Rate converted from Volume Flow Rate
REAL(r64) :: ParasiticElecLoad ! Boiler parasitic electric power at full load
REAL(r64) :: EffCurveOutput ! Output of boiler efficiency curve
REAL(r64) :: Cp
!FLOW
BoilerLoad = 0.0d0
ParasiticElecPower = 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
BoilerEff = Boiler(BoilerNum)%Effic
TempUpLimitBout = Boiler(BoilerNum)%TempUpLimitBoilerOut
BoilerMassFlowRateMax = Boiler(BoilerNum)%DesMassFlowRate
ParasiticElecLoad = Boiler(BoilerNum)%ParasiticElecLoad
LoopNum = Boiler(BoilerNum)%LoopNum
LoopSideNum = Boiler(BoilerNum)%LoopSideNum
Cp = GetSpecificHeatGlycol(PlantLoop(Boiler(BoilerNum)%LoopNum)%FluidName, &
Node(BoilerInletNode)%Temp, &
PlantLoop(Boiler(BoilerNum)%LoopNum)%FluidIndex, &
'CalcBoilerModel')
!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
IF (PlantLoop(LoopNum)%Loopside(LoopSideNum)%FlowLock==0) THEN
! Either set the flow to the Constant value or caluclate the flow for the variable volume
If ((Boiler(BoilerNum)%FlowMode == ConstantFlow ) .OR. (Boiler(BoilerNum)%FlowMode == NotModulated)) THEN
! Then find the flow rate and outlet temp
BoilerMassFlowRate = BoilerMassFlowRateMax
CALL SetComponentFlowRate(BoilerMassFlowRate, BoilerInletNode, BoilerOutletNode, &
Boiler(BoilerNum)%LoopNum, &
Boiler(BoilerNum)%LoopSideNum, &
Boiler(BoilerNum)%BranchNum, &
Boiler(BoilerNum)%CompNum)
IF ((BoilerMassFlowRate /= 0.0D0) .AND. (MyLoad > 0.d0)) THEN
BoilerDeltaTemp = BoilerLoad/BoilerMassFlowRate/Cp
ELSE
BoilerDeltaTemp = 0.0D0
ENDIF
BoilerOutletTemp = BoilerDeltaTemp + Node(BoilerInletNode)%Temp
ELSE IF (Boiler(BoilerNum)%FlowMode == LeavingSetpointModulated) THEN
! Calculate the Delta Temp from the inlet temp to the boiler outlet setpoint
! Then find the flow rate and outlet temp
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
IF((BoilerDeltaTemp > 0.0d0) .AND. (BoilerLoad > 0.d0) ) THEN
BoilerMassFlowRate = BoilerLoad/Cp/BoilerDeltaTemp
BoilerMassFlowRate = MIN(BoilerMassFlowRateMax, BoilerMassFlowRate)
ELSE
BoilerMassFlowRate =0.0d0
END IF
CALL SetComponentFlowRate(BoilerMassFlowRate, BoilerInletNode, BoilerOutletNode, &
Boiler(BoilerNum)%LoopNum, &
Boiler(BoilerNum)%LoopSideNum, &
Boiler(BoilerNum)%BranchNum, &
Boiler(BoilerNum)%CompNum)
END IF !End of Constant/Variable Flow If Block
ELSE ! If FlowLock is True
! Set the boiler flow rate from inlet node and then check performance
BoilerMassFlowRate = Node(BoilerInletNode)%MassFlowRate
IF ((MyLoad > 0.d0) .AND. (BoilerMassFlowRate > 0.d0)) THEN ! this boiler has a heat load
BoilerLoad = MyLoad
IF (BoilerLoad > BoilerNomCap*BoilerMaxPLR) BoilerLoad = BoilerNomCap*BoilerMaxPLR
IF (BoilerLoad < BoilerNomCap*BoilerMinPLR) BoilerLoad = BoilerNomCap*BoilerMinPLR
BoilerOutletTemp = Node(BoilerInletNode)%Temp + BoilerLoad /(BoilerMassFlowRate * Cp)
BoilerDeltaTemp = BoilerOutletTemp-Node(BoilerInletNode)%Temp
ELSE
BoilerLoad = 0.0d0
BoilerOutletTemp = Node(BoilerInletNode)%Temp
ENDIF
END IF !End of the FlowLock If block
! Limit BoilerOutletTemp. If > max temp, trip boiler off
IF(BoilerOutletTemp > TempUpLimitBout) THEN
BoilerDeltaTemp = 0.0d0
BoilerLoad = 0.0d0
BoilerOutletTemp = Node(BoilerInletNode)%Temp
END IF
OperPLR = BoilerLoad/BoilerNomCap
OperPLR = MIN(OperPLR,BoilerMaxPLR)
OperPLR = MAX(OperPLR,BoilerMinPLR)
! set report variable
BoilerPLR = OperPLR
! calculate theoretical fuel use based on nominal thermal efficiency
TheorFuelUse = BoilerLoad/BoilerEff
! calculate normalized efficiency based on curve object type
IF(Boiler(BoilerNum)%EfficiencyCurvePtr .GT. 0)THEN
IF(Boiler(BoilerNum)%EfficiencyCurveType .EQ. Biquadratic .OR. &
Boiler(BoilerNum)%EfficiencyCurveType .EQ. QuadraticLinear .OR. &
Boiler(BoilerNum)%EfficiencyCurveType .EQ. Bicubic)THEN
IF (Boiler(BoilerNum)%CurveTempMode == EnteringBoilerTemp) THEN
EffCurveOutput = CurveValue(Boiler(BoilerNum)%EfficiencyCurvePtr,OperPLR, &
Node(BoilerInletNode)%Temp)
ELSEIF (Boiler(BoilerNum)%CurveTempMode == LeavingBoilerTemp) THEN
EffCurveOutput = CurveValue(Boiler(BoilerNum)%EfficiencyCurvePtr,OperPLR,BoilerOutletTemp)
ENDIF
ELSE
EffCurveOutput = CurveValue(Boiler(BoilerNum)%EfficiencyCurvePtr,OperPLR)
END IF
ELSE
EffCurveOutput = 1.0d0
END IF
! warn if efficiency curve produces zero or negative results
IF(.NOT. WarmupFlag .AND. EffCurveOutput .LE. 0.0d0)THEN
IF(BoilerLoad .GT. 0.0d0)THEN
IF(Boiler(BoilerNum)%EffCurveOutputError .LT. 1)THEN
Boiler(BoilerNum)%EffCurveOutputError = Boiler(BoilerNum)%EffCurveOutputError + 1
CALL ShowWarningError('Boiler:HotWater "'//TRIM(Boiler(BoilerNum)%Name)//'"')
CALL ShowContinueError('...Normalized Boiler Efficiency Curve output is less than or equal to 0.')
CALL ShowContinueError('...Curve input x value (PLR) = '//TrimSigDigits(OperPLR,5))
IF(Boiler(BoilerNum)%EfficiencyCurveType .EQ. Biquadratic .OR. &
Boiler(BoilerNum)%EfficiencyCurveType .EQ. QuadraticLinear .OR. &
Boiler(BoilerNum)%EfficiencyCurveType .EQ. Bicubic)THEN
IF (Boiler(BoilerNum)%CurveTempMode == EnteringBoilerTemp) THEN
CALL ShowContinueError('...Curve input y value (Tinlet) = '// &
TrimSigDigits(Node(BoilerInletNode)%Temp,2))
ELSEIF (Boiler(BoilerNum)%CurveTempMode == LeavingBoilerTemp) THEN
CALL ShowContinueError('...Curve input y value (Toutlet) = '//TrimSigDigits(BoilerOutletTemp,2))
ENDIF
END IF
CALL ShowContinueError('...Curve output (normalized eff) = '//TrimSigDigits(EffCurveOutput,5))
CALL ShowContinueError('...Calculated Boiler efficiency = '//TRIM(TrimSigDigits(EffCurveOutput*BoilerEff,5))// &
' (Boiler efficiency = Nominal Thermal Efficiency * Normalized Boiler Efficiency Curve output)')
CALL ShowContinueErrorTimeStamp('...Curve output reset to 0.01 and simulation continues.')
ELSE
CALL ShowRecurringWarningErrorAtEnd('Boiler:HotWater "'//TRIM(Boiler(BoilerNum)%Name)//'":'//&
' Boiler Efficiency Curve output is less than or equal to 0 warning continues...' &
, Boiler(BoilerNum)%EffCurveOutputIndex, EffCurveOutput, EffCurveOutput)
END IF
END If
EffCurveOutput = 0.01d0
END IF
! warn if overall efficiency greater than 1.1
IF(.NOT. WarmupFlag .AND. EffCurveOutput*BoilerEff .GT. 1.1d0)THEN
IF(BoilerLoad .GT. 0.0d0 .AND. Boiler(BoilerNum)%EfficiencyCurvePtr .GT. 0)THEN
IF(Boiler(BoilerNum)%CalculatedEffError .LT. 1)THEN
Boiler(BoilerNum)%CalculatedEffError = Boiler(BoilerNum)%CalculatedEffError + 1
CALL ShowWarningError('Boiler:HotWater "'//TRIM(Boiler(BoilerNum)%Name)//'"')
CALL ShowContinueError('...Calculated Boiler Efficiency is greater than 1.1.')
CALL ShowContinueError('...Boiler Efficiency calculations shown below.')
CALL ShowContinueError('...Curve input x value (PLR) = '//TrimSigDigits(OperPLR,5))
IF(Boiler(BoilerNum)%EfficiencyCurveType .EQ. Biquadratic .OR. &
Boiler(BoilerNum)%EfficiencyCurveType .EQ. QuadraticLinear .OR. &
Boiler(BoilerNum)%EfficiencyCurveType .EQ. Bicubic)THEN
IF (Boiler(BoilerNum)%CurveTempMode == EnteringBoilerTemp) THEN
CALL ShowContinueError('...Curve input y value (Tinlet) = '// &
TrimSigDigits(Node(BoilerInletNode)%Temp,2))
ELSEIF (Boiler(BoilerNum)%CurveTempMode == LeavingBoilerTemp) THEN
CALL ShowContinueError('...Curve input y value (Toutlet) = '//TrimSigDigits(BoilerOutletTemp,2))
ENDIF
END IF
CALL ShowContinueError('...Curve output (normalized eff) = '//TrimSigDigits(EffCurveOutput,5))
CALL ShowContinueError('...Calculated Boiler efficiency = '//TRIM(TrimSigDigits(EffCurveOutput*BoilerEff,5))// &
' (Boiler efficiency = Nominal Thermal Efficiency * Normalized Boiler Efficiency Curve output)')
CALL ShowContinueErrorTimeStamp('...Curve output reset to 1.1 and simulation continues.')
ELSE
CALL ShowRecurringWarningErrorAtEnd('Boiler:HotWater "'//TRIM(Boiler(BoilerNum)%Name)//'":'//&
' Calculated Boiler Efficiency is greater than 1.1 warning continues...' &
, Boiler(BoilerNum)%CalculatedEffIndex, EffCurveOutput*BoilerEff, EffCurveOutput*BoilerEff)
END IF
END If
EffCurveOutput = 1.1d0
END IF
! calculate fuel used based on normalized boiler efficiency curve (=1 when no curve used)
FuelUsed=TheorFuelUse/EffCurveOutput
IF(BoilerLoad .GT. 0.0d0)ParasiticElecPower=ParasiticElecLoad*OperPLR
RETURN
END SUBROUTINE CalcBoilerModel