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 | ||
---|---|---|---|---|---|---|
logical, | intent(in) | :: | ShortenTimeStepSys | |||
logical, | intent(in) | :: | UseZoneTimeStepHistory | |||
real(kind=r64), | intent(in) | :: | PriorTimeStep |
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 CorrectZoneContaminants(ShortenTimeStepSys, UseZoneTimeStepHistory, PriorTimeStep)
! SUBROUTINE INFORMATION:
! AUTHOR Lixing Gu
! DATE WRITTEN July, 2010
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine updates the zone contaminants.
! This subroutine is modified from CorrectZoneHumRat in ZoneTempPredictorCorrector module
! 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
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
LOGICAL, INTENT(IN) :: ShortenTimeStepSys
LOGICAL, INTENT(IN) :: UseZoneTimeStepHistory ! if true then use zone timestep history, if false use system time step history
REAL(r64), INTENT(IN) :: PriorTimeStep ! the old value for timestep length is passed for possible use in interpolating
! 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) :: CO2Gain ! Zone CO2 internal gain
REAL(r64) :: GCGain ! Zone generic contaminant internal gain
REAL(r64) :: RhoAir
REAL(r64) :: A
REAL(r64) :: B
REAL(r64) :: C
REAL(r64) :: CO2MassFlowRate
REAL(r64) :: GCMassFlowRate
REAL(r64) :: ExhMassFlowRate
REAL(r64) :: TotExitMassFlowRate
REAL(r64) :: ZoneMassFlowRate
REAL(r64) :: SysTimeStepInSeconds
REAL(r64) :: ZoneMult
INTEGER :: ADUListIndex
INTEGER :: ADUNum
INTEGER :: ADUInNode
INTEGER :: ADUOutNode
INTEGER :: ZoneNum
! FLOW:
! Update zone CO2
DO ZoneNum = 1, NumOfZones
IF (Contaminant%CO2Simulation) Then
AZ(ZoneNum) = 0.0d0
BZ(ZoneNum) = 0.0d0
CZ(ZoneNum) = 0.0d0
End If
IF (Contaminant%GenericContamSimulation) Then
AZGC(ZoneNum) = 0.0d0
BZGC(ZoneNum) = 0.0d0
CZGC(ZoneNum) = 0.0d0
End If
! Update variables
IF (ShortenTimeStepSys) THEN
!time step has gotten smaller, use zone timestep history to interpolate new set of "DS" history terms.
If (NumOfSysTimeSteps /= NumOfSysTimeStepsLastZoneTimeStep) then ! cannot reuse existing DS data, interpolate from zone time
IF (Contaminant%CO2Simulation) Then
Call DownInterpolate4HistoryValues(PriorTimeStep,TimeStepSys, &
ZoneAirCO2(ZoneNum), CO2ZoneTimeMinus1(ZoneNum), CO2ZoneTimeMinus2(ZoneNum), & !
CO2ZoneTimeMinus3(ZoneNum), CO2ZoneTimeMinus4(ZoneNum), & !
ZoneAirCO2(ZoneNum), DSCO2ZoneTimeMinus1(ZoneNum), DSCO2ZoneTimeMinus2(ZoneNum), &
DSCO2ZoneTimeMinus3(ZoneNum), DSCO2ZoneTimeMinus4(ZoneNum))
ENDIF
IF (Contaminant%GenericContamSimulation) Then
Call DownInterpolate4HistoryValues(PriorTimeStep,TimeStepSys, &
ZoneAirGC(ZoneNum), GCZoneTimeMinus1(ZoneNum), GCZoneTimeMinus2(ZoneNum), & !
GCZoneTimeMinus3(ZoneNum), GCZoneTimeMinus4(ZoneNum), & !
ZoneAirGC(ZoneNum), DSGCZoneTimeMinus1(ZoneNum), DSGCZoneTimeMinus2(ZoneNum), &
DSGCZoneTimeMinus3(ZoneNum), DSGCZoneTimeMinus4(ZoneNum))
ENDIF
ELSE ! reuse history data in DS terms from last zone time step to preserve information that would be lost
! do nothing because DS history would have been pushed prior and should be ready?
ENDIF
ENDIF
! now update the variables actually used in the balance equations.
IF(.not. UseZoneTimeStepHistory) THEN
IF (Contaminant%CO2Simulation) Then
CO2ZoneTimeMinus1Temp(ZoneNum) = DSCO2ZoneTimeMinus1(ZoneNum)
CO2ZoneTimeMinus2Temp(ZoneNum) = DSCO2ZoneTimeMinus2(ZoneNum)
CO2ZoneTimeMinus3Temp(ZoneNum) = DSCO2ZoneTimeMinus3(ZoneNum)
END IF
IF (Contaminant%GenericContamSimulation) Then
GCZoneTimeMinus1Temp(ZoneNum) = DSGCZoneTimeMinus1(ZoneNum)
GCZoneTimeMinus2Temp(ZoneNum) = DSGCZoneTimeMinus2(ZoneNum)
GCZoneTimeMinus3Temp(ZoneNum) = DSGCZoneTimeMinus3(ZoneNum)
END IF
ELSE
IF (Contaminant%CO2Simulation) Then
CO2ZoneTimeMinus1Temp(ZoneNum) = CO2ZoneTimeMinus1(ZoneNum)
CO2ZoneTimeMinus2Temp(ZoneNum) = CO2ZoneTimeMinus2(ZoneNum)
CO2ZoneTimeMinus3Temp(ZoneNum) = CO2ZoneTimeMinus3(ZoneNum)
END IF
IF (Contaminant%GenericContamSimulation) Then
GCZoneTimeMinus1Temp(ZoneNum) = GCZoneTimeMinus1(ZoneNum)
GCZoneTimeMinus2Temp(ZoneNum) = GCZoneTimeMinus2(ZoneNum)
GCZoneTimeMinus3Temp(ZoneNum) = GCZoneTimeMinus3(ZoneNum)
END IF
END IF
! Start to calculate zone CO2 and genric contaminant levels
CO2MassFlowRate = 0.0d0
GCMassFlowRate = 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
IF (Contaminant%CO2Simulation) Then
CO2MassFlowRate = CO2MassFlowRate + &
(Node(ZoneEquipConfig(ZoneEquipConfigNum)%InletNode(NodeNum))%MassFlowRate * &
Node(ZoneEquipConfig(ZoneEquipConfigNum)%InletNode(NodeNum))%CO2) / ZoneMult
End If
IF (Contaminant%GenericContamSimulation) Then
GCMassFlowRate = GCMassFlowRate + &
(Node(ZoneEquipConfig(ZoneEquipConfigNum)%InletNode(NodeNum))%MassFlowRate * &
Node(ZoneEquipConfig(ZoneEquipConfigNum)%InletNode(NodeNum))%GenContam) / ZoneMult
End If
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
IF (Contaminant%CO2Simulation) Then
CO2MassFlowRate = CO2MassFlowRate + &
(Node(ZoneRetPlenCond(ZoneRetPlenumNum)%InletNode(NodeNum))%MassFlowRate * &
Node(ZoneRetPlenCond(ZoneRetPlenumNum)%InletNode(NodeNum))%CO2) / ZoneMult
End If
IF (Contaminant%GenericContamSimulation) Then
GCMassFlowRate = GCMassFlowRate + &
(Node(ZoneRetPlenCond(ZoneRetPlenumNum)%InletNode(NodeNum))%MassFlowRate * &
Node(ZoneRetPlenCond(ZoneRetPlenumNum)%InletNode(NodeNum))%GenContam) / ZoneMult
End If
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
IF (Contaminant%CO2Simulation) Then
CO2MassFlowRate = CO2MassFlowRate + &
(AirDistUnit(ADUNum)%MassFlowRateUpStrLk * Node(ADUInNode)%CO2) / ZoneMult
End If
IF (Contaminant%GenericContamSimulation) Then
GCMassFlowRate = GCMassFlowRate + &
(AirDistUnit(ADUNum)%MassFlowRateUpStrLk * Node(ADUInNode)%GenContam) / ZoneMult
End If
ZoneMassFlowRate = ZoneMassFlowRate + AirDistUnit(ADUNum)%MassFlowRateUpStrLk / ZoneMult
END IF
IF (AirDistUnit(ADUNum)%DownStreamLeak) THEN
ADUOutNode = AirDistUnit(ADUNum)%OutletNodeNum
IF (Contaminant%CO2Simulation) Then
CO2MassFlowRate = CO2MassFlowRate + &
(AirDistUnit(ADUNum)%MassFlowRateDnStrLk * Node(ADUOutNode)%CO2) / ZoneMult
End If
IF (Contaminant%GenericContamSimulation) Then
GCMassFlowRate = GCMassFlowRate + &
(AirDistUnit(ADUNum)%MassFlowRateDnStrLk * Node(ADUOutNode)%GenContam) / ZoneMult
End If
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
IF (Contaminant%CO2Simulation) Then
CO2MassFlowRate = CO2MassFlowRate + &
(Node(ZoneSupPlenCond(ZoneSupPlenumNum)%InletNode)%MassFlowRate * &
Node(ZoneSupPlenCond(ZoneSupPlenumNum)%InletNode)%CO2) / ZoneMult
END IF
IF (Contaminant%GenericContamSimulation) Then
GCMassFlowRate = GCMassFlowRate + &
(Node(ZoneSupPlenCond(ZoneSupPlenumNum)%InletNode)%MassFlowRate * &
Node(ZoneSupPlenCond(ZoneSupPlenumNum)%InletNode)%GenContam) / ZoneMult
END IF
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
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
! CO2 balance. There are 2 cases that should be considered, system
! operating and system shutdown.
RhoAir = PsyRhoAirFnPbTdbW(OutBaroPress,ZT(ZoneNum),ZoneAirHumRat(ZoneNum),'CorrectZoneContaminants')
! RhoAir = ZoneAirDensityCO(ZoneNum)
IF (Contaminant%CO2Simulation) ZoneAirDensityCO(ZoneNum) = RhoAir
! Calculate Co2 internal gain
IF (Contaminant%CO2Simulation) CO2Gain = ZoneCO2Gain(ZoneNum)*RhoAir*1.0d6
IF (Contaminant%GenericContamSimulation) GCGain = ZoneGCGain(ZoneNum)*RhoAir*1.0d6
! Check for the flow and NO flow condition
IF (ZoneMassFlowRate .GT. 0.0d0) THEN
IF (Contaminant%CO2Simulation) Then
B = CO2Gain+((oamfl(ZoneNum)+vamfl(ZoneNum)+eamfl(ZoneNum)+ctmfl(ZoneNum))* OutdoorCO2) &
+(CO2MassFlowRate) &
+MixingMassFlowCO2(ZoneNum)
A = TotExitMassFlowRate + oamfl(ZoneNum) + vamfl(ZoneNum) + eamfl(ZoneNum) + ctmfl(ZoneNum) &
+ MixingMassFlowZone(ZoneNum)
if (SimulateAirflowNetwork == AirflowNetworkControlMultizone .OR. &
SimulateAirflowNetwork == AirflowNetworkControlMultiADS .OR. &
(SimulateAirflowNetwork == AirflowNetworkControlSimpleADS .AND. AirflowNetworkFanActivated)) then
! Multizone airflow calculated in AirflowNetwork
B = CO2Gain+(AirflowNetworkExchangeData(ZoneNum)%SumMHrCO+AirflowNetworkExchangeData(ZoneNum)%SumMMHrCO)+CO2MassFlowRate
A = ZoneMassFlowRate + AirflowNetworkExchangeData(ZoneNum)%SumMHr +AirflowNetworkExchangeData(ZoneNum)%SumMMHr
end if
C = RhoAir*Zone(ZoneNum)%Volume*ZoneVolCapMultpCO2/SysTimeStepInSeconds
End If
ELSE IF (ZoneMassFlowRate .LE. 0.0d0) THEN
IF (Contaminant%CO2Simulation) Then
B = CO2Gain+((oamfl(ZoneNum)+vamfl(ZoneNum)+eamfl(ZoneNum)+ctmfl(ZoneNum)+ExhMassFlowRate)* OutdoorCO2) &
+ MixingMassFlowCO2(ZoneNum)
A = oamfl(ZoneNum) + vamfl(ZoneNum) + eamfl(ZoneNum) +ctmfl(ZoneNum) + ExhMassFlowRate + MixingMassFlowZone(ZoneNum)
if (SimulateAirflowNetwork == AirflowNetworkControlMultizone .OR. &
SimulateAirflowNetwork == AirflowNetworkControlMultiADS .OR. &
(SimulateAirflowNetwork == AirflowNetworkControlSimpleADS .AND. AirflowNetworkFanActivated)) then
! Multizone airflow calculated in AirflowNetwork
B = CO2Gain+AirflowNetworkExchangeData(ZoneNum)%SumMHrCO+AirflowNetworkExchangeData(ZoneNum)%SumMMHrCO
A = AirflowNetworkExchangeData(ZoneNum)%SumMHr+AirflowNetworkExchangeData(ZoneNum)%SumMMHr
end if
C = RhoAir*Zone(ZoneNum)%Volume*ZoneVolCapMultpCO2/SysTimeStepInSeconds
End If
END IF
IF (Contaminant%CO2Simulation) Then
if (SimulateAirflowNetwork > AirflowNetworkControlMultizone) then
B = B+AirflowNetworkExchangeData(ZoneNum)%TotalCO2
end if
AZ(ZoneNum) = A
BZ(ZoneNum) = B
CZ(ZoneNum) = C
! Use a 3rd order derivative to predict final zone CO2 and
! smooth the changes using the zone air capacitance.
SELECT CASE (ZoneAirSolutionAlgo)
CASE (Use3rdOrder)
ZoneAirCO2Temp(ZoneNum)=(B+C*(3.0d0*CO2ZoneTimeMinus1Temp(ZoneNum)-(3.0d0/2.0d0)*Co2ZoneTimeMinus2Temp(ZoneNum)+ &
(1.0d0/3.0d0)*Co2ZoneTimeMinus3Temp(ZoneNum)))/((11.0d0/6.0d0)*C+A)
! Exact solution
CASE (UseAnalyticalSolution)
If (A .eq. 0.0d0) Then ! B=0
ZoneAirCO2Temp(ZoneNum)= ZoneCO21(ZoneNum) + B/C
Else
ZoneAirCO2Temp(ZoneNum)= (ZoneCO21(ZoneNum)-B/A)*exp(MIN(700.d0,-A/C))+B/A
End If
CASE (UseEulerMethod)
ZoneAirCO2Temp(ZoneNum) = (C*ZoneCO21(ZoneNum)+B)/(C+A)
END SELECT
! Set the CO2 to zero if the zone has been large sinks
IF (ZoneAirCO2Temp(ZoneNum) .LT. 0.0d0) ZoneAirCO2Temp(ZoneNum) = 0.0d0
ZoneAirCO2(ZoneNum) = ZoneAirCO2Temp(ZoneNum)
! 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)%CO2 = ZoneAirCO2Temp(ZoneNum)
END IF
END IF
IF (ZoneMassFlowRate .GT. 0.0d0) THEN
IF (Contaminant%GenericContamSimulation) Then
B = GCGain+((oamfl(ZoneNum)+vamfl(ZoneNum)+eamfl(ZoneNum)+ctmfl(ZoneNum))* OutdoorGC) &
+(GCMassFlowRate) &
+MixingMassFlowGC(ZoneNum)
A = TotExitMassFlowRate + oamfl(ZoneNum) + vamfl(ZoneNum) + eamfl(ZoneNum) + ctmfl(ZoneNum) &
+ MixingMassFlowZone(ZoneNum)
if (SimulateAirflowNetwork == AirflowNetworkControlMultizone .OR. &
SimulateAirflowNetwork == AirflowNetworkControlMultiADS .OR. &
(SimulateAirflowNetwork == AirflowNetworkControlSimpleADS .AND. AirflowNetworkFanActivated)) then
! Multizone airflow calculated in AirflowNetwork
B = GCGain+(AirflowNetworkExchangeData(ZoneNum)%SumMHrGC+AirflowNetworkExchangeData(ZoneNum)%SumMMHrGC)+GCMassFlowRate
A = ZoneMassFlowRate + AirflowNetworkExchangeData(ZoneNum)%SumMHr +AirflowNetworkExchangeData(ZoneNum)%SumMMHr
end if
C = RhoAir*Zone(ZoneNum)%Volume*ZoneVolCapMultpGenContam/SysTimeStepInSeconds
End If
ELSE IF (ZoneMassFlowRate .LE. 0.0d0) THEN
IF (Contaminant%GenericContamSimulation) Then
B = GCGain+((oamfl(ZoneNum)+vamfl(ZoneNum)+eamfl(ZoneNum)+ctmfl(ZoneNum)+ExhMassFlowRate)* OutdoorGC) &
+ MixingMassFlowGC(ZoneNum)
A = oamfl(ZoneNum) + vamfl(ZoneNum) + eamfl(ZoneNum) +ctmfl(ZoneNum) + ExhMassFlowRate + MixingMassFlowZone(ZoneNum)
if (SimulateAirflowNetwork == AirflowNetworkControlMultizone .OR. &
SimulateAirflowNetwork == AirflowNetworkControlMultiADS .OR. &
(SimulateAirflowNetwork == AirflowNetworkControlSimpleADS .AND. AirflowNetworkFanActivated)) then
! Multizone airflow calculated in AirflowNetwork
B = GCGain+AirflowNetworkExchangeData(ZoneNum)%SumMHrGC+AirflowNetworkExchangeData(ZoneNum)%SumMMHrGC
A = AirflowNetworkExchangeData(ZoneNum)%SumMHr+AirflowNetworkExchangeData(ZoneNum)%SumMMHr
end if
C = RhoAir*Zone(ZoneNum)%Volume*ZoneVolCapMultpGenContam/SysTimeStepInSeconds
End If
END IF
IF (Contaminant%GenericContamSimulation) Then
if (SimulateAirflowNetwork > AirflowNetworkControlMultizone) then
B = B+AirflowNetworkExchangeData(ZoneNum)%TotalGC
end if
AZGC(ZoneNum) = A
BZGC(ZoneNum) = B
CZGC(ZoneNum) = C
! Use a 3rd order derivative to predict final zone generic contaminant and
! smooth the changes using the zone air capacitance.
SELECT CASE (ZoneAirSolutionAlgo)
CASE (Use3rdOrder)
ZoneAirGCTemp(ZoneNum)=(B+C*(3.0d0*GCZoneTimeMinus1Temp(ZoneNum)-(3.0d0/2.0d0)*GCZoneTimeMinus2Temp(ZoneNum)+ &
(1.0d0/3.0d0)*GCZoneTimeMinus3Temp(ZoneNum)))/((11.0d0/6.0d0)*C+A)
! Exact solution
CASE (UseAnalyticalSolution)
If (A .eq. 0.0d0) Then ! B=0
ZoneAirGCTemp(ZoneNum)= ZoneGC1(ZoneNum) + B/C
Else
ZoneAirGCTemp(ZoneNum)= (ZoneGC1(ZoneNum)-B/A)*exp(MIN(700.d0,-A/C))+B/A
End If
CASE (UseEulerMethod)
ZoneAirGCTemp(ZoneNum) = (C*ZoneGC1(ZoneNum)+B)/(C+A)
END SELECT
! Set the generic contaminant to zero if the zone has been large sinks
IF (ZoneAirGCTemp(ZoneNum) .LT. 0.0d0) ZoneAirGCTemp(ZoneNum) = 0.0d0
ZoneAirGC(ZoneNum) = ZoneAirGCTemp(ZoneNum)
! 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)%GenContam = ZoneAirGCTemp(ZoneNum)
END IF
END IF
END DO
RETURN
END SUBROUTINE CorrectZoneContaminants