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) | :: | PurchAirNum | |||
real(kind=r64), | intent(in) | :: | OAMassFlowRate | |||
real(kind=r64), | intent(in) | :: | SupplyMassFlowRate | |||
real(kind=r64), | intent(out) | :: | MixedAirTemp | |||
real(kind=r64), | intent(out) | :: | MixedAirHumRat | |||
real(kind=r64), | intent(out) | :: | MixedAirEnthalpy | |||
integer, | intent(in) | :: | OperatingMode |
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 CalcPurchAirMixedAir(PurchAirNum, OAMassFlowRate, SupplyMassFlowRate, &
MixedAirTemp, MixedAirHumRat, MixedAirEnthalpy, OperatingMode)
! SUBROUTINE INFORMATION:
! AUTHOR M. Witte (GARD)
! DATE WRITTEN Sep 2011
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Calculates the mixed air conditions, accounting for heat recovery.
! METHODOLOGY EMPLOYED:
! na
! REFERENCES:
! USE STATEMENTS:
USE DataLoopNode, ONLY: Node
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: PurchAirNum ! index to ideal loads unit
INTEGER, INTENT(IN) :: OperatingMode ! current operating mode, Off, Heating, Cooling, or Deadband
REAL(r64), INTENT(IN) :: OAMassFlowRate ! outside air mass flow rate [kg/s]
REAL(r64), INTENT(IN) :: SupplyMassFlowRate ! supply air mass flow rate [kg/s]
REAL(r64), INTENT(OUT) :: MixedAirTemp ! Mixed air dry bulb temperature [C]
REAL(r64), INTENT(OUT) :: MixedAirHumRat ! Mixed air humidity ratio [kg H2O/kg Air]
REAL(r64), INTENT(OUT) :: MixedAirEnthalpy ! Mixed air enthalpy [J/kg]
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: RecircNodeNum ! Zone return air node
INTEGER :: OANodeNum ! Outdoor air inlet node
REAL(r64) :: RecircTemp ! Recirculated air from zone dry bulb temperature [C]
REAL(r64) :: RecircHumRat ! Recirculated air from zone humidity ratio [kg H2O/kg Air]
REAL(r64) :: RecircEnthalpy ! Recirculated air from zone enthalpy [J/kg]
REAL(r64) :: RecircMassFlowRate ! Recirculated air mass flow rate [kg/s]
REAL(r64) :: OAInletTemp ! Outdoor air inlet dry bulb temperature [C]
REAL(r64) :: OAInletHumRat ! Outdoor air inlet humidity ratio [kg H2O/kg Air]
REAL(r64) :: OAInletEnthalpy ! Outdoor air inlet enthalpy [J/kg]
REAL(r64) :: OAAfterHtRecTemp ! Outdoor air after heat recovery to mixing box dry bulb temperature [C]
REAL(r64) :: OAAfterHtRecHumRat ! Outdoor air after heat recovery to mixing box humidity ratio [kg H2O/kg Air]
REAL(r64) :: OAAfterHtRecEnthalpy ! Outdoor air after heat recovery to mixing box enthalpy [J/kg]
LOGICAL :: HeatRecOn
REAL(r64) :: CpAir ! Specific heat [J/kg-C] reused in multiple places
! Initializations
OANodeNum = PurchAir(PurchAirNum)%OutdoorAirNodeNum
RecircNodeNum = PurchAir(PurchAirNum)%ZoneRecircAirNodeNum
RecircMassFlowRate = 0.0d0
RecircTemp = Node(RecircNodeNum)%Temp
RecircHumRat = Node(RecircNodeNum)%HumRat
RecircEnthalpy = Node(RecircNodeNum)%Enthalpy
IF (PurchAir(PurchAirNum)%OutdoorAir) THEN
OAInletTemp = Node(OANodeNum)%Temp
OAInletHumRat = Node(OANodeNum)%HumRat
OAInletEnthalpy = Node(OANodeNum)%Enthalpy
OAAfterHtRecTemp = OAInletTemp
OAAfterHtRecHumRat = OAInletHumRat
OAAfterHtRecEnthalpy = OAInletEnthalpy
ELSE
OAInletTemp = 0.0d0
OAInletHumRat = 0.0d0
OAInletEnthalpy = 0.0d0
OAAfterHtRecTemp = OAInletTemp
OAAfterHtRecHumRat = OAInletHumRat
OAAfterHtRecEnthalpy = OAInletEnthalpy
ENDIF
HeatRecOn = .FALSE.
IF (PurchAir(PurchAirNum)%OutdoorAir .AND. (OAMassFlowRate > 0.0d0)) THEN
! Determine if heat recovery is beneficial
IF ((PurchAir(PurchAirNum)%HtRecType == Sensible) ) THEN
IF ((OperatingMode == Heat) .AND. (RecircTemp > OAInletTemp)) HeatRecOn = .TRUE.
IF ((OperatingMode == Cool) .AND. (RecircTemp < OAInletTemp)) HeatRecOn = .TRUE.
END IF
IF ((PurchAir(PurchAirNum)%HtRecType == Enthalpy)) THEN
IF ((OperatingMode == Heat) .AND. (RecircEnthalpy > OAInletEnthalpy)) HeatRecOn = .TRUE.
IF ((OperatingMode == Cool) .AND. (RecircEnthalpy < OAInletEnthalpy)) HeatRecOn = .TRUE.
END IF
! Calculate heat recovery if active
IF (HeatRecOn) THEN
PurchAir(PurchAirNum)%TimeHtRecActive = TimeStepSys
OAAfterHtRecTemp = OAInletTemp + PurchAir(PurchAirNum)%HtRecSenEff*(RecircTemp - OAInletTemp)
IF (PurchAir(PurchAirNum)%HtRecType == Enthalpy) &
OAAfterHtRecHumRat = OAInletHumRat + PurchAir(PurchAirNum)%HtRecLatEff*(RecircHumRat - OAInletHumRat)
OAAfterHtRecEnthalpy = PsyHFnTdbW(OAAfterHtRecTemp,OAAfterHtRecHumRat, 'CalcPurchAirMixedAir')
! Check for saturation in supply outlet and reset temp, then humidity ratio at constant enthalpy
IF (PsyTsatFnHPb(OAAfterHtRecEnthalpy,OutBaroPress, 'CalcPurchAirMixedAir') > OAAfterHtRecTemp) THEN
OAAfterHtRecTemp = PsyTsatFnHPb(OAAfterHtRecEnthalpy,OutBaroPress, 'CalcPurchAirMixedAir')
OAAfterHtRecHumRat = PsyWFnTdbH(OAAfterHtRecTemp,OAAfterHtRecEnthalpy, 'CalcPurchAirMixedAir')
END IF
END IF
IF (SupplyMassFlowRate .GT. OAMassFlowRate) THEN
RecircMassFlowRate = SupplyMassFlowRate - OAMassFlowRate
MixedAirEnthalpy = (RecircMassFlowRate*Node(RecircNodeNum)%Enthalpy + OAMassFlowRate*OAAfterHtRecEnthalpy) / &
SupplyMassFlowRate
MixedAirHumRat = (RecircMassFlowRate*Node(RecircNodeNum)%HumRat + OAMassFlowRate*OAAfterHtRecHumRat) / &
SupplyMassFlowRate
! Mixed air temperature is calculated from the mixed air enthalpy and humidity ratio.
MixedAirTemp = PsyTdbFnHW(MixedAirEnthalpy,MixedAirHumRat, 'CalcPurchAirMixedAir')
ELSE
RecircMassFlowRate = 0.0d0
MixedAirEnthalpy = OAAfterHtRecEnthalpy
MixedAirHumRat = OAAfterHtRecHumRat
MixedAirTemp = OAAfterHtRecTemp
END IF
! Calculate OA and heat recovery sensible and latent rates
CpAir = PsyCpAirFnWTdb(OAInletHumRat,OAInletTemp)
PurchAir(PurchAirNum)%HtRecSenOutput = OAMassFlowRate * CPAir * (OAAfterHtRecTemp - OAInletTemp)
PurchAir(PurchAirNum)%HtRecLatOutput = OAMassFlowRate * (OAAfterHtRecEnthalpy - OAInletEnthalpy) &
- PurchAir(PurchAirNum)%HtRecSenOutput
ELSE ! No outdoor air
RecircMassFlowRate = SupplyMassFlowRate
MixedAirTemp = RecircTemp
MixedAirHumRat = RecircHumRat
MixedAirEnthalpy = RecircEnthalpy
PurchAir(PurchAirNum)%HtRecSenOutput = 0.0d0
PurchAir(PurchAirNum)%HtRecLatOutput = 0.0d0
END IF
! If exhaust node is specified, then set massflow on exhaust node, otherwise return node sets its own massflow
IF (PurchAir(PurchAirNum)%ZoneExhaustAirNodeNum .GT. 0) THEN
Node(RecircNodeNum)%MassFlowRate = RecircMassFlowRate
END IF
RETURN
END SUBROUTINE CalcPurchAirMixedAir