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 CalcPredictedHumidityRatio(ZoneNum)
! SUBROUTINE INFORMATION:
! AUTHOR Richard J. Liesen
! DATE WRITTEN May 2001
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine does the prediction step for humidity control
! METHODOLOGY EMPLOYED:
! This solves for the required system moisture required to try and achieve the desired
! Humidity Ratio in the Zone
! REFERENCES:
! Routine FinalZnCalcs - FINAL ZONE CALCULATIONS, authored by Dale Herron
! for BLAST.
! USE STATEMENTS:
USE ScheduleManager, ONLY: GetCurrentScheduleValue
USE General, ONLY: RoundSigDigits
USE DataSurfaces, ONLY: Surface, HeatTransferModel_EMPD, HeatTransferModel_HAMT
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:
REAL(r64) :: LatentGain ! Zone latent load
REAL(r64) :: RhoAir
REAL(r64) :: A
REAL(r64) :: B
REAL(r64) :: C
REAL(r64) :: SysTimeStepInSeconds
REAL(r64) :: H2OHtOfVap
REAL(r64) :: RHSetPoint ! Relative Humidity in percent
REAL(r64) :: WZoneSetPoint
INTEGER :: HumidControlledZoneNum
LOGICAL :: ControlledHumidZoneFlag ! This determines whether this is a humidity controlled zone or not
REAL(r64) :: ZoneRHHumidifyingSetPoint ! Zone humidifying set point (%)
REAL(r64) :: ZoneRHDehumidifyingSetPoint ! Zone dehumidifying set point (%)
REAL(r64) :: LoadToHumidifySetPoint ! Moisture load at humidifying set point
REAL(r64) :: LoadToDehumidifySetPoint ! Moisture load at dehumidifying set point
REAL(r64) :: ZoneAirRH ! Zone air relative humidity
LOGICAL :: SingleSetpoint ! This determines whether both setpoint are equal or not
! FLOW:
LoadToHumidifySetPoint=0.0d0
LoadToDehumidifySetPoint=0.0d0
SingleSetpoint = .FALSE.
ZoneSysMoistureDemand(ZoneNum)%TotalOutputRequired = 0.0d0
ZoneSysMoistureDemand(ZoneNum)%OutputRequiredToHumidifyingSP = 0.0d0
ZoneSysMoistureDemand(ZoneNum)%OutputRequiredToDehumidifyingSP = 0.0d0
! Check to see if this is a "humidity controlled zone"
ControlledHumidZoneFlag = .FALSE.
! Check all the controlled zones to see if it matches the zone simulated
DO HumidControlledZoneNum = 1, NumHumidityControlZones
IF (HumidityControlZone(HumidControlledZoneNum)%ActualZoneNum /= ZoneNum) CYCLE
ZoneAirRH = PsyRhFnTdbWPb(MAT(ZoneNum),ZoneAirHumRat(ZoneNum),OutBaroPress)*100.d0
ZoneRHHumidifyingSetPoint = GetCurrentScheduleValue(HumidityControlZone(HumidControlledZoneNum)%HumidifyingSchedIndex)
ZoneRHDehumidifyingSetPoint = GetCurrentScheduleValue(HumidityControlZone(HumidControlledZoneNum)%DehumidifyingSchedIndex)
IF (HumidityControlZone(HumidControlledZoneNum)%EMSOverrideHumidifySetpointOn) THEN
ZoneRHHumidifyingSetPoint = HumidityControlZone(HumidControlledZoneNum)%EMSOverrideHumidifySetpointValue
ENDIF
IF (HumidityControlZone(HumidControlledZoneNum)%EMSOverrideDehumidifySetpointOn) THEN
ZoneRHDehumidifyingSetPoint = HumidityControlZone(HumidControlledZoneNum)%EMSOverrideDehumidifySetpointValue
ENDIF
! Run-time error check
If (ZoneRHHumidifyingSetPoint > ZoneRHDehumidifyingSetPoint) then
! HumidityControlZone(HumidControlledZoneNum)%ErrorCount = HumidityControlZone(HumidControlledZoneNum)%ErrorCount + 1
if (HumidityControlZone(HumidControlledZoneNum)%ErrorIndex == 0) then
CALL ShowWarningMessage('HUMIDISTAT: The humidifying setpoint is above '// &
'the dehumidifying setpoint in '//TRIM(HumidityControlZone(HumidControlledZoneNum)%ControlName))
CALL ShowContinueError('The zone humidifying setpoint is set to the dehumidifying setpoint.')
CALL ShowContinueErrorTimeStamp(' Occurrence info: ')
endif
CALL ShowRecurringWarningErrorAtEnd('The humidifying setpoint is still above '// &
'the dehumidifying setpoint',HumidityControlZone(HumidControlledZoneNum)%ErrorIndex, &
ZoneRHHumidifyingSetPoint, ZoneRHHumidifyingSetPoint)
ZoneRHHumidifyingSetPoint = ZoneRHDehumidifyingSetPoint
End If
IF (ZoneRHHumidifyingSetPoint == ZoneRHDehumidifyingSetPoint) SingleSetpoint = .TRUE.
ControlledHumidZoneFlag = .TRUE.
EXIT
END DO ! HumidControlledZoneNum
If (ControlledHumidZoneFlag) Then
! Calculate hourly humidity ratio from infiltration + humidity added from latent load
! to determine system added/subtracted 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.
! SumHmARaW and SumHmARa will be used with the Moisture Balance on the building elements and
! are currently set to zero when the CTF only version is used.
! if no surface in the zone uses EMPD or HAMT then zero
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
! The density of air and latent heat of vaporization are calculated as functions.
RhoAir = PsyRhoAirFnPbTdbW(OutBaroPress,ZT(ZoneNum),ZoneAirHumRat(ZoneNum),'CalcPredictedHumidityRatio')
H2OHtOfVap = PsyHgAirFnWTdb(ZoneAirHumRat(ZoneNum),ZT(ZoneNum),'CalcPredictedHumidityRatio')
! Assume that the system will have flow
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+SumHmARaW(ZoneNum)
A = AirflowNetworkExchangeData(ZoneNum)%SumMHr+AirflowNetworkExchangeData(ZoneNum)%SumMMHr + &
SumHmARa(ZoneNum)
else
B = (LatentGain / H2OHtOfVap) + ((oamfl(ZoneNum) + vamfl(ZoneNum) + eamfl(ZoneNum) + ctmfl(ZoneNum)) * OutHumRat) + &
SumHmARaW(ZoneNum) + MixingMassFlowXHumRat(ZoneNum) + MDotOA(ZoneNum)* OutHumRat
A = oamfl(ZoneNum) + vamfl(ZoneNum) + eamfl(ZoneNum) + ctmfl(ZoneNum) + SumHmARa(ZoneNum) + MixingMassFlowZone(ZoneNum) &
+ MDotOA(ZoneNum)
end if
C = RhoAir * Zone(ZoneNum)%Volume * ZoneVolCapMultpMoist / SysTimeStepInSeconds
! Use a 3rd Order derivative to predict zone moisture addition or removal and
! smooth the changes using the zone air capacitance. Positive values of Moist Load means that
! this amount of moisture must be added to the zone to reach the setpoint. Negative values represent
! the amount of moisture that must be removed by the system.
!MoistLoadHumidSetPoint = massflow * HumRat = kg air/sec * kg H2O/kg Air = kg H2O/sec
WZoneSetPoint = PsyWFnTdbRhPb(ZT(ZoneNum),(ZoneRHHumidifyingSetPoint/100.0d0),OutBaroPress,'CalcPredictedHumidityRatio')
SELECT CASE (ZoneAirSolutionAlgo)
CASE (Use3rdOrder)
LoadToHumidifySetPoint = ((11.0d0/6.0d0) * C + A) * WZoneSetPoint - &
(B + C * (3.0d0 * WZoneTimeMinus1Temp(ZoneNum) - (3.0d0/2.0d0) * WZoneTimeMinus2Temp(ZoneNum) + &
(1.0d0/3.0d0) * WZoneTimeMinus3Temp(ZoneNum)))
! Exact solution
CASE (UseAnalyticalSolution)
If (A .eq. 0.0d0) Then ! B=0
LoadToHumidifySetPoint = C*(WZoneSetPoint-ZoneW1(ZoneNum)) - B
Else
LoadToHumidifySetPoint = A*(WZoneSetPoint-ZoneW1(ZoneNum)*exp(MIN(700.d0,-A/C)))/(1.0d0-exp(MIN(700.d0,-A/C))) - B
End If
CASE (UseEulerMethod)
LoadToHumidifySetPoint = C*(WZoneSetPoint-ZoneW1(ZoneNum)) + A*WZoneSetPoint - B
END SELECT
ZoneSysMoistureDemand(ZoneNum)%OutputRequiredToHumidifyingSP = LoadToHumidifySetPoint
WZoneSetPoint = PsyWFnTdbRhPb(ZT(ZoneNum),(ZoneRHDehumidifyingSetPoint / 100.0d0),OutBaroPress,'CalcPredictedHumidityRatio')
SELECT CASE (ZoneAirSolutionAlgo)
CASE (Use3rdOrder)
LoadToDehumidifySetPoint = ((11.0d0/6.0d0) * C + A) * WZoneSetPoint - &
(B + C * (3.0d0 * WZoneTimeMinus1Temp(ZoneNum) - (3.0d0/2.0d0) * WZoneTimeMinus2Temp(ZoneNum) + &
(1.0d0/3.0d0) * WZoneTimeMinus3Temp(ZoneNum)))
! Exact solution
CASE (UseAnalyticalSolution)
If (A .eq. 0.0d0) Then ! B=0
LoadToDehumidifySetPoint = C*(WZoneSetPoint-ZoneW1(ZoneNum)) - B
Else
LoadToDehumidifySetPoint = A*(WZoneSetPoint-ZoneW1(ZoneNum)*exp(MIN(700.d0,-A/C)))/(1.0d0-exp(MIN(700.d0,-A/C))) - B
End If
CASE (UseEulerMethod)
LoadToDehumidifySetPoint = C*(WZoneSetPoint-ZoneW1(ZoneNum)) + A*WZoneSetPoint - B
END SELECT
ZoneSysMoistureDemand(ZoneNum)%OutputRequiredToDehumidifyingSP = LoadToDehumidifySetPoint
! The load is added to the TotalOutputRequired as in the Temperature Predictor. There is also the remaining
! output variable for those who will use this for humidity control and stored in DataZoneEnergyDemands with the
! analogous temperature terms.
If (SingleSetpoint) Then
ZoneSysMoistureDemand(ZoneNum)%TotalOutputRequired = LoadToHumidifySetPoint
Else
IF (LoadToHumidifySetPoint .GT. 0.0d0 .AND. LoadToDehumidifySetPoint .GT. 0.0d0) THEN
ZoneSysMoistureDemand(ZoneNum)%TotalOutputRequired = LoadToHumidifySetPoint
RHSetPoint = ZoneRHHumidifyingSetPoint
ELSE IF (LoadToHumidifySetPoint .LT. 0.0d0 .AND. LoadToDehumidifySetPoint .LT. 0.0d0) THEN
ZoneSysMoistureDemand(ZoneNum)%TotalOutputRequired = LoadToDehumidifySetPoint
RHSetPoint = ZoneRHDehumidifyingSetPoint
ELSE IF (LoadToHumidifySetPoint .LE. 0.0d0 .AND. LoadToDehumidifySetPoint .GE. 0.0d0) THEN ! deadband includes zero loads
ZoneSysMoistureDemand(ZoneNum)%TotalOutputRequired = 0.0d0
ELSE ! this should never occur!
CALL ShowSevereError('Humidistat: Unanticipated combination of humidifying and dehumidifying loads - '// &
'report to EnergyPlus Development Team')
CALL ShowContinueErrorTimeStamp('occurs in Zone='//TRIM(Zone(ZoneNum)%Name))
CALL ShowContinueError('LoadToHumidifySetPoint='//TRIM(RoundSigDigits(LoadToHumidifySetPoint,5))// &
', LoadToDehumidifySetPoint='//TRIM(RoundSigDigits(LoadToDehumidifySetPoint,5)))
CALL ShowContinueError('Zone RH Humidifying Set-point='//TRIM(RoundSigDigits(ZoneRHHumidifyingSetPoint,1)))
CALL ShowContinueError('Zone RH Dehumidifying Set-point='//TRIM(RoundSigDigits(ZoneRHDehumidifyingSetPoint,2)))
CALL ShowFatalError('Program terminates due to above conditions.')
END IF
End If
End If
! Save the unmultiplied zone moisture load to a report variable
MoisturePredictedRate(ZoneNum) = ZoneSysMoistureDemand(ZoneNum)%TotalOutputRequired
! Apply the Zone Multiplier to the total zone moisture load
ZoneSysMoistureDemand(ZoneNum)%TotalOutputRequired = ZoneSysMoistureDemand(ZoneNum)%TotalOutputRequired &
* Zone(ZoneNum)%Multiplier * Zone(ZoneNum)%ListMultiplier
ZoneSysMoistureDemand(ZoneNum)%OutputRequiredToHumidifyingSP = ZoneSysMoistureDemand(ZoneNum)%OutputRequiredToHumidifyingSP &
* Zone(ZoneNum)%Multiplier * Zone(ZoneNum)%ListMultiplier
ZoneSysMoistureDemand(ZoneNum)%OutputRequiredToDehumidifyingSP = ZoneSysMoistureDemand(ZoneNum)%OutputRequiredToDehumidifyingSP &
* Zone(ZoneNum)%Multiplier * Zone(ZoneNum)%ListMultiplier
!init each sequenced demand to the full output
IF (ALLOCATED(ZoneSysMoistureDemand(ZoneNum)%SequencedOutputRequired)) &
ZoneSysMoistureDemand(ZoneNum)%SequencedOutputRequired = & ! array assignment
ZoneSysMoistureDemand(ZoneNum)%TotalOutputRequired
IF (ALLOCATED(ZoneSysMoistureDemand(ZoneNum)%SequencedOutputRequiredToHumidSP)) &
ZoneSysMoistureDemand(ZoneNum)%SequencedOutputRequiredToHumidSP = & ! array assignment
ZoneSysMoistureDemand(ZoneNum)%OutputRequiredToHumidifyingSP
IF (ALLOCATED(ZoneSysMoistureDemand(ZoneNum)%SequencedOutputRequiredToDehumidSP)) &
ZoneSysMoistureDemand(ZoneNum)%SequencedOutputRequiredToDehumidSP = & ! array assignment
ZoneSysMoistureDemand(ZoneNum)%OutputRequiredToDehumidifyingSP
RETURN
END SUBROUTINE CalcPredictedHumidityRatio