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) | :: | GeneratorType | |||
character(len=*), | intent(in) | :: | GeneratorName | |||
integer, | intent(in) | :: | GeneratorNum | |||
logical, | intent(in) | :: | RunFlagElectCenter | |||
logical, | intent(in) | :: | RunFlagPlant | |||
real(kind=r64), | intent(in) | :: | ElecLoadRequest | |||
real(kind=r64), | intent(in) | :: | ThermalLoadRequest | |||
real(kind=r64), | intent(out) | :: | ElecLoadProvided | |||
integer, | intent(out) | :: | OperatingMode | |||
real(kind=r64), | intent(out) | :: | PLRforSubtimestepStartUp | |||
real(kind=r64), | intent(out) | :: | PLRforSubtimestepShutDown | |||
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 ManageGeneratorControlState(GeneratorType, GeneratorName, GeneratorNum,RunFlagElectCenter, &
RunFlagPlant,ElecLoadRequest, ThermalLoadRequest, &
ElecLoadProvided, OperatingMode, PLRforSubtimestepStartUp, PLRforSubtimestepShutDown , &
FirstHVACIteration)
! SUBROUTINE INFORMATION:
! AUTHOR B Griffith
! DATE WRITTEN February-March 2007 (replaced July 2006 attempt)
! MODIFIED Dec 2009, check and constrain with flow available from plant
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! provide a service to other generators to make decisions, mostly temporal, or cross-timestep issues
! used to model internal controlling issues within an individual generator model
! This subroutine determines the current operating mode and returns the allowed power and
! and part load ratio for certain sub-time step switching e.g. in and out of normal mode or cool down mode
! METHODOLOGY EMPLOYED:
! model controls-related issues, rules based algorithm
! Control decision results include:
! -- electrical load allowed/resulting/provided
! -- new operating mode
! -- part load this timestep for shift to normal mode occuring midway in timestep
! -- part load this timestep for shift out of cool down mode
! Input data used to make control decisions include:
! -- Electrical load request
! -- Thermal Load request
! -- RunFlagElectricCenter
! -- RunFlagPlant
! -- previous timestep operating mode
! -- previous timestep Power generated
! -- availability schedule (off if not available)
! -- Generator control parameter constants including
! ** Start Up Time Delay (in hours)
! ** Cool-down time delay (in hours)
! -- Expected Plant flow rate
! -- minimum cooling water flow rate
! Algorithm summary
! 1. examine calling run flags and refine electric load request to account for
! thermal load requests (not yet ready for prime time)
! 2. Determine states of various control inputs that change during simulation
!
! 3. enter case statement based on previous operating mode.
! -- decide on current operating mode
! -- calculate part loads
! 4. based on current operating mode determine allowed/provided electrical load
! a. set allowed elec load by mode
! b. set allowed elec load by constraints on rate of change
! c. set allowed elec load by min and max
! 5. Calculated part load ratios for special cases.
!
!
! REFERENCES:
! controls specifications in Annex 42 model specs.
!
! USE STATEMENTS:
USE DataGlobalConstants
USE DataHVACGlobals, ONLY: SysTimeElapsed, TimeStepSys
USE ScheduleManager, ONLY: GetScheduleIndex, GetCurrentScheduleValue
USE DataLoopNode , ONLY: Node
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: GeneratorType ! type of Generator
CHARACTER(len=*), INTENT(IN) :: GeneratorName ! user specified name of Generator
INTEGER, INTENT(IN) :: GeneratorNum ! Generator number
LOGICAL, INTENT(IN) :: RunFlagElectCenter ! TRUE when Generator operating per electric load center request
LOGICAL, INTENT(IN) :: RunFlagPlant ! TRUE when generator operating per Plant request (always false)
REAL(r64) , INTENT(IN) :: ElecLoadRequest ! Generator Electrical power demand
REAL(r64) , INTENT(IN) :: ThermalLoadRequest ! cogenerator Thermal power demand
REAL(r64), INTENT(OUT) :: ElecLoadProvided ! power allowed
INTEGER, INTENT(OUT) :: OperatingMode ! operating mode
REAL(r64) , INTENT(OUT) :: PLRforSubtimestepStartUp ! part load ratio for switch to normal from start up
! this is the part in normal mode
REAL(r64) , INTENT(OUT) :: PLRforSubtimestepShutDown ! part load ratio for switch from cool down to other
! this is the part in cool down mode.
LOGICAL, INTENT(IN) :: FirstHVACIteration ! True is this is first HVAC iteration
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
LOGICAL :: RunFlag ! true if generator supposed to run
INTEGER :: DynaCntrlNum !index in GeneratorDynamics structure for this generator ! na
REAL(r64) :: CurrentFractionalDay !working var, time in decimal days
REAL(r64) :: EndingFractionalDay !working var, time is decimal days
REAL(r64) :: LastSystemTimeStepFractionalDay ! working var, time is decimal days
REAL(r64) :: MaxPel !working variable for max allowed by transient constraint
REAL(r64) :: MinPel !working variabel for min allowed by transient constraint
REAL(r64) :: PelInput !holds initial value of IN var
REAL(r64) :: Pel !
INTEGER :: newOpMode
REAL(r64) :: schedVal
! REAL(r64) :: PelDiff
REAL(r64) :: ElectLoadForThermalRequest
LOGICAL :: ConstrainedMaxP ! true if request was altered because of max power limit
LOGICAL :: ConstrainedMinP ! true if request was altered because of min power limit
LOGICAL :: ConstrainedIncreasingPdot ! true if request was altered because of power rate of change up
LOGICAL :: ConstrainedDecreasingPdot ! true if request was altered because of power rate of change down
LOGICAL :: ConstrainedByPlant ! true if request was altered because of cooling water problem
LOGICAL :: PLRStartUp ! true if subtimestep issue involving startup
LOGICAL :: PLRShutDown
! INTEGER :: OutletCWnode = 0 ! cooling water outlet node ID
INTEGER :: InletCWnode = 0 ! cooling water inlet node ID
LOGICAL :: InternalFlowControl = .FALSE.
REAL(r64) :: TcwIn = 0.0D0 ! inlet cooling water temperature (C)
REAL(r64) :: TrialMdotcw = 0.0D0 ! test or estimate of what the plant flows are going to be (kg/s)
REAL(r64) :: LimitMinMdotcw = 0.0D0 ! lower limit for cooling water flow for generatior operation (kg/s)
! inits
PLRforSubtimestepStartUp = 1.0d0
PLRforSubtimestepShutDown = 0.0d0
ConstrainedMaxP = .false.
ConstrainedMinP = .false.
ConstrainedIncreasingPdot = .false.
ConstrainedDecreasingPdot = .false.
ConstrainedByPlant = .false.
PLRStartUp = .false.
PLRShutDown = .false.
InternalFlowControl = .FALSE.
! get index for this generator in dynamics control structure
SELECT CASE (GeneratorType)
CASE (iGeneratorMicroCHP)
DynaCntrlNum = MicroCHP(GeneratorNum)%DynamicsControlID
! OutletCWnode = MicroCHP(GeneratorNum)%PlantOutletNodeID
InletCWnode = MicroCHP(GeneratorNum)%PlantInletNodeID
TcwIn = Node(MicroCHP(GeneratorNum)%PlantInletNodeID)%Temp
IF (MicroCHP(GeneratorNum)%A42Model%InternalFlowControl) THEN
InternalFlowControl = .TRUE.
ENDIF
LimitMinMdotcw = MicroCHP(GeneratorNum)%A42Model%MinWaterMdot
CASE (iGeneratorFuelCell)
! not yet
CASE DEFAULT
END SELECT
PelInput = ElecLoadRequest
ElectLoadForThermalRequest = 0.0d0
IF ((ThermalLoadRequest > 0.0d0) .AND. RunFlagPlant) THEN ! deal with possible thermal load following
!Modify electric load request based on thermal load following signal using nominal efficiencies
ElectLoadForThermalRequest = GeneratorDynamics(DynaCntrlNum)%ThermEffNom &
* ThermalLoadRequest / GeneratorDynamics(DynaCntrlNum)%ElectEffNom
PelInput = Max(PelInput, ElectLoadForThermalRequest)
ENDIF
IF ((RunFlagElectCenter) .OR. (RunFlagPlant)) then
RunFlag = .true.
ELSE
RunFlag = .false.
ENDIF
! check availability schedule
schedval = GetCurrentScheduleValue(GeneratorDynamics(DynaCntrlNum)%AvailabilitySchedID)
Pel = PelInput
! get data to check if sufficient flow available from Plant
IF (InternalFlowControl .AND. (schedval > 0.d0) ) THEN
TrialMdotcw = FuncDetermineCWMdotForInternalFlowControl(GeneratorNum, Pel, TcwIn)
ELSE
TrialMdotcw = Node(InletCWnode)%MassFlowRate
ENDIF
!determine current operating mode.
SELECT CASE (GeneratorDynamics(DynaCntrlNum)%LastOpMode)
CASE(OpModeOFF, OpModeStandby)
! possible future states {Off, Standby, WarmUp,Normal }
IF (schedval == 0.0d0) THEN
newOpMode = OpModeOFF
ELSEIF (((schedval /= 0.0d0) .AND. ( .NOT. RunFlag)) .OR. (TrialMdotcw < LimitMinMdotcw)) THEN
newOpMode = OpModeStandby
ELSEIF ((schedval /= 0.0d0) .AND. (Runflag) ) THEN
IF (GeneratorDynamics(DynaCntrlNum)%WarmUpByTimeDelay) THEN
If (GeneratorDynamics(DynaCntrlNum)%StartUpTimeDelay == 0.0d0) Then
newOpMode = OpModeNormal
! is startUp time delay longer than timestep?
ELSEIf (GeneratorDynamics(DynaCntrlNum)%StartUpTimeDelay >= TimeStepSys) THEN !
newOpMode = OpModeWarmUp
! generator just started so set start time
GeneratorDynamics(DynaCntrlNum)%FractionalDayofLastStartUp = REAL(DayOfSim,r64) &
+ (INT(CurrentTime)+(SysTimeElapsed+(CurrentTime - INT(CurrentTime) - TimeStepSys )))/HoursInDay
ELSE ! warm up period is less than a single system time step
newOpMode = OpModeNormal
PLRStartUp = .true.
PLRforSubtimestepStartUp = (TimeStepSys - GeneratorDynamics(DynaCntrlNum)%StartUpTimeDelay) / TimeStepSys
ENDIF
ENDIF
IF (GeneratorDynamics(DynaCntrlNum)%WarmUpByEngineTemp) THEN
IF (MicroCHP(GeneratorNum)%A42Model%Teng >= GeneratorDynamics(DynaCntrlNum)%TnomEngOp ) THEN
newOpMode = OpModeNormal
! assume linear interpolation for PLR
PLRStartUp = .true.
IF ( (MicroCHP(GeneratorNum)%A42Model%Teng - MicroCHP(GeneratorNum)%A42Model%TengLast) > 0.0d0 ) THEN
! protect divide by zero or neg
PLRforSubtimestepStartUp = (MicroCHP(GeneratorNum)%A42Model%Teng - GeneratorDynamics(DynaCntrlNum)%TnomEngOp ) &
/ (MicroCHP(GeneratorNum)%A42Model%Teng - MicroCHP(GeneratorNum)%A42Model%TengLast)
ELSE
PLRforSubtimestepStartUp = 1.0d0
ENDIF
ELSE
newOpMode = OpModeWarmUp
ENDIF
ENDIF
ENDIF
CASE(OpModeWarmUp)
! possible Future states {OFF, WarmUp, Normal, CoolDown }
! check availability manager
IF (schedval == 0.0d0) THEN
! to off unless cool down time period is needed
IF (GeneratorDynamics(DynaCntrlNum)%CoolDownDelay == 0.0d0) THEN
newOpMode = OpModeOFF
ELSE
IF (GeneratorDynamics(DynaCntrlNum)%CoolDownDelay > TimeStepSys) THEN
newOpMode = OpModeCoolDown
! need to reset time of last shut down here
GeneratorDynamics(DynaCntrlNum)%FractionalDayofLastShutDown = REAL(DayOfSim,r64) &
+ (INT(CurrentTime)+(SysTimeElapsed+(CurrentTime - INT(CurrentTime))))/HoursInDay
ELSE
newOpMode = OpModeOFF
ENDIF
ENDIF
ELSEIF (((schedval /= 0.0d0) .AND. ( .NOT. RunFlag)) .OR. (TrialMdotcw < LimitMinMdotcw)) THEN
! to standby unless cool down time period is needed
IF (GeneratorDynamics(DynaCntrlNum)%CoolDownDelay == 0.0d0) THEN
newOpMode = OpModeStandby
ELSE
IF (GeneratorDynamics(DynaCntrlNum)%CoolDownDelay > TimeStepSys) THEN
newOpMode = OpModeCoolDown
! need to reset time of last shut down here
GeneratorDynamics(DynaCntrlNum)%FractionalDayofLastShutDown = REAL(DayOfSim,r64) &
+ (INT(CurrentTime)+(SysTimeElapsed+(CurrentTime - INT(CurrentTime))))/HoursInDay
ELSE
newOpMode = OpModeStandby
! assuming no PLR situation unless engine made to normal operation.
ENDIF
ENDIF
ELSEIF ((schedval /= 0.0d0) .AND. (RunFlag)) THEN
! either warm up or normal
! check if warm up completed, depends on type of warm up control time delay or reach nominal temperature
IF (GeneratorDynamics(DynaCntrlNum)%WarmUpByTimeDelay) THEN
! compare current time to when warm up is over
!calculate time for end of warmup period
CurrentFractionalDay = REAL(DayOfSim,r64) &
+ (INT(CurrentTime)+(SysTimeElapsed+(CurrentTime - INT(CurrentTime))))/HoursInDay
EndingFractionalDay = GeneratorDynamics(DynaCntrlNum)%FractionalDayofLastStartUp &
+ GeneratorDynamics(DynaCntrlNum)%StartUpTimeDelay/HoursInDay
IF (( ABS(CurrentFractionalDay - EndingFractionalDay) < 0.000001d0) &
.or. (CurrentFractionalDay > EndingFractionalDay)) THEN
newOpMode = OpModeNormal
PLRStartUp = .true.
LastSystemTimeStepFractionalDay = CurrentFractionalDay - ( TimeStepSys/HoursInDay )
PLRforSubtimestepStartUp = ( (CurrentFractionalDay - EndingFractionalDay ) &
/ (CurrentFractionalDay - LastSystemTimeStepFractionalDay) )
ELSE
newOpMode = OpModeWarmUp
ENDIF
ELSEIF (GeneratorDynamics(DynaCntrlNum)%WarmUpByEngineTemp) THEN
IF (GeneratorType == iGeneratorMicroCHP) THEN
!only change to normal if this is result from completed timestep, not just an interation
IF (MicroCHP(GeneratorNum)%A42Model%TengLast >= GeneratorDynamics(DynaCntrlNum)%TnomEngOp ) THEN
newOpMode = OpModeNormal
! assume linear interpolation for PLR
PLRStartUp = .true.
IF ( (MicroCHP(GeneratorNum)%A42Model%Teng - MicroCHP(GeneratorNum)%A42Model%TengLast) > 0.0d0 ) THEN
! protect divide by zero or neg
PLRforSubtimestepStartUp = (MicroCHP(GeneratorNum)%A42Model%Teng - GeneratorDynamics(DynaCntrlNum)%TnomEngOp ) &
/ (MicroCHP(GeneratorNum)%A42Model%Teng - MicroCHP(GeneratorNum)%A42Model%TengLast)
ELSE
PLRforSubtimestepStartUp = 1.0d0
ENDIF
ELSE
newOpMode = OpModeWarmUp
ENDIF
ENDIF
ELSE
! shouldn't come here
! Write(*,*) 'problem with warm up type of control logical flags'
ENDif
ENDIF
CASE(OpModeNormal)
!possible Future states {CoolDown, standby, off}
IF (((schedval == 0.0d0) .OR. ( .NOT. RunFlag)).OR. (TrialMdotcw < LimitMinMdotcw)) THEN
! is cool down time delay longer than timestep?
IF (GeneratorDynamics(DynaCntrlNum)%CoolDownDelay == 0.0d0) THEN
If (schedval /= 0.0d0) then
newOpMode = OpModeStandBy
else
newOpMode = OpModeOff
endif
ElseIf (GeneratorDynamics(DynaCntrlNum)%CoolDownDelay >= TimeStepSys) THEN !
newOpMode = OpModeCoolDown
! also, generator just shut down so record shut down time
GeneratorDynamics(DynaCntrlNum)%FractionalDayofLastShutDown = REAL(DayOfSim,r64) &
+ (INT(CurrentTime)+(SysTimeElapsed+(CurrentTime - INT(CurrentTime))))/HoursInDay
ELSE ! cool down period is less than a single system time step
If (schedval /= 0.0d0) then
newOpMode = OpModeStandBy
else
newOpMode = OpModeOff
endif
PLRShutDown = .true.
PLRforSubtimestepShutdown = (GeneratorDynamics(DynaCntrlNum)%CoolDownDelay) / TimeStepSys
! also, generator just shut down so record shut down time
GeneratorDynamics(DynaCntrlNum)%FractionalDayofLastShutDown = REAL(DayOfSim,r64) &
+ (INT(CurrentTime)+(SysTimeElapsed+(CurrentTime - INT(CurrentTime))))/HoursInDay
ENDIF
ELSEIF ((schedval /= 0.0d0) .AND. ( RunFlag)) THEN
newOpMode = OpModeNormal
ENDIF
CASE(opModeCoolDown)
!possible Future States {Standby, OFF, WarmUp, Normal}
IF (schedval == 0.0d0) THEN ! no longer available.
! probably goes to off but could be stuck in cool down for awhile
If (GeneratorDynamics(DynaCntrlNum)%CoolDownDelay > 0.0d0) Then
! calculate time for end of cool down period
CurrentFractionalDay = REAL(DayOfSim,r64) &
+ (INT(CurrentTime)+(SysTimeElapsed+(CurrentTime - INT(CurrentTime))))/HoursInDay
EndingFractionalDay = GeneratorDynamics(DynaCntrlNum)%FractionalDayofLastShutDown &
+ GeneratorDynamics(DynaCntrlNum)%CoolDownDelay/HoursInDay - ( TimeStepSys/HoursInDay )
IF (( ABS(CurrentFractionalDay - EndingFractionalDay) < 0.000001d0) & ! CurrentFractionalDay == EndingFractionalDay
.or. (CurrentFractionalDay > EndingFractionalDay)) THEN
newOpMode = opModeOFF
PLRShutDown = .true.
LastSystemTimeStepFractionalDay = CurrentFractionalDay - ( TimeStepSys/HoursInDay )
PLRforSubtimestepShutDown = (EndingFractionalDay - LastSystemTimeStepFractionalDay)*HoursInDay &
/ TimeStepSys
ELSE ! CurrentFractionalDay > EndingFractionalDay
newOpMode = opModeCoolDown
ENDIF
ELSE !
newOpMode = opModeOFF
ENDIF
ELSEIF (((schedval /= 0.0d0) .AND. ( .NOT. RunFlag) ) .OR. (TrialMdotcw < LimitMinMdotcw))Then
! probably goes to standby but could be stuck in cool down for awhile
If (GeneratorDynamics(DynaCntrlNum)%CoolDownDelay > 0.0d0) Then
! calculate time for end of cool down period
CurrentFractionalDay = REAL(DayOfSim,r64) &
+ (INT(CurrentTime)+(SysTimeElapsed+(CurrentTime - INT(CurrentTime))))/HoursInDay
EndingFractionalDay = GeneratorDynamics(DynaCntrlNum)%FractionalDayofLastShutDown &
+ GeneratorDynamics(DynaCntrlNum)%CoolDownDelay/HoursInDay - ( TimeStepSys /HoursInDay )
IF (( ABS(CurrentFractionalDay - EndingFractionalDay) < 0.000001d0) & ! CurrentFractionalDay == EndingFractionalDay
.or. (CurrentFractionalDay > EndingFractionalDay)) THEN
newOpMode = OpModeStandby
PLRShutDown = .true.
LastSystemTimeStepFractionalDay = CurrentFractionalDay - ( TimeStepSys/HoursInDay )
PLRforSubtimestepShutDown = (EndingFractionalDay - LastSystemTimeStepFractionalDay)*HoursInDay &
/ TimeStepSys
ELSE ! CurrentFractionalDay < EndingFractionalDay
newOpMode = opModeCoolDown
ENDIF
ELSE !
newOpMode = OpModeStandby
ENDIF
ELSEIF ((schedval /= 0.0d0) .AND. ( RunFlag) ) THEN
! was in cool down mode but is now being asked to restart
! probably goes to warm up but could be stuck in cool down or jump to normal
IF (GeneratorDynamics(DynaCntrlNum)%MandatoryFullCoolDown) then
! is cool down done or not?
If (GeneratorDynamics(DynaCntrlNum)%CoolDownDelay > 0.0d0) Then
! calculate time for end of cool down period
CurrentFractionalDay = REAL(DayOfSim,r64) &
+ (INT(CurrentTime)+(SysTimeElapsed+(CurrentTime - INT(CurrentTime))))/HoursInDay
EndingFractionalDay = GeneratorDynamics(DynaCntrlNum)%FractionalDayofLastShutDown &
+ GeneratorDynamics(DynaCntrlNum)%CoolDownDelay/HoursInDay - ( TimeStepSys/HoursInDay )
IF (( ABS(CurrentFractionalDay - EndingFractionalDay) < 0.000001d0) & ! CurrentFractionalDay == EndingFractionalDay
.or. (CurrentFractionalDay < EndingFractionalDay)) THEN
newOpMode = opModeCoolDown
ELSE ! CurrentFractionalDay > EndingFractionalDay
! could go to warm up or normal now
PLRShutDown = .true.
LastSystemTimeStepFractionalDay = CurrentFractionalDay - ( TimeStepSys/HoursInDay )
PLRforSubtimestepShutDown = (EndingFractionalDay - LastSystemTimeStepFractionalDay)*HoursInDay &
/ TimeStepSys
If (GeneratorDynamics(DynaCntrlNum)%StartUpTimeDelay == 0.0d0) then
newOpMode = opModeNormal
! possible PLR on start up.
PLRStartUp = .true.
PLRforSubtimestepStartUp = ( (CurrentFractionalDay - EndingFractionalDay ) &
/ (CurrentFractionalDay - LastSystemTimeStepFractionalDay) )
ELSEIF (GeneratorDynamics(DynaCntrlNum)%StartUpTimeDelay > 0.0d0) then
! is remaining time enough?
IF (( CurrentFractionalDay - EndingFractionalDay) > GeneratorDynamics(DynaCntrlNum)%StartUpTimeDelay ) THEN
newOpMode = opModeNormal
! possible PLR on start up.
PLRStartUp = .true.
PLRforSubtimestepStartUp = ( (CurrentFractionalDay - EndingFractionalDay ) &
/ (CurrentFractionalDay - LastSystemTimeStepFractionalDay) )
ELSE
newOpMode = OpModeWarmUp
! generator just started so set start time
GeneratorDynamics(DynaCntrlNum)%FractionalDayofLastStartUp = REAL(DayOfSim,r64) &
+ (INT(CurrentTime)+(SysTimeElapsed+(CurrentTime - INT(CurrentTime) - TimeStepSys )))/HoursInDay
ENDIF
ENDIF
ENDIF
ELSE !
newOpMode = OpModeStandby
ENDIF
ELSE !not mandetory cool donw
! likely to go into warm up but if no warm up then back to normal
IF (GeneratorDynamics(DynaCntrlNum)%WarmUpByTimeDelay) THEN
If (GeneratorDynamics(DynaCntrlNum)%StartUpTimeDelay == 0.0d0) then
newOpMode = opModeNormal
ELSEIF (GeneratorDynamics(DynaCntrlNum)%StartUpTimeDelay > 0.0d0) then
CurrentFractionalDay = REAL(DayOfSim,r64) &
+ (INT(CurrentTime)+(SysTimeElapsed+(CurrentTime - INT(CurrentTime))))/HoursInDay
EndingFractionalDay = GeneratorDynamics(DynaCntrlNum)%FractionalDayofLastShutDown &
+ GeneratorDynamics(DynaCntrlNum)%CoolDownDelay/HoursInDay
IF (( ABS(CurrentFractionalDay - EndingFractionalDay) < 0.000001d0) & ! CurrentFractionalDay == EndingFractionalDay
.or. (CurrentFractionalDay > EndingFractionalDay)) THEN
newOpMode = opModeNormal
! possible PLR on start up.
PLRStartUp = .true.
LastSystemTimeStepFractionalDay = CurrentFractionalDay - ( TimeStepSys/HoursInDay )
PLRforSubtimestepStartUp = ( (CurrentFractionalDay - EndingFractionalDay ) &
/ (CurrentFractionalDay - LastSystemTimeStepFractionalDay) )
ELSE
newOpMode = OpModeWarmUp
! set start up time
! generator just started so set start time
GeneratorDynamics(DynaCntrlNum)%FractionalDayofLastStartUp = REAL(DayOfSim,r64) &
+ (INT(CurrentTime)+(SysTimeElapsed+(CurrentTime - INT(CurrentTime) - TimeStepSys )))/HoursInDay
ENDIF
ENDIF
ENDIF
ENDIF
ENDIF
END SELECT !previous case
If (PLRforSubtimestepStartUp < 0.0d0) PLRforSubtimestepStartUp = 0.0d0
If (PLRforSubtimestepStartUp > 1.0d0) PLRforSubtimestepStartUp = 1.0d0
If (PLRforSubtimestepShutDown < 0.0d0) PLRforSubtimestepShutDown = 0.0d0
If (PLRforSubtimestepShutDown > 1.0d0) PLRforSubtimestepShutDown = 1.0d0
IF (newOpmode == OpModeWarmUp) THEN
SELECT CASE (GeneratorType)
CASE( iGeneratorFuelCell )
!constant power level during start up (modeling artifact)
!? hours or seconds here?
Pel = GeneratorDynamics(DynaCntrlNum)%StartUpElectProd/GeneratorDynamics(DynaCntrlNum)%StartUpTimeDelay
CASE ( iGeneratorMicroCHP)
Pel = PelInput * PLRforSubtimestepStartUp
END SELECT
ENDIF
If (newOpmode == OpModeNormal) then
! correct if switched to normal at sub timestep
Pel = Pel * PLRforSubtimestepStartUp
!unit may have constraints from transient limits or operating ranges.
IF (Pel > GeneratorDynamics(DynaCntrlNum)%PelLastTimeStep) THEN ! powering up
MaxPel = GeneratorDynamics(DynaCntrlNum)%PelLastTimeStep &
+ GeneratorDynamics(DynaCntrlNum)%UpTranLimit * TimeStepSys * SecInHour
IF (MaxPel < Pel) THEN
Pel = MaxPel
ENDIF
ELSEIF (Pel< GeneratorDynamics(DynaCntrlNum)%PelLastTimeStep) THEN !powering down
MinPel = GeneratorDynamics(DynaCntrlNum)%PelLastTimeStep &
- GeneratorDynamics(DynaCntrlNum)%DownTranLimit * TimeStepSys * SecInHour
IF (Pel < MinPel) THEN
Pel = MinPel
ENDIF
ENDIF
ENDIF !
IF (newOpmode == opModeCoolDown) THEN
Pel = 0.0d0 ! assumes no power generated during shut down
ENDIF
IF (newOpmode == OpModeOFF) THEN
Pel = 0.0d0 ! assumes no power generated during OFF mode
ENDIF
IF (newOpmode == OpModeStandby) THEN
Pel = 0.0d0 ! assumes no power generated during standby mode
ENDIF
! Control step 3: adjust for max and min limits on Pel
IF ( Pel < GeneratorDynamics(DynaCntrlNum)%PelMin) THEN
Pel = GeneratorDynamics(DynaCntrlNum)%PelMin
ENDIF
IF ( Pel > GeneratorDynamics(DynaCntrlNum)%PelMax) THEN
Pel = GeneratorDynamics(DynaCntrlNum)%PelMax
ENDIF
!now do record keeping for amount of time spent in various operating modes
SELECT CASE (GeneratorType)
CASE (iGeneratorMicroCHP)
! first clear out values
MicroCHP(GeneratorNum)%A42model%OffModeTime = 0.0d0
MicroCHP(GeneratorNum)%A42model%StandyByModeTime = 0.0d0
MicroCHP(GeneratorNum)%A42model%WarmUpModeTime = 0.0d0
MicroCHP(GeneratorNum)%A42model%NormalModeTime = 0.0d0
MicroCHP(GeneratorNum)%A42model%CoolDownModeTime = 0.0d0
SELECT CASE (newOpMode)
CASE (OpModeOFF)
IF (PLRforSubtimestepShutDown == 0.0d0) THEN
MicroCHP(GeneratorNum)%A42model%OffModeTime = TimeStepSys * SecInHour
ELSEIF ( (PLRforSubtimestepShutDown > 0.0d0) .AND. (PLRforSubtimestepShutDown < 1.0d0)) THEN
MicroCHP(GeneratorNum)%A42model%CoolDownModeTime = TimeStepSys * SecInHour * (PLRforSubtimestepShutDown )
MicroCHP(GeneratorNum)%A42model%OffModeTime = TimeStepSys * SecInHour * (1.0d0 - PLRforSubtimestepShutDown )
ELSE
MicroCHP(GeneratorNum)%A42model%OffModeTime = TimeStepSys * SecInHour
ENDIF
CASE (OpModeStandby)
IF (PLRforSubtimestepShutDown == 0.0d0) THEN
MicroCHP(GeneratorNum)%A42model%StandyByModeTime = TimeStepSys * SecInHour
ELSEIF ( (PLRforSubtimestepShutDown > 0.0d0) .AND. (PLRforSubtimestepShutDown < 1.0d0)) THEN
MicroCHP(GeneratorNum)%A42model%CoolDownModeTime = TimeStepSys * SecInHour * (PLRforSubtimestepShutDown )
MicroCHP(GeneratorNum)%A42model%StandyByModeTime = TimeStepSys * SecInHour * (1.0d0 - PLRforSubtimestepShutDown )
ELSE
MicroCHP(GeneratorNum)%A42model%StandyByModeTime = TimeStepSys * SecInHour
ENDIF
CASE (OpModeWarmUp)
IF (PLRforSubtimestepShutDown == 0.0d0) THEN
MicroCHP(GeneratorNum)%A42model%WarmUpModeTime = TimeStepSys * SecInHour
ELSEIF ( (PLRforSubtimestepShutDown > 0.0d0) .AND. (PLRforSubtimestepShutDown < 1.0d0)) THEN
MicroCHP(GeneratorNum)%A42model%CoolDownModeTime = TimeStepSys * SecInHour * (PLRforSubtimestepShutDown )
MicroCHP(GeneratorNum)%A42model%WarmUpModeTime = TimeStepSys * SecInHour * (1.0d0 - PLRforSubtimestepShutDown )
ELSE
MicroCHP(GeneratorNum)%A42model%WarmUpModeTime = TimeStepSys * SecInHour
ENDIF
CASE (OpModeNormal)
IF (PLRforSubtimestepStartUp == 0.0d0) THEN
MicroCHP(GeneratorNum)%A42model%WarmUpModeTime = TimeStepSys * SecInHour
ELSEIF ( (PLRforSubtimestepStartUp > 0.0d0) .AND. (PLRforSubtimestepStartUp < 1.0d0)) THEN
MicroCHP(GeneratorNum)%A42model%WarmUpModeTime = TimeStepSys * SecInHour * ( 1.0d0 -PLRforSubtimestepStartUp )
MicroCHP(GeneratorNum)%A42model%NormalModeTime = TimeStepSys * SecInHour * ( PLRforSubtimestepStartUp )
ELSE
IF (PLRforSubtimestepShutDown == 0.0d0) THEN
MicroCHP(GeneratorNum)%A42model%NormalModeTime = TimeStepSys * SecInHour
ELSEIF ( (PLRforSubtimestepShutDown > 0.0d0) .AND. (PLRforSubtimestepShutDown < 1.0d0)) THEN
MicroCHP(GeneratorNum)%A42model%CoolDownModeTime = TimeStepSys * SecInHour * (PLRforSubtimestepShutDown )
MicroCHP(GeneratorNum)%A42model%NormalModeTime = TimeStepSys * SecInHour * (1.0d0 - PLRforSubtimestepShutDown )
ELSE
MicroCHP(GeneratorNum)%A42model%NormalModeTime = TimeStepSys * SecInHour
ENDIF
ENDIF
CASE (opModeCoolDown)
MicroCHP(GeneratorNum)%A42model%CoolDownModeTime = TimeStepSys * SecInHour
END SELECT
CASE (iGeneratorFuelCell)
! not yet using this control manager
CASE DEFAULT
END SELECT
ElecLoadProvided = Pel
GeneratorDynamics(DynaCntrlNum)%CurrentOpMode = newOpMode
OperatingMode = newOpMode
RETURN
END SUBROUTINE ManageGeneratorControlState