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) | :: | RunFlagElectCenter | |||
logical, | intent(in) | :: | RunFlagPlant | |||
real(kind=r64), | intent(in) | :: | MyElectricload | |||
real(kind=r64), | intent(in) | :: | MyThermalLoad | |||
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 CalcMicroCHPNoNormalizeGeneratorModel(GeneratorNum,RunFlagElectCenter, &
RunFlagPlant, MyElectricLoad,MyThermalLoad, FirstHVACIteration)
! SUBROUTINE INFORMATION:
! AUTHOR B Griffith
! DATE WRITTEN July 2006
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Main calculation subroutine for the IEA Annex 42 model
! METHODOLOGY EMPLOYED:
! curve fit, dynamic control limits,
! REFERENCES:
! IEA Annex 42 FC-COGEN-SIM "A Generic Model Specification for Combustion-based Residential CHP Devices"
! Alex Ferguson, Nick Kelly, Version 3, June 26, 2006
! USE STATEMENTS:
USE DataLoopNode , ONLY: Node
USE DataHeatBalFanSys, ONLY: MAT
Use DataHVACGlobals, ONLY: SysTimeElapsed, TimeStepSys
USE DataGlobals , ONLY: TimeStep, TimeStepZone, SecInHour, HoursInDay
USE CurveManager, ONLY: CurveValue
USE DataGlobalConstants
USE FluidProperties, ONLY: GetSpecificHeatGlycol
USE DataPlant, ONLY: PlantLoop
USE PlantUtilities, ONLY: SetComponentFlowRate
USE DataEnvironment, ONLY: OutDryBulbTemp
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: GeneratorNum ! Generator number
LOGICAL, INTENT(IN) :: RunFlagElectCenter ! TRUE when Generator operating
LOGICAL, INTENT(IN) :: RunFlagPlant !
REAL(r64) , INTENT(IN) :: MyElectricload ! Generator demand
REAL(r64) , INTENT(IN) :: MyThermalLoad
LOGICAL, INTENT(IN) :: FirstHVACIteration
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: AllowedLoad = 0.0d0
INTEGER :: CurrentOpMode = 0
REAL(r64) :: PLRforSubtimestepStartUp = 1.0d0
REAL(r64) :: PLRforSubtimestepShutDown = 0.0d0
LOGICAL :: RunFlag = .false.
INTEGER :: DynaCntrlNum = 0
REAL(r64) :: Pnetss = 0.0d0
REAL(r64) :: Pstandby = 0.0d0 ! power draw during standby, positive here means negative production
REAL(r64) :: Pcooler = 0.0d0 ! power draw during cool down, positive here means negative production
! REAL(r64) :: Pnet = 0.0d0
REAL(r64) :: NdotFuel = 0.0d0
LOGICAL :: ConstrainedIncreasingNdot = .false.
LOGICAL :: ConstrainedDecreasingNdot = .false.
INTEGER :: I = 0
REAL(r64) :: dt = 0.0d0
REAL(r64) :: ElecEff = 0.0d0
REAL(r64) :: MdotAir = 0.0d0
REAL(r64) :: Qgenss = 0.0d0
REAL(r64) :: Mdotcw = 0.0d0
REAL(r64) :: TcwIn = 0.0d0
REAL(r64) :: Tcwout = 0.0d0
REAL(r64) :: MdotFuel = 0.0d0
REAL(r64) :: MdotFuelAllowed = 0.0d0
REAL(r64) :: MdotFuelMax = 0.0d0
REAL(r64) :: MdotFuelWarmup = 0.0d0
REAL(r64) :: Pmax = 0.0d0
REAL(r64) :: Qgross = 0.0d0
REAL(r64) :: Teng = 0.0d0
REAL(r64) :: ThermEff = 0.0d0
REAL(r64) :: Cp = 0.d0 ! local fluid specific heat
REAL(r64) :: thisAmbientTemp = 0.d0
LOGICAL :: EnergyBalOK ! check for balance to exit loop
DynaCntrlNum = MicroCHP(GeneratorNum)%DynamicsControlID
CALL ManageGeneratorControlState(iGeneratorMicroCHP, MicroCHP(GeneratorNum)%Name, &
GeneratorNum, RunFlagElectCenter, RunFlagPlant, MyElectricLoad, MyThermalLoad, &
AllowedLoad, CurrentOpMode,&
PLRforSubtimestepStartUp, PLRforSubtimestepShutDown, FirstHVACIteration)
If (RunFlagElectCenter .or. RunFlagPlant ) RunFlag = .true.
Teng = MicroCHP(GeneratorNum)%A42Model%Teng
Tcwout = MicroCHP(GeneratorNum)%A42Model%Tcwout
dt = TimeStepSys * SecInHour
IF (MicroCHP(GeneratorNum)%ZoneID > 0) THEN
thisAmbientTemp = MAT(MicroCHP(GeneratorNum)%ZoneID)
ELSE ! outdoor location, no zone
thisAmbientTemp = OutDryBulbTemp
ENDIF
Select CASE (CurrentOpMode)
CASE (OpModeOFF) ! same as standby in model spec but no Pnet standby electicity losses.
Qgenss = 0.0d0
Mdotcw = Node(MicroCHP(GeneratorNum)%PlantInletNodeID)%MassFlowRate !kg/s
TcwIn = Node(MicroCHP(GeneratorNum)%PlantInletNodeID)%Temp !C
Pnetss = 0.0d0
Pstandby = 0.0d0
Pcooler = MicroCHP(GeneratorNum)%A42Model%PcoolDown * PLRforSubtimestepShutDown
ElecEff = 0.0d0
ThermEff = 0.0d0
Qgross = 0.0d0
NdotFuel = 0.0d0
MdotFuel = 0.0d0
MdotAir = 0.0d0
Mdotcw = 0.d0
CALL SetComponentFlowRate(Mdotcw, &
MicroCHP(GeneratorNum)%PlantInletNodeID, &
MicroCHP(GeneratorNum)%PlantOutletNodeID, &
MicroCHP(GeneratorNum)%CWLoopNum, &
MicroCHP(GeneratorNum)%CWLoopSideNum, &
MicroCHP(GeneratorNum)%CWBranchNum, &
MicroCHP(GeneratorNum)%CWCompNum)
MicroCHP(GeneratorNum)%PlantMassFlowRate = Mdotcw
CASE (OpModeStandby)
Qgenss = 0.0d0
Mdotcw = Node(MicroCHP(GeneratorNum)%PlantInletNodeID)%MassFlowRate !kg/s
TcwIn = Node(MicroCHP(GeneratorNum)%PlantInletNodeID)%Temp !C
Pnetss = 0.0d0
Pstandby = MicroCHP(GeneratorNum)%A42Model%Pstandby * (1.0 - PLRforSubtimestepShutDown)
Pcooler = MicroCHP(GeneratorNum)%A42Model%PcoolDown * PLRforSubtimestepShutDown
ElecEff = 0.0d0
ThermEff = 0.0d0
Qgross = 0.0d0
NdotFuel = 0.0d0
MdotFuel = 0.0d0
MdotAir = 0.0d0
Mdotcw = 0.d0
CALL SetComponentFlowRate(Mdotcw, &
MicroCHP(GeneratorNum)%PlantInletNodeID, &
MicroCHP(GeneratorNum)%PlantOutletNodeID, &
MicroCHP(GeneratorNum)%CWLoopNum, &
MicroCHP(GeneratorNum)%CWLoopSideNum, &
MicroCHP(GeneratorNum)%CWBranchNum, &
MicroCHP(GeneratorNum)%CWCompNum)
MicroCHP(GeneratorNum)%PlantMassFlowRate = Mdotcw
CASE (OpModeWarmUp)
IF ( MicroCHP(GeneratorNum)%A42Model%WarmUpByTimeDelay ) Then
! Internal combustion engine. This is just like normal operation but no net power yet.
Pnetss = MyElectricLoad ! W
Pstandby = 0.0d0
Pcooler = MicroCHP(GeneratorNum)%A42Model%PcoolDown * PLRforSubtimestepShutDown
TcwIn = Node(MicroCHP(GeneratorNum)%PlantInletNodeID)%Temp !C
Mdotcw = Node(MicroCHP(GeneratorNum)%PlantInletNodeID)%MassFlowRate !kg/s
IF (MicroCHP(GeneratorNum)%A42Model%InternalFlowControl) THEN
Mdotcw = FuncDetermineCWMdotForInternalFlowControl(GeneratorNum, Pnetss, TcwIn)
ENDIF
ElecEff = CurveValue(MicroCHP(GeneratorNum)%A42Model%ElecEffCurveID, Pnetss, Mdotcw , TcwIn )
ElecEff = MAX(0.0D0, ElecEff) !protect against bad curve result
IF ( ElecEff > 0.0d0) THEN ! trap divide by bad thing
Qgross = Pnetss/ElecEff !W
ELSE
Qgross = 0.0d0
ENDIF
ThermEff = CurveValue(MicroCHP(GeneratorNum)%A42Model%ThermalEffCurveID, Pnetss, Mdotcw , TcwIN )
ThermEff = MAX(0.0D0, ThermEff) !protect against bad curve result
Qgenss = ThermEff * Qgross !W
MdotFuel = Qgross / (FuelSupply(MicroCHP(GeneratorNum)%FuelSupplyID)%LHV * 1000.0d0 *1000.0d0)&
* FuelSupply(MicroCHP(GeneratorNum)%FuelSupplyID)%KmolPerSecToKgPerSec
! kMol/s = (J/s) /(KJ/mol * 1000 J/KJ * 1000 mol/kmol)
CALL ManageGeneratorFuelFlow(iGeneratorMicroCHP, MicroCHP(GeneratorNum)%Name, GeneratorNum,RunFlag,MdotFuel, &
MdotFuelAllowed, ConstrainedIncreasingNdot, ConstrainedDecreasingNdot)
IF (ConstrainedIncreasingNdot .OR. ConstrainedDecreasingNdot) THEN ! recalculate Pnetss with new NdotFuel with iteration
MdotFuel = MdotFuelAllowed
NdotFuel = MdotFuel / FuelSupply(MicroCHP(GeneratorNum)%FuelSupplyID)%KmolPerSecToKgPerSec
Qgross = NdotFuel * (FuelSupply(MicroCHP(GeneratorNum)%FuelSupplyID)%LHV *1000.0d0* 1000.0d0)
DO I=1, 20 ! iterating here could add use of seach method .
Pnetss = Qgross * ElecEff
IF (MicroCHP(GeneratorNum)%A42Model%InternalFlowControl) THEN
Mdotcw = FuncDetermineCWMdotForInternalFlowControl(GeneratorNum, Pnetss, TcwIn)
ENDIF
ElecEff = CurveValue(MicroCHP(GeneratorNum)%A42Model%ElecEffCurveID, Pnetss, Mdotcw, TcwIN)
ElecEff = MAX(0.0D0, ElecEff) !protect against bad curve result
ENDDO
ThermEff = CurveValue(MicroCHP(GeneratorNum)%A42Model%ThermalEffCurveID, Pnetss, Mdotcw, TcwIN )
ThermEff = MAX(0.0D0, ThermEff) !protect against bad curve result
Qgenss = ThermEff * Qgross !W
ENDIf
Pnetss = 0.0d0 ! no actually power produced here.
NdotFuel = MdotFuel / FuelSupply(MicroCHP(GeneratorNum)%FuelSupplyID)%KmolPerSecToKgPerSec
MdotAir = CurveValue(MicroCHP(GeneratorNum)%A42Model%AirFlowCurveID, MdotFuel)
MdotAir = MAX(0.0D0, MdotAir) !protect against bad curve result
ELSEIF ( MicroCHP(GeneratorNum)%A42Model%WarmUpByEngineTemp) THEN
! Stirling engine mode warm up
! find MdotFuelMax
Pmax = MicroCHP(GeneratorNum)%A42Model%MaxElecPower
Pnetss = 0.0d0
Pstandby = 0.0d0
Pcooler = MicroCHP(GeneratorNum)%A42Model%PcoolDown * PLRforSubtimestepShutDown ! could be here with part load in cool down
TcwIn = Node(MicroCHP(GeneratorNum)%PlantInletNodeID)%Temp !C
Mdotcw = Node(MicroCHP(GeneratorNum)%PlantInletNodeID)%MassFlowRate !kg/s
ElecEff = CurveValue(MicroCHP(GeneratorNum)%A42Model%ElecEffCurveID, Pmax, Mdotcw, TcwIN)
ElecEff = MAX(0.0D0, ElecEff) !protect against bad curve result
IF ( ElecEff > 0.0d0) THEN ! trap divide by bad thing
Qgross = Pmax/ElecEff !W
ELSE
Qgross = 0.0d0
ENDIF
NdotFuel = Qgross / (FuelSupply(MicroCHP(GeneratorNum)%FuelSupplyID)%LHV * 1000.0d0 *1000.0d0)
! kMol/s = (J/s) /(KJ/mol * 1000 J/KJ * 1000 mol/kmol)
MdotFuelMax = NdotFuel * FuelSupply(MicroCHP(GeneratorNum)%FuelSupplyID)%KmolPerSecToKgPerSec
If (Teng > thisAmbientTemp ) Then
MdotFuelWarmup = MdotFuelMax + MicroCHP(GeneratorNum)%A42Model%kf * MdotFuelMax * &
( ( MicroCHP(GeneratorNum)%A42Model%TnomEngOp - thisAmbientTemp ) &
/ (Teng - thisAmbientTemp ) )
! check that numerical answer didn't blow up beyond limit, and reset if it did
IF (MdotFuelWarmup > MicroCHP(GeneratorNum)%A42Model%Rfuelwarmup * MdotFuelMax) THEN
MdotFuelWarmup = MicroCHP(GeneratorNum)%A42Model%Rfuelwarmup * MdotFuelMax
ENDIF
ELSEIF (Teng < thisAmbientTemp) Then
MdotFuelWarmup = MicroCHP(GeneratorNum)%A42Model%Rfuelwarmup * MdotFuelMax
ELSE ! equal would divide by zero
MdotFuelWarmup = MicroCHP(GeneratorNum)%A42Model%Rfuelwarmup * MdotFuelMax
ENDIF
If (MicroCHP(GeneratorNum)%A42Model%TnomEngOp > thisAmbientTemp ) Then
Pnetss = Pmax * MicroCHP(GeneratorNum)%A42Model%kp * &
( (Teng - thisAmbientTemp ) &
/ ( MicroCHP(GeneratorNum)%A42Model%TnomEngOp - thisAmbientTemp ) )
ELSEIF (MicroCHP(GeneratorNum)%A42Model%TnomEngOp < thisAmbientTemp) Then
Pnetss = Pmax
ELSE ! equal would divide by zero
Pnetss = Pmax
ENDIF
!If ( MicroCHP(GeneratorNum)%A42Model%TnomEngOp < thisAmbientTemp) then
! !this case where zone is super hot and more than engine op. temp.
! ! never going to get here because E+ zones don't like to be over 50C. (and no cogen devices should operate below 50C)
!ENDIF
MdotFuel = MdotFuelWarmup
NdotFuel = MdotFuel / FuelSupply(MicroCHP(GeneratorNum)%FuelSupplyID)%KmolPerSecToKgPerSec
MdotAir = CurveValue(MicroCHP(GeneratorNum)%A42Model%AirFlowCurveID, MdotFuelWarmup)
MdotAir = MAX(0.0D0, MdotAir) !protect against bad curve result
Qgross = NdotFuel * (FuelSupply(MicroCHP(GeneratorNum)%FuelSupplyID)%LHV * 1000.0d0 *1000.0d0)
ThermEff = CurveValue(MicroCHP(GeneratorNum)%A42Model%ThermalEffCurveID, Pmax, Mdotcw, TcwIN)
Qgenss = ThermEff * Qgross !W
ENDIF
NdotFuel = MdotFuel / FuelSupply(MicroCHP(GeneratorNum)%FuelSupplyID)%KmolPerSecToKgPerSec
CASE (OpModeNormal)
If (PLRforSubtimestepStartUp < 1.0d0) then
If (RunFlagElectCenter) Pnetss = MyElectricLoad ! W
If (RunFlagPlant) Pnetss = AllowedLoad
else
Pnetss = AllowedLoad
endif
Pstandby = 0.0d0
Pcooler = 0.0d0
TcwIn = Node(MicroCHP(GeneratorNum)%PlantInletNodeID)%Temp !C
Mdotcw = Node(MicroCHP(GeneratorNum)%PlantInletNodeID)%MassFlowRate !kg/s
IF (MicroCHP(GeneratorNum)%A42Model%InternalFlowControl) THEN
Mdotcw = FuncDetermineCWMdotForInternalFlowControl(GeneratorNum, Pnetss, TcwIn)
ENDIF
ElecEff = CurveValue(MicroCHP(GeneratorNum)%A42Model%ElecEffCurveID, Pnetss, Mdotcw, TcwIN )
ElecEff = MAX(0.0D0, ElecEff) !protect against bad curve result
IF ( ElecEff > 0.0d0) THEN ! trap divide by bad thing
Qgross = Pnetss/ElecEff !W
ELSE
Qgross = 0.0d0
ENDIF
ThermEff = CurveValue(MicroCHP(GeneratorNum)%A42Model%ThermalEffCurveID, Pnetss, Mdotcw, TcwIN)
ThermEff = MAX(0.0D0, ThermEff) !protect against bad curve result
Qgenss = ThermEff * Qgross !W
MdotFuel = Qgross / (FuelSupply(MicroCHP(GeneratorNum)%FuelSupplyID)%LHV * 1000.0d0 *1000.0d0) &
* FuelSupply(MicroCHP(GeneratorNum)%FuelSupplyID)%KmolPerSecToKgPerSec
! kMol/s = (J/s) /(KJ/mol * 1000 J/KJ * 1000 mol/kmol)
CALL ManageGeneratorFuelFlow(iGeneratorMicroCHP, MicroCHP(GeneratorNum)%Name, GeneratorNum,RunFlag,MdotFuel, &
MdotFuelAllowed, ConstrainedIncreasingNdot, ConstrainedDecreasingNdot)
IF (ConstrainedIncreasingNdot .OR. ConstrainedDecreasingNdot) THEN ! recalculate Pnetss with new NdotFuel with iteration
MdotFuel = MdotFuelAllowed
NdotFuel = MdotFuel / FuelSupply(MicroCHP(GeneratorNum)%FuelSupplyID)%KmolPerSecToKgPerSec
Qgross = NdotFuel * (FuelSupply(MicroCHP(GeneratorNum)%FuelSupplyID)%LHV * 1000.0d0 * 1000.0d0)
DO I=1, 20 ! iterating here, could add use of seach method error signal
Pnetss = Qgross * ElecEff
IF (MicroCHP(GeneratorNum)%A42Model%InternalFlowControl) THEN
Mdotcw = FuncDetermineCWMdotForInternalFlowControl(GeneratorNum, Pnetss, TcwIn)
ENDIF
ElecEff = CurveValue(MicroCHP(GeneratorNum)%A42Model%ElecEffCurveID, Pnetss, Mdotcw, TcwIN )
ElecEff = MAX(0.0D0, ElecEff) !protect against bad curve result
ENDDO
ThermEff = CurveValue(MicroCHP(GeneratorNum)%A42Model%ThermalEffCurveID, Pnetss,Mdotcw , TcwIN )
ThermEff = MAX(0.0D0, ThermEff) !protect against bad curve result
Qgenss = ThermEff * Qgross !W
ENDIF
NdotFuel = MdotFuel / FuelSupply(MicroCHP(GeneratorNum)%FuelSupplyID)%KmolPerSecToKgPerSec
MdotAir = CurveValue(MicroCHP(GeneratorNum)%A42Model%AirFlowCurveID, MdotFuel)
MdotAir = MAX(0.0D0, MdotAir) !protect against bad curve result
IF (PLRforSubtimestepStartUp < 1.0d0) THEN
Pnetss = AllowedLoad
ENDIF
CASE (opModeCoolDown)
Pnetss = 0.0d0
Pstandby = 0.0d0
Pcooler = MicroCHP(GeneratorNum)%A42Model%PcoolDown
TcwIn = Node(MicroCHP(GeneratorNum)%PlantInletNodeID)%Temp !C
Mdotcw = Node(MicroCHP(GeneratorNum)%PlantInletNodeID)%MassFlowRate !kg/s
IF (MicroCHP(GeneratorNum)%A42Model%InternalFlowControl) THEN
Mdotcw = FuncDetermineCWMdotForInternalFlowControl(GeneratorNum, Pnetss, TcwIn )
ENDIF
NdotFuel = 0.0d0
MdotFuel = 0.0d0
MdotAir = 0.0d0
ElecEff = 0.0d0
ThermEff = 0.0d0
Qgross = 0.0d0
Qgenss = 0.0d0
END SELECT
EnergyBalOK = .false.
DO I=1, 20 ! sequential search with exit criteria
! calculate new value for engine temperature
! for Stirling in warmup, need to include dependency of Qgness on Teng
If ((MicroCHP(GeneratorNum)%A42Model%WarmUpByEngineTemp) .AND. ( CurrentOpMode == OpModeWarmUp)) then
Pmax = MicroCHP(GeneratorNum)%A42Model%MaxElecPower
TcwIn = Node(MicroCHP(GeneratorNum)%PlantInletNodeID)%Temp !C
Mdotcw = Node(MicroCHP(GeneratorNum)%PlantInletNodeID)%MassFlowRate !kg/s
ElecEff = CurveValue(MicroCHP(GeneratorNum)%A42Model%ElecEffCurveID, Pmax, Mdotcw, TcwIN)
ElecEff = MAX(0.0D0, ElecEff) !protect against bad curve result
IF ( ElecEff > 0.0d0) THEN ! trap divide by bad thing
Qgross = Pmax/ElecEff !W
ELSE
Qgross = 0.0d0
ENDIF
NdotFuel = Qgross / (FuelSupply(MicroCHP(GeneratorNum)%FuelSupplyID)%LHV * 1000.0d0 *1000.0d0)
! kMol/s = (J/s) /(KJ/mol * 1000 J/KJ * 1000 mol/kmol)
MdotFuelMax = NdotFuel * FuelSupply(MicroCHP(GeneratorNum)%FuelSupplyID)%KmolPerSecToKgPerSec
IF (Teng > thisAmbientTemp ) Then
MdotFuelWarmup = MdotFuelMax + MicroCHP(GeneratorNum)%A42Model%kf * MdotFuelMax * &
( ( MicroCHP(GeneratorNum)%A42Model%TnomEngOp - thisAmbientTemp ) &
/ (Teng - thisAmbientTemp ) )
! check that numerical answer didn't blow up beyond limit, and reset if it did
IF (MdotFuelWarmup > MicroCHP(GeneratorNum)%A42Model%Rfuelwarmup * MdotFuelMax) THEN
MdotFuelWarmup = MicroCHP(GeneratorNum)%A42Model%Rfuelwarmup * MdotFuelMax
ENDIF
If (MicroCHP(GeneratorNum)%A42Model%TnomEngOp > thisAmbientTemp ) Then
Pnetss = Pmax * MicroCHP(GeneratorNum)%A42Model%kp * &
( (Teng - thisAmbientTemp ) &
/ ( MicroCHP(GeneratorNum)%A42Model%TnomEngOp - thisAmbientTemp ) )
ELSEIF (MicroCHP(GeneratorNum)%A42Model%TnomEngOp < thisAmbientTemp) Then
Pnetss = Pmax
ELSE ! equal would divide by zero
Pnetss = Pmax
ENDIF
ELSEIF (Teng < thisAmbientTemp) Then
MdotFuelWarmup = MicroCHP(GeneratorNum)%A42Model%Rfuelwarmup * MdotFuelMax
ELSE ! equal would divide by zero
MdotFuelWarmup = MicroCHP(GeneratorNum)%A42Model%Rfuelwarmup * MdotFuelMax
ENDIF
MdotFuel = MdotFuelWarmup
NdotFuel = MdotFuel / FuelSupply(MicroCHP(GeneratorNum)%FuelSupplyID)%KmolPerSecToKgPerSec
MdotAir = CurveValue(MicroCHP(GeneratorNum)%A42Model%AirFlowCurveID, MdotFuelWarmup)
MdotAir = MAX(0.0D0, MdotAir) !protect against bad curve result
Qgross = NdotFuel * (FuelSupply(MicroCHP(GeneratorNum)%FuelSupplyID)%LHV * 1000.0d0 *1000.0d0)
ThermEff = CurveValue(MicroCHP(GeneratorNum)%A42Model%ThermalEffCurveID, Pmax, Mdotcw, TcwIN)
ThermEff = MAX(0.0D0, ThermEff) !protect against bad curve result
Qgenss = ThermEff * Qgross !W
ENDIF
Teng = FuncDetermineEngineTemp(Tcwout, MicroCHP(GeneratorNum)%A42Model%MCeng, MicroCHP(GeneratorNum)%A42Model%UAhx,&
MicroCHP(GeneratorNum)%A42Model%UAskin, thisAmbientTemp, Qgenss, &
MicroCHP(GeneratorNum)%A42Model%TengLast, dt )
Cp = GetSpecificHeatGlycol(PlantLoop(MicroCHP(GeneratorNum)%CWLoopNum)%FluidName, &
TcwIn, &
PlantLoop(MicroCHP(GeneratorNum)%CWLoopNum)%FluidIndex, &
'CalcMicroCHPNoNormalizeGeneratorModel')
Tcwout = FuncDetermineCoolantWaterExitTemp(TcwIn,MicroCHP(GeneratorNum)%A42Model%MCcw,MicroCHP(GeneratorNum)%A42Model%UAhx , &
Mdotcw * Cp , Teng, MicroCHP(GeneratorNum)%A42Model%TempCWOutLast, dt)
! form balance and exit once met.
EnergyBalOK = CheckMicroCHPThermalBalance(MicroCHP(GeneratorNum)%A42Model%MaxElecPower, Tcwin, Tcwout, Teng, &
thisAmbientTemp, MicroCHP(GeneratorNum)%A42Model%UAhx, &
MicroCHP(GeneratorNum)%A42Model%UAskin, Qgenss, MicroCHP(GeneratorNum)%A42Model%MCeng, &
MicroCHP(GeneratorNum)%A42Model%MCcw , Mdotcw * Cp )
If (EnergyBalOK .AND. (I > 4)) Exit
ENDDO
MicroCHP(GeneratorNum)%PlantMassFlowRate = Mdotcw
MicroCHP(GeneratorNum)%A42Model%Pnet = Pnetss - Pcooler - Pstandby
MicroCHP(GeneratorNum)%A42Model%ElecEff = ElecEff
MicroCHP(GeneratorNum)%A42Model%Qgross = Qgross
MicroCHP(GeneratorNum)%A42Model%ThermEff = ThermEff
MicroCHP(GeneratorNum)%A42Model%Qgenss = Qgenss
MicroCHP(GeneratorNum)%A42Model%NdotFuel = NdotFuel
MicroCHP(GeneratorNum)%A42Model%MdotFuel = MdotFuel
MicroCHP(GeneratorNum)%A42Model%Teng = Teng
MicroCHP(GeneratorNum)%A42Model%Tcwout = Tcwout
MicroCHP(GeneratorNum)%A42Model%Tcwin = Tcwin
MicroCHP(GeneratorNum)%A42Model%MdotAir = MdotAir
MicroCHP(GeneratorNum)%A42Model%QdotSkin = MicroCHP(GeneratorNum)%A42Model%UAskin*(Teng - thisAmbientTemp)
MicroCHP(GeneratorNum)%A42Model%OpMode = CurrentOpMode
RETURN
END SUBROUTINE CalcMicroCHPNoNormalizeGeneratorModel