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 | |||
real(kind=r64), | intent(inout) | :: | Pel | |||
logical, | intent(out) | :: | Constrained | |||
real(kind=r64), | intent(out) | :: | PelDiff |
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 FigureTransientConstraints(GeneratorNum, Pel, Constrained, PelDiff)
! SUBROUTINE INFORMATION:
! AUTHOR Brent Griffith
! DATE WRITTEN Aug 2005
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! <description>
! METHODOLOGY EMPLOYED:
! <description>
! REFERENCES:
! na
! USE STATEMENTS:
! na
USE DataHVACGlobals, ONLY: SysTimeElapsed, TimeStepSys
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: GeneratorNum !index number for accessing correct generator
REAL(r64), INTENT(INOUT) :: Pel ! DC power control setting for power module
LOGICAL, INTENT(OUT) :: Constrained ! true if transient constraints kick in
REAL(r64), INTENT(OUT) :: PelDiff ! if constrained then this is the difference, positive
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
!unused REAL(r64) :: CurrentHours
REAL(r64) :: CurrentFractionalDay !working var, time in decimal days
REAL(r64) :: EndingFractionalDay !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 !hold initial value of inout var
PelInput = Pel
! Check if in start up and if it still should be
IF (FuelCell(GeneratorNum)%FCPM%DuringStartUp) THEN
!calculate time for end of start up period
CurrentFractionalDay = REAL(DayOfSim,r64) &
+ (INT(CurrentTime)+(SysTimeElapsed+(CurrentTime - INT(CurrentTime))))/HoursInDay
EndingFractionalDay = FuelCell(GeneratorNum)%FCPM%FractionalDayofLastStartUp + &
FuelCell(GeneratorNum)%FCPM%StartUpTime/HoursInDay
IF (CurrentFractionalDay > EndingFractionalDay) THEN
!start up period is now over
FuelCell(GeneratorNum)%FCPM%DuringStartUp = .false.
ENDIF
ENDIF
! Check if in shut down up and if it still should be
IF (FuelCell(GeneratorNum)%FCPM%DuringShutDown) THEN
!calculate time for end of shut down period
CurrentFractionalDay = REAL(DayOfSim,r64) &
+ (INT(CurrentTime)+(SysTimeElapsed+(CurrentTime - INT(CurrentTime))))/HoursInDay !
EndingFractionalDay = FuelCell(GeneratorNum)%FCPM%FractionalDayofLastShutDown + &
FuelCell(GeneratorNum)%FCPM%ShutDownTime/HoursInDay
IF (CurrentFractionalDay > EndingFractionalDay) THEN
!start up period is now over
FuelCell(GeneratorNum)%FCPM%DuringShutDown = .false.
ENDIF
ENDIF
!compare
If (.NOT. (FuelCell(GeneratorNum)%FCPM%DuringShutDown) .AND. .NOT. (FuelCell(GeneratorNum)%FCPM%DuringStartUp)) then
!unit is neither starting or stopping and the only constraints would come from transient limits
IF (Pel > FuelCell(GeneratorNum)%FCPM%PelLastTimeStep) THEN ! powering up
MaxPel = FuelCell(GeneratorNum)%FCPM%PelLastTimeStep + FuelCell(GeneratorNum)%FCPM%UpTranLimit * TimeStepSys * SecInHour
IF (MaxPel < Pel) THEN
Pel = MaxPel
Constrained = .TRUE.
Else
Constrained = .FALSE.
ENDIF
ELSEIF (Pel< FuelCell(GeneratorNum)%FCPM%PelLastTimeStep) THEN !powering down
MinPel = FuelCell(GeneratorNum)%FCPM%PelLastTimeStep - FuelCell(GeneratorNum)%FCPM%DownTranLimit * TimeStepSys * SecInHour
IF (Pel < MinPel) THEN
Pel = MinPel
Constrained = .TRUE.
ELSE
Constrained = .FALSE.
ENDIF
ELSE !the same
!do nothing
Constrained = .FALSE.
ENDIF
ENDIF !not in start up or shut down
IF (FuelCell(GeneratorNum)%FCPM%DuringStartUp) THEN
!constant during start up modeling artifact
Pel = FuelCell(GeneratorNum)%FCPM%StartUpElectProd/FuelCell(GeneratorNum)%FCPM%StartUpTime
Constrained = .true.
ENDIF
IF (FuelCell(GeneratorNum)%FCPM%DuringShutDown) THEN
Pel = 0.0d0 ! assumes no power generated during shut down
Constrained = .true.
ENDIF
PelDiff = 0.0d0
IF (constrained) then
PelDiff = PelInput - Pel
endif
RETURN
END SUBROUTINE FigureTransientConstraints