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) | :: | EIRChillNum | |||
real(kind=r64), | intent(inout) | :: | QCond | |||
real(kind=r64), | intent(in) | :: | CondMassFlow | |||
real(kind=r64), | intent(in) | :: | CondInletTemp | |||
real(kind=r64), | intent(out) | :: | QHeatRec |
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 ReformEIRChillerHeatRecovery(EIRChillNum,QCond,CondMassFlow,CondInletTemp,QHeatRec)
! SUBROUTINE INFORMATION:
! AUTHOR: Lixing Gu, FSEC
! DATE WRITTEN: July 2006
! MODIFIED: na
! PURPOSE OF THIS SUBROUTINE:
! Calculate the heat recovered from the chiller condenser
! METHODOLOGY EMPLOYED:
! na
! REFERENCES:
! na
! USE STATEMENTS:
USE DataPlant, ONLY: SingleSetPoint, DualSetPointDeadBand, PlantLoop
USE ScheduleManager, ONLY: GetCurrentScheduleValue
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT (IN) :: EIRChillNum ! Number of the current electric EIR chiller being simulated
REAL(r64),INTENT(INOUT) :: QCond ! Current condenser load [W]
REAL(r64),INTENT(OUT) :: QHeatRec ! Amount of heat recovered [W]
REAL(r64),INTENT(IN) :: CondMassFlow ! Current condenser mass flow [kg/s]
REAL(r64),INTENT(IN) :: CondInletTemp ! Current condenser inlet temp [C]
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: CondInletNode ! Condenser inlet node number
INTEGER :: CondOutletNode ! Condenser outlet node number
INTEGER :: HeatRecInNode ! Node number for heat recovery water inlet node
INTEGER :: HeatRecOutNode ! Node number for heat recovery water outlet node
REAL(r64) :: QTotal ! Total condenser heat [W]
! REAL(r64) :: QCondTmp ! Total condenser heat based on average temperatures [W]
REAL(r64) :: HeatRecInletTemp ! Heat reclaim inlet temp [C]
REAL(r64) :: HeatRecMassFlowRate ! Heat reclaim mass flow rate [m3/s]
REAL(r64) :: FracHeatRec ! Fraction of condenser heat reclaimed
REAL(r64) :: TAvgIn ! Average inlet temperature of heat reclaim inlet and condenser inlet [C]
REAL(r64) :: TAvgOut ! Average outlet temperature [C]
REAL(r64) :: CpHeatRec ! Heat reclaim water inlet specific heat [J/kg-K]
REAL(r64) :: CpCond ! Condenser water inlet specific heat [J/kg-K]
REAL(r64) :: QHeatRecToSetpoint
REAL(r64) :: THeatRecSetpoint
REAL(r64) :: HeatRecHighInletLimit
! Begin routine
HeatRecInNode = ElecReformEIRChiller(EIRChillNum)%HeatRecInletNodeNum
HeatRecOutNode = ElecReformEIRChiller(EIRChillNum)%HeatRecOutletNodeNum
CondInletNode = ElecReformEIRChiller(EIRChillNum)%CondInletNodeNum
CondOutletNode = ElecReformEIRChiller(EIRChillNum)%CondOutletNodeNum
! inlet node to the heat recovery heat exchanger
HeatRecInletTemp = Node(HeatRecInNode)%Temp
HeatRecMassFlowRate = Node(HeatRecInNode)%MassFlowRate
CpHeatRec = GetSpecificHeatGlycol(PlantLoop(ElecReformEIRChiller(EIRChillNum)%HRLoopNum)%FluidName, &
HeatRecInletTemp, &
PlantLoop(ElecReformEIRChiller(EIRChillNum)%HRLoopNum)%FluidIndex, &
'EIRChillerHeatRecovery')
CpCond = GetSpecificHeatGlycol(PlantLoop(ElecReformEIRChiller(EIRChillNum)%CDLoopNum)%FluidName, &
CondInletTemp, &
PlantLoop(ElecReformEIRChiller(EIRChillNum)%CDLoopNum)%FluidIndex, &
'EIRChillerHeatRecovery')
! Before we modify the QCondenser, the total or original value is transferred to QTot
QTotal = QCond
IF (ElecReformEIRChiller(EIRChillNum)%HeatRecSetpointNodeNum == 0) THEN ! use original algorithm that blends temps
TAvgIn = (HeatRecMassFlowRate*CpHeatRec*HeatRecInletTemp + CondMassFlow*CpCond*CondInletTemp)/ &
(HeatRecMassFlowRate*CpHeatRec + CondMassFlow*CpCond)
TAvgOut = QTotal/(HeatRecMassFlowRate*CpHeatRec + CondMassFlow*CpCond) + TAvgIn
QHeatRec = HeatRecMassFlowRate * CpHeatRec * (TAvgOut - HeatRecInletTemp)
QHeatRec = MAX(QHeatRec, 0.d0) ! ensure non negative
!check if heat flow too large for physical size of bundle
QHeatRec = MIN(QHeatRec, ElecReformEIRChiller(EIRChillNum)%HeatRecMaxCapacityLimit)
ELSE ! use new algorithm to meet setpoint
SELECT CASE (PlantLoop(ElecReformEIRChiller(EIRChillNum)%HRLoopNum)%LoopDemandCalcScheme)
CASE (SingleSetPoint)
THeatRecSetpoint = Node(ElecReformEIRChiller(EIRChillNum)%HeatRecSetpointNodeNum)%TempSetPoint
CASE (DualSetPointDeadBand)
THeatRecSetpoint = Node(ElecReformEIRChiller(EIRChillNum)%HeatRecSetpointNodeNum)%TempSetPointHi
END SELECT
QHeatRecToSetpoint = HeatRecMassFlowRate * CpHeatRec * (THeatRecSetpoint - HeatRecInletTemp)
QHeatRecToSetpoint = MAX(QHeatRecToSetpoint, 0.d0)
QHeatRec = MIN(QTotal, QHeatRecToSetpoint)
!check if heat flow too large for physical size of bundle
QHeatRec = MIN(QHeatRec, ElecReformEIRChiller(EIRChillNum)%HeatRecMaxCapacityLimit)
ENDIF
! check if limit on inlet is present and exceeded.
IF (ElecReformEIRChiller(EIRChillNum)%HeatRecInletLimitSchedNum > 0) THEN
HeatRecHighInletLimit = GetCurrentScheduleValue(ElecReformEIRChiller(EIRChillNum)%HeatRecInletLimitSchedNum)
IF ( HeatRecInletTemp > HeatRecHighInletLimit) THEN ! shut down heat recovery
QHeatRec = 0.d0
ENDIF
ENDIF
QCond = QTotal - QHeatRec
! Calculate a new Heat Recovery Coil Outlet Temp
IF (HeatRecMassFlowRate > 0.0d0) THEN
HeatRecOutletTemp = QHeatRec/(HeatRecMassFlowRate*CpHeatRec) + HeatRecInletTemp
ELSE
HeatRecOutletTemp = HeatRecInletTemp
END IF
RETURN
END SUBROUTINE ReformEIRChillerHeatRecovery