MODULE ZoneDehumidifier ! Module containing the routines dealing with the ZoneDehumidifier ! MODULE INFORMATION: ! AUTHOR Don Shirey, FSEC ! DATE WRITTEN July/Aug 2009 ! MODIFIED na ! RE-ENGINEERED na ! PURPOSE OF THIS MODULE: ! Calculate the performance of zone (room) air dehumidifiers. Meant to model ! conventional direct expansion (DX) cooling-based room air dehumidifiers ! (reject 100% of condenser heat to the zone air), but the approach ! might be able to be used to model other room air dehumidifier types. ! METHODOLOGY EMPLOYED: ! Model as a piece of zone equipment, with inputs for water removal and ! energy factor at rated conditions (26.7C, 60% RH). Then provide curve objects ! to describe performance at off-rated conditions. A part-load cycling curve ! input is also provided. It is assumed that this equipment dehumidifies but ! heats the air. If used in tandem with another system that cools and dehumidifies, ! then the zone dehumidifier should be specified as the lowest cooling priority ! in the ZoneHVAC:EquipmentList object. The cooling and dehumidification system ! operates first to meet the temperature setpoint (and possibly the high humidity ! setpoint as well). If additional dehumidification is needed, then the zone ! dehumidifier operates. The excess sensible heat generated by the dehumidifier ! is carried over to the next HVAC time step. ! REFERENCES: ! na ! OTHER NOTES: ! Example manufacturer's data at: ! http://www.thermastor.com/HI-E-DRY-100/HI-E-DRY-100-Spec.pdf ! http://www.thermastor.com/HI-E-DRY-195/HI-E-DRY-195-Spec.pdf ! USE STATEMENTS: USE DataPrecisionGlobals USE DataLoopNode USE DataGlobals, ONLY: MaxNameLength, BeginEnvrnFlag, SecInHour, ScheduleAlwaysOn USE DataInterfaces, ONLY: ShowWarningError, ShowSevereError, ShowFatalError, ShowContinueError, & SetupOutputVariable, ShowRecurringWarningErrorAtEnd, ShowContinueErrorTimeSTamp USE DataEnvironment, ONLY: OutBaroPress, StdBaroPress USE General, ONLY: TrimSigDigits USE ScheduleManager IMPLICIT NONE ! Enforce explicit typing of all variables PRIVATE ! Everything private unless explicitly made public ! MODULE PARAMETER DEFINITIONS: ! Unit type index INTEGER, PARAMETER :: ZoneDehumidUnit = 1 ! 1 is the index for ZoneHVAC:Dehumidifier:DX ! Water Systems INTEGER, PARAMETER :: CondensateDiscarded = 1001 ! Default mode where water is "lost" INTEGER, PARAMETER :: CondensateToTank = 1002 ! Collect coil condensate from air and store in water storage tank ! DERIVED TYPE DEFINITIONS: TYPE ZoneDehumidifierData ! input data and others required during calculations CHARACTER(len=MaxNameLength) :: Name =' ' ! Name of unit CHARACTER(len=MaxNameLength) :: UnitType =' ' ! Type of unit INTEGER :: UnitType_Num = 0 ! Parameter equivalent to type of unit INTEGER :: SchedPtr = 0 ! Index number to availability schedule REAL(r64) :: RatedWaterRemoval = 0.0d0 ! Rated water removal [liters/day] REAL(r64) :: RatedEnergyFactor = 0.0d0 ! Rated energy factor [liters/kWh] REAL(r64) :: RatedAirVolFlow = 0.0d0 ! Rated air flow rate through the dehumidifier [m3/s] REAL(r64) :: RatedAirMassFlow = 0.0d0 ! Rated air mass flow rate through the dehumidifier [kg/s] REAL(r64) :: MinInletAirTemp = 0.0d0 ! Minimum dry-bulb temperature for dehumidifier operation [C] REAL(r64) :: MaxInletAirTemp = 0.0d0 ! Maximum dry-bulb temperature for dehumidifier operation [C] REAL(r64) :: InletAirMassFlow = 0.0d0 ! Inlet air mass flow rate for the time step being simulated [kg/s] REAL(r64) :: OutletAirEnthalpy = 0.0d0 ! Dehumidifier outlet air enthalpy [J/kg] REAL(r64) :: OutletAirHumRat = 0.0d0 ! Dehumidifier outlet air humidity ratio [kg/kg] REAL(r64) :: OffCycleParasiticLoad = 0.0d0 ! Off Cycle Parasitic Load, user input [W] INTEGER :: AirInletNodeNum = 0 ! Inlet air node number INTEGER :: AirOutletNodeNum = 0 ! Outlet air node number INTEGER :: WaterRemovalCurveIndex = 0 ! Index for water removal curve INTEGER :: WaterRemovalCurveType = 0 ! Water removal curve type. 2 = biquadratic INTEGER :: WaterRemovalCurveErrorCount = 0 ! Count number of times water removal curve returns a negative value INTEGER :: WaterRemovalCurveErrorIndex = 0 ! Index for negative value water removal factor recurring messages INTEGER :: EnergyFactorCurveIndex = 0 ! Index for energy factor curve INTEGER :: EnergyFactorCurveType = 0 ! Energy factor curve type. 2 = biquadratic INTEGER :: EnergyFactorCurveErrorCount = 0 ! Count number of times energy factor curve returns negative value INTEGER :: EnergyFactorCurveErrorIndex = 0 ! Index for negative value energy factor recurring messages INTEGER :: PartLoadCurveIndex = 0 ! Index for part load curve INTEGER :: PartLoadCurveType = 0 ! Part load curve type. 1 = quadratic, cubic = 3 INTEGER :: LowPLFErrorCount = 0 ! Count number of times PLF < 0.7 INTEGER :: LowPLFErrorIndex = 0 ! Index for PLF < 0.7 recurring warning messages INTEGER :: HighPLFErrorCount = 0 ! Count number of times PLF > 1.0 INTEGER :: HighPLFErrorIndex = 0 ! Index for PLF > 1.0 recurring warning messages INTEGER :: HighRTFErrorCount = 0 ! Count number of times RTF > 1.0 INTEGER :: HighRTFErrorIndex = 0 ! Index for RTF > 1.0 recurring warning messages INTEGER :: PLFPLRErrorCount = 0 ! Count number of times PLF < PLR INTEGER :: PLFPLRErrorIndex = 0 ! Index for PLF < PLR recurring warning messages INTEGER :: CondensateCollectMode = CondensateDiscarded ! Where does water come from CHARACTER(len=MaxNameLength) :: CondensateCollectName = ' ' ! Name of water storage (collection) tank INTEGER :: CondensateTankID = 0 ! Condensate collection tank ID number INTEGER :: CondensateTankSupplyARRID = 0 ! Condensate collection tank supply ID number ! Report data REAL(r64) :: SensHeatingRate = 0.0d0 ! Zone Dehumidifier Sensible Heating Rate [W] REAL(r64) :: SensHeatingEnergy = 0.0d0 ! Zone Dehumidifier Sensible Heating Energy [J] REAL(r64) :: WaterRemovalRate = 0.0d0 ! Zone Dehumidifier Water Removal Rate [kg/s] REAL(r64) :: WaterRemoved = 0.0d0 ! Zone Dehumidifier Water Removed [kg] REAL(r64) :: ElecPower = 0.0d0 ! Zone Dehumidifier Electric Power [W] REAL(r64) :: ElecConsumption = 0.0d0 ! Zone Dehumidifier Electric Consumption [J] REAL(r64) :: DehumidPLR = 0.0d0 ! Zone Dehumidifier Part-Load Ratio [-] REAL(r64) :: DehumidRTF = 0.0d0 ! Zone Dehumidifier Runtime Fraction [-] REAL(r64) :: DehumidCondVolFlowRate = 0.0d0 ! Zone Dehumidifier Condensate Volumetric Flow Rate [m3/s] REAL(r64) :: DehumidCondVol = 0.0d0 ! Zone Dehumidifier Condensate Volume [m3] REAL(r64) :: OutletAirTemp = 0.0d0 ! Zone Dehumidifier Outlet Air Temperature [C] REAL(r64) :: OffCycleParasiticElecPower = 0.0d0 ! Zone Dehumidifier Off-Cycle Parasitic Electric Power [W] REAL(r64) :: OffCycleParasiticElecCons = 0.0d0 ! Zone Dehumidifier Off-Cycle Parasitic Electric Consumption [J] END TYPE ZoneDehumidifierData ! MODULE VARIABLE DECLARATIONS: TYPE (ZoneDehumidifierData), ALLOCATABLE, DIMENSION(:) :: ZoneDehumid INTEGER :: NumDehumidifiers=0 ! Number of zone dehumidifier objects in the input file LOGICAL :: GetInputFlag = .TRUE. ! Set to FALSE after first time input is "gotten" LOGICAL, ALLOCATABLE, DIMENSION(:) :: CheckEquipName ! SUBROUTINE SPECIFICATIONS FOR MODULE: ! Driver/Manager Routines PUBLIC SimZoneDehumidifier ! Get Input routines for module PRIVATE GetZoneDehumidifierInput ! Initialization routines for module PRIVATE InitZoneDehumidifier PRIVATE SizeZoneDehumidifier ! Algorithms/Calculation routines for the module PRIVATE CalcZoneDehumidifier ! Update routine to update node information PRIVATE UpdateZoneDehumidifier ! Reporting routines for module PRIVATE ReportZoneDehumidifier ! Get either inlet or outlet node number PUBLIC GetZoneDehumidifierNodeNumber CONTAINS SUBROUTINE SimZoneDehumidifier(CompName,ZoneNum,FirstHVACIteration,QSensOut,QLatOut,CompIndex) ! SUBROUTINE INFORMATION: ! AUTHOR Don Shirey, FSEC ! DATE WRITTEN July/Aug 2009 ! MODIFIED na ! RE-ENGINEERED na ! PURPOSE OF THIS SUBROUTINE: ! Simulate a zone dehumidifier. ! METHODOLOGY EMPLOYED: ! Call appropriate subroutines to get input values, initialize variables, model performanc ! update node information, report model outputs. ! REFERENCES: ! na ! USE STATEMENTS: USE InputProcessor, ONLY: FindItemInList USE DataZoneEnergyDemands, ONLY: ZoneSysMoistureDemand IMPLICIT NONE ! Enforce explicit typing of all variables in this routine ! SUBROUTINE ARGUMENT DEFINITIONS: CHARACTER(len=*), INTENT (IN) :: CompName ! Name of the zone dehumidifier INTEGER, INTENT (IN) :: ZoneNum ! Number of zone being served LOGICAL, INTENT (IN) :: FirstHVACIteration ! TRUE if 1st HVAC simulation of system timestep REAL(r64), INTENT (OUT) :: QSensOut ! Sensible capacity delivered to zone (W) REAL(r64), INTENT (OUT) :: QLatOut ! Latent capacity delivered to zone (kg/s), dehumidify = negative INTEGER, INTENT (INOUT) :: CompIndex ! Index to the zone dehumidifier ! SUBROUTINE PARAMETER DEFINITIONS: ! na ! INTERFACE BLOCK SPECIFICATIONS: ! na ! DERIVED TYPE DEFINITIONS: ! na ! SUBROUTINE LOCAL VARIABLE DECLARATIONS: INTEGER :: ZoneDehumidNum ! Index of zone dehumidifier being simulated REAL(r64) :: QZnDehumidReq ! Zone dehumidification load required (kg moisture/sec) IF (GetInputFlag) THEN CALL GetZoneDehumidifierInput GetInputFlag=.FALSE. ENDIF ! Find the correct zone dehumidifier IF (CompIndex == 0) THEN ZoneDehumidNum = FindItemInList(CompName,ZoneDehumid%Name,NumDehumidifiers) IF (ZoneDehumidNum == 0) THEN CALL ShowFatalError('SimZoneDehumidifier: Unit not found= '//TRIM(CompName)) END IF CompIndex=ZoneDehumidNum ELSE ZoneDehumidNum=CompIndex IF (ZoneDehumidNum > NumDehumidifiers .or. ZoneDehumidNum < 1) THEN CALL ShowFatalError('SimZoneDehumidifier: Invalid CompIndex passed= '// & TRIM(TrimSigDigits(ZoneDehumidNum))// & ', Number of Units= '//TRIM(TrimSigDigits(NumDehumidifiers))// & ', Entered Unit name= '//TRIM(CompName)) END IF IF (CheckEquipName(ZoneDehumidNum)) THEN IF (CompName /= ZoneDehumid(ZoneDehumidNum)%Name) THEN CALL ShowFatalError('SimZoneDehumidifier: Invalid CompIndex passed='// & TRIM(TrimSigDigits(ZoneDehumidNum))// & ', Unit name= '//TRIM(CompName)//', stored Unit Name for that index= '// & TRIM(ZoneDehumid(ZoneDehumidNum)%Name)) END IF CheckEquipName(ZoneDehumidNum)=.false. ENDIF END IF QZnDehumidReq = ZoneSysMoistureDemand(ZoneNum)%RemainingOutputReqToDehumidSP ! Negative means dehumidify CALL InitZoneDehumidifier(ZoneDehumidNum) CALL CalcZoneDehumidifier(ZoneDehumidNum,QZnDehumidReq,QSensOut,QLatOut) CALL UpdateZoneDehumidifier(ZoneDehumidNum) CALL ReportZoneDehumidifier(ZoneDehumidNum) RETURN END SUBROUTINE SimZoneDehumidifier SUBROUTINE GetZoneDehumidifierInput ! SUBROUTINE INFORMATION: ! AUTHOR Don Shirey, FSEC ! DATE WRITTEN July/Aug 2009 ! MODIFIED na ! RE-ENGINEERED na ! PURPOSE OF THIS SUBROUTINE: ! Retrieve the inputs from the input data file (idf) being simulated. ! METHODOLOGY EMPLOYED: ! Standard EnergyPlus methodology using available utility routines where appropriate. ! REFERENCES: ! na ! USE STATEMENTS: USE InputProcessor, ONLY: GetNumObjectsFound, GetObjectItem, VerifyName, GetObjectDefMaxArgs USE NodeInputManager, ONLY: GetOnlySingleNode USE CurveManager, ONLY: GetCurveIndex, GetCurveType, CurveValue USE WaterManager, ONLY: SetupTankSupplyComponent IMPLICIT NONE ! Enforce explicit typing of all variables in this routine ! SUBROUTINE ARGUMENT DEFINITIONS: ! na ! SUBROUTINE PARAMETER DEFINITIONS: CHARACTER(len=*), PARAMETER :: RoutineName='GetZoneDehumidifierInput' CHARACTER(len=*), PARAMETER :: CurrentModuleObject='ZoneHVAC:Dehumidifier:DX' ! Curve Types INTEGER, PARAMETER :: Quadratic = 1 INTEGER, PARAMETER :: Biquadratic = 2 INTEGER, PARAMETER :: Cubic = 3 REAL(r64), PARAMETER :: RatedInletAirTemp = 26.7d0 REAL(r64), PARAMETER :: RatedInletAirRH = 60.0d0 ! INTERFACE BLOCK SPECIFICATIONS: ! na ! DERIVED TYPE DEFINITIONS: ! na ! SUBROUTINE LOCAL VARIABLE DECLARATIONS: INTEGER :: ZoneDehumidIndex ! Loop index INTEGER :: NumAlphas=0 ! Number of Alphas to allocate arrays, then used for each GetObjectItem call INTEGER :: NumNumbers=0 ! Number of Numbers to allocate arrays, then used for each GetObjectItem call INTEGER :: IOStatus ! Used in GetObjectItem LOGICAL :: ErrorsFound=.FALSE. ! Set to true if errors in input, fatal at end of routine LOGICAL :: IsNotOK ! Flag to verify name LOGICAL :: IsBlank ! Flag for blank name CHARACTER(len=MaxNameLength), ALLOCATABLE, DIMENSION(:) :: Alphas ! Alpha input items for object CHARACTER(len=MaxNameLength), ALLOCATABLE, DIMENSION(:) :: cAlphaFields ! Alpha field names CHARACTER(len=MaxNameLength), ALLOCATABLE, DIMENSION(:) :: cNumericFields ! Numeric field names REAL(r64), ALLOCATABLE, DIMENSION(:) :: Numbers ! Numeric input items for object LOGICAL, ALLOCATABLE, DIMENSION(:) :: lAlphaBlanks ! Logical array, alpha field input BLANK = .TRUE. LOGICAL, ALLOCATABLE, DIMENSION(:) :: lNumericBlanks ! Logical array, numeric field input BLANK = .TRUE. INTEGER :: TotalArgs=0 ! Total number of alpha and numeric arguments (max) REAL(r64) :: CurveVal ! Output from curve object (water removal or energy factor curves) NumDehumidifiers = GetNumObjectsFound(CurrentModuleObject) ALLOCATE(ZoneDehumid(NumDehumidifiers)) ALLOCATE(CheckEquipName(NumDehumidifiers)) CheckEquipName=.true. CALL GetObjectDefMaxArgs(CurrentModuleObject,TotalArgs,NumAlphas,NumNumbers) ALLOCATE(Alphas(NumAlphas)) Alphas=' ' ALLOCATE(cAlphaFields(NumAlphas)) cAlphaFields=' ' ALLOCATE(cNumericFields(NumNumbers)) cNumericFields=' ' ALLOCATE(Numbers(NumNumbers)) Numbers=0.0d0 ALLOCATE(lAlphaBlanks(NumAlphas)) lAlphaBlanks=.TRUE. ALLOCATE(lNumericBlanks(NumNumbers)) lNumericBlanks=.TRUE. DO ZoneDehumidIndex=1,NumDehumidifiers CALL GetObjectItem(CurrentModuleObject,ZoneDehumidIndex,Alphas,NumAlphas, & Numbers,NumNumbers,IOStatus, & AlphaBlank=lAlphaBlanks,NumBlank=lNumericBlanks, & AlphaFieldnames=cAlphaFields,NumericFieldNames=cNumericFields) IsNotOK=.FALSE. IsBlank=.FALSE. CALL VerifyName(Alphas(1),ZoneDehumid%Name,ZoneDehumidIndex-1,IsNotOK,IsBlank,TRIM(CurrentModuleObject)//' Name') IF (IsNotOK) THEN ErrorsFound=.TRUE. IF (IsBlank) Alphas(1)='xxxxx' END IF ! A1, \field Name ZoneDehumid(ZoneDehumidIndex)%Name = Alphas(1) ZoneDehumid(ZoneDehumidIndex)%UnitType = CurrentModuleObject ! 'ZoneHVAC:Dehumidifier:DX' ZoneDehumid(ZoneDehumidIndex)%UnitType_Num = ZoneDehumidUnit ! 'ZoneHVAC:Dehumidifier:DX' = 1 ! A2, \field Availability Schedule Name IF (lAlphaBlanks(2)) THEN ZoneDehumid(ZoneDehumidIndex)%SchedPtr = ScheduleAlwaysOn ELSE ZoneDehumid(ZoneDehumidIndex)%SchedPtr = GetScheduleIndex(Alphas(2)) ! Convert schedule name to pointer IF (ZoneDehumid(ZoneDehumidIndex)%SchedPtr .EQ. 0) THEN CALL ShowSevereError(TRIM(cAlphaFields(2))//' not found = '//TRIM(Alphas(2))) CALL ShowContinueError('Occurs in '//TRIM(CurrentModuleObject)//' = '//TRIM(ZoneDehumid(ZoneDehumidIndex)%Name)) ErrorsFound=.TRUE. ENDIF END IF ! A3 , \field Air Inlet Node Name ZoneDehumid(ZoneDehumidIndex)%AirInletNodeNum = & GetOnlySingleNode(Alphas(3),ErrorsFound,TRIM(CurrentModuleObject),Alphas(1), & NodeType_Air,NodeConnectionType_Inlet,1,ObjectIsNotParent) ! A4 , \field Air Outlet Node Name ZoneDehumid(ZoneDehumidIndex)%AirOutletNodeNum = & GetOnlySingleNode(Alphas(4),ErrorsFound,TRIM(CurrentModuleObject),Alphas(1), & NodeType_Air,NodeConnectionType_Outlet,1,ObjectIsNotParent) ! N1, \field Rated Water Removal ZoneDehumid(ZoneDehumidIndex)%RatedWaterRemoval = Numbers(1) IF (ZoneDehumid(ZoneDehumidIndex)%RatedWaterRemoval .LE. 0.0d0) THEN CALL ShowSevereError(TRIM(cNumericFields(1))//' must be greater than zero.') CALL ShowContinueError('Value specified = '//TRIM(TrimSigDigits(Numbers(1),5))) CALL ShowContinueError('Occurs in '//TRIM(CurrentModuleObject)//' = '//TRIM(ZoneDehumid(ZoneDehumidIndex)%Name)) ErrorsFound=.TRUE. END IF ! N2, \field Rated Energy Factor ZoneDehumid(ZoneDehumidIndex)%RatedEnergyFactor = Numbers(2) IF (ZoneDehumid(ZoneDehumidIndex)%RatedEnergyFactor .LE. 0.0d0) THEN CALL ShowSevereError(TRIM(cNumericFields(2))//' must be greater than zero.') CALL ShowContinueError('Value specified = '//TRIM(TrimSigDigits(Numbers(2),5))) CALL ShowContinueError('Occurs in '//TRIM(CurrentModuleObject)//' = '//TRIM(ZoneDehumid(ZoneDehumidIndex)%Name)) ErrorsFound=.TRUE. END IF ! N3, \field Rated Air Flow Rate ZoneDehumid(ZoneDehumidIndex)%RatedAirVolFlow = Numbers(3) IF (ZoneDehumid(ZoneDehumidIndex)%RatedAirVolFlow .LE. 0.0d0) THEN CALL ShowSevereError(TRIM(cNumericFields(3))//' must be greater than zero.') CALL ShowContinueError('Value specified = '//TRIM(TrimSigDigits(Numbers(3),5))) CALL ShowContinueError('Occurs in '//TRIM(CurrentModuleObject)//' = '//TRIM(ZoneDehumid(ZoneDehumidIndex)%Name)) ErrorsFound=.TRUE. END IF ! A5, \field Water Removal Curve Name ZoneDehumid(ZoneDehumidIndex)%WaterRemovalCurveIndex = GetCurveIndex(Alphas(5)) ! Convert curve name to index number IF (ZoneDehumid(ZoneDehumidIndex)%WaterRemovalCurveIndex .EQ. 0) THEN IF (lAlphaBlanks(5)) THEN CALL ShowSevereError(RoutineName//':'//TRIM(CurrentModuleObject)//'="'//TRIM(cAlphaFields(5))// & '" is required, missing for '//TRIM(cAlphaFields(1))// & ' = '//TRIM(ZoneDehumid(ZoneDehumidIndex)%Name)) ELSE CALL ShowSevereError(TRIM(cAlphaFields(5))//' not found = '//TRIM(Alphas(5))) CALL ShowContinueError('Occurs in '//TRIM(CurrentModuleObject)//' = '//TRIM(ZoneDehumid(ZoneDehumidIndex)%Name)) END IF ErrorsFound = .TRUE. ELSE ! Verify Curve object, only legal type is BiQuadratic SELECT CASE(GetCurveType(ZoneDehumid(ZoneDehumidIndex)%WaterRemovalCurveIndex)) CASE('BIQUADRATIC') ZoneDehumid(ZoneDehumidIndex)%WaterRemovalCurveType=Biquadratic CurveVal = CurveValue(ZoneDehumid(ZoneDehumidIndex)%WaterRemovalCurveIndex,RatedInletAirTemp,RatedInletAirRH) IF(CurveVal .GT. 1.10d0 .OR. CurveVal .LT. 0.90d0) THEN CALL ShowWarningError(TRIM(cAlphaFields(5))//' output is not equal to 1.0') CALL ShowContinueError('(+ or -10%) at rated conditions for '//TRIM(CurrentModuleObject)//' = ' & //TRIM(Alphas(1))) CALL ShowContinueError('Curve output at rated conditions = '//TRIM(TrimSigDigits(CurveVal,3))) END IF CASE DEFAULT CALL ShowSevereError(RoutineName//':'//TRIM(CurrentModuleObject)//'="'//TRIM(ZoneDehumid(ZoneDehumidIndex)%Name)// & '" illegal '//TRIM(cAlphaFields(5))//' type for this object = '// & TRIM(GetCurveType(ZoneDehumid(ZoneDehumidIndex)%WaterRemovalCurveIndex))) CALL ShowContinueError('Curve type must be BiQuadratic.') ErrorsFound=.TRUE. END SELECT END IF ! A6, \field Energy Factor Curve Name ZoneDehumid(ZoneDehumidIndex)%EnergyFactorCurveIndex = GetCurveIndex(Alphas(6)) ! convert curve name to number IF (ZoneDehumid(ZoneDehumidIndex)%EnergyFactorCurveIndex .EQ. 0) THEN IF (lAlphaBlanks(6)) THEN CALL ShowSevereError(RoutineName//':'//TRIM(CurrentModuleObject)//'="'//TRIM(cAlphaFields(6))// & '" is required, missing for '//TRIM(cAlphaFields(1))// & ' = '//TRIM(ZoneDehumid(ZoneDehumidIndex)%Name)) ELSE CALL ShowSevereError(TRIM(cAlphaFields(6))//' not found = '//TRIM(Alphas(6))) CALL ShowContinueError('Occurs in '//TRIM(CurrentModuleObject)//' = '//TRIM(ZoneDehumid(ZoneDehumidIndex)%Name)) END IF ErrorsFound = .TRUE. ELSE ! Verify Curve Object, only legal type is BiQuadratic SELECT CASE(GetCurveType(ZoneDehumid(ZoneDehumidIndex)%EnergyFactorCurveIndex)) CASE('BIQUADRATIC') ZoneDehumid(ZoneDehumidIndex)%EnergyFactorCurveType=Biquadratic CurveVal = CurveValue(ZoneDehumid(ZoneDehumidIndex)%EnergyFactorCurveIndex,RatedInletAirTemp,RatedInletAirRH) IF(CurveVal .GT. 1.10d0 .OR. CurveVal .LT. 0.90d0) THEN CALL ShowWarningError(TRIM(cAlphaFields(6))//' output is not equal to 1.0') CALL ShowContinueError('(+ or -10%) at rated conditions for '//TRIM(CurrentModuleObject)//' = ' & //TRIM(Alphas(1))) CALL ShowContinueError('Curve output at rated conditions = '//TRIM(TrimSigDigits(CurveVal,3))) END IF CASE DEFAULT CALL ShowSevereError(RoutineName//':'//TRIM(CurrentModuleObject)//'="'//TRIM(ZoneDehumid(ZoneDehumidIndex)%Name)// & '" illegal '//TRIM(cAlphaFields(6))//' type for this object = '// & TRIM(GetCurveType(ZoneDehumid(ZoneDehumidIndex)%EnergyFactorCurveIndex))) CALL ShowContinueError('Curve type must be BiQuadratic.') ErrorsFound=.TRUE. END SELECT END IF ! A7, \field Part Load Fraction Correlation Curve Name ZoneDehumid(ZoneDehumidIndex)%PartLoadCurveIndex = GetCurveIndex(Alphas(7)) ! convert curve name to number IF (ZoneDehumid(ZoneDehumidIndex)%PartLoadCurveIndex .EQ. 0) THEN IF (lAlphaBlanks(7)) THEN CALL ShowSevereError(RoutineName//':'//TRIM(CurrentModuleObject)//'="'//TRIM(cAlphaFields(7))// & '" is required, missing for '//TRIM(cAlphaFields(1))// & ' = '//TRIM(ZoneDehumid(ZoneDehumidIndex)%Name)) ELSE CALL ShowSevereError(TRIM(cAlphaFields(7))//' not found = '//TRIM(Alphas(7))) CALL ShowContinueError('Occurs in '//TRIM(CurrentModuleObject)//' = '//TRIM(ZoneDehumid(ZoneDehumidIndex)%Name)) END IF ErrorsFound = .TRUE. ELSE ! Verify Curve Object, legal types are Quadratic and Cubic SELECT CASE(GetCurveType(ZoneDehumid(ZoneDehumidIndex)%PartLoadCurveIndex)) CASE('QUADRATIC') ZoneDehumid(ZoneDehumidIndex)%PartLoadCurveType=Quadratic CASE('CUBIC') ZoneDehumid(ZoneDehumidIndex)%PartLoadCurveType=Cubic CASE DEFAULT CALL ShowSevereError(RoutineName//':'//TRIM(CurrentModuleObject)//'="'//TRIM(ZoneDehumid(ZoneDehumidIndex)%Name)// & '" illegal '//TRIM(cAlphaFields(7))//' type for this object = '// & TRIM(GetCurveType(ZoneDehumid(ZoneDehumidIndex)%PartLoadCurveIndex))) CALL ShowContinueError('Curve type must be Quadratic or Cubic.') ErrorsFound=.TRUE. END SELECT END IF ! N4, \field Minimum Dry-Bulb Temperature for Dehumidifier Operation ! N5, \field Maximum Dry-Bulb Temperature for Dehumidifier Operation ZoneDehumid(ZoneDehumidIndex)%MinInletAirTemp = Numbers(4) ZoneDehumid(ZoneDehumidIndex)%MaxInletAirTemp = Numbers(5) IF (ZoneDehumid(ZoneDehumidIndex)%MinInletAirTemp .GE. ZoneDehumid(ZoneDehumidIndex)%MaxInletAirTemp) THEN CALL ShowSevereError(TRIM(cNumericFields(5))//' must be greater than '//TRIM(cNumericFields(4))) CALL ShowContinueError(TRIM(cNumericFields(5))//' specified = '//TRIM(TrimSigDigits(Numbers(5),1))) CALL ShowContinueError(TRIM(cNumericFields(4))//' specified = '//TRIM(TrimSigDigits(Numbers(4),1))) CALL ShowContinueError('Occurs in '//TRIM(CurrentModuleObject)//' = '//TRIM(ZoneDehumid(ZoneDehumidIndex)%Name)) ErrorsFound=.TRUE. END IF ! N6, \field Off Cycle Parasitic Electric Load ZoneDehumid(ZoneDehumidIndex)%OffCycleParasiticLoad = Numbers(6) ! Off Cycle Parasitic Load [W] IF (ZoneDehumid(ZoneDehumidIndex)%OffCycleParasiticLoad .LT. 0.0d0) THEN CALL ShowSevereError(TRIM(cNumericFields(6))//' must be >= zero.') CALL ShowContinueError('Value specified = '//TRIM(TrimSigDigits(Numbers(6),2))) CALL ShowContinueError('Occurs in '//TRIM(CurrentModuleObject)//' = '//TRIM(ZoneDehumid(ZoneDehumidIndex)%Name)) ErrorsFound=.TRUE. END IF ! A8; \field Condensate Collection Water Storage Tank Name ZoneDehumid(ZoneDehumidIndex)%CondensateCollectName = Alphas(8) IF (lAlphaBlanks(8)) THEN ZoneDehumid(ZoneDehumidIndex)%CondensateCollectMode = CondensateDiscarded ELSE ZoneDehumid(ZoneDehumidIndex)%CondensateCollectMode = CondensateToTank CALL SetupTankSupplyComponent(ZoneDehumid(ZoneDehumidIndex)%Name,TRIM(CurrentModuleObject), & ZoneDehumid(ZoneDehumidIndex)%CondensateCollectName, ErrorsFound, ZoneDehumid(ZoneDehumidIndex)%CondensateTankID, & ZoneDehumid(ZoneDehumidIndex)%CondensateTankSupplyARRID ) END IF END DO ! DO ZoneDehumidIndex=1,NumDehumidifiers DEALLOCATE(Alphas) DEALLOCATE(cAlphaFields) DEALLOCATE(cNumericFields) DEALLOCATE(Numbers) DEALLOCATE(lAlphaBlanks) DEALLOCATE(lNumericBlanks) IF (ErrorsFound) THEN CALL ShowFatalError(RoutineName//':'//CurrentModuleObject//': Errors found in input.') END IF DO ZoneDehumidIndex=1,NumDehumidifiers ! Set up report variables for the dehumidifiers CALL SetupOutputVariable('Zone Dehumidifier Sensible Heating Rate [W]',ZoneDehumid(ZoneDehumidIndex)%SensHeatingRate, & 'System','Average',ZoneDehumid(ZoneDehumidIndex)%Name) CALL SetupOutputVariable('Zone Dehumidifier Sensible Heating Energy [J]',ZoneDehumid(ZoneDehumidIndex)%SensHeatingEnergy, & 'System','Sum',ZoneDehumid(ZoneDehumidIndex)%Name) CALL SetupOutputVariable('Zone Dehumidifier Removed Water Mass Flow Rate [kg/s]', & ZoneDehumid(ZoneDehumidIndex)%WaterRemovalRate, & 'System','Average',ZoneDehumid(ZoneDehumidIndex)%Name) CALL SetupOutputVariable('Zone Dehumidifier Removed Water Mass [kg]',ZoneDehumid(ZoneDehumidIndex)%WaterRemoved, & 'System','Sum',ZoneDehumid(ZoneDehumidIndex)%Name) CALL SetupOutputVariable('Zone Dehumidifier Electric Power [W]',ZoneDehumid(ZoneDehumidIndex)%ElecPower, & 'System','Average',ZoneDehumid(ZoneDehumidIndex)%Name) CALL SetupOutputVariable('Zone Dehumidifier Electric Energy [J]',ZoneDehumid(ZoneDehumidIndex)%ElecConsumption, & 'System','Sum',ZoneDehumid(ZoneDehumidIndex)%Name, & ResourceTypeKey='Electric',EndUseKey='COOLING',GroupKey='System') CALL SetupOutputVariable('Zone Dehumidifier Off Cycle Parasitic Electric Power [W]', & ZoneDehumid(ZoneDehumidIndex)%OffCycleParasiticElecPower, & 'System','Average',ZoneDehumid(ZoneDehumidIndex)%Name) CALL SetupOutputVariable('Zone Dehumidifier Off Cycle Parasitic Electric Energy [J]', & ZoneDehumid(ZoneDehumidIndex)%OffCycleParasiticElecCons, & 'System','Sum',ZoneDehumid(ZoneDehumidIndex)%Name) CALL SetupOutputVariable('Zone Dehumidifier Part Load Ratio []',ZoneDehumid(ZoneDehumidIndex)%DehumidPLR, & 'System','Average',ZoneDehumid(ZoneDehumidIndex)%Name) CALL SetupOutputVariable('Zone Dehumidifier Runtime Fraction []',ZoneDehumid(ZoneDehumidIndex)%DehumidRTF, & 'System','Average',ZoneDehumid(ZoneDehumidIndex)%Name) CALL SetupOutputVariable('Zone Dehumidifier Outlet Air Temperature [C]',ZoneDehumid(ZoneDehumidIndex)%OutletAirTemp, & 'System','Average',ZoneDehumid(ZoneDehumidIndex)%Name) IF (ZoneDehumid(ZoneDehumidIndex)%CondensateCollectMode == CondensateToTank) THEN CALL SetupOutputVariable('Zone Dehumidifier Condensate Volume Flow Rate [m3/s]', & ZoneDehumid(ZoneDehumidIndex)%DehumidCondVolFlowRate, & 'System','Average',ZoneDehumid(ZoneDehumidIndex)%Name) CALL SetupOutputVariable('Zone Dehumidifier Condensate Volume [m3]',ZoneDehumid(ZoneDehumidIndex)%DehumidCondVol, & 'System','Sum',ZoneDehumid(ZoneDehumidIndex)%Name,ResourceTypeKey='OnSiteWater', & EndUseKey='Condensate',GroupKey='System') END IF END DO RETURN END SUBROUTINE GetZoneDehumidifierInput SUBROUTINE InitZoneDehumidifier(ZoneDehumNum) ! SUBROUTINE INFORMATION: ! AUTHOR Don Shirey, FSEC ! DATE WRITTEN July/Aug 2009 ! MODIFIED na ! RE-ENGINEERED na ! PURPOSE OF THIS SUBROUTINE: ! This subroutine initializes information for the zone dehumidifier model ! METHODOLOGY EMPLOYED: ! Use status flags to trigger various initializations ! REFERENCES: ! na ! USE STATEMENTS: USE DataZoneEquipment, ONLY: ZoneEquipInputsFilled,CheckZoneEquipmentList USE Psychrometrics, ONLY: PsyWFnTdbRhPb,PsyRhoAirFnPbTdbW IMPLICIT NONE ! Enforce explicit typing of all variables in this routine ! SUBROUTINE ARGUMENT DEFINITIONS: INTEGER, INTENT (IN) :: ZoneDehumNum ! Number of the current zone dehumidifier being simulated ! SUBROUTINE PARAMETER DEFINITIONS: ! na ! INTERFACE BLOCK SPECIFICATIONS ! na ! DERIVED TYPE DEFINITIONS ! na ! SUBROUTINE LOCAL VARIABLE DECLARATIONS: LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: MyEnvrnFlag ! Used for initializations each begin environment flag ! LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: MySizeFlag ! Used for sizing zone dehumidifier inputs one time LOGICAL,SAVE :: MyOneTimeFlag = .TRUE. ! initialization flag LOGICAL,SAVE :: ZoneEquipmentListChecked = .FALSE. ! True after the Zone Equipment List has been checked for items INTEGER :: LoopIndex ! DO loop index INTEGER :: AirInletNode ! Inlet air node number REAL(r64) :: RatedAirHumrat ! Humidity ratio (kg/kg) at rated inlet air conditions of 26.6667C, 60% RH REAL(r64) :: RatedAirDBTemp ! Dry-bulb air temperature at rated conditions 26.6667C REAL(r64) :: RatedAirRH ! Relative humidity of air (0.6 --> 60%) at rated conditions ! Do the one time initializations IF (MyOneTimeFlag) THEN ALLOCATE(MyEnvrnFlag(NumDehumidifiers)) ! ALLOCATE(MySizeFlag(NumDehumidifiers)) MyEnvrnFlag = .TRUE. ! MySizeFlag = .TRUE. MyOneTimeFlag = .FALSE. END IF ! Need to check all dehumidifiers to see if they are on Zone Equipment List or issue warning IF (.not. ZoneEquipmentListChecked .and. ZoneEquipInputsFilled) THEN ZoneEquipmentListChecked=.TRUE. DO LoopIndex=1,NumDehumidifiers IF (CheckZoneEquipmentList(ZoneDehumid(LoopIndex)%UnitType,ZoneDehumid(LoopIndex)%Name)) CYCLE CALL ShowSevereError('InitZoneDehumidifier: Zone Dehumidifier="'//TRIM(ZoneDehumid(LoopIndex)%UnitType)//','// & TRIM(ZoneDehumid(LoopIndex)%Name)//'" is not on any ZoneHVAC:EquipmentList. It will not be simulated.') END DO END IF AirInletNode = ZoneDehumid(ZoneDehumNum)%AirInletNodeNum ! Do the Begin Environment initializations IF (BeginEnvrnFlag .and. MyEnvrnFlag(ZoneDehumNum)) THEN ! Set the mass flow rates from the input volume flow rates, at rated conditions of 26.6667C, 60% RH ! Might default back to STP later after discussion with M. Witte, use StdRhoAir instead of calc'd RhoAir at rated conditions RatedAirDBTemp = 26.6667d0 ! 26.6667 C, 80F RatedAirRH = 0.6d0 ! 60% RH RatedAirHumrat = PsyWFnTdbRhPb(RatedAirDBTemp,RatedAirRH,StdBaroPress,'InitZoneDehumidifier') ZoneDehumid(ZoneDehumNum)%RatedAirMassFlow = PsyRhoAirFnPbTdbW(StdBaroPress,RatedAirDBTemp,RatedAirHumrat, & 'InitZoneDehumidifier') * ZoneDehumid(ZoneDehumNum)%RatedAirVolFlow ! Set the node max and min mass flow rates on inlet node... outlet node gets updated in UPDATE subroutine Node(AirInletNode)%MassFlowRateMax = ZoneDehumid(ZoneDehumNum)%RatedAirMassFlow Node(AirInletNode)%MassFlowRateMaxAvail = ZoneDehumid(ZoneDehumNum)%RatedAirMassFlow Node(AirInletNode)%MassFlowRateMinAvail = 0.0d0 Node(AirInletNode)%MassFlowRateMin = 0.0d0 MyEnvrnFlag(ZoneDehumNum) = .FALSE. END IF ! End one time inits IF (.not. BeginEnvrnFlag) THEN MyEnvrnFlag(ZoneDehumNum) = .TRUE. END IF ! These initializations are done every iteration Node(AirInletNode)%MassFlowRate = ZoneDehumid(ZoneDehumNum)%RatedAirMassFlow ! Zero out the report variables ZoneDehumid(ZoneDehumNum)%SensHeatingRate = 0.0d0 ! Zone Dehumidifier Sensible Heating Rate [W] ZoneDehumid(ZoneDehumNum)%SensHeatingEnergy = 0.0d0 ! Zone Dehumidifier Sensible Heating Energy [J] ZoneDehumid(ZoneDehumNum)%WaterRemovalRate = 0.0d0 ! Zone Dehumidifier Water Removal Rate [kg/s] ZoneDehumid(ZoneDehumNum)%WaterRemoved = 0.0d0 ! Zone Dehumidifier Water Removed [kg] ZoneDehumid(ZoneDehumNum)%ElecPower = 0.0d0 ! Zone Dehumidifier Electric Power [W] ZoneDehumid(ZoneDehumNum)%ElecConsumption = 0.0d0 ! Zone Dehumidifier Electric Consumption [J] ZoneDehumid(ZoneDehumNum)%DehumidPLR = 0.0d0 ! Zone Dehumidifier Part-Load Ratio [-] ZoneDehumid(ZoneDehumNum)%DehumidRTF = 0.0d0 ! Zone Dehumidifier Runtime Fraction [-] ZoneDehumid(ZoneDehumNum)%OffCycleParasiticElecPower = 0.0d0 ! Zone Dehumidifier Off-Cycle Parasitic Electric Power [W] ZoneDehumid(ZoneDehumNum)%OffCycleParasiticElecCons = 0.0d0 ! Zone Dehumidifier Off-Cycle Parasitic Electric Consumption [J] ZoneDehumid(ZoneDehumNum)%DehumidCondVolFlowRate = 0.0d0 ! Zone Dehumidifier Condensate Volumetric Flow Rate [m3/s] ZoneDehumid(ZoneDehumNum)%DehumidCondVol = 0.0d0 ! Zone Dehumidifier Condensate Volume [m3] ZoneDehumid(ZoneDehumNum)%OutletAirTemp = Node(AirInletNode)%Temp ! Zone Dehumidifier Outlet Air Temperature [C] RETURN END SUBROUTINE InitZoneDehumidifier SUBROUTINE SizeZoneDehumidifier ! SUBROUTINE INFORMATION: ! AUTHOR Don Shirey, FSEC ! DATE WRITTEN July 2009 ! MODIFIED na ! RE-ENGINEERED na ! PURPOSE OF THIS SUBROUTINE: ! No automatic sizing for this model (yet). Left in place for later (autosize based on latent requirements) ! METHODOLOGY EMPLOYED: ! na ! REFERENCES: ! na ! USE STATEMENTS: ! na IMPLICIT NONE ! Enforce explicit typing of all variables in this routine ! SUBROUTINE ARGUMENT DEFINITIONS: ! na ! SUBROUTINE PARAMETER DEFINITIONS: ! na ! INTERFACE BLOCK SPECIFICATIONS ! na ! DERIVED TYPE DEFINITIONS ! na ! SUBROUTINE LOCAL VARIABLE DECLARATIONS: ! na RETURN END SUBROUTINE SizeZoneDehumidifier SUBROUTINE CalcZoneDehumidifier(ZoneDehumNum,QZnDehumidReq,SensibleOutput,LatentOutput) ! SUBROUTINE INFORMATION: ! AUTHOR Don Shirey, FSEC ! DATE WRITTEN July/Aug 2009 ! MODIFIED na ! RE-ENGINEERED na ! PURPOSE OF THIS SUBROUTINE: ! Calculate the delivered capacity, electric energy consumption and water/condensate ! removal rates for the zone dehumidifier. ! METHODOLOGY EMPLOYED: ! Cycle the dehumidifier as needed to meet the remaining zone dehumidification load. ! Send excess sensible heat to zone energy balance (via SensibleOutput) for next HVAC time step, ! so set the dehumidifier outlet air temp = inlet air temp to avoid double counting excess sensible. ! REFERENCES: ! na ! USE STATEMENTS: USE CurveManager, ONLY: CurveValue USE Psychrometrics, ONLY: RhoH2O, PsyRhFnTdbWPb, PsyHfgAirFnWTdb, PsyCpAirFnWTdb, PsyHFnTdbW IMPLICIT NONE ! Enforce explicit typing of all variables in this routine ! SUBROUTINE ARGUMENT DEFINITIONS: INTEGER, INTENT (IN) :: ZoneDehumNum ! Index number of the current zone dehumidifier being simulated REAL(r64), INTENT (IN) :: QZnDehumidReq ! Dehumidification load to be met (kg/s), negative value means dehumidification load REAL(r64), INTENT (OUT) :: SensibleOutput ! Sensible (heating) output (W), sent to load predictor for next simulation time step REAL(r64), INTENT (OUT) :: LatentOutput ! Latent (dehumidification) output provided (kg/s) ! SUBROUTINE PARAMETER DEFINITIONS: ! na ! INTERFACE BLOCK SPECIFICATIONS: ! na ! DERIVED TYPE DEFINITIONS: ! na ! SUBROUTINE LOCAL VARIABLE DECLARATIONS: REAL(r64) :: WaterRemovalRateFactor ! Adjustment to Rate Water Removal as a function of inlet air T and RH REAL(r64) :: WaterRemovalVolRate ! Actual water removal rate at current inlet air conditions (L/day) REAL(r64) :: WaterRemovalMassRate ! Actual water removal rate at current inlet air conditions (kg/s) REAL(r64) :: EnergyFactorAdjFactor ! Adjustment to Rate Energy Factor as a function of inlet air T and RH REAL(r64) :: EnergyFactor ! Actual Energy Factor as a function of inlet air T and RH REAL(r64) :: InletAirTemp ! Dry-bulb temperature of air entering the dehumidifier (C) REAL(r64) :: InletAirHumRat ! Humidity ratio of the air entering the dehumidifier (kg/kg) REAL(r64) :: InletAirRH ! Relative humidity of air entering the dehumidifier (%) REAL(r64) :: OutletAirTemp ! Dry-bulb temperature of air leaving the dehumidifier (C) REAL(r64) :: OutletAirHumRat ! Humidity ratio of air leaving the dehumidifier (kg/kg) REAL(r64) :: PLR ! Part-load ratio = (dehumid load to be met)/(dehumid capacity of the dehumidifier) REAL(r64) :: PLF ! Part-load fraction (-), RuntimeFraction = PLR/PLF REAL(r64) :: RunTimeFraction ! Dehumidifier runtime fraction (-) REAL(r64) :: ElectricPowerOnCycle ! Electric power when dehumidifier is operating (W) REAL(r64) :: ElectricPowerAvg ! Average electric power for this dehumidifier (W) REAL(r64) :: hfg ! Enthalpy of evaporation of inlet air (J/kg) REAL(r64) :: AirMassFlowRate ! Air mass flow rate through this dehumidifier (kg/s) REAL(r64) :: Cp ! Heat capacity of inlet air (J/kg-C) INTEGER :: AirInletNodeNum = 0 ! Node number for the inlet air to the dehumidifier INTEGER :: AirOutletNodeNum = 0 ! Node number for the outlet air from the dehumidifier SensibleOutput = 0.0d0 LatentOutput = 0.0d0 WaterRemovalRateFactor = 0.0d0 AirMassFlowRate = 0.0d0 PLR = 0.0d0 PLF = 0.0d0 EnergyFactorAdjFactor = 0.0d0 RunTimeFraction = 0.0d0 ElectricPowerAvg = 0.0d0 ElectricPowerOnCycle = 0.0d0 AirInletNodeNum = ZoneDehumid(ZoneDehumNum)%AirInletNodeNum AirOutletNodeNum = ZoneDehumid(ZoneDehumNum)%AirOutletNodeNum InletAirTemp = Node(AirInletNodeNum)%Temp InletAirHumRat = Node(AirInletNodeNum)%Humrat InletAirRH = 100.0d0 * PsyRhFnTdbWPb(InletAirTemp,InletAirHumRat,OutBaroPress,'CalcZoneDehumidifier') ! RH in percent (%) IF (QZnDehumidReq .LT. 0.0d0 .AND. GetCurrentScheduleValue(ZoneDehumid(ZoneDehumNum)%SchedPtr) .GT. 0.0d0 .AND. & InletAirTemp .GE. ZoneDehumid(ZoneDehumNum)%MinInletAirTemp .AND. & InletAirTemp .LE. ZoneDehumid(ZoneDehumNum)%MaxInletAirTemp) THEN ! A dehumidification load is being requested and dehumidifier is available (schedule value > 0) ! and the inlet air temperature is within the min/max values specified by user input WaterRemovalRateFactor = CurveValue(ZoneDehumid(ZoneDehumNum)%WaterRemovalCurveIndex,InletAirTemp,InletAirRH) ! Warn user if curve output goes negative IF (WaterRemovalRateFactor .LE. 0.0d0) THEN IF (ZoneDehumid(ZoneDehumNum)%WaterRemovalCurveErrorCount .LT. 1) THEN ZoneDehumid(ZoneDehumNum)%WaterRemovalCurveErrorCount = ZoneDehumid(ZoneDehumNum)%WaterRemovalCurveErrorCount + 1 CALL ShowWarningError(TRIM(ZoneDehumid(ZoneDehumNum)%UnitType)//' "'//TRIM(ZoneDehumid(ZoneDehumNum)%Name)//'":') CALL ShowContinueError(' Water Removal Rate Curve output is <= 0.0 (' & //TRIM(TrimSigDigits(WaterRemovalRateFactor,5))//').') CALL ShowContinueError(' Negative value occurs using an inlet air dry-bulb temperature of ' & //TRIM(TrimSigDigits(InletAirTemp,2))// & ' and an inlet air relative humidity of '//TRIM(TrimSigDigits(InletAirRH,1))//'.') CALL ShowContinueErrorTimeStamp(' Dehumidifier turned off for this time step but simulation continues.') ELSE CALL ShowRecurringWarningErrorAtEnd(TRIM(ZoneDehumid(ZoneDehumNum)%UnitType)//' "'// & TRIM(ZoneDehumid(ZoneDehumNum)%Name)//'":'//& ' Water Removal Rate Curve output is <= 0.0 warning continues...' & , ZoneDehumid(ZoneDehumNum)%WaterRemovalCurveErrorIndex, WaterRemovalRateFactor, WaterRemovalRateFactor) END IF WaterRemovalRateFactor = 0.0d0 END IF WaterRemovalVolRate = WaterRemovalRateFactor * ZoneDehumid(ZoneDehumNum)%RatedWaterRemoval WaterRemovalMassRate = WaterRemovalVolRate / (24.0d0 * SecInHour * 1000.0d0) * & !(L/d)/(24 hr/day *3600 sec/hr * 1000 L/m3) RhoH2O(MAX((InletAirTemp-11.0d0),1.0d0),'CalcZoneDehumidifier') ! Density of water, minimum temp = 1.0C IF (WaterRemovalMassRate .GT. 0.0d0) THEN PLR = MAX(0.0d0, MIN(1.0d0, -QZnDehumidReq / WaterRemovalMassRate)) ELSE PLR = 0.0d0 RunTimeFraction = 0.0d0 END IF EnergyFactorAdjFactor = CurveValue(ZoneDehumid(ZoneDehumNum)%EnergyFactorCurveIndex,InletAirTemp,InletAirRH) ! Warn user if curve output goes negative IF (EnergyFactorAdjFactor .LE. 0.0d0) THEN IF (ZoneDehumid(ZoneDehumNum)%EnergyFactorCurveErrorCount .LT. 1) THEN ZoneDehumid(ZoneDehumNum)%EnergyFactorCurveErrorCount = ZoneDehumid(ZoneDehumNum)%EnergyFactorCurveErrorCount + 1 CALL ShowWarningError(TRIM(ZoneDehumid(ZoneDehumNum)%UnitType)//' "'//TRIM(ZoneDehumid(ZoneDehumNum)%Name)//'":') CALL ShowContinueError(' Energy Factor Curve output is <= 0.0 (' & //TRIM(TrimSigDigits(EnergyFactorAdjFactor,5))//').') CALL ShowContinueError(' Negative value occurs using an inlet air dry-bulb temperature of ' & //TRIM(TrimSigDigits(InletAirTemp,2))// & ' and an inlet air relative humidity of '//TRIM(TrimSigDigits(InletAirRH,1))//'.') CALL ShowContinueErrorTimeStamp(' Dehumidifier turned off for this time step but simulation continues.') ELSE CALL ShowRecurringWarningErrorAtEnd(TRIM(ZoneDehumid(ZoneDehumNum)%UnitType)//' "'// & TRIM(ZoneDehumid(ZoneDehumNum)%Name)//'":'//& ' Energy Factor Curve output is <= 0.0 warning continues...' & , ZoneDehumid(ZoneDehumNum)%EnergyFactorCurveErrorIndex, EnergyFactorAdjFactor, EnergyFactorAdjFactor) END IF ElectricPowerAvg = 0.0d0 PLR = 0.0d0 RunTimeFraction = 0.0d0 ELSE ! EnergyFactorAdjFactor is not negative, so proceed with calculations EnergyFactor = EnergyFactorAdjFactor * ZoneDehumid(ZoneDehumNum)%RatedEnergyFactor IF (ZoneDehumid(ZoneDehumNum)%PartLoadCurveIndex .GT. 0) THEN PLF = CurveValue(ZoneDehumid(ZoneDehumNum)%PartLoadCurveIndex,PLR) ! Calculate part load fraction ELSE PLF = 1.0d0 END IF IF (PLF < 0.7d0) THEN IF (ZoneDehumid(ZoneDehumNum)%LowPLFErrorCount .LT. 1) THEN ZoneDehumid(ZoneDehumNum)%LowPLFErrorCount = ZoneDehumid(ZoneDehumNum)%LowPLFErrorCount + 1 CALL ShowWarningError(TRIM(ZoneDehumid(ZoneDehumNum)%UnitType)//' "'//TRIM(ZoneDehumid(ZoneDehumNum)%Name)//'":') CALL ShowContinueError(' The Part Load Fraction Correlation Curve output is (' & //TRIM(TrimSigDigits(PLF,2))//') at a part-load ratio ='//TRIM(TrimSigDigits(PLR,3))) CALL ShowContinueErrorTimeStamp(' PLF curve values must be >= 0.7. '//& ' PLF has been reset to 0.7 and simulation is continuing.') ELSE CALL ShowRecurringWarningErrorAtEnd(TRIM(ZoneDehumid(ZoneDehumNum)%UnitType)//' "'// & TRIM(ZoneDehumid(ZoneDehumNum)%Name)//'":'//& ' Part Load Fraction Correlation Curve output < 0.7 warning continues...' & , ZoneDehumid(ZoneDehumNum)%LowPLFErrorIndex, PLF, PLF) END IF PLF = 0.7d0 END IF IF (PLF > 1.0d0) THEN IF (ZoneDehumid(ZoneDehumNum)%HighPLFErrorCount .LT. 1) THEN ZoneDehumid(ZoneDehumNum)%HighPLFErrorCount = ZoneDehumid(ZoneDehumNum)%HighPLFErrorCount + 1 CALL ShowWarningError(TRIM(ZoneDehumid(ZoneDehumNum)%UnitType)//' "'//TRIM(ZoneDehumid(ZoneDehumNum)%Name)//'":') CALL ShowContinueError(' The Part Load Fraction Correlation Curve output is (' & //TRIM(TrimSigDigits(PLF,2))//') at a part-load ratio ='//TRIM(TrimSigDigits(PLR,3))) CALL ShowContinueErrorTimeStamp(' PLF curve values must be < 1.0. '//& ' PLF has been reset to 1.0 and simulation is continuing.') ELSE CALL ShowRecurringWarningErrorAtEnd(TRIM(ZoneDehumid(ZoneDehumNum)%UnitType)//' "'// & TRIM(ZoneDehumid(ZoneDehumNum)%Name)//'":'//& ' Part Load Fraction Correlation Curve output > 1.0 warning continues...' & , ZoneDehumid(ZoneDehumNum)%HighPLFErrorIndex, PLF, PLF) END IF PLF = 1.0d0 END IF IF (PLF .GT. 0.0d0 .AND. PLF .GE. PLR) THEN RunTimeFraction = PLR/PLF ! Calculate dehumidifier runtime fraction ELSE IF (ZoneDehumid(ZoneDehumNum)%PLFPLRErrorCount .LT. 1) THEN ZoneDehumid(ZoneDehumNum)%PLFPLRErrorCount = ZoneDehumid(ZoneDehumNum)%PLFPLRErrorCount + 1 CALL ShowWarningError(TRIM(ZoneDehumid(ZoneDehumNum)%UnitType)//' "'//TRIM(ZoneDehumid(ZoneDehumNum)%Name)//'":') CALL ShowContinueError('The part load fraction was less than the part load ratio calculated'// & ' for this time step [PLR='//TRIM(TrimSigDigits(PLR,4))//', PLF='//TRIM(TrimSigDigits(PLF,4))//'].') CALL ShowContinueError('Runtime fraction reset to 1 and the simulation will continue.') CALL ShowContinueErrorTimeStamp(' ') ELSE CALL ShowRecurringWarningErrorAtEnd(TRIM(ZoneDehumid(ZoneDehumNum)%UnitType)//' "'// & TRIM(ZoneDehumid(ZoneDehumNum)%Name)//'":'//& ' Part load fraction less than part load ratio warning continues...' & , ZoneDehumid(ZoneDehumNum)%PLFPLRErrorIndex) END IF RunTimeFraction = 1.0d0 END IF IF (RunTimeFraction > 1.0d0 .AND. ABS(RunTimeFraction-1.0d0) > 0.001d0) THEN IF (ZoneDehumid(ZoneDehumNum)%HighRTFErrorCount .LT. 1) THEN ZoneDehumid(ZoneDehumNum)%HighRTFErrorCount = ZoneDehumid(ZoneDehumNum)%HighRTFErrorCount + 1 CALL ShowWarningError(TRIM(ZoneDehumid(ZoneDehumNum)%UnitType)//' "'//TRIM(ZoneDehumid(ZoneDehumNum)%Name)//'":') CALL ShowContinueError('The runtime fraction for this zone dehumidifier'// & ' exceeded 1.0 ['//TRIM(TrimSigDigits(RunTimeFraction,4))//'].') CALL ShowContinueError('Runtime fraction reset to 1 and the simulation will continue.') CALL ShowContinueErrorTimeStamp(' ') ELSE CALL ShowRecurringWarningErrorAtEnd(TRIM(ZoneDehumid(ZoneDehumNum)%UnitType)//' "'// & TRIM(ZoneDehumid(ZoneDehumNum)%Name)//'":'//& ' Runtime fraction for zone dehumidifier exceeded 1.0 warning continues...' & , ZoneDehumid(ZoneDehumNum)%HighRTFErrorIndex, RunTimeFraction, RunTimeFraction) END IF RunTimeFraction = 1.0d0 END IF ! ElectricPowerOnCycle = Water removal volumetric rate (L/day) / (Energy Factor(L/kWh) * 24 hrs/day ) * 1000 Wh/kWh ElectricPowerOnCycle = WaterRemovalVolRate / (EnergyFactor*24.0d0) * 1000.0d0 ! Watts ! ElectricPowerAvg = ElectricPowerOnCycle * RTF + (1-RTF)*OffCycleParsiticLoad ElectricPowerAvg = ElectricPowerOnCycle * RunTimeFraction + & ! average Watts (1.0d0 - RunTimeFraction)*ZoneDehumid(ZoneDehumNum)%OffCycleParasiticLoad END IF LatentOutput = WaterRemovalMassRate * PLR ! Average moisture removal rate, kg/s, for this timestep hfg = PsyHfgAirFnWTdb(InletAirHumRat,InletAirTemp) SensibleOutput = (LatentOutput * hfg) + ElectricPowerAvg ! Average sensible output, Watts ! Send SensibleOutput to zone air heat balance via SysDepZoneLoads in ZoneEquipmentManager Node(AirInletNodeNum)%MassFlowRate = ZoneDehumid(ZoneDehumNum)%RatedAirMassFlow * PLR AirMassFlowRate = Node(AirInletNodeNum)%MassFlowRate ! Average air mass flow for this timestep Cp = PsyCpAirFnWTdb(InletAirHumRat,InletAirTemp) ! Heat capacity of air IF (AirMassFlowRate .GT. 0.0d0 .AND. Cp .GT. 0.0d0) THEN OutletAirTemp = InletAirTemp + (ElectricPowerOnCycle + (WaterRemovalMassRate*hfg)) / & (ZoneDehumid(ZoneDehumNum)%RatedAirMassFlow * Cp) OutletAirHumRat = InletAirHumRat - LatentOutput / AirMassFlowRate ELSE OutletAirTemp = InletAirTemp OutletAirHumRat = InletAirHumRat END IF ELSE ! No load or not available or inlet air temps beyond min/max limits, then set outlet conditions ! equal to inlet conditions and PLR = RTF = 0.0 OutletAirTemp = InletAirTemp OutletAirHumRat = InletAirHumRat PLR = 0.0d0 RunTimeFraction = 0.0d0 Node(AirInletNodeNum)%MassFlowRate = 0.0d0 ! If available but didn't operate, then set electric power = off cycle parasitic load. ! Else, electric power = 0.0 IF (GetCurrentScheduleValue(ZoneDehumid(ZoneDehumNum)%SchedPtr) .GT. 0.0d0) THEN ElectricPowerAvg = ZoneDehumid(ZoneDehumNum)%OffCycleParasiticLoad ! off cycle parasitic is on entire timestep ELSE ElectricPowerAvg = 0.0d0 END IF END IF ZoneDehumid(ZoneDehumNum)%OutletAirTemp = OutletAirTemp ! Update report variable here. Node outlet Temp set equal ! to Node inlet Temp in Update subroutine ZoneDehumid(ZoneDehumNum)%OutletAirHumRat = OutletAirHumRat ! Store in structure, updated outlet node in Update subroutine ! Use inlet air temperature in outlet air enthalpy calculation... since the sensible heat output ! from the dehumidifier is being sent directly to the zone air heat balance for next hvac simulation time step ZoneDehumid(ZoneDehumNum)%OutletAirEnthalpy = PsyHFnTdbW(InletAirTemp,OutletAirHumRat,'CalcZoneDehumidifier') ZoneDehumid(ZoneDehumNum)%SensHeatingRate = SensibleOutput ! Report variable update, W, avg sens output when unit is 'on' ZoneDehumid(ZoneDehumNum)%WaterRemovalRate = LatentOutput ! Report variable update, kg/s LatentOutput = - LatentOutput ! change sign... negative is dehumidification in zone air balance ZoneDehumid(ZoneDehumNum)%OffCycleParasiticElecPower=(1.0d0 - RunTimeFraction)*ZoneDehumid(ZoneDehumNum)%OffCycleParasiticLoad ZoneDehumid(ZoneDehumNum)%ElecPower = ElectricPowerAvg ZoneDehumid(ZoneDehumNum)%DehumidPLR = PLR ZoneDehumid(ZoneDehumNum)%DehumidRTF = RunTimeFraction RETURN END SUBROUTINE CalcZoneDehumidifier SUBROUTINE UpdateZoneDehumidifier(ZoneDehumNum) ! SUBROUTINE INFORMATION: ! AUTHOR Don Shirey, FSEC ! DATE WRITTEN August 2009 ! MODIFIED na ! RE-ENGINEERED na ! PURPOSE OF THIS SUBROUTINE: ! This subroutine is for passing results to the outlet air node. ! METHODOLOGY EMPLOYED: ! na ! REFERENCES: ! na ! USE STATEMENTS: USE DataContaminantBalance, ONLY: Contaminant IMPLICIT NONE ! Enforce explicit typing of all variables in this routine ! SUBROUTINE ARGUMENT DEFINITIONS: INTEGER, INTENT (IN) :: ZoneDehumNum ! Number of the current zone dehumidifier being simulated ! SUBROUTINE PARAMETER DEFINITIONS: ! na ! INTERFACE BLOCK SPECIFICATIONS: ! na ! DERIVED TYPE DEFINITIONS: ! na ! SUBROUTINE LOCAL VARIABLE DECLARATIONS: INTEGER :: AirInletNodeNum ! Node number corresponding to the air entering dehumidifier INTEGER :: AirOutletNodeNum ! Node number corresponding to the air leaving dehumidifier AirInletNodeNum = ZoneDehumid(ZoneDehumNum)%AirInletNodeNum AirOutletNodeNum = ZoneDehumid(ZoneDehumNum)%AirOutletNodeNum ! Changed outlet node properties Node(AirOutletNodeNum)%Enthalpy = ZoneDehumid(ZoneDehumNum)%OutletAirEnthalpy Node(AirOutletNodeNum)%HumRat = ZoneDehumid(ZoneDehumNum)%OutletAirHumRat ! Set outlet temp = inlet temp; send excess sensible heat directly to air heat balance ! (via SensibleOutput and QSensOut) for the next hvac simulation time step. Node(AirOutletNodeNum)%Temp = Node(AirInletNodeNum)%Temp ! Pass through output node properties Node(AirOutletNodeNum)%Quality = Node(AirInletNodeNum)%Quality Node(AirOutletNodeNum)%Press = Node(AirInletNodeNum)%Press Node(AirOutletNodeNum)%MassFlowRate = Node(AirInletNodeNum)%MassFlowRate Node(AirOutletNodeNum)%MassFlowRateMin = Node(AirInletNodeNum)%MassFlowRateMin Node(AirOutletNodeNum)%MassFlowRateMax = Node(AirInletNodeNum)%MassFlowRateMax Node(AirOutletNodeNum)%MassFlowRateMinAvail = Node(AirInletNodeNum)%MassFlowRateMinAvail Node(AirOutletNodeNum)%MassFlowRateMaxAvail = Node(AirInletNodeNum)%MassFlowRateMaxAvail IF (Contaminant%CO2Simulation) Then Node(AirOutletNodeNum)%CO2 = Node(AirInletNodeNum)%CO2 End If IF (Contaminant%GenericContamSimulation) Then Node(AirOutletNodeNum)%GenContam = Node(AirInletNodeNum)%GenContam End If RETURN END SUBROUTINE UpdateZoneDehumidifier SUBROUTINE ReportZoneDehumidifier(DehumidNum) ! SUBROUTINE INFORMATION: ! AUTHOR Don Shirey, FSEC ! DATE WRITTEN August 2009 ! MODIFIED na ! RE-ENGINEERED na ! PURPOSE OF THIS SUBROUTINE: ! Fills some of the report variables for the zone dehumidifiers ! METHODOLOGY EMPLOYED: ! na ! REFERENCES: ! na ! USE STATEMENTS: USE DataHVACGlobals, ONLY: TimeStepSys USE DataWater, ONLY: WaterStorage USE Psychrometrics, ONLY: RhoH2O IMPLICIT NONE ! Enforce explicit typing of all variables in this routine ! SUBROUTINE ARGUMENT DEFINITIONS: INTEGER, INTENT (IN) :: DehumidNum ! Index of the current zone dehumidifier being simulated ! SUBROUTINE PARAMETER DEFINITIONS: ! na ! INTERFACE BLOCK SPECIFICATIONS: ! na ! DERIVED TYPE DEFINITIONS: ! na ! SUBROUTINE LOCAL VARIABLE DECLARATIONS: REAL(r64) :: ReportingConstant ! Number of seconds per HVAC system time step, to convert from W (J/s) to J REAL(r64) :: RhoWater ! Density of condensate (water) being removed (kg/m3) REAL(r64) :: InletAirTemp ! Dry-bulb temperature of air entering the dehumidifier (C) REAL(r64) :: OutletAirTemp ! Dry-bulb temperature of air leaving the dehumidifier (C) INTEGER :: AirInletNodeNum ! Node number corresponding to the air entering dehumidifier ReportingConstant = TimeStepSys*SecInHour ZoneDehumid(DehumidNum)%SensHeatingEnergy = ZoneDehumid(DehumidNum)%SensHeatingRate * ReportingConstant ZoneDehumid(DehumidNum)%WaterRemoved = ZoneDehumid(DehumidNum)%WaterRemovalRate * ReportingConstant ZoneDehumid(DehumidNum)%ElecConsumption = ZoneDehumid(DehumidNum)%ElecPower * ReportingConstant ZoneDehumid(DehumidNum)%OffCycleParasiticElecCons = ZoneDehumid(DehumidNum)%OffCycleParasiticElecPower * ReportingConstant ! Dehumidifier water collection to water storage tank (if needed) IF (ZoneDehumid(DehumidNum)%CondensateCollectMode == CondensateToTank) THEN ! Calculate and report condensation rate (how much water extracted from the air stream) ! Volumetric flow of water in m3/s for water system interactions AirInletNodeNum = ZoneDehumid(DehumidNum)%AirInletNodeNum InletAirTemp = Node(AirInletNodeNum)%Temp OutletAirTemp = MAX((InletAirTemp-11.0d0),1.0d0) ! Assume coil outlet air is 11C (20F) lower than inlet air temp RhoWater = RhoH2O(OutletAirTemp,'ReportZoneDehumidifier') ! Density of water, minimum temp = 1.0 C IF (RhoWater .GT. 0.0d0) THEN ZoneDehumid(DehumidNum)%DehumidCondVolFlowRate = ZoneDehumid(DehumidNum)%WaterRemovalRate / RhoWater END IF ZoneDehumid(DehumidNum)%DehumidCondVol = ZoneDehumid(DehumidNum)%DehumidCondVolFlowRate * ReportingConstant WaterStorage(ZoneDehumid(DehumidNum)%CondensateTankID)%VdotAvailSupply(ZoneDehumid(DehumidNum)%CondensateTankSupplyARRID) & = ZoneDehumid(DehumidNum)%DehumidCondVolFlowRate ! Assume water outlet temp = air outlet temp.... same assumption in other places in code (e.g., water coil component) WaterStorage(ZoneDehumid(DehumidNum)%CondensateTankID)%TwaterSupply(ZoneDehumid(DehumidNum)%CondensateTankSupplyARRID) & = OutletAirTemp END IF RETURN END SUBROUTINE ReportZoneDehumidifier FUNCTION GetZoneDehumidifierNodeNumber(NodeNumber) RESULT(FindZoneDehumidifierNodeNumber) ! FUNCTION INFORMATION: ! AUTHOR Lixing Gu ! DATE WRITTEN August 2009 ! MODIFIED na ! RE-ENGINEERED na ! PURPOSE OF THIS FUNCTION: ! After making sure get input is done, the node number of indicated ! zone dehumidifier is returned. ! METHODOLOGY EMPLOYED: ! na ! REFERENCES: ! na ! USE STATEMENTS: ! na IMPLICIT NONE ! Enforce explicit typing of all variables in this routine ! FUNCTION ARGUMENT DEFINITIONS: INTEGER, INTENT(IN) :: NodeNumber ! Node being tested LOGICAL :: FindZoneDehumidifierNodeNumber ! Zone Dehumidifier Node Number Check INTEGER :: ZoneDehumidIndex ! Loop index ! FUNCTION PARAMETER DEFINITIONS: ! na ! INTERFACE BLOCK SPECIFICATIONS: ! na ! DERIVED TYPE DEFINITIONS: ! na ! FUNCTION LOCAL VARIABLE DECLARATIONS: ! na IF (GetInputFlag) THEN CALL GetZoneDehumidifierInput GetInputFlag=.FALSE. END IF FindZoneDehumidifierNodeNumber=.FALSE. DO ZoneDehumidIndex=1,NumDehumidifiers IF (NodeNumber == ZoneDehumid(ZoneDehumidIndex)%AirInletNodeNum) THEN FindZoneDehumidifierNodeNumber = .TRUE. EXIT END IF IF (NodeNumber == ZoneDehumid(ZoneDehumidIndex)%AirOutletNodeNum) THEN FindZoneDehumidifierNodeNumber = .TRUE. EXIT END IF END DO RETURN END FUNCTION GetZoneDehumidifierNodeNumber ! NOTICE ! ! Copyright © 1996-2013 The Board of Trustees of the University of Illinois ! and The Regents of the University of California through Ernest Orlando Lawrence ! Berkeley National Laboratory. All rights reserved. ! ! Portions of the EnergyPlus software package have been developed and copyrighted ! by other individuals, companies and institutions. These portions have been ! incorporated into the EnergyPlus software package under license. For a complete ! list of contributors, see "Notice" located in EnergyPlus.f90. ! ! NOTICE: The U.S. Government is granted for itself and others acting on its ! behalf a paid-up, nonexclusive, irrevocable, worldwide license in this data to ! reproduce, prepare derivative works, and perform publicly and display publicly. ! Beginning five (5) years after permission to assert copyright is granted, ! subject to two possible five year renewals, the U.S. Government is granted for ! itself and others acting on its behalf a paid-up, non-exclusive, irrevocable ! worldwide license in this data to reproduce, prepare derivative works, ! distribute copies to the public, perform publicly and display publicly, and to ! permit others to do so. ! ! TRADEMARKS: EnergyPlus is a trademark of the US Department of Energy. ! END MODULE ZoneDehumidifier