Set DataHeatGlobal heat reclaim variable for use by heat reclaim coil (part load ratio is accounted for) Calculation for heat reclaim needs to be corrected to use compressor power (not including condenser fan power)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | DXCoilNum | |||
integer, | intent(in) | :: | CompOp | |||
logical, | intent(in) | :: | FirstHVACIteration | |||
real(kind=r64), | intent(in) | :: | PartLoadRatio | |||
integer, | intent(in) | :: | FanOpMode | |||
real(kind=r64), | intent(in) | :: | CompCycRatio | |||
integer, | intent(in), | optional | :: | PerfMode | ||
real(kind=r64), | intent(in), | optional | :: | OnOffAirFlowRatio | ||
real(kind=r64), | intent(in), | optional | :: | MaxCoolCap |
SUBROUTINE CalcVRFCoolingCoil(DXCoilNum,CompOp,FirstHVACIteration,PartLoadRatio,FanOpMode,CompCycRatio, &
PerfMode,OnOffAirFlowRatio, MaxCoolCap)
! SUBROUTINE INFORMATION:
! AUTHOR Richard Raustad
! DATE WRITTEN August 2010
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Calculates the air-side performance of a direct-expansion, air-cooled
! VRF terminal unit cooling coil.
! A new subroutine was created in case this DX coil model is significantly
! different from the existing CalcDoe2DXCoil subroutine. The VRF heating coil
! uses the existing DX heating coil subroutine (CalcDXHeatingCoil).
! METHODOLOGY EMPLOYED:
! This routine simulates the performance of a variable refrigerant flow cooling coil.
! The routine requires the user to enter the total cooling capacity and sensible heat ratio.
! Since different manufacturer's rate their equipment at different air flow rates,
! the supply air flow rate corresponding to the rated capacities must also be
! entered (should be between 300 cfm/ton and 450 cfm/ton). The rated information entered by
! the user should NOT include the thermal or electrical impacts of the supply air fan, as
! this is addressed by another module.
! With the rated performance data entered by the user, the model employs some of the
! DOE-2.1E curve fits to adjust the capacity and efficiency of the unit as a function
! of entering air temperatures and supply air flow rate (actual vs rated flow). The model
! does NOT employ the exact same methodology to calculate performance as DOE-2.
!
! This VRF cooling coil model adjusts the rated total cooling capacity by the CAPFT
! and CAP funciton of flow curve/model currently used by the existing DX coil model.
! The part-load ratio is then applied to the total operating capacity to find the capacity
! required to meet the load. This VRF model then uses the ADP/bypass method to find the
! SHR and resulting outlet conditions given that total capacity (or delta H).
! The model checks for coil dryout conditions, and adjusts the calculated performance
! appropriately.
! REFERENCES:
! na
! USE STATEMENTS:
USE CurveManager, ONLY: CurveValue
USE DataGlobals, ONLY: CurrentTime
USE DataHVACGlobals, ONLY: HPWHCrankcaseDBTemp, TimeStepSys, SysTimeElapsed
USE General, ONLY: TrimSigDigits, RoundSigDigits, CreateSysTimeIntervalString
USE DataWater, ONLY: WaterStorage
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: DXCoilNum ! the number of the DX coil to be simulated
INTEGER, INTENT(IN) :: CompOp ! compressor operation; 1=on, 0=off
LOGICAL, INTENT(IN) :: FirstHVACIteration ! true if this is the first iteration of HVAC
REAL(r64), INTENT(IN) :: PartLoadRatio ! sensible cooling load / full load sensible cooling capacity
INTEGER, INTENT(IN) :: FanOpMode ! Allows parent object to control fan operation
REAL(r64), INTENT(IN) :: CompCycRatio ! cycling ratio of VRF condenser
INTEGER, INTENT(IN), OPTIONAL :: PerfMode ! Performance mode for MultiMode DX coil; Always 1 for other coil types
REAL(r64), INTENT(IN), OPTIONAL :: OnOffAirFlowRatio ! ratio of compressor on airflow to compressor off airflow
! REAL(r64), INTENT(IN), OPTIONAL :: CoolingHeatingPLR ! used for cycling fan RH control
REAL(r64), INTENT(IN), OPTIONAL :: MaxCoolCap ! maximum capacity of DX coil
! SUBROUTINE PARAMETER DEFINITIONS:
CHARACTER(len=*), PARAMETER :: RoutineName='CalcVRFCoolingCoil'
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: AirMassFlow ! dry air mass flow rate through coil [kg/s] (adjusted for bypass if any)
REAL(r64) :: AirMassFlowRatio ! Ratio of actual air mass flow to rated air mass flow (adjusted for bypass if any)
REAL(r64) :: AirVolumeFlowRate ! Air volume flow rate across the cooling coil [m3/s] (adjusted for bypass if any)
! (average flow if cycling fan, full flow if constant fan)
REAL(r64) :: VolFlowperRatedTotCap ! Air volume flow rate divided by rated total cooling capacity [m3/s-W] (adjusted for bypass)
REAL(r64) :: TotCap ! gross total cooling capacity at off-rated conditions [W]
REAL(r64) :: TotCapTempModFac ! Total capacity modifier (function of entering wetbulb, outside drybulb)
REAL(r64) :: TotCapFlowModFac ! Total capacity modifier (function of actual supply air flow vs rated flow)
REAL(r64) :: InletAirWetBulbC ! wetbulb temperature of inlet air [C]
REAL(r64) :: InletAirDryBulbTemp ! inlet air dry bulb temperature [C]
REAL(r64) :: InletAirEnthalpy ! inlet air enthalpy [J/kg]
REAL(r64) :: InletAirHumRat ! inlet air humidity ratio [kg/kg]
REAL(r64) :: InletAirHumRatTemp ! inlet air humidity ratio used in ADP/BF loop [kg/kg]
! Eventually inlet air conditions will be used in DX Coil, these lines are commented out and marked with this comment line
!REAL(r64) :: InletAirPressure ! inlet air pressure [Pa]
REAL(r64) :: RatedCBF ! coil bypass factor at rated conditions
REAL(r64) :: SHR ! Sensible Heat Ratio (sensible/total) of the cooling coil
REAL(r64) :: CBF ! coil bypass factor at off rated conditions
REAL(r64) :: A0 ! NTU * air mass flow rate, used in CBF calculation
REAL(r64) :: hDelta ! Change in air enthalpy across the cooling coil [J/kg]
REAL(r64) :: hADP ! Apparatus dew point enthalpy [J/kg]
REAL(r64) :: hTinwADP ! Enthalpy at inlet dry-bulb and wADP [J/kg]
REAL(r64) :: hTinwout ! Enthalpy at inlet dry-bulb and outlet humidity ratio [J/kg]
REAL(r64) :: tADP ! Apparatus dew point temperature [C]
REAL(r64) :: wADP ! Apparatus dew point humidity ratio [kg/kg]
REAL(r64) :: FullLoadOutAirEnth ! outlet full load enthalpy [J/kg]
REAL(r64) :: FullLoadOutAirHumRat ! outlet humidity ratio at full load
REAL(r64) :: FullLoadOutAirTemp ! outlet air temperature at full load [C]
REAL(r64) :: PLF ! Part load factor, accounts for thermal lag at compressor startup, used in power calculation
REAL(r64) :: QLatActual ! operating latent capacity of DX coil
REAL(r64) :: QLatRated ! Rated latent capacity of DX coil
REAL(r64) :: SHRUnadjusted ! SHR prior to latent degradation effective SHR calculation
INTEGER :: Counter ! Counter for dry evaporator iterations
INTEGER :: MaxIter ! Maximum number of iterations for dry evaporator calculations
REAL(r64) :: RF ! Relaxation factor for dry evaporator iterations
REAL(r64) :: Tolerance ! Error tolerance for dry evaporator iterations
REAL(r64) :: werror ! Deviation of humidity ratio in dry evaporator iteration loop
REAL(r64) :: CondInletTemp ! Condenser inlet temperature (C). Outdoor dry-bulb temp for air-cooled condenser.
! Outdoor Wetbulb +(1 - effectiveness)*(outdoor drybulb - outdoor wetbulb) for evap condenser.
REAL(r64) :: CondInletHumrat ! Condenser inlet humidity ratio (kg/kg). Zero for air-cooled condenser.
! For evap condenser, its the humidity ratio of the air leaving the evap cooling pads.
REAL(r64) :: CondAirMassFlow ! Condenser air mass flow rate [kg/s]
REAL(r64) :: RhoAir ! Density of air [kg/m3]
REAL(r64) :: CrankcaseHeatingPower ! power due to crankcase heater
REAL(r64) :: CompAmbTemp = 0.0d0 ! Ambient temperature at compressor
REAL(r64) :: AirFlowRatio ! ratio of compressor on airflow to average timestep airflow
! used when constant fan mode yields different air flow rates when compressor is ON and OFF
! (e.g. Packaged Terminal Heat Pump)
REAL(r64) :: OutdoorDryBulb ! Outdoor dry-bulb temperature at condenser (C)
REAL(r64) :: OutdoorWetBulb ! Outdoor wet-bulb temperature at condenser (C)
REAL(r64) :: OutdoorHumRat ! Outdoor humidity ratio at condenser (kg/kg)
REAL(r64) :: OutdoorPressure ! Outdoor barometric pressure at condenser (Pa)
REAL(r64) :: CurrentEndTime = 0.0d0 ! end time of time step for current simulation time step
REAL(r64) :: MinAirHumRat = 0.0d0 ! minimum of the inlet air humidity ratio and the outlet air humidity ratio
INTEGER :: Mode ! Performance mode for Multimode DX coil; Always 1 for other coil types
REAL(r64) :: OutletAirTemp ! Supply air temperature (average value if constant fan, full output if cycling fan)
REAL(r64) :: OutletAirHumRat ! Supply air humidity ratio (average value if constant fan, full output if cycling fan)
REAL(r64) :: OutletAirEnthalpy ! Supply air enthalpy (average value if constant fan, full output if cycling fan)
REAL(r64) :: Adiff ! Used for exponential
! If Performance mode not present, then set to 1. Used only by Multimode/Multispeed DX coil (otherwise mode = 1)
IF (PRESENT(PerfMode)) THEN
Mode = PerfMode
ELSE
Mode = 1
END IF
! If AirFlowRatio not present, then set to 1. Used only by DX coils with different air flow
! during cooling and when no cooling is required (constant fan, fan speed changes)
IF (PRESENT(OnOffAirFlowRatio)) THEN
AirFlowRatio = OnOffAirFlowRatio
ELSE
AirFlowRatio = 1.0d0
END IF
MaxIter = 30
RF = 0.4d0
Counter = 0
Tolerance = 0.01d0
CondInletTemp = 0.0d0
CondInletHumrat = 0.0d0
AirMassFlow = DXCoil(DXCoilNum)%InletAirMassFlowRate
InletAirDryBulbTemp = DXCoil(DXCoilNum)%InletAirTemp
InletAirEnthalpy = DXCoil(DXCoilNum)%InletAirEnthalpy
InletAirHumRat = DXCoil(DXCoilNum)%InletAirHumRat
! Eventually inlet air conditions will be used in DX Coil, these lines are commented out and marked with this comment line
!InletAirPressure = DXCoil(DXCoilNum)%InletAirPressure
HeatReclaimDXCoil(DXCoilNum)%AvailCapacity = 0.0d0
DXCoil(DXCoilNum)%CoolingCoilRuntimeFraction = 0.0d0
DXCoil(DXCoilNum)%PartLoadRatio = 0.0d0
DXCoil(DXCoilNum)%BasinHeaterPower = 0.0d0
IF (DXCoil(DXCoilNum)%CondenserInletNodeNum(Mode) /= 0) THEN
OutdoorDryBulb = Node(DXCoil(DXCoilNum)%CondenserInletNodeNum(Mode))%Temp
IF(DXCoil(DXCoilNum)%CondenserType(Mode) == WaterCooled)THEN
OutdoorHumRat = OutHumRat
OutdoorPressure = OutBaroPress
OutdoorWetBulb = OutWetBulbTemp
ELSE
OutdoorPressure = Node(DXCoil(DXCoilNum)%CondenserInletNodeNum(Mode))%Press
! If node is not connected to anything, pressure = default, use weather data
IF(OutdoorPressure == DefaultNodeValues%Press)THEN
OutdoorDryBulb = OutDryBulbTemp
OutdoorHumRat = OutHumRat
OutdoorPressure = OutBaroPress
OutdoorWetBulb = OutWetBulbTemp
ELSE
OutdoorHumRat = Node(DXCoil(DXCoilNum)%CondenserInletNodeNum(Mode))%HumRat
! this should use Node%WetBulbTemp or a PSYC function, not OAWB
OutdoorWetBulb = Node(DXCoil(DXCoilNum)%CondenserInletNodeNum(Mode))%OutAirWetBulb
END IF
END IF
ELSE
OutdoorDryBulb = OutDryBulbTemp
OutdoorHumRat = OutHumRat
OutdoorPressure = OutBaroPress
OutdoorWetBulb = OutWetBulbTemp
ENDIF
IF (DXCoil(DXCoilNum)%CondenserType(Mode) == EvapCooled) THEN
RhoAir = PsyRhoAirFnPbTdbW(OutdoorPressure,OutdoorDryBulb,OutdoorHumRat)
CondAirMassFlow = RhoAir * DXCoil(DXCoilNum)%EvapCondAirFlow(Mode)
! (Outdoor wet-bulb temp from DataEnvironment) + (1.0-EvapCondEffectiveness) * (drybulb - wetbulb)
CondInletTemp = OutdoorWetBulb + (OutdoorDryBulb-OutdoorWetBulb)*(1.0d0 - DXCoil(DXCoilNum)%EvapCondEffect(Mode))
CondInletHumrat = PsyWFnTdbTwbPb(CondInletTemp,OutdoorWetBulb,OutdoorPressure)
CompAmbTemp = OutdoorDryBulb
ELSE ! for air or water-cooled, inlet temp is stored in OutdoorDryBulb temp
CondInletTemp = OutdoorDryBulb ! Outdoor dry-bulb temp or water inlet temp
IF(DXCoil(DXCoilNum)%CondenserType(Mode) == WaterCooled)THEN
CompAmbTemp = OutDryBulbTemp ! for crankcase heater use actual outdoor temp for water-cooled
ELSE
CompAmbTemp = OutdoorDryBulb
END IF
END IF
! Initialize crankcase heater, operates below OAT defined in input deck for HP DX cooling coil
! If used in a heat pump, the value of MaxOAT in the heating coil overrides that in the cooling coil (in GetInput)
IF (CompAmbTemp .LT. DXCoil(DXCoilNum)%MaxOATCrankcaseHeater)THEN
CrankcaseHeatingPower = DXCoil(DXCoilNum)%CrankcaseHeaterCapacity
ELSE
CrankcaseHeatingPower = 0.0d0
END IF
! calculate end time of current time step to determine if error messages should be printed
CurrentEndTime = CurrentTime + SysTimeElapsed
! Print warning messages only when valid and only for the first ocurrance. Let summary provide statistics.
! Wait for next time step to print warnings. If simulation iterates, print out
! the warning for the last iteration only. Must wait for next time step to accomplish this.
! If a warning occurs and the simulation down shifts, the warning is not valid.
IF(DXCoil(DXCoilNum)%PrintLowAmbMessage)THEN ! .AND. &
IF(CurrentEndTime .GT. DXCoil(DXCoilNum)%CurrentEndTimeLast .AND. &
TimeStepSys .GE. DXCoil(DXCoilNum)%TimeStepSysLast)THEN
IF (DXCoil(DXCoilNum)%LowAmbErrIndex == 0) THEN
CALL ShowWarningMessage(TRIM(DXCoil(DXCoilNum)%LowAmbBuffer1))
CALL ShowContinueError(TRIM(DXCoil(DXCoilNum)%LowAmbBuffer2))
CALL ShowContinueError('... Operation at low inlet temperatures may require special performance curves.')
ENDIF
CALL ShowRecurringWarningErrorAtEnd(TRIM(DXCoil(DXCoilNum)%DXCoilType)//' "'&
//TRIM(DXCoil(DXCoilNum)%Name)//'" - Low condenser inlet temperature error continues...' &
,DXCoil(DXCoilNum)%LowAmbErrIndex,DXCoil(DXCoilNum)%LowTempLast,DXCoil(DXCoilNum)%LowTempLast, &
ReportMinUnits='[C]',ReportMaxUnits='[C]')
END IF
END IF
IF(DXCoil(DXCoilNum)%PrintHighAmbMessage)THEN ! .AND. &
IF(CurrentEndTime .GT. DXCoil(DXCoilNum)%CurrentEndTimeLast .AND. &
TimeStepSys .GE. DXCoil(DXCoilNum)%TimeStepSysLast)THEN
IF (DXCoil(DXCoilNum)%HighAmbErrIndex == 0) THEN
CALL ShowWarningMessage(TRIM(DXCoil(DXCoilNum)%HighAmbBuffer1))
CALL ShowContinueError(TRIM(DXCoil(DXCoilNum)%HighAmbBuffer2))
CALL ShowContinueError('... Operation at high inlet temperatures may require special performance curves.')
ENDIF
CALL ShowRecurringWarningErrorAtEnd(TRIM(DXCoil(DXCoilNum)%DXCoilType)//' "'&
//TRIM(DXCoil(DXCoilNum)%Name)//'" - High condenser inlet temperature error continues...' &
,DXCoil(DXCoilNum)%HighAmbErrIndex,DXCoil(DXCoilNum)%HighTempLast,DXCoil(DXCoilNum)%HighTempLast, &
ReportMinUnits='[C]',ReportMaxUnits='[C]')
END IF
END IF
IF(DXCoil(DXCoilNum)%PrintLowOutTempMessage)THEN
IF(CurrentEndTime .GT. DXCoil(DXCoilNum)%CurrentEndTimeLast .AND. &
TimeStepSys .GE. DXCoil(DXCoilNum)%TimeStepSysLast)THEN
IF(DXCoil(DXCoilNum)%LowOutletTempIndex == 0)THEN
CALL ShowWarningMessage(TRIM(DXCoil(DXCoilNum)%LowOutTempBuffer1))
CALL ShowContinueError(TRIM(DXCoil(DXCoilNum)%LowOutTempBuffer2))
CALL ShowContinueError('... Possible reasons for low outlet air dry-bulb temperatures are: This DX coil')
CALL ShowContinueError(' 1) may have a low inlet air dry-bulb temperature. Inlet air temperature = '// &
TRIM(TrimSigDigits(DXCoil(DXCoilNum)%FullLoadInletAirTempLast,3))//' C.')
CALL ShowContinueError(' 2) may have a low air flow rate per watt of cooling capacity. Check inputs.')
CALL ShowContinueError(' 3) is used as part of a HX assisted cooling coil which uses a high sensible'// &
' effectiveness. Check inputs.')
END IF
CALL ShowRecurringWarningErrorAtEnd(TRIM(DXCoil(DXCoilNum)%DXCoilType)//' "'&
//TRIM(DXCoil(DXCoilNum)%Name)//'" - Full load outlet temperature'// &
' indicates a possibility of frost/freeze error continues. Outlet air temperature statistics follow:', &
DXCoil(DXCoilNum)%LowOutletTempIndex, DXCoil(DXCoilNum)%FullLoadOutAirTempLast, &
DXCoil(DXCoilNum)%FullLoadOutAirTempLast)
END IF
END IF
! save last system time step and last end time of current time step (used to determine if warning is valid)
DXCoil(DXCoilNum)%TimeStepSysLast = TimeStepSys
DXCoil(DXCoilNum)%CurrentEndTimeLast = CurrentEndTime
DXCoil(DXCoilNum)%PrintLowAmbMessage = .FALSE.
DXCoil(DXCoilNum)%PrintLowOutTempMessage = .FALSE.
IF((AirMassFlow .GT. 0.0d0) .AND. &
(GetCurrentScheduleValue(DXCoil(DXCoilNum)%SchedPtr) .GT. 0.0d0) .AND. &
(PartLoadRatio .GT. 0.0d0) .AND. (CompOp == On)) THEN ! for cycling fan, reset mass flow to full on rate
IF (FanOpMode .EQ. CycFanCycCoil) THEN
AirMassFlow = AirMassFlow / PartLoadRatio
ELSE IF (FanOpMode .EQ. ContFanCycCoil) THEN
AirMassFlow = AirMassFlow * AirFlowRatio
ELSE
AirMassFlow = DXCoil(DXCoilNum)%RatedAirMassFlowRate(Mode)
END IF
! Check for valid air volume flow per rated total cooling capacity (200 - 500 cfm/ton)
! for some reason there are diff's when using coil inlet air pressure
! these lines (more to follow) are commented out for the time being
InletAirWetbulbC = PsyTwbFnTdbWPb(InletAirDryBulbTemp,InletAirHumRat,OutdoorPressure)
AirVolumeFlowRate = AirMassFlow/ PsyRhoAirFnPbTdbW(OutdoorPressure,InletAirDryBulbTemp, InletAirHumRat)
VolFlowperRatedTotCap = AirVolumeFlowRate/DXCoil(DXCoilNum)%RatedTotCap(Mode)
IF (DXCoil(DXCoilNum)%RatedTotCap(Mode) .LE. 0.0d0) THEN
CALL ShowFatalError(TRIM(DXCoil(DXCoilNum)%DXCoilType)//' "'//TRIM(DXCoil(DXCoilNum)%Name)//&
'" - Rated total cooling capacity is zero or less.')
END IF
IF (.NOT. FirstHVACIteration .AND. .NOT. WarmupFlag .AND. &
((VolFlowperRatedTotCap .LT. MinOperVolFlowPerRatedTotCap(DXCT)) .OR. &
(VolFlowperRatedTotCap .GT. MaxCoolVolFlowPerRatedTotCap(DXCT)))) THEN
IF (DXCoil(DXCoilNum)%ErrIndex1 == 0) THEN
CALL ShowWarningMessage(TRIM(DXCoil(DXCoilNum)%DXCoilType)//' "'//TRIM(DXCoil(DXCoilNum)%Name)//&
'" - Air volume flow rate per watt of rated total cooling capacity is out of range at '// &
TRIM(RoundSigDigits(VolFlowperRatedTotCap,3))//' m3/s/W.')
CALL ShowContinueErrorTimeStamp(' ')
CALL ShowContinueError('...Expected range for VolumeFlowPerRatedTotalCapacity=['// &
TRIM(RoundSigDigits(MinOperVolFlowPerRatedTotCap(DXCT),3))//'--'// &
TRIM(RoundSigDigits(MaxCoolVolFlowPerRatedTotCap(DXCT),3))//']')
CALL ShowContinueError('...Possible causes include inconsistent air flow rates in system components,')
CALL ShowContinueError('...or mixing manual inputs with autosize inputs.'// &
' Also check the following values and calculations.')
CALL ShowContinueError('...Volume Flow Rate per Rated Total Capacity = Volume Flow Rate / Rated Total Capacity')
CALL ShowContinueError('...Volume Flow Rate = Air Mass Flow Rate / Air Density')
CALL ShowContinueError('...Data used for calculations:')
CALL ShowContinueError('...Rated Total Capacity = '//TRIM(RoundSigDigits(DXCoil(DXCoilNum)%RatedTotCap(Mode),2))//' W.')
CALL ShowContinueError('...Volume Flow Rate = Air Mass Flow Rate / Air Density')
CALL ShowContinueError('...Volume Flow Rate = '//TRIM(RoundSigDigits(AirVolumeFlowRate,8))//' m3/s.')
CALL ShowContinueError('...Air Mass Flow Rate = '//TRIM(RoundSigDigits(AirMassFlow,8))//' kg/s.')
CALL ShowContinueError('...Air Density = '// &
TRIM(RoundSigDigits(PsyRhoAirFnPbTdbW(OutdoorPressure,InletAirDryBulbTemp, InletAirHumRat),8))//' kg/m3.')
CALL ShowContinueError('...Data used for air density calculation:')
CALL ShowContinueError('...Outdoor Air Pressure = '//TRIM(RoundSigDigits(OutdoorPressure,3))//' Pa.')
CALL ShowContinueError('...Inlet Air Dry-Bulb Temp = '//TRIM(RoundSigDigits(InletAirDryBulbTemp,3))//' C.')
CALL ShowContinueError('...Inlet Air Humidity Ratio = '//TRIM(RoundSigDigits(InletAirHumRat,8))//' kgWater/kgDryAir.')
ENDIF
CALL ShowRecurringWarningErrorAtEnd(TRIM(DXCoil(DXCoilNum)%DXCoilType)//' "'//TRIM(DXCoil(DXCoilNum)%Name)//&
'" - Air volume flow rate per watt of rated total cooling capacity is out ' //&
'of range error continues...',DXCoil(DXCoilNum)%ErrIndex1,VolFlowperRatedTotCap,VolFlowperRatedTotCap)
END IF
!
! Adjust coil bypass factor for actual air flow rate. Use relation CBF = exp(-NTU) where
! NTU = A0/(m*cp). Relationship models the cooling coil as a heat exchanger with Cmin/Cmax = 0.
RatedCBF = DXCoil(DXCoilNum)%RatedCBF(Mode)
IF (RatedCBF .gt. 0.0d0) THEN
A0 = -log(RatedCBF)*DXCoil(DXCoilNum)%RatedAirMassFlowRate(Mode)
ELSE
A0 = 0.0d0
END IF
ADiff=-A0/AirMassFlow
IF (ADiff >= EXP_LowerLimit) THEN
CBF = exp(ADiff)
ELSE
CBF = 0.0d0
END IF
! check boundary for low ambient temperature and post warnings to individual DX coil buffers to print at end of time step
IF(OutdoorDryBulb .LT. DXCoil(DXCoilNum)%MinOATCompressor .AND. .NOT. WarmupFlag) THEN
DXCoil(DXCoilNum)%PrintLowAmbMessage = .TRUE.
DXCoil(DXCoilNum)%LowTempLast = OutdoorDryBulb
IF(DXCoil(DXCoilNum)%LowAmbErrIndex == 0)THEN
DXCoil(DXCoilNum)%LowAmbBuffer1 = TRIM(DXCoil(DXCoilNum)%DXCoilType)//' "'//TRIM(DXCoil(DXCoilNum)%Name)// &
'" - Condenser inlet temperature below '// &
TRIM(RoundSigDigits(DXCoil(DXCoilNum)%MinOATCompressor,2))//' C. Condenser inlet temperature = '// &
TRIM(RoundSigDigits(OutdoorDryBulb,2))
DXCoil(DXCoilNum)%LowAmbBuffer2 = ' '//'... Occurrence info = '//TRIM(EnvironmentName)//', '//Trim(CurMnDy)//' '&
//TRIM(CreateSysTimeIntervalString())
END IF
END IF
! check boundary for high ambient temperature and post warnings to individual DX coil buffers to print at end of time step
IF(OutdoorDryBulb .GT. DXCoil(DXCoilNum)%MaxOATCompressor .AND. .NOT. WarmupFlag) THEN
DXCoil(DXCoilNum)%PrintHighAmbMessage = .TRUE.
DXCoil(DXCoilNum)%HighTempLast = OutdoorDryBulb
IF(DXCoil(DXCoilNum)%HighAmbErrIndex == 0)THEN
DXCoil(DXCoilNum)%HighAmbBuffer1 = TRIM(DXCoil(DXCoilNum)%DXCoilType)//' "'//TRIM(DXCoil(DXCoilNum)%Name)// &
'" - Condenser inlet temperature above '// &
TRIM(RoundSigDigits(DXCoil(DXCoilNum)%MaxOATCompressor,2))//' C. Condenser temperature = '// &
TRIM(RoundSigDigits(OutdoorDryBulb,2))
DXCoil(DXCoilNum)%HighAmbBuffer2 = ' '//'... Occurrence info = '//TRIM(EnvironmentName)//', '//Trim(CurMnDy)//' '&
//TRIM(CreateSysTimeIntervalString())
END IF
END IF
! Get total capacity modifying factor (function of temperature) for off-rated conditions
! InletAirHumRat may be modified in this ADP/BF loop, use temporary varible for calculations
InletAirHumRatTemp = InletAirHumRat
! No need to differentiate between curve types, single-independent curve will just use first variable
! (as long as the first independent variable is the same for both curve types)
50 TotCapTempModFac = CurveValue(DXCoil(DXCoilNum)%CCapFTemp(Mode),InletAirWetbulbC,CondInletTemp)
! Warn user if curve output goes negative
IF(TotCapTempModFac .LT. 0.0d0)THEN
IF(DXCoil(DXCoilNum)%CCapFTempErrorIndex == 0)THEN
CALL ShowWarningMessage(TRIM(DXCoil(DXCoilNum)%DXCoilType)//' "'//TRIM(DXCoil(DXCoilNum)%Name)//'":')
CALL ShowContinueError(' Total Cooling Capacity Modifier curve (function of temperature) output is negative (' &
//TRIM(TrimSigDigits(TotCapTempModFac,3))//').')
CALL ShowContinueError(' Negative value occurs using a condenser inlet temperature of ' &
//TRIM(TrimSigDigits(CondInletTemp,1))// &
' and an inlet air wet-bulb temperature of '//TRIM(TrimSigDigits(InletAirWetbulbC,1))//'.')
IF(Mode .GT. 1)THEN
Call ShowContinueError(' Negative output results from stage '//TRIM(TrimSigDigits(Mode))// &
' compressor operation.')
END IF
CALL ShowContinueErrorTimeStamp(' Resetting curve output to zero and continuing simulation.')
END IF
CALL ShowRecurringWarningErrorAtEnd(TRIM(DXCoil(DXCoilNum)%DXCoilType)//' "'//TRIM(DXCoil(DXCoilNum)%Name)//'":'//&
' Total Cooling Capacity Modifier curve (function of temperature) output is negative warning continues...' &
, DXCoil(DXCoilNum)%CCapFTempErrorIndex, TotCapTempModFac, TotCapTempModFac)
TotCapTempModFac = 0.0d0
END IF
! Get total capacity modifying factor (function of mass flow) for off-rated conditions
AirMassFlowRatio = AirMassFlow/DXCoil(DXCoilNum)%RatedAirMassFlowRate(Mode)
TotCapFlowModFac = CurveValue(DXCoil(DXCoilNum)%CCapFFlow(Mode),AirMassFlowRatio)
! Warn user if curve output goes negative
IF(TotCapFlowModFac .LT. 0.0d0)THEN
IF(DXCoil(DXCoilNum)%CCapFFlowErrorIndex == 0)THEN
CALL ShowWarningMessage(TRIM(DXCoil(DXCoilNum)%DXCoilType)//' "'//TRIM(DXCoil(DXCoilNum)%Name)//'":')
CALL ShowContinueError(' Total Cooling Capacity Modifier curve (function of flow fraction) output is negative (' &
//TRIM(TrimSigDigits(TotCapFlowModFac,3))//').')
CALL ShowContinueError(' Negative value occurs using an air flow fraction of ' &
//TRIM(TrimSigDigits(AirMassFlowRatio,3))//'.')
CALL ShowContinueErrorTimeStamp(' Resetting curve output to zero and continuing simulation.')
IF(Mode .GT. 1)THEN
Call ShowContinueError(' Negative output results from stage '//TRIM(TrimSigDigits(Mode))// &
' compressor operation.')
END IF
END IF
CALL ShowRecurringWarningErrorAtEnd(TRIM(DXCoil(DXCoilNum)%DXCoilType)//' "'//TRIM(DXCoil(DXCoilNum)%Name)//'":'//&
' Total Cooling Capacity Modifier curve (function of flow fraction) output is negative warning continues...' &
, DXCoil(DXCoilNum)%CCapFFlowErrorIndex, TotCapFlowModFac, TotCapFlowModFac)
TotCapFlowModFac = 0.0d0
END IF
IF(PRESENT(MaxCoolCap))THEN
TotCap = MIN(MaxCoolCap,DXCoil(DXCoilNum)%RatedTotCap(Mode) * TotCapFlowModFac * TotCapTempModFac)
ELSE
TotCap = DXCoil(DXCoilNum)%RatedTotCap(Mode) * TotCapFlowModFac * TotCapTempModFac
END IF
TotCap = TotCap * PartLoadRatio
! Calculate apparatus dew point conditions using TotCap and CBF
hDelta = TotCap/AirMassFlow
! there is an issue here with using CBF to calculate the ADP enthalpy.
! at low loads the bypass factor increases significantly.
hADP = InletAirEnthalpy - hDelta/(1.d0-CBF)
tADP = PsyTsatFnHPb(hADP,OutdoorPressure,'CalcVRFCoolingCoil')
! Eventually inlet air conditions will be used in DX Coil, these lines are commented out and marked with this comment line
! tADP = PsyTsatFnHPb(hADP,InletAirPressure)
wADP = MIN(InletAirHumRat,PsyWFnTdbH(tADP,hADP,'CalcVRFCoolingCoil'))
hTinwADP = PsyHFnTdbW(InletAirDryBulbTemp,wADP,'CalcVRFCoolingCoil')
IF((InletAirEnthalpy-hADP) > 1.d-10)THEN
SHR = MIN((hTinwADP-hADP)/(InletAirEnthalpy-hADP),1.d0)
ELSE
SHR = 1.0d0
END IF
!
! Check for dry evaporator conditions (win < wadp)
!
IF (wADP .gt. InletAirHumRatTemp .or. (Counter .ge. 1 .and. Counter .lt. MaxIter)) THEN
If(InletAirHumRatTemp == 0.0d0)InletAirHumRatTemp=0.00001d0
werror = (InletAirHumRatTemp - wADP)/InletAirHumRatTemp
!
! Increase InletAirHumRatTemp at constant InletAirTemp to find coil dry-out point. Then use the
! capacity at the dry-out point to determine exiting conditions from coil. This is required
! since the TotCapTempModFac doesn't work properly with dry-coil conditions.
!
InletAirHumRatTemp = RF*wADP + (1.d0-RF)*InletAirHumRatTemp
InletAirWetbulbC = PsyTwbFnTdbWPb(InletAirDryBulbTemp,InletAirHumRatTemp,OutdoorPressure)
! Eventually inlet air conditions will be used in DX Coil, these lines are commented out and marked with this comment line
! InletAirWetbulbC = PsyTwbFnTdbWPb(InletAirDryBulbTemp,InletAirHumRatTemp,InletAirPressure)
Counter = Counter + 1
IF (ABS(werror) .gt. Tolerance) go to 50 ! Recalculate with modified inlet conditions
END IF
IF(DXCoil(DXCoilNum)%PLFFPLR(mode) .GT. 0 .AND. CompCycRatio .LT. 1.d0)THEN
PLF = CurveValue(DXCoil(DXCoilNum)%PLFFPLR(mode),CompCycRatio) ! Calculate part-load factor
ELSE
PLF = 1.0d0
END IF
IF (PLF < 0.7d0) THEN
IF (DXCoil(DXCoilNum)%ErrIndex2 == 0) THEN
CALL ShowWarningMessage('The PLF curve value for the DX cooling coil '//TRIM(DXCoil(DXCoilNum)%Name)//&
' ='//TRIM(RoundSigDigits(PLF,3))// &
' for part-load ratio ='//TRIM(RoundSigDigits(PartLoadRatio,3)))
CALL ShowContinueErrorTimeStamp('PLF curve values must be >= 0.7. PLF has been reset to 0.7 and simulation is continuing.')
CALL ShowContinueError('Check the IO reference manual for PLF curve guidance [Coil:Cooling:DX:SingleSpeed].')
END IF
CALL ShowRecurringWarningErrorAtEnd(TRIM(DXCoil(DXCoilNum)%Name)// &
', DX cooling coil PLF curve < 0.7 warning continues...', &
DXCoil(DXCoilNum)%ErrIndex2,PLF,PLF)
PLF = 0.7d0
END IF
DXCoil(DXCoilNum)%PartLoadRatio = PartLoadRatio
DXCoil(DXCoilNum)%CoolingCoilRuntimeFraction = CompCycRatio / PLF
IF (DXCoil(DXCoilNum)%CoolingCoilRuntimeFraction > 1.0d0 .and. &
ABS(DXCoil(DXCoilNum)%CoolingCoilRuntimeFraction-1.0d0) > .001d0 ) THEN
IF (DXCoil(DXCoilNum)%ErrIndex3 == 0) THEN
CALL ShowWarningMessage('The runtime fraction for DX cooling coil '//TRIM(DXCoil(DXCoilNum)%Name)//&
' exceeded 1.0. ['//TRIM(RoundSigDigits(DXCoil(DXCoilNum)%CoolingCoilRuntimeFraction,4))//'].')
CALL ShowContinueError('Runtime fraction reset to 1 and the simulation will continue.')
CALL ShowContinueError('Check the IO reference manual for PLF curve guidance [Coil:Cooling:DX:SingleSpeed].')
CALL ShowContinueErrorTimeStamp(' ')
END IF
CALL ShowRecurringWarningErrorAtEnd(TRIM(DXCoil(DXCoilNum)%Name)// &
', DX cooling coil runtime fraction > 1.0 warning continues...', &
DXCoil(DXCoilNum)%ErrIndex3,DXCoil(DXCoilNum)%CoolingCoilRuntimeFraction,DXCoil(DXCoilNum)%CoolingCoilRuntimeFraction)
DXCoil(DXCoilNum)%CoolingCoilRuntimeFraction = 1.0d0 ! Reset coil runtime fraction to 1.0
ELSEIF (DXCoil(DXCoilNum)%CoolingCoilRuntimeFraction > 1.0d0) THEN
DXCoil(DXCoilNum)%CoolingCoilRuntimeFraction = 1.0d0 ! Reset coil runtime fraction to 1.0
END IF
! If cycling fan, send coil part-load fraction to on/off fan via HVACDataGlobals
IF (FanOpMode .EQ. CycFanCycCoil) OnOffFanPartLoadFraction = PLF
! Calculate full load output conditions
IF (SHR .gt. 1.0d0 .OR. Counter .gt. 0) SHR = 1.d0
FullLoadOutAirEnth = InletAirEnthalpy - TotCap/AirMassFlow
hTinwout = InletAirEnthalpy - (1.0d0-SHR)*hDelta
IF (SHR < 1.0d0) THEN
FullLoadOutAirHumRat = PsyWFnTdbH(InletAirDryBulbTemp,hTinwout)
ELSE
FullLoadOutAirHumRat = InletAirHumRat
END IF
FullLoadOutAirTemp = PsyTdbFnHW(FullLoadOutAirEnth,FullLoadOutAirHumRat)
! Check for saturation error and modify temperature at constant enthalpy
IF(FullLoadOutAirTemp .LT. PsyTsatFnHPb(FullLoadOutAirEnth,OutdoorPressure)) THEN
FullLoadOutAirTemp = PsyTsatFnHPb(FullLoadOutAirEnth,OutdoorPressure)
! Eventually inlet air conditions will be used in DX Coil, these lines are commented out and marked with this comment line
! IF(FullLoadOutAirTemp .LT. PsyTsatFnHPb(FullLoadOutAirEnth,InletAirPressure)) THEN
! FullLoadOutAirTemp = PsyTsatFnHPb(FullLoadOutAirEnth,InletAirPressure)
FullLoadOutAirHumRat = PsyWFnTdbH(FullLoadOutAirTemp,FullLoadOutAirEnth)
END IF
! Store actual outlet conditions when DX coil is ON for use in heat recovery module
DXCoilFullLoadOutAirTemp(DXCoilNum) = FullLoadOutAirTemp
DXCoilFullLoadOutAirHumRat(DXCoilNum) = FullLoadOutAirHumRat
! Add warning message for cold cooling coil (FullLoadOutAirTemp < 2 C)
IF(FullLoadOutAirTemp .LT. 2.0d0 .AND. .NOT. FirstHVACIteration .AND. .NOT. WarmupFlag)THEN
DXCoil(DXCoilNum)%PrintLowOutTempMessage = .TRUE.
DXCoil(DXCoilNum)%FullLoadOutAirTempLast = FullLoadOutAirTemp
IF(DXCoil(DXCoilNum)%LowOutletTempIndex == 0)THEN
DXCoil(DXCoilNum)%FullLoadInletAirTempLast = InletAirDryBulbTemp
DXCoil(DXCoilNum)%LowOutTempBuffer1= TRIM(DXCoil(DXCoilNum)%DXCoilType)//' "'//TRIM(DXCoil(DXCoilNum)%Name)// &
'" - Full load outlet air dry-bulb temperature < 2C. This indicates the possibility of coil frost/freeze.'// &
' Outlet temperature = '//TRIM(RoundSigDigits(FullLoadOutAirTemp,2))//' C.'
DXCoil(DXCoilNum)%LowOutTempBuffer2 = ' '//'...Occurrence info = '//TRIM(EnvironmentName)//', '//Trim(CurMnDy)//' '&
//TRIM(CreateSysTimeIntervalString())
END IF
END IF
! If constant fan with cycling compressor, call function to determine "effective SHR"
! which includes the part-load degradation on latent capacity
IF (FanOpMode .EQ. ContFanCycCoil .AND. CompCycRatio .LT. 1.d0) THEN
QLatRated = DXCoil(DXCoilNum)%RatedTotCap(Mode) * (1.d0 - DXCoil(DXCoilNum)%RatedSHR(Mode))
QLatActual = TotCap * (1.d0 - SHR)
SHRUnadjusted = SHR
SHR = CalcEffectiveSHR(DXCoilNum, SHR, DXCoil(DXCoilNum)%CoolingCoilRuntimeFraction, &
QLatRated, QLatActual, InletAirDryBulbTemp, InletAirWetbulbC, Mode)
! Calculate full load output conditions
IF (SHR .gt. 1.d0 .OR. Counter .gt. 0) SHR = 1.d0
FullLoadOutAirEnth = InletAirEnthalpy - TotCap/AirMassFlow
hTinwout = InletAirEnthalpy - (1.0d0-SHR)*hDelta
IF (SHR < 1.0d0) THEN
FullLoadOutAirHumRat = PsyWFnTdbH(InletAirDryBulbTemp,hTinwout)
ELSE
FullLoadOutAirHumRat = InletAirHumRat
END IF
FullLoadOutAirTemp = PsyTdbFnHW(FullLoadOutAirEnth,FullLoadOutAirHumRat)
END IF
! Calculate actual outlet conditions for the input part load ratio
! Actual outlet conditions are "average" for time step when compressor cycles
IF (FanOpMode .EQ. ContFanCycCoil .AND. CompCycRatio .LT. 1.d0) THEN
! Continuous fan, cycling compressor
OutletAirEnthalpy = ((PartLoadRatio * AirFlowRatio)*FullLoadOutAirEnth + &
(1.d0-(PartLoadRatio * AirFlowRatio))*InletAirEnthalpy)
OutletAirHumRat = ((PartLoadRatio * AirFlowRatio)*FullLoadOutAirHumRat + &
(1.d0-(PartLoadRatio * AirFlowRatio))*InletAirHumRat)
OutletAirTemp = PsyTdbFnHW(OutletAirEnthalpy,OutletAirHumRat)
ELSE
! Default to cycling fan, cycling compressor
OutletAirEnthalpy = FullLoadOutAirEnth
OutletAirHumRat = FullLoadOutAirHumRat
OutletAirTemp = FullLoadOutAirTemp
END IF
! Check for saturation error and modify temperature at constant enthalpy
IF(OutletAirTemp .LT. PsyTsatFnHPb(OutletAirEnthalpy,OutdoorPressure,'CalcVRFCoolingCoil')) THEN
OutletAirTemp = PsyTsatFnHPb(OutletAirEnthalpy,OutdoorPressure)
! Eventually inlet air conditions will be used in DX Coil, these lines are commented out and marked with this comment line
! IF(OutletAirTemp .LT. PsyTsatFnHPb(OutletAirEnthalpy,InletAirPressure)) THEN
! OutletAirTemp = PsyTsatFnHPb(OutletAirEnthalpy,InletAirPressure)
OutletAirHumRat = PsyWFnTdbH(OutletAirTemp,OutletAirEnthalpy)
END IF
! Reset AirMassFlow to inlet node air mass flow for final total, sensible and latent calculations
! since AirMassFlow might have been modified above (in this subroutine):
! IF (FanOpMode .EQ. CycFanCycCoil) AirMassFlow = AirMassFlow / PartLoadRatio
!
! For multimode coil, this should be full flow including bypassed fraction
AirMassFlow = DXCoil(DXCoilNum)%InletAirMassFlowRate
DXCoil(DXCoilNum)%TotalCoolingEnergyRate = AirMassFlow * (InletAirEnthalpy - OutletAirEnthalpy)
!! Set DataHeatGlobal heat reclaim variable for use by heat reclaim coil (part load ratio is accounted for)
!! Calculation for heat reclaim needs to be corrected to use compressor power (not including condenser fan power)
! HeatReclaimDXCoil(DXCoilNum)%AvailCapacity = DXCoil(DXCoilNum)%TotalCoolingEnergyRate + DXCoil(DXCoilNum)%ElecCoolingPower
MinAirHumRat = MIN(InletAirHumRat,OutletAirHumRat)
DXCoil(DXCoilNum)%SensCoolingEnergyRate = AirMassFlow * &
(PsyHFnTdbW(InletAirDryBulbTemp,MinAirHumRat) - &
PsyHFnTdbW(OutletAirTemp,MinAirHumRat))
! Don't let sensible capacity be greater than total capacity
IF (DXCoil(DXCoilNum)%SensCoolingEnergyRate .GT. DXCoil(DXCoilNum)%TotalCoolingEnergyRate) THEN
DXCoil(DXCoilNum)%SensCoolingEnergyRate = DXCoil(DXCoilNum)%TotalCoolingEnergyRate
END IF
!
DXCoil(DXCoilNum)%LatCoolingEnergyRate = DXCoil(DXCoilNum)%TotalCoolingEnergyRate - DXCoil(DXCoilNum)%SensCoolingEnergyRate
DXCoil(DXCoilNum)%OutletAirTemp = OutletAirTemp
DXCoil(DXCoilNum)%OutletAirHumRat = OutletAirHumRat
DXCoil(DXCoilNum)%OutletAirEnthalpy = OutletAirEnthalpy
ELSE
! DX coil is off; just pass through conditions
DXCoil(DXCoilNum)%OutletAirEnthalpy = DXCoil(DXCoilNum)%InletAirEnthalpy
DXCoil(DXCoilNum)%OutletAirHumRat = DXCoil(DXCoilNum)%InletAirHumRat
DXCoil(DXCoilNum)%OutletAirTemp = DXCoil(DXCoilNum)%InletAirTemp
DXCoil(DXCoilNum)%ElecCoolingPower = 0.0d0
DXCoil(DXCoilNum)%TotalCoolingEnergyRate = 0.0d0
DXCoil(DXCoilNum)%SensCoolingEnergyRate = 0.0d0
DXCoil(DXCoilNum)%LatCoolingEnergyRate = 0.0d0
DXCoil(DXCoilNum)%EvapCondPumpElecPower = 0.0d0
DXCoil(DXCoilNum)%EvapWaterConsumpRate = 0.0d0
! Reset globals when DX coil is OFF for use in heat recovery module
DXCoilFullLoadOutAirTemp(DXCoilNum) = 0.0d0
DXCoilFullLoadOutAirHumRat(DXCoilNum) = 0.0d0
END IF ! end of on/off if - else
!set water system demand request (if needed)
IF ( DXCoil(DxCoilNum)%EvapWaterSupplyMode == WaterSupplyFromTank) THEN
WaterStorage(DXCoil(DXCoilNum)%EvapWaterSupTankID)%VdotRequestDemand(DXCoil(DXCoilNum)%EvapWaterTankDemandARRID) &
= DXCoil(DXCoilNum)%EvapWaterConsumpRate
ENDIF
DXCoilOutletTemp(DXCoilNum) = DXCoil(DXCoilNum)%OutletAirTemp
DXCoilOutletHumRat(DXCoilNum) = DXCoil(DXCoilNum)%OutletAirHumRat
DXCoilPartLoadRatio(DXCoilNum) = DXCoil(DXCoilNum)%PartLoadRatio
DXCoilFanOpMode(DXCoilNum) = FanOpMode
DXCoil(DXCoilNum)%CondInletTemp = CondInletTemp
DXCoilTotalCooling(DXCoilNum) = DXCoil(DXCoilNum)%TotalCoolingEnergyRate
DXCoilCoolInletAirWBTemp(DXCoilNum) = PsyTwbFnTdbWPb(InletAirDryBulbTemp,InletAirHumRat,OutdoorPressure)
RETURN
END SUBROUTINE CalcVRFCoolingCoil