Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | ExNum |
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 FrostControl(ExNum)
! SUBROUTINE INFORMATION:
! AUTHOR Richard Raustad, FSEC
! DATE WRITTEN June 2003
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Calculates fraction of timestep necessary to eliminate frost on ERV surface
! by comparing secondary outlet or outdoor temperature to a frost control threshold
! temperature. Supply air and secondary air outlet conditions are calculated
! based on frost control method selected.
! METHODOLOGY EMPLOYED:
! NA
! REFERENCES:
! na
! USE STATEMENTS:
! na
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT (IN) :: ExNum ! number of the current heat exchanger being simulated
! SUBROUTINE PARAMETER DEFINITIONS:
REAL(r64), PARAMETER :: ErrorTol = 0.001d0 ! error tolerence for iteration loop
! na
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: DFFraction ! fraction of timestep ERV is in frost control mode
REAL(r64) :: RhoSup ! density of supply air [kg/m3]
REAL(r64) :: RhoSec ! density of secondary air [kg/m3]
REAL(r64) :: Error ! iteration loop error variable
REAL(r64) :: Iter ! iteration counter
REAL(r64) :: CSup ! mdot Cp of supply air [W/K]
REAL(r64) :: CSec ! mdot Cp of secondary air [W/K]
REAL(r64) :: CMin ! minimum mdot Cp of supply or secondary air [W/K]
REAL(r64) :: QTotTrans ! total heat transfer by ERV [W]
REAL(r64) :: QSensTrans ! sensible heat transfer by ERV [W]
REAL(r64) :: HXSecAirVolFlowRate ! air volume flow rate of the secondary air stream through the heat exchanger [m3/sec]
REAL(r64) :: HXSupAirVolFlowRate ! air volume flow rate of the supply air stream through the heat exchanger [m3/sec]
REAL(r64) :: HXAvgAirVolFlowRate ! average air volume flow rate through the heat exchanger [m3/sec]
REAL(r64) :: HXAirVolFlowRatio ! nominal to actual air volume flow ratio
REAL(r64) :: MassFlowSupIn ! supply air mass flow rate at HX inlet
REAL(r64) :: MassFlowSupOut ! supply air mass flow rate through HX core outlet
REAL(r64) :: MassFlowSupBypass ! supply air bypass mass flow rate around HX core
REAL(r64) :: TempSupIn ! supply side temperature of air entering HX
REAL(r64) :: TempSupOut ! supply side temperature of air leaving HX core
REAL(r64) :: HumRatSupIn ! supply side humidity ratio of air entering HX
REAL(r64) :: TempSecIn ! secondary side temperature of air entering HX
REAL(r64) :: TempSecOut ! secondary side temperature of air leaving HX core
REAL(r64) :: TempThreshold ! threshold temperature below which frost control is active
ExchCond(ExNum)%SupOutMassFlow = ExchCond(ExNum)%SupInMassFlow
ExchCond(ExNum)%SecOutMassFlow = ExchCond(ExNum)%SecInMassFlow
ExchCond(ExNum)%SupBypassMassFlow = 0.0d0
ExchCond(ExNum)%SecBypassMassFlow = 0.0d0
RhoSup = PsyRhoAirFnPbTdbW(OutBaroPress,ExchCond(ExNum)%SupInTemp,ExchCond(ExNum)%SupInHumRat)
RhoSec = PsyRhoAirFnPbTdbW(OutBaroPress,ExchCond(ExNum)%SecInTemp,ExchCond(ExNum)%SecInHumRat)
CSup = ExchCond(ExNum)%SupOutMassFlow * PsyCpAirFnWTdb(ExchCond(ExNum)%SupInHumRat,ExchCond(ExNum)%SupInTemp)
CSec = ExchCond(ExNum)%SecOutMassFlow * PsyCpAirFnWTdb(ExchCond(ExNum)%SecInHumRat,ExchCond(ExNum)%SecInTemp)
CMin = MIN(CSup, CSec)
TempThreshold = ExchCond(ExNum)%ThresholdTemperature
IF (ExchCond(ExNum)%ControlToTemperatureSetPoint) THEN
! Recalculate HX outlet conditions as if control to temperature setpoint was not activated,
! because defrost will override those results
HXSupAirVolFlowRate = ExchCond(ExNum)%SupOutMassFlow/RhoSup
HXSecAirVolFlowRate = ExchCond(ExNum)%SecOutMassFlow/RhoSec
HXAvgAirVolFlowRate = (HXSecAirVolFlowRate + HXSupAirVolFlowRate)/2.0d0
HXAirVolFlowRatio = HXAvgAirVolFlowRate/ExchCond(ExNum)%NomSupAirVolFlow
ExchCond(ExNum)%SensEffectiveness = ExchCond(ExNum)%HeatEffectSensible75 + &
(ExchCond(ExNum)%HeatEffectSensible100 - ExchCond(ExNum)%HeatEffectSensible75)* &
(HXAirVolFlowRatio - 0.75d0)/(1.d0 - 0.75d0)
ExchCond(ExNum)%LatEffectiveness = ExchCond(ExNum)%HeatEffectLatent75 + &
(ExchCond(ExNum)%HeatEffectLatent100 - ExchCond(ExNum)%HeatEffectLatent75)* &
(HXAirVolFlowRatio - 0.75d0)/(1.d0 - 0.75d0)
ExchCond(ExNum)%SupOutTemp = ExchCond(ExNum)%SupInTemp + &
ExchCond(ExNum)%SensEffectiveness*CMin/CSup*(ExchCond(ExNum)%SecInTemp-ExchCond(ExNum)%SupInTemp)
ExchCond(ExNum)%SupOutHumRat = ExchCond(ExNum)%SupInHumRat + &
ExchCond(ExNum)%LatEffectiveness*CMin/CSup*(ExchCond(ExNum)%SecInHumRat-ExchCond(ExNum)%SupInHumRat)
ExchCond(ExNum)%SupOutEnth = PsyHFnTdbW(ExchCond(ExNum)%SupOutTemp,ExchCond(ExNum)%SupOutHumRat)
! Check for saturation in supply outlet and reset temp, then humidity ratio at constant enthalpy
IF (PsyTsatFnHPb(ExchCond(ExNum)%SupOutEnth,OutBaroPress).GT.ExchCond(ExNum)%SupOutTemp) THEN
ExchCond(ExNum)%SupOutTemp = PsyTsatFnHPb(ExchCond(ExNum)%SupOutEnth,OutBaroPress)
ExchCond(ExNum)%SupOutHumRat = PsyWFnTdbH(ExchCond(ExNum)%SupOutTemp,ExchCond(ExNum)%SupOutEnth)
END IF
QSensTrans = CSup * (ExchCond(ExNum)%SupInTemp - ExchCond(ExNum)%SupOutTemp)
ExchCond(ExNum)%SecOutTemp = ExchCond(ExNum)%SecInTemp + QSensTrans / CSec
QTotTrans = ExchCond(ExNum)%SupOutMassFlow * (ExchCond(ExNum)%SupInEnth - ExchCond(ExNum)%SupOutEnth)
ExchCond(ExNum)%SecOutEnth = ExchCond(ExNum)%SecInEnth + QTotTrans/ExchCond(ExNum)%SecOutMassFlow
ExchCond(ExNum)%SecOutHumRat = PsyWFnTdbH(ExchCond(ExNum)%SecOutTemp,ExchCond(ExNum)%SecOutEnth)
END IF
! Check frost control by type
IF(ExchCond(ExNum)%FrostControlType == 'MINIMUMEXHAUSTTEMPERATURE') THEN
! A plate HX will bypass air on the supply side to keep exhaust temp above a
! threshold temperature and requires recalculating effectiveness based on
! the reduced air flow rate. A rotary HX modulates rotational speed to try to keep the
! exhaust air temperature above the threshold temperature. Assume that
! sensible and latent effectiveness decrease proportionally with rotary HX speed.
DFFraction = MAX(0.0d0,MIN(1.0d0,SafeDiv((TempThreshold - ExchCond(ExNum)%SecOutTemp), &
(ExchCond(ExNum)%SecInTemp - ExchCond(ExNum)%SecOutTemp))))
IF (ExchCond(ExNum)%ExchConfigNum == ROTARY) THEN
ExchCond(ExNum)%SensEffectiveness = (1.d0-DFFraction) * ExchCond(ExNum)%SensEffectiveness
ExchCond(ExNum)%LatEffectiveness = (1.d0-DFFraction) * ExchCond(ExNum)%LatEffectiveness
ELSE ! HX is a plate heat exchanger, bypass air to eliminate frost
Error = 1.0d0
Iter = 0.0d0
MassFlowSupIn = ExchCond(ExNum)%SupInMassFlow
MassFlowSupOut = ExchCond(ExNum)%SupOutMassFlow
MassFlowSupBypass = ExchCond(ExNum)%SupBypassMassFlow
TempSupIn = ExchCond(ExNum)%SupInTemp
HumRatSupIn = ExchCond(ExNum)%SupInHumRat
TempSecIn = ExchCond(ExNum)%SecInTemp
DO WHILE (ABS(Error) .GT. ErrorTol .AND. Iter .lt. 10)
MassFlowSupOut = MassFlowSupIn*(1.d0-DFFraction)
MassFlowSupBypass = MassFlowSupIn*DFFraction
HXSupAirVolFlowRate = MassFlowSupOut/RhoSup
HXSecAirVolFlowRate = ExchCond(ExNum)%SecOutMassFlow/RhoSec
HXAvgAirVolFlowRate = (HXSecAirVolFlowRate + HXSupAirVolFlowRate)/2.0d0
HXAirVolFlowRatio = HXAvgAirVolFlowRate/ExchCond(ExNum)%NomSupAirVolFlow
CSup = MassFlowSupOut * PsyCpAirFnWTdb(HumRatSupIn,TempSupIn)
CMin = MIN(CSup,CSec)
IF (TempSupIn .LT. TempSecIn) THEN
! Use heating effectiveness values
ExchCond(ExNum)%SensEffectiveness = ExchCond(ExNum)%HeatEffectSensible75 + &
(ExchCond(ExNum)%HeatEffectSensible100 - ExchCond(ExNum)%HeatEffectSensible75)* &
(HXAirVolFlowRatio - 0.75d0)/(1.d0 - 0.75d0)
ExchCond(ExNum)%LatEffectiveness = ExchCond(ExNum)%HeatEffectLatent75 + &
(ExchCond(ExNum)%HeatEffectLatent100 - ExchCond(ExNum)%HeatEffectLatent75)* &
(HXAirVolFlowRatio - 0.75d0)/(1.d0 - 0.75d0)
ELSE
! Use cooling effectiveness values
ExchCond(ExNum)%SensEffectiveness = ExchCond(ExNum)%CoolEffectSensible75 + &
(ExchCond(ExNum)%CoolEffectSensible100 - ExchCond(ExNum)%CoolEffectSensible75)* &
(HXAirVolFlowRatio - 0.75d0)/(1.d0 - 0.75d0)
ExchCond(ExNum)%LatEffectiveness = ExchCond(ExNum)%CoolEffectLatent75 + &
(ExchCond(ExNum)%CoolEffectLatent100 - ExchCond(ExNum)%CoolEffectLatent75)* &
(HXAirVolFlowRatio - 0.75d0)/(1.d0 - 0.75d0)
END IF
! calculation of local variable Csup can be 0, gaurd against divide by 0.
TempSupOut = TempSupIn + &
ExchCond(ExNum)%SensEffectiveness * SafeDiv(CMin,CSup) * (TempSecIn - TempSupIn)
QSensTrans = CSup * (TempSupIn - TempSupOut)
! Csec cannot be 0 in this subroutine
TempSecOut = TempSecIn + QSensTrans / CSec
Error = (TempSecOut - TempThreshold)
! recalculate DFFraction until convergence, gaurd against divide by 0 (unlikely).
DFFraction = MAX(0.0d0,MIN(1.0d0,DFFraction * SafeDiv((TempSecIn - TempSecOut),(TempSecIn - TempThreshold))))
Iter = Iter + 1
END DO
ExchCond(ExNum)%SupInMassFlow = MassFlowSupIn
ExchCond(ExNum)%SupOutMassFlow = MassFlowSupOut
ExchCond(ExNum)%SupBypassMassFlow = MassFlowSupBypass
END IF
ExchCond(ExNum)%SupOutTemp = ExchCond(ExNum)%SupInTemp + &
ExchCond(ExNum)%SensEffectiveness*SafeDiv(CMin,CSup)*(ExchCond(ExNum)%SecInTemp-ExchCond(ExNum)%SupInTemp)
ExchCond(ExNum)%SupOutHumRat = ExchCond(ExNum)%SupInHumRat + &
ExchCond(ExNum)%LatEffectiveness*SafeDiv(CMin,CSup)*(ExchCond(ExNum)%SecInHumRat-ExchCond(ExNum)%SupInHumRat)
ExchCond(ExNum)%SupOutEnth = PsyHFnTdbW(ExchCond(ExNum)%SupOutTemp,ExchCond(ExNum)%SupOutHumRat)
! Check for saturation in supply outlet and reset temp, then humidity ratio at constant enthalpy
IF (PsyTsatFnHPb(ExchCond(ExNum)%SupOutEnth,OutBaroPress).GT.ExchCond(ExNum)%SupOutTemp) THEN
ExchCond(ExNum)%SupOutTemp = PsyTsatFnHPb(ExchCond(ExNum)%SupOutEnth,OutBaroPress)
ExchCond(ExNum)%SupOutHumRat = PsyWFnTdbH(ExchCond(ExNum)%SupOutTemp,ExchCond(ExNum)%SupOutEnth)
END IF
QSensTrans = CSup * (ExchCond(ExNum)%SupInTemp - ExchCond(ExNum)%SupOutTemp)
ExchCond(ExNum)%SecOutTemp = ExchCond(ExNum)%SecInTemp + QSensTrans / CSec
QTotTrans = ExchCond(ExNum)%SupOutMassFlow * (ExchCond(ExNum)%SupInEnth - ExchCond(ExNum)%SupOutEnth)
ExchCond(ExNum)%SecOutEnth = ExchCond(ExNum)%SecInEnth + QTotTrans/ExchCond(ExNum)%SecOutMassFlow
ExchCond(ExNum)%SecOutHumRat = PsyWFnTdbH(ExchCond(ExNum)%SecOutTemp,ExchCond(ExNum)%SecOutEnth)
! Perform mixing of core air stream and bypass air stream and set mass flow rates at outlet nodes
ExchCond(ExNum)%SupOutEnth = (ExchCond(ExNum)%SupOutMassFlow*ExchCond(ExNum)%SupOutEnth &
+ ExchCond(ExNum)%SupBypassMassFlow*ExchCond(ExNum)%SupInEnth) &
/ ExchCond(ExNum)%SupInMassFlow
ExchCond(ExNum)%SupOutHumRat = (ExchCond(ExNum)%SupOutMassFlow*ExchCond(ExNum)%SupOutHumRat &
+ ExchCond(ExNum)%SupBypassMassFlow*ExchCond(ExNum)%SupInHumRat) &
/ ExchCond(ExNum)%SupInMassFlow
ExchCond(ExNum)%SupOutTemp = PsyTdbFnHW(ExchCond(ExNum)%SupOutEnth,ExchCond(ExNum)%SupOutHumRat)
ExchCond(ExNum)%SupOutMassFlow = ExchCond(ExNum)%SupInMassFlow
ExchCond(ExNum)%SecOutEnth = (ExchCond(ExNum)%SecOutMassFlow*ExchCond(ExNum)%SecOutEnth &
+ ExchCond(ExNum)%SecBypassMassFlow*ExchCond(ExNum)%SecInEnth) &
/ ExchCond(ExNum)%SecInMassFlow
ExchCond(ExNum)%SecOutHumRat = (ExchCond(ExNum)%SecOutMassFlow*ExchCond(ExNum)%SecOutHumRat &
+ ExchCond(ExNum)%SecBypassMassFlow*ExchCond(ExNum)%SecInHumRat) &
/ ExchCond(ExNum)%SecInMassFlow
ExchCond(ExNum)%SecOutTemp = PsyTdbFnHW(ExchCond(ExNum)%SecOutEnth,ExchCond(ExNum)%SecOutHumRat)
ExchCond(ExNum)%SecOutMassFlow = ExchCond(ExNum)%SecInMassFlow
END IF ! End of IF (Minimum Exhaust Temperature)
IF(ExchCond(ExNum)%FrostControlType == 'EXHAUSTAIRRECIRCULATION') Then
!
! Directing exhaust outlet air back across the HX core on the supply side
! Assume no heat exchange when in frost control mode, full heat exchange otherwise
!
DFFraction = MAX(0.0d0,MIN((ExchCond(ExNum)%InitialDefrostTime + &
ExchCond(ExNum)%RateofDefrostTimeIncrease * &
(TempThreshold-ExchCond(ExNum)%SupInTemp)),1.0d0))
! Calculate derated heat transfer using outlet air conditions assuming no defrost (calculated earlier)
! and (1-DefrostFraction)
QSensTrans = (1.d0-DFFraction) * CSup * (ExchCond(ExNum)%SupInTemp - ExchCond(ExNum)%SupOutTemp)
QTotTrans = (1.d0-DFFraction) * ExchCond(ExNum)%SupOutMassFlow * (ExchCond(ExNum)%SupInEnth - ExchCond(ExNum)%SupOutEnth)
ExchCond(ExNum)%SupOutMassFlow = (1.d0-DFFraction) * ExchCond(ExNum)%SupInMassFlow + &
DFFraction * ExchCond(ExNum)%SecInMassFlow
! Blend supply outlet condition of HX core with exhaust air inlet to get final supply air outlet conditions
ExchCond(ExNum)%SupOutTemp = ((1.d0-DFFraction) * ExchCond(ExNum)%SupInMassFlow * ExchCond(ExNum)%SupOutTemp + &
DFFraction * ExchCond(ExNum)%SecInMassFlow * ExchCond(ExNum)%SecInTemp) / &
ExchCond(ExNum)%SupOutMassFlow
ExchCond(ExNum)%SupOutHumRat = ((1.d0-DFFraction) * ExchCond(ExNum)%SupInMassFlow * ExchCond(ExNum)%SupOutHumRat + &
DFFraction * ExchCond(ExNum)%SecInMassFlow * ExchCond(ExNum)%SecInHumRat) / &
ExchCond(ExNum)%SupOutMassFlow
ExchCond(ExNum)%SupOutEnth = PsyHFnTdbW(ExchCond(ExNum)%SupOutTemp,ExchCond(ExNum)%SupOutHumRat)
! No need to check for saturation after SA out and EA inlet are blended
! Derate effectiveness based on frost control time fraction for reporting purposes
ExchCond(ExNum)%SensEffectiveness = (1.d0-DFFraction) * ExchCond(ExNum)%SensEffectiveness
ExchCond(ExNum)%LatEffectiveness = (1.d0-DFFraction) * ExchCond(ExNum)%LatEffectiveness
! Secondary air outlet conditions are previously calculated as the conditions when not
! in defrost, and this is what we want to report so no changes here.
!
! Average SupInMassFlow and SecOutMassFlow rates have been reduced due to frost control
! Equipment attached to the supply inlet node may have problems with our setting the
! mass flow rate in the next statement. This is done only to simulate exhaust air recirc.
Node(ExchCond(ExNum)%SupInletNode)%MassFlowRate = ExchCond(ExNum)%SupInMassFlow * (1.d0-DFFraction)
ExchCond(ExNum)%SecOutMassFlow = ExchCond(ExNum)%SecOutMassFlow * (1.d0-DFFraction)
END IF ! End of IF (Exhaust Air Recirculation)
IF(ExchCond(ExNum)%FrostControlType == 'EXHAUSTONLY') Then
! Perform frost control by bypassing the supply air around the HX core during the defrost
! time period. HX heat transfer is reduced proportionally to (1 - defrosttimefraction)
DFFraction = MAX(0.0d0,MIN((ExchCond(ExNum)%InitialDefrostTime + &
ExchCond(ExNum)%RateofDefrostTimeIncrease * &
(TempThreshold-ExchCond(ExNum)%SupInTemp)),1.0d0))
! Calculate derated heat transfer based on defrost time
QSensTrans = (1.d0-DFFraction) * CSup * (ExchCond(ExNum)%SupInTemp - ExchCond(ExNum)%SupOutTemp)
QTotTrans = (1.d0-DFFraction) * ExchCond(ExNum)%SupOutMassFlow * (ExchCond(ExNum)%SupInEnth - ExchCond(ExNum)%SupOutEnth)
! Calculate the air conditions leaving heat exchanger unit
! Heat exchanger effectiveness is not derated, HX is fully bypassed during frost control
ExchCond(ExNum)%SupBypassMassFlow = ExchCond(ExNum)%SupInMassFlow * DFFraction
ExchCond(ExNum)%SupOutTemp = ExchCond(ExNum)%SupInTemp - QSensTrans / CSup
ExchCond(ExNum)%SupOutEnth = ExchCond(ExNum)%SupInEnth - QTotTrans/ExchCond(ExNum)%SupOutMassFlow
ExchCond(ExNum)%SupOutHumRat = PsyWFnTdbH(ExchCond(ExNum)%SupOutTemp,ExchCond(ExNum)%SupOutEnth)
IF (PsyTsatFnHPb(ExchCond(ExNum)%SupOutEnth,OutBaroPress).GT.ExchCond(ExNum)%SupOutTemp) THEN
ExchCond(ExNum)%SupOutTemp = PsyTsatFnHPb(ExchCond(ExNum)%SupOutEnth,OutBaroPress)
ExchCond(ExNum)%SupOutHumRat = PsyWFnTdbH(ExchCond(ExNum)%SupOutTemp,ExchCond(ExNum)%SupOutEnth)
QSensTrans = CSup * (ExchCond(ExNum)%SupInTemp - ExchCond(ExNum)%SupOutTemp)
! Should we be updating the sensible and latent effectiveness values also?
END IF
ExchCond(ExNum)%SecOutEnth = ExchCond(ExNum)%SecInEnth + QTotTrans/ExchCond(ExNum)%SecOutMassFlow
ExchCond(ExNum)%SecOutTemp = ExchCond(ExNum)%SecInTemp + QSensTrans / CSec
ExchCond(ExNum)%SecOutHumRat = PsyWFnTdbH(ExchCond(ExNum)%SecOutTemp,ExchCond(ExNum)%SecOutEnth)
END IF ! End of IF (Exhaust Only)
ExchCond(ExNum)%DefrostFraction = DFFraction
RETURN
END SUBROUTINE FrostControl