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) | :: | ZoneNum |
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 CorrectZoneHumRat(ZoneNum)
! SUBROUTINE INFORMATION:
! AUTHOR Richard Liesen
! DATE WRITTEN 2000
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine updates the zone humidities.
! METHODOLOGY EMPLOYED:
! na
! REFERENCES:
! Routine FinalZnCalcs - FINAL ZONE CALCULATIONS, authored by Dale Herron
! for BLAST.
! USE STATEMENTS:
USE DataLoopNode, ONLY: Node
USE DataZoneEquipment, ONLY: ZoneEquipConfig
USE ZonePlenum, ONLY: ZoneRetPlenCond, ZoneSupPlenCond, NumZoneReturnPlenums, NumZoneSupplyPlenums
USE DataDefineEquip, ONLY: AirDistUnit, NumAirDistUnits
USE DataSurfaces, ONLY: Surface, HeatTransferModel_HAMT, HeatTransferModel_EMPD
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: ZoneNum
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: NodeNum
INTEGER :: ZoneNodeNum
INTEGER :: ZoneEquipConfigNum
LOGICAL :: ControlledZoneAirFlag
INTEGER :: ZoneRetPlenumNum
INTEGER :: ZoneSupPlenumNum
LOGICAL :: ZoneRetPlenumAirFlag
LOGICAL :: ZoneSupPlenumAirFlag
REAL(r64) :: LatentGain ! Zone latent load
REAL(r64) :: RhoAir
REAL(r64) :: A
REAL(r64) :: B
REAL(r64) :: C
REAL(r64) :: WZSat
REAL(r64) :: MoistureMassFlowRate
REAL(r64) :: ExhMassFlowRate
REAL(r64) :: TotExitMassFlowRate
REAL(r64) :: ZoneMassFlowRate
REAL(r64) :: SysTimeStepInSeconds
REAL(r64) :: H2OHtOfVap
REAL(r64) :: ZoneMult
INTEGER :: ADUListIndex
INTEGER :: ADUNum
INTEGER :: ADUInNode
INTEGER :: ADUOutNode
! FLOW:
MoistureMassFlowRate = 0.0d0
ZoneMassFlowRate = 0.0d0
ExhMassFlowRate = 0.0d0
TotExitMassFlowRate = 0.0d0
ZoneMult = Zone(ZoneNum)%Multiplier * Zone(ZoneNum)%ListMultiplier
! Check to see if this is a controlled zone
ControlledZoneAirFlag = .FALSE.
DO ZoneEquipConfigNum = 1, NumOfZones
IF (.not. Zone(ZoneEquipConfigNum)%IsControlled) CYCLE
IF (ZoneEquipConfig(ZoneEquipConfigNum)%ActualZoneNum /= ZoneNum) CYCLE
ControlledZoneAirFlag = .TRUE.
EXIT
END DO ! ZoneEquipConfigNum
! Check to see if this is a plenum zone
ZoneRetPlenumAirFlag = .FALSE.
DO ZoneRetPlenumNum = 1, NumZoneReturnPlenums
IF (ZoneRetPlenCond(ZoneRetPlenumNum)%ActualZoneNum /= ZoneNum) CYCLE
ZoneRetPlenumAirFlag = .TRUE.
EXIT
END DO ! ZoneRetPlenumNum
ZoneSupPlenumAirFlag = .FALSE.
DO ZoneSupPlenumNum = 1, NumZoneSupplyPlenums
IF (ZoneSupPlenCond(ZoneSupPlenumNum)%ActualZoneNum /= ZoneNum) CYCLE
ZoneSupPlenumAirFlag = .TRUE.
EXIT
END DO ! ZoneSupPlenumNum
IF (ControlledZoneAirFlag) THEN ! If there is system flow then calculate the flow rates
! Calculate moisture flow rate into each zone
DO NodeNum = 1, ZoneEquipConfig(ZoneEquipConfigNum)%NumInletNodes
MoistureMassFlowRate = MoistureMassFlowRate + &
(Node(ZoneEquipConfig(ZoneEquipConfigNum)%InletNode(NodeNum))%MassFlowRate * &
Node(ZoneEquipConfig(ZoneEquipConfigNum)%InletNode(NodeNum))%HumRat) / ZoneMult
ZoneMassFlowRate = ZoneMassFlowRate + &
Node(ZoneEquipConfig(ZoneEquipConfigNum)%InletNode(NodeNum))%MassFlowRate / ZoneMult
END DO ! NodeNum
DO NodeNum = 1, ZoneEquipConfig(ZoneEquipConfigNum)%NumExhaustNodes
ExhMassFlowRate = ExhMassFlowRate + Node(ZoneEquipConfig(ZoneEquipConfigNum)%ExhaustNode(NodeNum))%MassFlowRate / ZoneMult
END DO ! NodeNum
IF (ZoneEquipConfig(ZoneEquipConfigNum)%ReturnAirNode > 0) THEN
TotExitMassFlowRate = ExhMassFlowRate + Node(ZoneEquipConfig(ZoneEquipConfigNum)%ReturnAirNode)%MassFlowRate / ZoneMult
END IF
! Do the calculations for the plenum zone
ELSE IF (ZoneRetPlenumAirFlag) THEN
DO NodeNum = 1, ZoneRetPlenCond(ZoneRetPlenumNum)%NumInletNodes
MoistureMassFlowRate = MoistureMassFlowRate + &
(Node(ZoneRetPlenCond(ZoneRetPlenumNum)%InletNode(NodeNum))%MassFlowRate * &
Node(ZoneRetPlenCond(ZoneRetPlenumNum)%InletNode(NodeNum))%HumRat) / ZoneMult
ZoneMassFlowRate = ZoneMassFlowRate + &
Node(ZoneRetPlenCond(ZoneRetPlenumNum)%InletNode(NodeNum))%MassFlowRate / ZoneMult
END DO ! NodeNum
! add in the leak flow
DO ADUListIndex=1,ZoneRetPlenCond(ZoneRetPlenumNum)%NumADUs
ADUNum = ZoneRetPlenCond(ZoneRetPlenumNum)%ADUIndex(ADUListIndex)
IF (AirDistUnit(ADUNum)%UpStreamLeak) THEN
ADUInNode = AirDistUnit(ADUNum)%InletNodeNum
MoistureMassFlowRate = MoistureMassFlowRate + &
(AirDistUnit(ADUNum)%MassFlowRateUpStrLk * Node(ADUInNode)%HumRat) / ZoneMult
ZoneMassFlowRate = ZoneMassFlowRate + AirDistUnit(ADUNum)%MassFlowRateUpStrLk / ZoneMult
END IF
IF (AirDistUnit(ADUNum)%DownStreamLeak) THEN
ADUOutNode = AirDistUnit(ADUNum)%OutletNodeNum
MoistureMassFlowRate = MoistureMassFlowRate + &
(AirDistUnit(ADUNum)%MassFlowRateDnStrLk * Node(ADUOutNode)%HumRat) / ZoneMult
ZoneMassFlowRate = ZoneMassFlowRate + AirDistUnit(ADUNum)%MassFlowRateDnStrLk / ZoneMult
END IF
END DO
! Do not allow exhaust mass flow for a plenum zone
ExhMassFlowRate = 0.0d0
TotExitMassFlowRate = ExhMassFlowRate + ZoneMassFlowRate
ELSE IF (ZoneSupPlenumAirFlag) THEN
MoistureMassFlowRate = MoistureMassFlowRate + &
(Node(ZoneSupPlenCond(ZoneSupPlenumNum)%InletNode)%MassFlowRate * &
Node(ZoneSupPlenCond(ZoneSupPlenumNum)%InletNode)%HumRat) / ZoneMult
ZoneMassFlowRate = ZoneMassFlowRate + &
Node(ZoneSupPlenCond(ZoneSupPlenumNum)%InletNode)%MassFlowRate / ZoneMult
! Do not allow exhaust mass flow for a plenum zone
ExhMassFlowRate = 0.0d0
TotExitMassFlowRate = ExhMassFlowRate + ZoneMassFlowRate
END IF
! Calculate hourly humidity ratio from infiltration + humdidity added from latent load + system added moisture
LatentGain = ZoneLatentGain(ZoneNum) + SumLatentHTRadSys(ZoneNum)
SysTimeStepInSeconds = SecInHour * TimeStepSys
! Calculate the coefficients for the 3rd order derivative for final
! zone humidity ratio. The A, B, C coefficients are analogous to the
! heat balance. There are 2 cases that should be considered, system
! operating and system shutdown.
! SumHmARaW and SumHmARa will be used with the moisture balance on the building elements and
! are currently set to zero to remind us where they need to be in the future
IF ((.NOT. ANY(Surface(Zone(ZoneNum)%SurfaceFirst:Zone(ZoneNum)%SurfaceLast)%HeatTransferAlgorithm == HeatTransferModel_EMPD))&
.AND. &
(.NOT. ANY(Surface(Zone(ZoneNum)%SurfaceFirst:Zone(ZoneNum)%SurfaceLast)%HeatTransferAlgorithm == HeatTransferModel_HAMT)))&
THEN
SumHmARaW(ZoneNum) = 0.0d0
SumHmARa(ZoneNum) = 0.0d0
END IF
RhoAir = PsyRhoAirFnPbTdbW(OutBaroPress,ZT(ZoneNum),ZoneAirHumRat(ZoneNum),'CorrectZoneHumRat')
H2OHtOfVap = PsyHgAirFnWTdb(ZoneAirHumRat(ZoneNum),ZT(ZoneNum),'CorrectZoneHumRat')
! Check for the flow and NO flow condition
IF (ZoneMassFlowRate .GT. 0.0d0) THEN
B = (LatentGain/H2OHtOfVap)+((oamfl(ZoneNum)+vamfl(ZoneNum)+eamfl(ZoneNum)+ctmfl(ZoneNum))* OutHumRat) &
+(MoistureMassFlowRate) &
+SumHmARaW(ZoneNum) &
+MixingMassFlowXHumRat(ZoneNum) + MDotOA(ZoneNum) * OutHumRat
A = TotExitMassFlowRate + oamfl(ZoneNum) + vamfl(ZoneNum) + eamfl(ZoneNum) + ctmfl(ZoneNum) &
+ SumHmARa(ZoneNum) + MixingMassFlowZone(ZoneNum) + MDotOA(ZoneNum)
if (SimulateAirflowNetwork == AirflowNetworkControlMultizone .OR. SimulateAirflowNetwork == AirflowNetworkControlMultiADS.OR. &
(SimulateAirflowNetwork == AirflowNetworkControlSimpleADS .AND. AirflowNetworkFanActivated)) then
! Multizone airflow calculated in AirflowNetwork
B = (LatentGain/H2OHtOfVap)+(AirflowNetworkExchangeData(ZoneNum)%SumMHrW+AirflowNetworkExchangeData(ZoneNum)%SumMMHrW)+ &
(MoistureMassFlowRate)+SumHmARaW(ZoneNum)
A = TotExitMassFlowRate + AirflowNetworkExchangeData(ZoneNum)%SumMHr +AirflowNetworkExchangeData(ZoneNum)%SumMMHr + &
SumHmARa(ZoneNum)
end if
C = RhoAir*Zone(ZoneNum)%Volume*ZoneVolCapMultpMoist/SysTimeStepInSeconds
ELSE IF (ZoneMassFlowRate .LE. 0.0d0) THEN
B = (LatentGain/H2OHtOfVap)+((oamfl(ZoneNum)+vamfl(ZoneNum)+eamfl(ZoneNum)+ctmfl(ZoneNum)+ExhMassFlowRate)* OutHumRat) &
+SumHmARaW(ZoneNum) + MixingMassFlowXHumRat(ZoneNum)
A = oamfl(ZoneNum) + vamfl(ZoneNum) + eamfl(ZoneNum) +ctmfl(ZoneNum) + ExhMassFlowRate + SumHmARa(ZoneNum) &
+ MixingMassFlowZone(ZoneNum)
if (SimulateAirflowNetwork == AirflowNetworkControlMultizone .OR. SimulateAirflowNetwork == AirflowNetworkControlMultiADS .OR. &
(SimulateAirflowNetwork == AirflowNetworkControlSimpleADS .AND. AirflowNetworkFanActivated)) then
! Multizone airflow calculated in AirflowNetwork
B = (LatentGain/H2OHtOfVap) + SumHmARaW(ZoneNum)+ &
AirflowNetworkExchangeData(ZoneNum)%SumMHrW+AirflowNetworkExchangeData(ZoneNum)%SumMMHrW
A = AirflowNetworkExchangeData(ZoneNum)%SumMHr+AirflowNetworkExchangeData(ZoneNum)%SumMMHr+ &
SumHmARa(ZoneNum)
end if
C = RhoAir*Zone(ZoneNum)%Volume*ZoneVolCapMultpMoist/SysTimeStepInSeconds
END IF
if (SimulateAirflowNetwork > AirflowNetworkControlMultizone) then
B = B+AirflowNetworkExchangeData(ZoneNum)%TotalLat
end if
! Use a 3rd order derivative to predict final zone humidity ratio and
! smooth the changes using the zone air capacitance.
SELECT CASE (ZoneAirSolutionAlgo)
CASE (Use3rdOrder)
ZoneAirHumRatTemp(ZoneNum)=(B+C*(3.0d0*WZoneTimeMinus1Temp(ZoneNum)-(3.0d0/2.0d0)*WZoneTimeMinus2Temp(ZoneNum)+ &
(1.0d0/3.0d0)*WZoneTimeMinus3Temp(ZoneNum)))/((11.0d0/6.0d0)*C+A)
! Exact solution
CASE (UseAnalyticalSolution)
If (A .eq. 0.0d0) Then ! B=0
ZoneAirHumRatTemp(ZoneNum)= ZoneW1(ZoneNum) + B/C
Else
ZoneAirHumRatTemp(ZoneNum)= (ZoneW1(ZoneNum)-B/A)*exp(MIN(700.d0,-A/C))+B/A
End If
CASE (UseEulerMethod)
ZoneAirHumRatTemp(ZoneNum) = (C*ZoneW1(ZoneNum)+B)/(C+A)
END SELECT
! Set the humidity ratio to zero if the zone has been dried out
IF (ZoneAirHumRatTemp(ZoneNum) .LT. 0.0d0) ZoneAirHumRatTemp(ZoneNum) = 0.0d0
! Check to make sure that is saturated there is condensation in the zone
! by resetting to saturation conditions.
Wzsat = PsyWFnTdbRhPb(Zt(ZoneNum),1.0d0,OutBaroPress,'CorrectZoneHumRat')
IF (ZoneAirHumRatTemp(ZoneNum) .GT. Wzsat) ZoneAirHumRatTemp(ZoneNum) = Wzsat
! Now put the calculated info into the actual zone nodes; ONLY if there is zone air flow, i.e. controlled zone or plenum zone
ZoneNodeNum = Zone(ZoneNum)%SystemZoneNodeNumber
IF (ZoneNodeNum > 0) THEN
Node(ZoneNodeNum)%HumRat = ZoneAirHumRatTemp(ZoneNum)
Node(ZoneNodeNum)%Enthalpy = PsyHFnTdbW(ZT(ZoneNum),ZoneAirHumRatTemp(ZoneNum))
END IF
RETURN
END SUBROUTINE CorrectZoneHumRat