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) | :: | GeneratorNum | |||
logical, | intent(in) | :: | RunFlag | |||
real(kind=r64), | intent(in) | :: | MyLoad | |||
logical, | intent(in) | :: | FirstHVACIteration |
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 CalcCTGeneratorModel(GeneratorNum,Runflag,MyLoad,FirstHVACIteration)
! SUBROUTINE INFORMATION:
! AUTHOR Dan Fisher
! DATE WRITTEN Sept. 2000
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! simulate a vapor compression Generator using the CT model
! METHODOLOGY EMPLOYED:
! curve fit of performance data. This model was originally
! developed by Dale Herron for the BLAST program
! REFERENCES: na
! USE STATEMENTS:
USE DataHVACGlobals, ONLY : FirstTimeStepSysFlag, TimeStepSys
USE DataEnvironment, ONLY : OutDryBulbTemp
USE CurveManager, ONLY : CurveValue
USE FluidProperties, ONLY : GetSpecificHeatGlycol
USE DataPlant, ONLY : PlantLoop
IMPLICIT NONE
! SUBROUTINE ARGUMENT DEFINITIONS:
REAL(r64) , INTENT(IN) :: MyLoad ! Generator demand
INTEGER, INTENT(IN) :: GeneratorNum ! Generator number
LOGICAL, INTENT(IN) :: RunFlag ! TRUE when Generator operating
LOGICAL, INTENT(IN) :: FirstHVACIteration
! SUBROUTINE PARAMETER DEFINITIONS:
REAL(r64), PARAMETER :: ExhaustCP = 1.047d0 !Exhaust Gas Specific Heat (J/kg-K)
REAL(r64), PARAMETER :: KJtoJ = 1000.d0 !convert Kjoules to joules
! INTERFACE BLOCK SPECIFICATIONS
! INTERFACE
! REAL(r64) FUNCTION CurveValue(CurveIndex,Var1,Var2)
!
! INTEGER, INTENT (IN) :: CurveIndex ! index of curve in curve array
! REAL(r64), INTENT (IN) :: Var1 ! 1st independent variable
! REAL(r64), INTENT (IN), OPTIONAL :: Var2 ! 2nd independent variable
!
! END FUNCTION CurveValue
!
! END INTERFACE
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: MinPartLoadRat ! min allowed operating frac full load
REAL(r64) :: MaxPartLoadRat ! max allowed operating frac full load
REAL(r64) :: RatedPowerOutput ! Generator nominal capacity (W)
REAL(r64) :: ElecPowerGenerated ! Generator output (W)
REAL(r64) :: ElectricEnergyGen ! Generator output (J)
! Special variables for CT Generator
REAL(r64) :: MaxExhaustperCTPower !MAX EXHAUST FLOW PER W POWER OUTPUT COEFF
REAL(r64) :: PLR ! Generator operating part load ratio
REAL(r64) :: FuelUseRate !(EFUEL) rate of Fuel Energy Required to run COMBUSTION turbine (W)
REAL(r64) :: FuelEnergyUsed !Amount of Fuel Energy Required to run COMBUSTION turbine (J)
REAL(r64) :: ExhaustFlow !(FEX) Exhaust Gas Flow Rate cubic meters per second???
REAL(r64) :: ExhaustTemp !(TEX) Exhaust Gas Temperature in C
REAL(r64) :: UA !(UACGC) Heat Exchanger UA to Capacity
REAL(r64) :: AmbientDeltaT !(ATAIR) Difference between ambient actual and ambient design temperatures
REAL(r64) :: DesignAirInletTemp ! design turbine inlet temperature (C)
REAL(r64) :: QLubeOilRec ! recovered lube oil heat (W)
REAL(r64) :: QExhaustRec ! recovered exhaust heat (W)
REAL(r64) :: LubeOilEnergyRec ! recovered lube oil heat (J)
REAL(r64) :: ExhaustEnergyRec ! recovered exhaust heat (J)
REAL(r64) :: MinHeatRecMdot ! Heat Recovery Flow Rate if minimal heat recovery is accomplished
REAL(r64) :: DesignMinExitGasTemp ! design engine stact saturated steam temp. (C)
REAL(r64) :: ExhaustStackTemp ! turbine stack temp. (C)
INTEGER :: HeatRecInNode !Heat Recovery Fluid Inlet Node Num
!notused INTEGER :: HeatRecOutNode !Heat Recovery Fluid Outlet Node Num
REAL(r64) :: HeatRecInTemp !Heat Recovery Fluid Inlet Temperature (C)
REAL(r64) :: HeatRecOutTemp !Heat Recovery Fluid Outlet Temperature (C)
REAL(r64) :: HeatRecMdot !Heat Recovery Fluid Mass FlowRate (kg/s)
REAL(r64) :: HeatRecCp !Specific Heat of the Heat Recovery Fluid (J/kg-K)
REAL(r64) :: FuelHeatingValue !Heating Value of Fuel in (kJ/kg)
REAL(r64) :: HRecRatio !When Max Temp is reached the amount of recovered heat has to be reduced.
! and this assumption uses this ratio to accomplish this task.
! LOAD LOCAL VARIABLES FROM DATA STRUCTURE (for code readability)
MinPartLoadRat = CTGenerator(GeneratorNum)%MinPartLoadRat
MaxPartLoadRat = CTGenerator(GeneratorNum)%MaxPartLoadRat
RatedPowerOutput = CTGenerator(GeneratorNum)%RatedPowerOutput
MaxExhaustperCTPower = CTGenerator(GeneratorNum)%MaxExhaustperCTPower
DesignAirInletTemp = CTGenerator(GeneratorNum)%DesignAirInletTemp
IF (CTGenerator(GeneratorNum)%HeatRecActive) THEN
HeatRecInNode = CTGenerator(GeneratorNum)%HeatRecInletNodeNum
HeatRecInTemp = Node(HeatRecInNode)%Temp
HeatRecCp = GetSpecificHeatGlycol(PlantLoop(CTGenerator(GeneratorNum)%HRLoopNum)%FluidName, &
HeatRecInTemp, &
PlantLoop(CTGenerator(GeneratorNum)%HRLoopNum)%FluidIndex, &
'CalcCTGeneratorModel')
If(FirstHVACIteration .AND. RunFlag) Then
HeatRecMdot = CTGenerator(GeneratorNum)%DesignHeatRecMassFlowRate
Else
HeatRecMdot = Node(HeatRecInNode)%MassFlowRate
End If
ELSE
HeatRecInTemp=0.0d0
HeatRecCp=0.0d0
HeatRecMdot=0.0d0
ENDIF
!If no loop demand or Generator OFF, return
IF (.NOT. Runflag) THEN
CTGenerator(GeneratorNum)%ElecPowerGenerated = 0.0d0
CTGenerator(GeneratorNum)%ElecEnergyGenerated = 0.0d0
CTGenerator(GeneratorNum)%HeatRecInletTemp = HeatRecInTemp
CTGenerator(GeneratorNum)%HeatRecOutletTemp = HeatRecInTemp
CTGenerator(GeneratorNum)%HeatRecMdot = 0.0d0
CTGenerator(GeneratorNum)%QLubeOilRecovered = 0.0d0
CTGenerator(GeneratorNum)%QExhaustRecovered = 0.0d0
CTGenerator(GeneratorNum)%QTotalHeatRecovered = 0.0d0
CTGenerator(GeneratorNum)%LubeOilEnergyRec = 0.0d0
CTGenerator(GeneratorNum)%ExhaustEnergyRec = 0.0d0
CTGenerator(GeneratorNum)%TotalHeatEnergyRec = 0.0d0
CTGenerator(GeneratorNum)%FuelEnergyUseRate = 0.0d0
CTGenerator(GeneratorNum)%FuelEnergy = 0.0d0
CTGenerator(GeneratorNum)%FuelMdot = 0.0d0
CTGenerator(GeneratorNum)%ExhaustStackTemp = 0.0d0
RETURN
END IF
! CALCULATE POWER GENERATED AND PLR
ElecPowerGenerated = MIN(MyLoad,RatedPowerOutput)
ElecPowerGenerated = MAX(ElecPowerGenerated,0.0d0)
PLR = MIN(ElecPowerGenerated/RatedPowerOutput, MaxPartLoadRat)
PLR = MAX(PLR, MinPartLoadRat)
ElecPowerGenerated = PLR*RatedPowerOutput
! SET OFF-DESIGN AIR TEMPERATURE DIFFERENCE
! use OA node if set by user CR7021
If (CTGenerator(GeneratorNum)%OAInletNode == 0) then
AmbientDeltaT = OutDryBulbTemp - DesignAirInletTemp
ELSE
AmbientDeltaT = Node(CTGenerator(GeneratorNum)%OAInletNode)%Temp - DesignAirInletTemp
ENDIF
!Use Curve fit to determine Fuel Energy Input. For electric power generated in Watts, the fuel
!energy input is calculated in J/s. The PLBasedFuelInputCurve selects ratio of fuel flow (J/s)/power generated (J/s).
!The TempBasedFuelInputCurve is a correction based on deviation from design inlet air temperature conditions.
!The first coefficient of this fit should be 1.0 to ensure that no correction is made at design conditions.
FuelUseRate = ElecPowerGenerated * CurveValue(CTGenerator(GeneratorNum)%PLBasedFuelInputCurve, PLR) * &
CurveValue(CTGenerator(GeneratorNum)%TempBasedFuelInputCurve, AmbientDeltaT)
!Use Curve fit to determine Exhaust Flow. This curve shows the ratio of exhaust gas flow (kg/s) to electric power
!output (J/s). The units on ExhaustFlowCurve are (kg/J). When multiplied by the rated power of the unit,
!it gives the exhaust flow rate in kg/s
ExhaustFlow = RatedPowerOutput * CurveValue(CTGenerator(GeneratorNum)%ExhaustFlowCurve, AmbientDeltaT)
!Use Curve fit to determine Exhaust Temperature. This curve calculates the exhaust temperature (C) by
!multiplying the exhaust temperature (C) for a particular part load as given by PLBasedExhaustTempCurve
!a correction factor based on the deviation from design temperature, TempBasedExhaustTempCurve
IF ((PLR > 0.0d0) .AND. ( (ExhaustFlow > 0.0D0) .or. (MaxExhaustperCTPower > 0.0D0))) THEN
ExhaustTemp = CurveValue(CTGenerator(GeneratorNum)%PLBasedExhaustTempCurve, PLR) * &
CurveValue(CTGenerator(GeneratorNum)%TempBasedExhaustTempCurve, AmbientDeltaT)
UA = CTGenerator(GeneratorNum)%UACoef(1) * RatedPowerOutput ** &
CTGenerator(GeneratorNum)%UACoef(2)
DesignMinExitGasTemp = CTGenerator(GeneratorNum)%DesignMinExitGasTemp
ExhaustStackTemp = DesignMinExitGasTemp + (ExhaustTemp - DesignMinExitGasTemp) / &
EXP(UA/(MAX(ExhaustFlow, MaxExhaustperCTPower * RatedPowerOutput) * ExhaustCP))
QExhaustRec = MAX(ExhaustFlow*ExhaustCP*(ExhaustTemp-ExhaustStackTemp),0.0d0)
ELSE
ExhaustStackTemp = CTGenerator(GeneratorNum)%DesignMinExitGasTemp
QExhaustRec = 0.0d0
END IF
!Use Curve fit to determine Heat Recovered Lubricant heat. This curve calculates the lube heat recovered (J/s) by
!multiplying the total power generated by the fraction of that power that could be recovered in the lube oil at that
!particular part load.
QLubeOilRec = ElecPowerGenerated * CurveValue(CTGenerator(GeneratorNum)%QLubeOilRecoveredCurve, PLR)
!Check for divide by zero
IF ((HeatRecMdot .GT. 0.0d0) .AND. (HeatRecCp .GT. 0.0d0)) THEN
HeatRecOutTemp = (QExhaustRec + QLubeOilRec)/(HeatRecMdot * HeatRecCp) + HeatRecInTemp
ELSE
HeatRecMdot = 0.0d0
HeatRecOutTemp = HeatRecInTemp
QExhaustRec =0.0d0
QLubeOilRec =0.0d0
END IF
!Now verify the maximum temperature was not exceeded
HRecRatio = 1.0d0
MinHeatRecMdot=0.0d0
IF(HeatRecOutTemp > CTGenerator(GeneratorNum)%HeatRecMaxTemp) THEN
IF(CTGenerator(GeneratorNum)%HeatRecMaxTemp /= HeatRecInTemp)THEN
MinHeatRecMdot = (QExhaustRec + QLubeOilRec)/(HeatRecCp * (CTGenerator(GeneratorNum)%HeatRecMaxTemp - HeatRecInTemp))
If(MinHeatRecMdot < 0.0d0) MinHeatRecMdot = 0.0d0
END IF
!Recalculate Outlet Temperature, with adjusted flowrate
IF ((MinHeatRecMdot .GT. 0.0d0) .AND. (HeatRecCp .GT. 0.0d0)) THEN
HeatRecOutTemp = (QExhaustRec + QLubeOilRec)/(MinHeatRecMdot * HeatRecCp) + HeatRecInTemp
HRecRatio = HeatRecMdot/MinHeatRecMdot
ELSE
HeatRecOutTemp = HeatRecInTemp
HRecRatio = 0.0d0
END IF
QLubeOilRec = QLubeOilRec*HRecRatio
QExhaustRec = QExhaustRec*HRecRatio
END IF
!Calculate Energy
ElectricEnergyGen = ElecPowerGenerated*TimeStepSys*SecInHour
FuelEnergyUsed = FuelUseRate*TimeStepSys*SecInHour
LubeOilEnergyRec = QLubeOilRec*TimeStepSys*SecInHour
ExhaustEnergyRec = QExhaustRec*TimeStepSys*SecInHour
CTGenerator(GeneratorNum)%ElecPowerGenerated = ElecPowerGenerated
CTGenerator(GeneratorNum)%ElecEnergyGenerated = ElectricEnergyGen
CTGenerator(GeneratorNum)%HeatRecInletTemp = HeatRecInTemp
CTGenerator(GeneratorNum)%HeatRecOutletTemp = HeatRecOutTemp
CTGenerator(GeneratorNum)%HeatRecMdot = HeatRecMdot
CTGenerator(GeneratorNum)%QExhaustRecovered = QExhaustRec
CTGenerator(GeneratorNum)%QLubeOilRecovered = QLubeOilRec
CTGenerator(GeneratorNum)%QTotalHeatRecovered = QExhaustRec + QLubeOilRec
CTGenerator(GeneratorNum)%FuelEnergyUseRate = ABS(FuelUseRate)
CTGenerator(GeneratorNum)%ExhaustEnergyRec = ExhaustEnergyRec
CTGenerator(GeneratorNum)%LubeOilEnergyRec = LubeOilEnergyRec
CTGenerator(GeneratorNum)%TotalHeatEnergyRec = ExhaustEnergyRec + LubeOilEnergyRec
CTGenerator(GeneratorNum)%FuelEnergy = ABS(FuelEnergyUsed)
FuelHeatingValue = CTGenerator(GeneratorNum)%FuelHeatingValue
CTGenerator(GeneratorNum)%FuelMdot = ABS(FuelUseRate)/(FuelHeatingValue * KJtoJ)
CTGenerator(GeneratorNum)%ExhaustStackTemp = ExhaustStackTemp
RETURN
END SUBROUTINE CalcCTGeneratorModel