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) | :: | Num | |||
real(kind=r64), | intent(in) | :: | Pdemand | |||
real(kind=r64), | intent(in) | :: | PpcuLosses | |||
logical, | intent(out) | :: | Constrained | |||
real(kind=r64), | intent(out) | :: | Pstorage | |||
real(kind=r64), | intent(out) | :: | PgridOverage |
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 ManageElectStorInteractions(Num,Pdemand, PpcuLosses, &
Constrained, Pstorage, PgridOverage)
! SUBROUTINE INFORMATION:
! AUTHOR B. Griffith
! DATE WRITTEN Aug 2005
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! manage controls and calculations related to electrical storage in FuelCell model
! METHODOLOGY EMPLOYED:
!
! REFERENCES:
! na
! USE STATEMENTS:
USE DataHVACGlobals, ONLY: TimeStepSys
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: Num ! Generator number, index for structure
REAL(r64) , INTENT(IN) :: Pdemand !
REAL(r64) , INTENT(IN) :: PpcuLosses
Logical, INTENT(OUT) :: Constrained
REAL(r64) , INTENT(OUT) :: Pstorage
REAL(r64) , INTENT(OUT) :: PgridOverage !electricity that can't be stored and needs to go out
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: tmpPdraw ! power draw from storage, working var
REAL(r64) :: tmpPcharge ! power charge to storage, working var
Logical :: drawing ! true if drawing power
Logical :: charging ! true if charging
!initialize locals
tmpPdraw = 0.0d0
tmpPcharge = 0.0d0
drawing = .false.
charging = .false.
Constrained = .false.
Pstorage = 0.0d0
PgridOverage = 0.0d0
! step 1 figure out what is desired of electrical storage system
If (FuelCell(Num)%FCPM%Pel < (Pdemand )) THEN
!draw from storage
tmpPdraw = (Pdemand ) - FuelCell(Num)%FCPM%Pel
drawing = .true.
ENDIF
IF (FuelCell(Num)%FCPM%Pel > (Pdemand )) THEN
!add to storage
tmpPcharge = FuelCell(Num)%FCPM%Pel - (Pdemand )
charging = .true.
ENDIF
! step 2, figure out what is possible for electrical storage draws/charges
If (charging) then
IF (FuelCell(Num)%ElecStorage%StorageModelMode == SimpleEffConstraints) THEN
IF (FuelCell(Num)%ElecStorage%LastTimeStepStateOfCharge >= FuelCell(Num)%ElecStorage%NominalEnergyCapacity) THEN
! storage full! no more allowed!
PgridOverage = tmpPcharge
tmpPcharge = 0.0d0
Constrained = .true.
ENDIF
IF (tmpPcharge > FuelCell(Num)%ElecStorage%MaxPowerStore) THEN
PgridOverage = tmpPcharge - FuelCell(Num)%ElecStorage%MaxPowerStore
tmpPcharge = FuelCell(Num)%ElecStorage%MaxPowerStore
Constrained = .true.
ENDIF
!now add energy to storage from charging
IF ((FuelCell(Num)%ElecStorage%LastTimeStepStateOfCharge &
+ tmpPcharge *TimeStepSys*SecInHour*FuelCell(Num)%ElecStorage%EnergeticEfficCharge) &
< FuelCell(Num)%ElecStorage%NominalEnergyCapacity) THEN
FuelCell(Num)%ElecStorage%ThisTimeStepStateOfCharge = FuelCell(Num)%ElecStorage%LastTimeStepStateOfCharge &
+ tmpPcharge *TimeStepSys*SecInHour*FuelCell(Num)%ElecStorage%EnergeticEfficCharge
ELSE ! would over charge this time step
tmpPcharge = (FuelCell(Num)%ElecStorage%NominalEnergyCapacity - FuelCell(Num)%ElecStorage%LastTimeStepStateOfCharge) &
/(TimeStepSys*SecInHour*FuelCell(Num)%ElecStorage%EnergeticEfficCharge)
Constrained = .true.
FuelCell(Num)%ElecStorage%ThisTimeStepStateOfCharge = FuelCell(Num)%ElecStorage%LastTimeStepStateOfCharge &
+ tmpPcharge *TimeStepSys*SecInHour*FuelCell(Num)%ElecStorage%EnergeticEfficCharge
ENDIF
!losses go into QairIntake
FuelCell(Num)%ElecStorage%QairIntake = tmpPcharge * (1.0d0 - FuelCell(Num)%ElecStorage%EnergeticEfficCharge)
ELSEIF (FuelCell(Num)%ElecStorage%StorageModelMode == LeadAcidBatterManwellMcGowan) THEN
CALL ShowWarningError('ManageElectStorInteractions: Not yet implemented: Lead Acid Battery By Manwell and McGowan 1993 ')
ELSEIF (FuelCell(Num)%ElecStorage%StorageModelMode == LeadAcidBatterySaupe) THEN
CALL ShowWarningError('ManageElectStorInteractions: Not yet implemented: Lead Acid Battery By Saupe 1993 ')
ELSE
!should not come here
ENDIF
Pstorage = tmpPcharge
ENDIF !charging
IF (drawing) THEN
IF (FuelCell(Num)%ElecStorage%StorageModelMode == SimpleEffConstraints) THEN
IF (FuelCell(Num)%ElecStorage%LastTimeStepStateOfCharge <= 0.0d0) THEN
! storage empty no more allowed!
tmpPdraw = 0.0d0
Constrained = .true.
drawing = .false.
ENDIF
IF (tmpPdraw > FuelCell(Num)%ElecStorage%MaxPowerDraw) THEN
tmpPdraw = FuelCell(Num)%ElecStorage%MaxPowerDraw
Constrained = .true.
ENDIF
!now take energy from storage by drawing (amplified by energetic effic)
IF ((FuelCell(Num)%ElecStorage%LastTimeStepStateOfCharge &
- tmpPdraw *TimeStepSys*SecInHour/FuelCell(Num)%ElecStorage%EnergeticEfficDischarge) > 0.0d0 ) Then
FuelCell(Num)%ElecStorage%ThisTimeStepStateOfCharge = FuelCell(Num)%ElecStorage%LastTimeStepStateOfCharge &
- tmpPdraw *TimeStepSys*SecInHour/FuelCell(Num)%ElecStorage%EnergeticEfficDischarge
ELSE !would over drain storage this timestep so reduce tmpPdraw
tmpPdraw = FuelCell(Num)%ElecStorage%LastTimeStepStateOfCharge * FuelCell(Num)%ElecStorage%EnergeticEfficDischarge &
/(TimeStepSys*SecInHour)
FuelCell(Num)%ElecStorage%ThisTimeStepStateOfCharge = FuelCell(Num)%ElecStorage%LastTimeStepStateOfCharge &
- tmpPdraw *TimeStepSys*SecInHour/FuelCell(Num)%ElecStorage%EnergeticEfficDischarge
Constrained = .true.
ENDIF
!losses go into QairIntake
FuelCell(Num)%ElecStorage%QairIntake = tmpPdraw * (1.0d0/FuelCell(Num)%ElecStorage%EnergeticEfficDischarge - 1.0d0)
ELSEIF (FuelCell(Num)%ElecStorage%StorageModelMode == LeadAcidBatterManwellMcGowan) THEN
CALL ShowWarningError('ManageElectStorInteractions: Not yet implemented: Lead Acid Battery By Manwell and McGowan 1993 ')
ELSEIF (FuelCell(Num)%ElecStorage%StorageModelMode == LeadAcidBatterySaupe) THEN
CALL ShowWarningError('ManageElectStorInteractions: Not yet implemented: Lead Acid Battery By Saupe 1993 ')
ELSE
!should not come here
ENDIF
Pstorage = - tmpPdraw
ENDIF !drawing
IF ((.not. charging) .and. ( .not. drawing)) THEN
FuelCell(Num)%ElecStorage%ThisTimeStepStateOfCharge = FuelCell(Num)%ElecStorage%LastTimeStepStateOfCharge
FuelCell(Num)%ElecStorage%PelNeedFromStorage = 0.0d0
FuelCell(Num)%ElecStorage%PelFromStorage = 0.0d0
FuelCell(Num)%ElecStorage%QairIntake = 0.0d0
ENDIF
IF (Pstorage >= 0.0d0) THEN
FuelCell(Num)%ElecStorage%PelIntoStorage = Pstorage
FuelCell(Num)%ElecStorage%PelFromStorage = 0.0d0
ENDIF
IF (Pstorage < 0.0d0) THEN
FuelCell(Num)%ElecStorage%PelIntoStorage = 0.0d0
FuelCell(Num)%ElecStorage%PelFromStorage = - Pstorage
ENDIF
RETURN
END SUBROUTINE ManageElectStorInteractions