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) | :: | CaseID |
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 CalculateCase(CaseID)
! SUBROUTINE INFORMATION:
! AUTHOR Richard Raustad and Don Shirey, FSEC
! DATE WRITTEN Oct/Nov 2004
! MODIFIED Therese Stovall, ORNL, May 2008
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! To model refrigerated cases.
! METHODOLOGY EMPLOYED:
! Case performance is based on a latent component calculated using a user input curve object. The sensible
! component is made up of all equipment loads (fan, light, anti-sweat) and the sensible case credit
! calculated during initialization. A master schedule is used for the refrigerated case operation and
! additional schedules control the lights and defrost operation.
! The fan is assumed to be off for Hot-Gas and Electric defrost.
! Unmet loads are accumulated to be met the following time step. This usually occurs only during the
! defrost period, so the case calls for full capacity at the end of defrost to make up for the sensible
! case gains during the defrost period. This feature is also used if needed for restocking loads.
! REFERENCES:
! "Calculation of Humidity Effects on Energy Requirements of Refrigerated Display Cases",
! R. H. Howell, Ph. D., P.E., ASHRAE Paper, 3687 (CH-93-16-4) (RP-596)
! "Effects of Store Relative Humidity on Refrigerated Display Case Performance",
! R. H. Howell, Ph. D., P.E., ASHRAE Paper, 3686 (CH-93-16-1) (RP-596)
! "Analysis of Supermarket Dehumidification Alternatives",
! Electric Power Research Institute, EPRI TR-100352, Project 2891-03 Final Report, Nov. 1992.
! "Impact of ASHRAE Standard 62-1989 on Florida Supermarkets",
! Florida Solar Energy Center, FSEC-CR-910-96, Final Report, Oct. 1996
! USE STATEMENTS:
USE CurveManager, ONLY: CurveValue
USE DataLoopNode
USE DataEnvironment, ONLY:OutBaroPress !, Month
USE Psychrometrics, ONLY: PsyRhFnTdbWPb, PsyTdpFnWPb
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: CaseID ! Absolute pointer to refrigerated case
! SUBROUTINE PARAMETER DEFINITIONS:
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: ActualZoneNum = 0 ! Index to zone
INTEGER :: DefCapCurvePtr = 0
INTEGER :: DefrostEnergyCurveType = 0
INTEGER :: DefrostType = 0
INTEGER :: ZoneNodeNum = 0 ! Zone node number
REAL(r64) :: CapAvail =0.0d0 ! capacity available to meet current and stored load (W)
REAL(r64) :: CaseRAFraction =0.0d0 ! Fraction of case credits applied to return air
REAL(r64) :: CaseCreditFraction =0.0d0 ! Reduction in case credits due to e.g., reduced door openings at night
REAL(r64) :: CaseSenCreditToZone =0.0d0 ! Amount of sensible case credit applied to zone load (W)
REAL(r64) :: CaseLatCreditToZone =0.0d0 ! Amount of latent case credit applied to zone load (W)
REAL(r64) :: CaseSenCreditToHVAC =0.0d0 ! Amount of sensible case credit applied to HVAC RA duct (W)
REAL(r64) :: CaseLatCreditToHVAC =0.0d0 ! Amount of latent case credit applied to HVAC RA duct (W)
REAL(r64) :: CaseSchedule =0.0d0 ! Current value of case operating (availability) schedule
REAL(r64) :: DefrostEnergy =0.0d0 ! Energy form of defrost capacity (J)
REAL(r64) :: DefrostSchedule =0.0d0 ! Display case defrost schedule
REAL(r64) :: DefrostDripDownSchedule =0.0d0 ! Display case drip-down schedule (allows coil to drain after defrost)
REAL(r64) :: DefCapModFrac =0.0d0 ! Defrost capacity modifier curve based on case operating temperature
REAL(r64) :: DefrostRatio =0.0d0 !ratio of defrost energy at current zone temp/humrat to defrost
! capacity at design condition
REAL(r64) :: DefrostLoad_Actual =0.0d0 ! heat load on case due to defrost (W)
REAL(r64) :: DefrostCap_Actual =0.0d0 ! power used to defrost (W)
REAL(r64) :: DeltaFreezeKgFrost =0.0d0 ! change in frost on coils (kg)
REAL(r64) :: DeltaStockingEnergy =0.0d0 ! Used to keep track of problems if sizing not consistent (J)
REAL(r64) :: DeltaWarmEnvEnergy =0.0d0 ! Used to keep track of problems if sizing not consistent (J)
REAL(r64) :: DesignRatedCap =0.0d0 ! Design rated capacity of display case (W)
REAL(r64) :: DesignDefrostCap =0.0d0 ! Design defrost capacity of display case (W)
REAL(r64) :: DesignLatentCap =0.0d0 ! Design latent capacity of display case (W)
REAL(r64) :: DesignLighting =0.0d0 ! Total design display case lighting power (W)
REAL(r64) :: FrostMeltedKg =0.0d0 ! Frost melted by defrost during a time step (kg)
REAL(r64) :: LatentLoad =0.0d0 ! Latent load placed on case at actual zone conditions (W)
REAL(r64) :: LatentRatio =0.0d0 !ratio of latent capacity at current zone temp/humrat to
! latent capacity at design condition
REAL(r64) :: LatentCap_Actual =0.0d0 ! Refrigerated case latent capacity at specific operating conditions
REAL(r64) :: LatentCaseCredit =0.0d0 ! Latent case credit delivered to zone (W)
REAL(r64) :: LatCapModFrac =0.0d0 ! Latent capacity modifier curve based on case operating temperature
REAL(r64) :: LightingSchedule =0.0d0 ! Display case lighting schedule
REAL(r64) :: Length =0.0d0 ! Length of display case (m)
REAL(r64) :: LoadRequested =0.0d0 ! TotalLoad_Actual + StoredEnergyRate
REAL(r64) :: RatedAmbientRH =0.0d0 ! Local variable for the RH corresponding to case rating conditions
REAL(r64) :: SensibleCaseCredit =0.0d0 ! Sensible case credit delivered to zone (W)
REAL(r64) :: SensibleCap_Actual =0.0d0 ! Refrigerated case sensible capacity at specific operating conditions
!REAL(r64) :: SensibleFraction =0.0d0 ! Portion of total load due to sensible load
REAL(r64) :: SensibleLoadPrime =0.0d0 ! Sensible load due to cond, conv, rad, infil (W)
REAL(r64) :: SensibleLoadAux =0.0d0 ! Sensible load due to heaters, lighting (W)
REAL(r64) :: SensibleLoadTotal =0.0d0 ! Total sensible load on case, may not = capacity applied (W)
REAL(r64) :: StockingSchedule =0.0d0 ! Current value of product stocking schedule (W/m)
REAL(r64) :: StockingLoad =0.0d0 ! Total load due to stocking case product (W)
REAL(r64) :: StoredEnergyRate =0.0d0 ! Rate needed to serve all stored energy during single time step (W)
REAL(r64) :: TotalLoad_Actual =0.0d0 ! total load on case at zone conditions (W)
REAL(r64) :: StartFrostKg =0.0d0 ! frost load at start of time step (kg of ice)
REAL(r64) :: TotalCap_Actual =0.0d0 ! Refrigerated case total capacity at specific operating conditions
REAL(r64) :: TotalLightingLoad =0.0d0 ! Total lighting energy rate (W)
REAL(r64) :: TotalFan =0.0d0 ! Total fan energy rate (W)
REAL(r64) :: TotalAntiSweat =0.0d0 ! Total anti-sweat heater energy rate (W)
REAL(r64) :: TotalLightToCase =0.0d0 ! Lighting energy to case
REAL(r64) :: TotalASHeaterToCase =0.0d0 ! Anti-sweat heater energy to case
REAL(r64) :: TotalLightToZone =0.0d0 ! Lighting energy to zone
REAL(r64) :: TotalASHeaterToZone =0.0d0 ! Anti-sweat heater energy to zone
REAL(r64) :: TCase =0.0d0 ! Display case operating temperature
REAL(r64) :: ZoneRHPercent =0.0d0 ! Zone relative humidity (%)
REAL(r64) :: ZoneDewPoint =0.0d0 ! Zone dew point (C)
REAL(r64) :: ZoneTempFactor =0.0d0 ! used to look at extra sensible load due to excursions in zone T
! Refrigerated display case defrost type (parameters)
! DefNone = 0
! DefOffCycle = 1
! DefHotFluid = 2
! DefHotFluidOnDemand = 3 (not available)
! DefHotFluidTerm = 4
! DefElectric = 5
! DefElectricOnDemand = 6 (not available)
! DefElectricTerm = 7
!Initialize this case for this time step (
! All report variables prev set to zero for case when schedule for case is 'off')
TotalCap_Actual = 0.0d0
LatentCap_Actual = 0.0d0
SensibleCap_Actual = 0.0d0
SensibleLoadTotal = 0.0d0
SensibleLoadPrime = 0.0d0
SensibleLoadAux = 0.0d0
DefrostLoad_Actual = 0.0d0
DefrostCap_Actual = 0.0d0
DefrostRatio = 0.0d0
LatentRatio = 0.0d0
StartFrostKg = 0.0d0
SensibleCaseCredit = 0.0d0
LatentCaseCredit = 0.0d0
CaseSenCreditToZone = 0.0d0
CaseLatCreditToZone = 0.0d0
CaseSenCreditToHVAC = 0.0d0
CaseLatCreditToHVAC = 0.0d0
CaseRAFactor = 0.0d0
TotalLightingLoad = 0.0d0
TotalAntiSweat = 0.0d0
TotalFan = 0.0d0
!Set local subroutine variables for convenience
ActualZoneNum = RefrigCase(CaseID)%ActualZoneNum
ZoneNodeNum = RefrigCase(CaseID)%ZoneNodeNum
ZoneRHPercent = PsyRhFnTdbWPb(Node(ZoneNodeNum)%Temp,Node(ZoneNodeNum)%Humrat,OutBaroPress)*100.0d0
ZoneDewPoint = PsyTdpFnWPb(Node(ZoneNodeNum)%Humrat,OutBaroPress)
Length = RefrigCase(CaseID)%Length
TCase = RefrigCase(CaseID)%Temperature
DesignRatedCap = RefrigCase(CaseID)%DesignRatedCap
DesignLatentCap = RefrigCase(CaseID)%DesignLatentCap
DesignDefrostCap = RefrigCase(CaseID)%DesignDefrostCap
DesignLighting = RefrigCase(CaseID)%DesignLighting
DefCapCurvePtr = RefrigCase(CaseID)%DefCapCurvePtr
DefrostEnergyCurveType = RefrigCase(CaseID)%DefrostEnergyCurveType
DefrostType = RefrigCase(CaseID)%DefrostType
RatedAmbientRH = RefrigCase(CaseID)%RatedAmbientRH
! GET ALL SCHEDULES (note all schedules can be fractions if on/off a portion of time step)
! case schedule should be coincident with the zone time step otherwise the simulation proceeds
CaseSchedule = GetCurrentScheduleValue(RefrigCase(CaseID)%SchedPtr)
IF (CaseSchedule <= 0) RETURN
! get defrost schedule
IF(DefrostType > DefNone) THEN
DefrostSchedule = GetCurrentScheduleValue(RefrigCase(CaseID)%DefrostSchedPtr)
DefrostDripDownSchedule = GetCurrentScheduleValue(RefrigCase(CaseID)%DefrostDripDownSchedPtr)
!next statement In case user doesn't understand concept of drip down schedule
DefrostDripDownSchedule = MAX(DefrostDripDownSchedule,DefrostSchedule)
ELSE
DefrostSchedule = 0.0d0
DefrostDripDownSchedule = 0.0d0
END IF
! get product stocking schedule and load due to product stocking, if no schedule exists load is 0
IF (RefrigCase(CaseID)%StockingSchedPtr > 0) THEN
StockingSchedule = GetCurrentScheduleValue(RefrigCase(CaseID)%StockingSchedPtr)
ELSE
StockingSchedule = 0.0d0
END IF
! get lighting schedule and total load due to lighting
LightingSchedule = GetCurrentScheduleValue(RefrigCase(CaseID)%LightingSchedPtr)
! if case credit reduction fraction schedule exists, modify both sensible and latent case credits
! according to schedule - used to account for variable case envelope, such as night covers.
IF(RefrigCase(CaseID)%CaseCreditFracSchedPtr /= 0) THEN
CaseCreditFraction = GetCurrentScheduleValue(RefrigCase(CaseID)%CaseCreditFracSchedPtr)
ELSE
CaseCreditFraction = 1.0d0
END IF
! CALCULATE AUX LOADS DUE TO LIGHTS, FAN AND STOCKING
TotalLightingLoad = DesignLighting * LightingSchedule
TotalLightToCase = TotalLightingLoad*RefrigCase(CaseID)%LightingFractionToCase
TotalLightToZone = TotalLightingLoad - TotalLightToCase
! cycle fan according to defrost schedule
! turn fan on for none or off-cycle defrost types
IF(DefrostType == DefNone .OR. DefrostType == DefOffCycle) THEN
TotalFan = RefrigCase(CaseID)%DesignFanPower
ELSE
TotalFan = RefrigCase(CaseID)%DesignFanPower * ( 1.0d0 - DefrostDripDownSchedule )
END IF
! get load due to product stocking
! accumulate stocking loads for reporting to help evaluate any cumulative unmet loads problems
! only accumulate energy during actual simulation (so same if DD's are switched)
StockingLoad = StockingSchedule * Length
IF(.NOT. WarmUpFlag) THEN
DeltaStockingEnergy = (StockingLoad * TimeStepZone * SecInHour)
RefrigCase(CaseID)%StockingEnergy = RefrigCase(CaseID)%StockingEnergy + DeltaStockingEnergy
END IF !warm up
! CALCULTE ALL LOADS INFLUENCED BY ZONE TEMPERATURE AND RH
! Anti-sweat heater capacity
SELECT CASE (RefrigCase(CaseID)%AntiSweatControlType)
CASE (ASNone)
TotalAntiSweat = 0.0d0
CASE (ASConstant)
TotalAntiSweat = RefrigCase(CaseID)%AntiSweatPower
CASE (ASLinear)
TotalAntiSweat = RefrigCase(CaseID)%AntiSweatPower * &
MIN(1.0d0, MAX(0.0d0,1.0d0-(RatedAmbientRH-ZoneRHPercent)/ &
(RatedAmbientRH-RefrigCase(CaseID)%HumAtZeroAS)))
TotalAntiSweat = MAX(RefrigCase(CaseID)%MinimumASPower, TotalAntiSweat)
CASE (ASDewPoint)
TotalAntiSweat = RefrigCase(CaseID)%AntiSweatPower * &
MIN(1.0d0, MAX(0.0d0,(ZoneDewPoint-TCase)/(RefrigCase(CaseID)%RatedAmbientDewPoint-TCase)))
TotalAntiSweat = MAX(RefrigCase(CaseID)%MinimumASPower, TotalAntiSweat)
CASE (ASHeatBalance)
IF(RefrigCase(CaseID)%Rcase > 0.0d0) THEN
TotalAntiSweat = (((ZoneDewPoint-Node(ZoneNodeNum)%Temp)*RefrigCase(CaseID)%Height &
/Rair) + &
((ZoneDewPoint-Tcase)*RefrigCase(CaseID)%Height &
/RefrigCase(CaseID)%Rcase))
TotalAntiSweat = MIN(RefrigCase(CaseID)%AntiSweatPower,MAX(RefrigCase(CaseID)%MinimumASPower, &
TotalAntiSweat))
ELSE
TotalAntiSweat = 0.0d0
END IF
CASE DEFAULT
! should never execute this CASE statement
TotalAntiSweat = 0.0d0
END SELECT
TotalAntiSweat = TotalAntiSweat * Length
TotalASHeaterToCase = RefrigCase(CaseID)%ASHeaterFractionToCase * TotalAntiSweat
TotalASHeaterToZone = TotalAntiSweat - TotalASHeaterToCase
! latent capacity correction term at off-design conditions
SELECT CASE (RefrigCase(CaseID)%LatentEnergyCurveType)
CASE (CaseTemperatureMethod)
LatCapModFrac = CurveValue(RefrigCase(CaseID)%LatCapCurvePtr,TCase)
LatentRatio = MAX(0.0d0,(1.0d0 - (RatedAmbientRH - ZoneRHPercent)*LatCapModFrac))
CASE (RHCubic)
LatentRatio = MAX(0.0d0,CurveValue(RefrigCase(CaseID)%LatCapCurvePtr,ZoneRHPercent))
CASE ( DPCubic)
LatentRatio = MAX(0.0d0,CurveValue(RefrigCase(CaseID)%LatCapCurvePtr,ZoneDewPoint))
END SELECT
! calculate latent case load (assumes no moisture load due to stocking)
! assume sensible case credits continue to accumulate in case during defrost/dripdown,
! but latent credits/load and capacity only applied outside dripdownschedule
LatentLoad = DesignLatentCap * LatentRatio * CaseCreditFraction * ( 1.0d0 - DefrostDripDownSchedule )
LatentCaseCredit = -LatentLoad
! adjust sensible loads and case credit for actual zone temperature
! If zone temp rises above rated ambient temperature, total load can exceed case design capacity,
! so unmet cooling loads are accumulated to meet in the next time step. (Case credit fraction allows
! extra insulation, e.g. night covers, or imitating a better insulated walk-in cooler)
ZoneTempFactor = (Node(ZoneNodeNum)%Temp-Tcase)/(RefrigCase(CaseID)%RatedAmbientTemp-Tcase)
SensibleLoadPrime = RefrigCase(CaseID)%DesignSensCaseCredit * ZoneTempFactor * CaseCreditFraction
SensibleLoadAux = TotalLightToCase + TotalASHeaterToCase + TotalFan + StockingLoad
SensibleLoadTotal = SensibleLoadPrime + SensibleLoadAux
! include lighting and anti-sweat power not attributed to case load to sensible case credit
SensibleCaseCredit = TotalLightToZone + TotalASHeaterToZone - SensibleLoadPrime
! FROST: keep track of frost build up on evaporator coil
!avoid accumulation during warm-up to avoid reverse dd test problem
IF(.NOT. WarmUpFlag) THEN
DeltaFreezeKgFrost = LatentLoad * TimeStepZone * SecInHour/IcetoVaporEnthalpy
RefrigCase(CaseID)%KgFrost = RefrigCase(CaseID)%KgFrost + DeltaFreezeKgFrost
END IF
IF(Tcase > TempTooHotToFrost) RefrigCase(CaseID)%KgFrost = 0.0d0
!DEFROST CALCULATIONS
IF(DefrostSchedule > 0.0d0) THEN
IF(DefrostType /= DefNone .AND. DefrostType /= DefOffCycle) THEN
DefrostCap_Actual = DesignDefrostCap * DefrostSchedule
IF(DefrostType == DefElectricTerm .OR. DefrostType == DefHotFluidTerm )THEN
! calculate correction term for temperature termination defrost control
SELECT CASE (DefrostEnergyCurveType)
CASE(CaseTemperatureMethod)
DefCapModFrac = CurveValue(DefCapCurvePtr,TCase)
DefrostRatio = MAX(0.0d0,(1.0d0 - (RatedAmbientRH - ZoneRHPercent)*DefCapModFrac))
CASE(RHCubic)
DefrostRatio = MAX(0.0d0,CurveValue(DefCapCurvePtr,ZoneRHPercent))
CASE(DPCubic)
DefrostRatio = MAX(0.0d0,CurveValue(DefCapCurvePtr,ZoneDewPoint))
CASE(None)
DefrostRatio = 1.0d0
END SELECT
DefrostCap_Actual = DefrostCap_Actual * DefrostRatio
END IF
StartFrostKg = RefrigCase(CaseID)%KgFrost
DefrostEnergy = DefrostCap_Actual*TimeStepZone*SecInHour
FrostMeltedKg = MIN(DefrostEnergy/IceMeltEnthalpy,StartFrostKg)
RefrigCase(CaseID)%KgFrost = RefrigCase(CaseID)%KgFrost - FrostMeltedKg
!Reduce defrost heat load on case by amount of ice melted during time step
!However, don't reduce the defrost capacity applied
DefrostLoad_Actual = DefrostCap_Actual - FrostMeltedKg*IceMeltEnthalpy/TimeStepZone/SecInHour
IF(.NOT. WarmUpFlag)THEN !avoid reverse dd test problems
! keep running total of defrost energy above that needed to melt frost for use in evaluating
! problems of excessive unmet loads
RefrigCase(CaseID)%DeltaDefrostEnergy = MAX(0.0D0,(DefrostEnergy -(FrostMeltedKg*IceMeltEnthalpy)))
RefrigCase(CaseID)%DefrostEnergy = RefrigCase(CaseID)%DefrostEnergy + RefrigCase(CaseID)%DeltaDefrostEnergy
END IF
! If hot brine or hot gas is used for defrost, need to reduce condenser load
! Note this condenser credit is not applied in compressor-rack systems.
IF (DefrostType /= DefElectric .AND. DefrostType /= DefElectricOnDemand .AND. &
DefrostType /= DefElectricTerm ) RefrigCase(CaseID)%HotDefrostCondCredit=DefrostCap_Actual*DefrostSchedule
ELSE !no defrost or off-cycle defrost
DefrostCap_Actual = 0.0d0
DefrostLoad_Actual = 0.0d0
RefrigCase(CaseID)%KgFrost = 0.0d0
! Off-Cycle defrost is assumed to melt all the ice
END IF ! defrost type
ELSE !DefrostSchedule = 0, so no defrost load or capacity
DefrostLoad_Actual = 0.0d0
DefrostCap_Actual = 0.0d0
END IF !Defrost calculations
!*** See if capacity meets load and manage accumulated stored energy ***********************************
TotalLoad_Actual = SensibleLoadTotal + LatentLoad + DefrostLoad_Actual
StoredEnergyRate = RefrigCase(CaseID)%StoredEnergy/TimeStepZone/SecInHour
LoadRequested = TotalLoad_Actual + StoredEnergyRate
! prorate available cooling capacity for portion of time off due to drip down.
CapAvail = DesignRatedCap * (1.0d0 - DefrostDripDownSchedule)
IF(CapAvail >= LoadRequested) THEN
!Have more at least as much capacity available as needed, even counting stored energy
TotalCap_Actual = LoadRequested
SensibleCap_Actual = SensibleLoadTotal + StoredEnergyRate
LatentCap_Actual = LatentLoad
RefrigCase(CaseID)%StoredEnergy = 0.0d0
ELSE
!Don't have as much capacity as needed (during dripdown or period following dripdown)
TotalCap_Actual = CapAvail
LatentCap_Actual = MIN(LatentLoad,CapAvail) !Latent load should never be > capavail, but just in case...
SensibleCap_Actual = TotalCap_Actual - LatentCap_Actual
IF(.NOT. WarmUpFlag) RefrigCase(CaseID)%StoredEnergy = RefrigCase(CaseID)%StoredEnergy + &
(TotalLoad_Actual - CapAvail)*TimeStepZone*SecInHour
END IF !CapAvail vs Load requested
! Reset DefrostLoad_Actual to zero for non-electric defrost types, for reporting purposes
IF (DefrostType /= DefElectric .AND. DefrostType /= DefElectricOnDemand .AND. &
DefrostType /= DefElectricTerm ) DefrostCap_Actual = 0.0d0
CaseRAFraction = MIN(0.8d0, RefrigCase(CaseID)%RAFrac)
CaseRAFactor = (1.0d0 - ((0.8d0 - CaseRAFraction) / 0.8d0)) * 0.5d0
! Update globals for use in ZoneTemperaturePredictorCorrector (Air Heat Balance) and
! Zone Equipment Manager. Sum case credits to zone and case credits to HVAC
!** this needs a moisture variable NonAirSystemMoistureResponse (equivalent of NonAirSystemResponse) to properly
!** allocate moisture to the zone when the HVAC system is off.
CaseSenCreditToZone = SensibleCaseCredit * (1.0d0 - CaseRAFactor)
CaseLatCreditToZone = LatentCaseCredit * (1.0d0 - CaseRAFactor)
CaseSenCreditToHVAC = SensibleCaseCredit * CaseRAFactor
CaseLatCreditToHVAC = LatentCaseCredit * CaseRAFactor
RefrigCaseCredit(ActualZoneNum)%SenCaseCreditToZone = &
RefrigCaseCredit(ActualZoneNum)%SenCaseCreditToZone + CaseSenCreditToZone
RefrigCaseCredit(ActualZoneNum)%LatCaseCreditToZone = &
RefrigCaseCredit(ActualZoneNum)%LatCaseCreditToZone + CaseLatCreditToZone
RefrigCaseCredit(ActualZoneNum)%SenCaseCreditToHVAC = &
RefrigCaseCredit(ActualZoneNum)%SenCaseCreditToHVAC + CaseSenCreditToHVAC
RefrigCaseCredit(ActualZoneNum)%LatCaseCreditToHVAC = &
RefrigCaseCredit(ActualZoneNum)%LatCaseCreditToHVAC + CaseLatCreditToHVAC
! ReportRefrigeratedCase(CaseID)
RefrigCase(CaseID)%TotalCoolingLoad = TotalCap_Actual
RefrigCase(CaseID)%TotalCoolingEnergy = TotalCap_Actual * TimeStepZone * SecInHour
RefrigCase(CaseID)%SensCoolingEnergyRate = SensibleCap_Actual
RefrigCase(CaseID)%SensCoolingEnergy = SensibleCap_Actual * TimeStepZone * SecInHour
RefrigCase(CaseID)%LatCoolingEnergyRate = LatentCap_Actual
RefrigCase(CaseID)%LatCoolingEnergy = LatentCap_Actual * TimeStepZone * SecInHour
RefrigCase(CaseID)%SensZoneCreditRate = CaseSenCreditToZone ! both positive or negative
! This rate can be positive or negative, split into separate output variables and always report positive value
IF(CaseSenCreditToZone <= 0.0d0) THEN
RefrigCase(CaseID)%SensZoneCreditCoolRate = -CaseSenCreditToZone
RefrigCase(CaseID)%SensZoneCreditCool = -CaseSenCreditToZone * TimeStepZone * SecInHour
RefrigCase(CaseID)%SensZoneCreditHeatRate = 0.0d0
RefrigCase(CaseID)%SensZoneCreditHeat = 0.0d0
ELSE
RefrigCase(CaseID)%SensZoneCreditHeatRate = CaseSenCreditToZone
RefrigCase(CaseID)%SensZoneCreditHeat = CaseSenCreditToZone * TimeStepZone * SecInHour
RefrigCase(CaseID)%SensZoneCreditCoolRate = 0.0d0
RefrigCase(CaseID)%SensZoneCreditCool = 0.0d0
END IF
! This rate should always be negative
RefrigCase(CaseID)%LatZoneCreditRate = CaseLatCreditToZone
RefrigCase(CaseID)%LatZoneCredit = CaseLatCreditToZone * TimeStepZone * SecInHour
RefrigCase(CaseID)%SensHVACCreditRate = CaseSenCreditToHVAC
! This rate can be positive or negative, split into separate output variables and always report positive value
IF(CaseSenCreditToHVAC <= 0.0d0) THEN
RefrigCase(CaseID)%SensHVACCreditCoolRate = -CaseSenCreditToHVAC
RefrigCase(CaseID)%SensHVACCreditCool = -CaseSenCreditToHVAC * TimeStepZone * SecInHour
RefrigCase(CaseID)%SensHVACCreditHeatRate = 0.0d0
RefrigCase(CaseID)%SensHVACCreditHeat = 0.0d0
ELSE
RefrigCase(CaseID)%SensHVACCreditHeatRate = CaseSenCreditToHVAC
RefrigCase(CaseID)%SensHVACCreditHeat = CaseSenCreditToHVAC * TimeStepZone * SecInHour
RefrigCase(CaseID)%SensHVACCreditCoolRate = 0.0d0
RefrigCase(CaseID)%SensHVACCreditCool = 0.0d0
END IF
! This rate should always be negative
RefrigCase(CaseID)%LatHVACCreditRate = CaseLatCreditToHVAC
RefrigCase(CaseID)%LatHVACCredit = CaseLatCreditToHVAC * TimeStepZone * SecInHour
RefrigCase(CaseID)%ElecFanPower = TotalFan
RefrigCase(CaseID)%ElecFanConsumption = TotalFan * TimeStepZone * SecInHour
RefrigCase(CaseID)%ElecAntiSweatPower = TotalAntiSweat
RefrigCase(CaseID)%ElecAntiSweatConsumption = TotalAntiSweat * TimeStepZone * SecInHour
RefrigCase(CaseID)%ElecLightingPower = TotalLightingLoad
RefrigCase(CaseID)%ElecLightingConsumption = TotalLightingLoad * TimeStepZone * SecInHour
RefrigCase(CaseID)%ElecDefrostPower = DefrostCap_Actual
RefrigCase(CaseID)%ElecDefrostConsumption = DefrostCap_Actual * TimeStepZone * SecInHour
RefrigCase(CaseID)%DefEnergyCurveValue = DefrostRatio
RefrigCase(CaseID)%LatEnergyCurveValue = LatentRatio
!**************************************************************************************************
! Cap Energy and Kg Frost to avoid floating overflow errors
! 1-time warning is issued. It should be rare but could happen with unrealistic inputs.
!Collect extra sensible load above design for possible warning if that is determining factor in
! excessively large stored energy
IF ((ZoneTempFactor*CaseCreditFraction) > 1.0d0) THEN
IF(.NOT. WarmUpFlag) THEN
DeltaWarmEnvEnergy = (SensibleLoadPrime - RefrigCase(CaseID)%DesignSensCaseCredit) * TimeStepZone * SecInHour
RefrigCase(CaseID)%WarmEnvEnergy = RefrigCase(CaseID)%WarmEnvEnergy + DeltaWarmEnvEnergy
END IF
END IF
IF(RefrigCase(CaseID)%DefrostEnergy > MyLargeNumber)RefrigCase(CaseID)%DefrostEnergy=MyLargeNumber
IF(RefrigCase(CaseID)%WarmEnvEnergy > MyLargeNumber)RefrigCase(CaseID)%WarmEnvEnergy=MyLargeNumber
IF(RefrigCase(CaseID)%StockingEnergy > MyLargeNumber)RefrigCase(CaseID)%StockingEnergy=MyLargeNumber
IF(RefrigCase(CaseID)%StoredEnergy > MyLargeNumber) THEN
RefrigCase(CaseID)%StoredEnergy=MyLargeNumber
IF(ShowStoreEnergyWarning(CaseID)) THEN
CALL ShowWarningError('Refrigeration:Case: '//TRIM(RefrigCase(CaseID)%Name))
IF(RefrigCase(CaseID)%StockingEnergy >= RefrigCase(CaseID)%DefrostEnergy) THEN
IF(RefrigCase(CaseID)%StockingEnergy >= RefrigCase(CaseID)%WarmEnvEnergy) THEN
CALL ShowContinueError(' This case has insufficient capacity to meet excess energy associated'// &
' with stocking.')
CALL ShowContinueError(' Refer to documentation for further explanation of product stocking requirements and')
CALL ShowContinueError(' Total Cooling Capacity.')
ELSE
CALL ShowContinueError(' This case has insufficient capacity to meet excess energy associated'// &
' with a zone enviroment temperature greater than the design ambient for the case.')
CALL ShowContinueError(' Refer to documentation for further explanation of ')
CALL ShowContinueError(' Total Cooling Capacity.')
END IF ! Stocking energy > warm environment energy
ELSE
IF(RefrigCase(CaseID)%DefrostEnergy >= RefrigCase(CaseID)%WarmEnvEnergy) THEN
CALL ShowContinueError(' This case has insufficient capacity to meet excess energy associated'// &
' with defrost.')
CALL ShowContinueError(' Refer to documentation for further explanation of defrost control requirements and')
CALL ShowContinueError(' recommendations regarding Total Cooling Capacity, Sensible Heat Ratio, and Defrost Capacity.')
ELSE
CALL ShowContinueError(' This case has insufficient capacity to meet excess energy associated'// &
' with a zone enviroment temperature greater than the design ambient for the case.')
CALL ShowContinueError(' Refer to documentation for further explanation of ')
CALL ShowContinueError(' Total Cooling Capacity.')
END IF ! defrost energy > warm environment energy
END IF ! stock > defrost ELSE
ShowStoreEnergyWarning(CaseID) = .FALSE. ! only give this warning once for any one case
END IF !showstoreenergy warning true
END IF ! stored energy > large number
IF(RefrigCase(CaseID)%KgFrost > MyLargeNumber) THEN
RefrigCase(CaseID)%KgFrost=MyLargeNumber
IF(ShowFrostWarning(CaseID)) THEN
CALL ShowWarningError('Refrigeration:Case: '//TRIM(RefrigCase(CaseID)%Name))
CALL ShowContinueError(' This case has insufficient defrost capacity to remove the excess frost accumulation.')
CALL ShowContinueError(' Refer to documentation for further explanation of product stocking requirements and')
CALL ShowContinueError(' recommendations regarding Total Cooling Capacity, Sensible Heat Ratio, and Latent Heat Ratio.')
ShowFrostWarning(CaseID) = .FALSE.
END IF
END IF
RETURN
END SUBROUTINE CalculateCase