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) | :: | WalkInID |
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 CalculateWalkIn(WalkInID)
! SUBROUTINE INFORMATION:
! AUTHOR Therese Stovall, ORNL, May 2009
! DATE WRITTEN Oct/Nov 2004
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! To model Walk In Coolers.
! METHODOLOGY EMPLOYED:
! Walk-in cooler performance is based on the ASHRAE load model, which includes
! infiltration through door openings and sensible loss through walls/ceilings identified
! by the user as sum of UA for each zone. A sub-floor heater is assumed to be sized so that
! the temperature of the slab beneath the floor insulation is the same as the ground
! temperature (to avoid ground freezing and heaving).
! All equipment loads (fan, light, heaters) are modeled as well. Sensible and latent
! exchange with multiple adjoining zones is included. A master schedule is used for the Walk In operation and
! additional schedules control the lights, defrost, and heater operation.
! The fan is assumed to be off for Hot-Gas, Hot-Brine, and Electric defrost. The user can choose
! to include the load due to bringing the coil mass up from the evaporating temperature to the melting temperature
! if they choose. Otherwise this factor is set to zero.
! Unmet loads are accumulated to be met the following time step. This usually occurs during defrost and
! restocking.
! REFERENCES:
! ASHRAE 2006 Handbook, chapters 13 and 14.
! Gosney, W.B., Olama, G.A.-L., Heat and Enthalpy Gains through Cold Room Doorways,
! Proceedings of the Institute of Refrigeration, vol. 72, pp 31-41, 1975
! USE STATEMENTS:
USE CurveManager, ONLY: CurveValue
USE DataLoopNode
USE Psychrometrics, ONLY: PsyRhoAirFnPbTdbW,RhoH2O,PsyWFnTdbTwbPb,PsyTwbFnTdbWPb,CPHW,&
PsyHFnTdbW,PsyTsatFnHPb, PsyWFnTdpPb,PsyHFnTdbRhPb, PsyRhFnTdbWPb, &
PsyTdpFnWPb, PsyWFnTdbH
! USE DataEnvironment, ONLY: OutBaroPress, OutDryBulbTemp
USE DataEnvironment, ONLY: OutBaroPress
USE General, ONLY: CreateSysTimeIntervalString
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: WalkInID ! Absolute pointer to Walk In
! SUBROUTINE PARAMETER DEFINITIONS:
REAL(r64), Parameter :: DefaultWalkInDoorOpenFactor = 0.05d0 ! walk in door open factor (fraction time open)
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: ZoneNodeNum =0 ! Zone node number
INTEGER :: ZoneNum =0 ! Index to zone
INTEGER :: ZoneID =0 ! Index to zone
REAL(r64) :: CapApplied =0.0d0 ! Walk In total capacity at specific operating conditions
REAL(r64) :: CircFanSchedule =0.0d0
REAL(r64) :: Conv =0.0d0 ! conversion factor in gravity equation
REAL(r64) :: DefrostCap =0.0d0 ! Design defrost capacity of WalkIn (W)
REAL(r64) :: DefrostEnergy =0.0d0 ! (J)
REAL(r64) :: DefEnergyFraction = 0.0d0 !dimensionless
REAL(r64) :: AvailDefrostEnergy = 0.0d0 !available to melt ice with temp term control (J)
REAL(r64) :: DefrostLoad =0.0d0 ! (W)
REAL(r64) :: DefrostSchedule =0.0d0 ! WalkIn defrost schedule, between 0 and 1
REAL(r64) :: DefrostDripDownSchedule =0.0d0 ! WalkIn drip-down schedule (allows coil to drain after defrost)
REAL(r64) :: DefrostEnergyNeeded =0.0d0 ! Energy needed to melt all ice, used with temperature termination (J)
REAL(r64) :: DensityAirWalkIn =0.0d0 ! Density at Walk in temperature and 90% assumed RH
REAL(r64) :: DensityZoneAir =0.0d0 ! Density of the air in a particular zone (kg/m3)
REAL(r64) :: DensityFactorFm =0.0d0 ! called Fm in ASHRAE 2010 eq 13 page 24.5 for door infiltration
REAL(r64) :: DensitySqRtFactor =0.0d0 ! from ASHRAE 2010 eq 12 page 24.4 for door infiltration
REAL(r64) :: DelTemp =0.0d0 ! Difference between zone and walk in temperatures (C)
REAL(r64) :: DesignLighting =0.0d0 ! Total design display WalkIn lighting power (W)
REAL(r64) :: DesignRatedCap =0.0d0 ! Rated capacity of walk in cooler coil (W)
REAL(r64) :: DoorFlowFactor =0.0d0 ! Derate compared to fully developed flow through 100% open door
REAL(r64) :: DoorOpenFactor =0.0d0 ! Derate based upon fraction time door opened
REAL(r64) :: DoorProtectEff =0.0d0 ! Door protection effectiveness
REAL(r64) :: DrHeight =0.0d0 ! Door height (m)
REAL(r64) :: DrArea =0.0d0 ! Door area (m2)
REAL(r64) :: EnthalpyAirWalkIn =0.0d0 ! Enthalpy of air corresponding to walk in temperatuer and 90% assumed RH (J/kg)
REAL(r64) :: EnthalpyZoneAir =0.0d0 ! Enthalpy of the air in a particular zone (J/kg)
REAL(r64) :: FanLoad =0.0d0 ! Total fan energy rate (W)
REAL(r64) :: FloorLoad =0.0d0 ! Total floor energy rate (W)
REAL(r64) :: FrostChangekg =0.0d0 ! Amount of frost added or melted (kg)
REAL(r64) :: FullFlowInfLoad =0.0d0 ! Total load (lat + sens) due to 100% open doors w/ fully developed flow (W)
REAL(r64) :: GlassDoorInfLoad =0.0d0 ! infiltration through glass reach-in doors in a particular zone (W)
REAL(r64) :: GlassDoorSensHeat =0.0d0 ! sensible heat gain through glass reach-in doors (UA*delta T) (W)
REAL(r64) :: GlassDoorArea =0.0d0 ! facing a particular zone (m2)
REAL(r64) :: Gravity =0.0d0 !
REAL(r64) :: HeaterSchedule =0.0d0 ! zero to one
REAL(r64) :: HeaterLoad =0.0d0 ! Total heater (except defrost) energy rate (W)
REAL(r64) :: HumRatioAirWalkIn =0.0d0 ! corresponds to walk in temp and 90% assumed RH(kg water/kg dry air)
REAL(r64) :: HumRatioZoneAir =0.0d0 ! Humidity Ratio of the air in a particular zone (kg water/kg dry air)
REAL(r64) :: IceSensHeatNeeded =0.0d0 ! Energy to raise frost temperature to 0C, used w/ temp termination (J)
REAL(r64) :: LatentCapApplied =0.0d0 ! Walk In latent capacity at specific operating conditions
REAL(r64) :: LatentLoadTotal =0.0d0 ! total latent load on WalkIn over all zones (W)
REAL(r64) :: LightLoad =0.0d0 ! Total lighting energy rate (W)
REAL(r64) :: LightingSchedule =0.0d0 ! WalkIn lighting schedule
REAL(r64) :: LoadRequested =0.0d0 ! Load necessary to meet current and all stored energy needs (W)
REAL(r64) :: LoadTotal =0.0d0 ! total load in time step (W)
REAL(r64) :: MassDryAirRate =0.0d0 ! Mass dry air infiltrating into/out-of walkin through doors (kg/s)
REAL(r64) :: MaxCap =0.0d0 ! Design chilling capacity reduced according to drip-down schedule (W)
REAL(r64) :: SensibleCapApplied =0.0d0 ! Walk In sensible capacity at specific operating conditions
REAL(r64) :: SensibleLoadTotal =0.0d0 ! Total sensible load on WalkIn over all zones (W)
REAL(r64) :: StoredEnergyRate =0.0d0 ! Rate needed to serve all stored energy during single time step (W)
REAL(r64) :: StartIceTemp =0.0d0 ! Frost temperature at start of time step [C]
REAL(r64) :: StartFrostkg =0.0d0 ! frost load at start of time step (kg of ice)
REAL(r64) :: StockDoorInfLoad =0.0d0 ! infiltration through stock doors in a particular zone (W)
REAL(r64) :: StockDoorSensHeat =0.0d0 ! sensible heat gain through stock doors (UA*delta T) (W)
REAL(r64) :: StockDoorArea =0.0d0 ! (m2)
REAL(r64) :: StockingLoad =0.0d0 ! Total load due to stocking WalkIn product (W)
REAL(r64) :: TWalkIn =0.0d0 ! WalkIn operating temperature (C)
REAL(r64) :: UAOtherSurfaces =0.0d0 ! UA for non-door surfaces facing a certain zone (W/C)
REAL(r64) :: WalkInSchedule =0.0d0 ! Current value of WalkIn operating (availability) schedule
REAL(r64) :: WalkInSensLoad =0.0d0 ! Walk in cooler sensible load facing particular zone (W)
REAL(r64) :: WalkInLatLoad =0.0d0 ! Walk in cooler latent load facing particular zone (W)
REAL(r64) :: WaterRemovRate =0.0d0 ! Walk in cooler removes water at this rate in this zone (kg/s)
REAL(r64) :: ZoneDryBulb =0.0d0 ! Dry Bulb Temperature of adjacent zone
REAL(r64) :: ZoneSensLoad =0.0d0 ! Sensible WalkIn credit delivered to a particular zone (W)
REAL(r64) :: ZoneLatentLoad =0.0d0 ! Latent WalkIn credit delivered to zone (W)
REAL(r64) :: ZoneRHFrac =0.0d0 ! Zone relative humidity fraction (decimal)
REAL(r64) :: ZoneInfilLoad =0.0d0 ! Walk in cooler infiltration load (sens + latent) in certain zone (W)
REAL(r64) :: ZinfilSensLoad =0.0d0 ! Sensible load due to infiltration in one zone
REAL(r64) :: ZdoorSensLoad =0.0d0 ! Sensible load due to UA delta T through closed door in one zone
WalkInSchedule = GetCurrentScheduleValue( WalkIn( WalkInID)%SchedPtr)
IF ( WalkInSchedule <= 0) RETURN
! GET OTHER SCHEDULES
DefrostSchedule = GetCurrentScheduleValue( WalkIn( WalkInID)%DefrostSchedPtr)
DefrostDripDownSchedule = GetCurrentScheduleValue( WalkIn( WalkInID)%DefrostDripDownSchedPtr)
!next statement In case user doesn't understand concept of drip down schedule
DefrostDripDownSchedule = MAX(DefrostDripDownSchedule,DefrostSchedule)
!next four values optional, so set to default before checking for schedule
StockingLoad = 0.0d0
LightingSchedule = 1.0d0
HeaterSchedule = 1.0d0
CircFanSchedule = 1.0d0
IF (WalkIn(WalkInID)%StockingSchedPtr > 0)StockingLoad = GetCurrentScheduleValue(WalkIn(WalkInID)%StockingSchedPtr)
IF (WalkIn(WalkInID)%LightingSchedPtr > 0)LightingSchedule= GetCurrentScheduleValue(WalkIn(WalkInID)%LightingSchedPtr)
IF (WalkIn(WalkInID)%HeaterSchedPtr > 0) HeaterSchedule = GetCurrentScheduleValue(WalkIn(WalkInID)%HeaterSchedPtr)
IF (WalkIn(WalkInID)%CircFanSchedPtr > 0) CircFanSchedule = GetCurrentScheduleValue(WalkIn(WalkInID)%CircFanSchedPtr)
!Set local subroutine variables for convenience
TWalkIn = WalkIn( WalkInID)%Temperature
DesignRatedCap = WalkIn( WalkInID)%DesignRatedCap
DefrostCap = WalkIn( WalkInID)%DefrostCapacity
! %DefrostCapacity already set to zero for WalkInDefrostNone , WalkInDefrostOffCycle
DesignLighting = WalkIn( WalkInID)%DesignLighting
EnthalpyAirWalkIn = PsyHFnTdbRhPb(TWalkIn,0.9d0,OutBaroPress)!assume 90%RH in cooler
HumRatioAirWalkIn = PsyWFnTdbH(TWalkIn,EnthalpyAirWalkIn)
DensityAirWalkIn = PsyRhoAirFnPbTdbW(OutBaroPress,TWalkIn,HumRatioAirWalkIn)
Conv = Latitude*2.d0*PI/360.d0 !Convert Latitude to radians
Gravity=9.780373d0*(1.d0+.0052891d0*(SIN(CONV))**2-.0000059d0*(SIN(2.d0*CONV))**2)
! CALCULATE ALL LOADS INFLUENCED BY ZONE TEMPERATURE AND RH
!set to zero before summing over zones
SensibleLoadTotal = 0.d0
LatentLoadTotal = 0.d0
WalkIn(WalkInID)%SensZoneCreditRate = 0.0d0
WalkIn(WalkInID)%SensZoneCreditCoolRate = 0.0d0
WalkIn(WalkInID)%SensZoneCreditCool = 0.0d0
WalkIn(WalkInID)%SensZoneCreditHeatRate = 0.0d0
WalkIn(WalkInID)%SensZoneCreditHeat = 0.0d0
WalkIn(WalkInID)%LatZoneCreditRate = 0.0d0
!Start zone loop:
DO ZoneID = 1,WalkIn(WalkInID)%NumZones
ZoneSensLoad = 0.d0
GlassDoorSensHeat = 0.d0
StockDoorSensHeat = 0.d0
ZoneNum = WalkIn(WalkInID)%ZoneNum(ZoneID)
ZoneNodeNum = WalkIn(WalkInID)%ZoneNodeNum(ZoneID)
ZoneDryBulb = Node(ZoneNodeNum)%Temp
DelTemp = ZoneDryBulb - TWalkIn
StockDoorArea = WalkIn(WalkInID)%AreaStockDr(ZoneID)
GlassDoorArea = WalkIn(WalkInID)%AreaGlassDr(ZoneID)
UAOtherSurfaces = WalkIn(WalkInID)%SurfaceArea(ZoneID)*WalkIn(WalkInID)%UValue(ZoneID)
DoorFlowFactor = 0.8d0 !see ASHRAE Refrigeration, p13.5, 2006
IF (Deltemp <= 11.d0) DoorFlowFactor = 1.1d0 ! from ASHRAE Refrigeration Loads
!Get infiltration loads if either type of door is present in this zone
IF(StockDoorArea > 0.d0 .OR. GlassDoorArea > 0.d0) THEN
ZoneRHFrac = PsyRhFnTdbWPb(Node(ZoneNodeNum)%Temp,Node(ZoneNodeNum)%Humrat,OutBaroPress,'CalculateWalkIn')
EnthalpyZoneAir = PsyHFnTdbRhPb(ZoneDryBulb,ZoneRHFrac,OutBaroPress,'CalculateWalkIn')
HumRatioZoneAir = PsyWFnTdbH(ZoneDryBulb,EnthalpyZoneAir,'CalculateWalkIn')
DensityZoneAir = PsyRhoAirFnPbTdbW(OutBaroPress,ZoneDryBulb,HumRatioZoneAir,'CalculateWalkIn')
IF (DensityZoneAir < DensityAirWalkIn)THEN !usual case when walk in is colder than zone
DensitySqRtFactor = (1.d0 - DensityZoneAir/DensityAirWalkIn)**0.5d0
DensityFactorFm = (2.d0/(1.d0 + (DensityAirWalkIn/DensityZoneAir)**0.333d0))**1.5d0
ELSE !temperature inversion with zone colder and/or drier than walk-in, infiltration in reverse direction
!The enthalpy difference will show whether the energy transport is reversed
!(same air mass exchange in either direction )
!That is, these factors establish the magnitude of the exchange air flow, not direction
DensitySqRtFactor = (1.d0 - DensityAirWalkIn/DensityZoneAir)**0.5d0
DensityFactorFm = (2.d0/(1.d0 + (DensityZoneAir/DensityAirWalkIn)**0.333d0))**1.5d0
END IF ! check for density in zone and in walk-in to avoid taking sqrt of neg number
GlassDoorInfLoad = 0.d0
StockDoorInfLoad = 0.d0
StockDoorSensHeat = 0.d0
GlassDoorSensHeat = 0.d0
IF(StockDoorArea > 0.d0) THEN
SELECT CASE (WalkIn(WalkInID)%StockDoorProtectType(ZoneID))
!Values from ASHRAE Ref p 13.6
CASE (WIStockDoorNone)
DoorProtectEff = 0.0d0
CASE (WIStockDoorAirCurtain)
DoorProtectEff = 0.5d0
CASE (WIStockDoorStripCurtain)
DoorProtectEff = 0.9d0
END SELECT
DrHeight = WalkIn(WalkInID)%HeightStockDr(ZoneID)
DrArea = StockDoorArea
! if exists, get Stock Door Zone schedule
DoorOpenFactor = DefaultWalkInDoorOpenFactor
IF (WalkIn(WalkInID)%StockDoorOpenSchedPtr(ZoneID) > 0)&
DoorOpenFactor = GetCurrentScheduleValue( WalkIn( WalkInID)%StockDoorOpenSchedPtr(ZoneID))
FullFlowInfLoad = 0.221d0*DrArea*(EnthalpyZoneAir - EnthalpyAirWalkIn)* &
DensityAirWalkIn * DensitySqRtFactor * &
((Gravity*DrHeight)**0.5d0)*DensityFactorFm
StockDoorInfLoad = FullFlowInfLoad*DoorOpenFactor*DoorFlowFactor*(1.d0 - DoorProtectEff)
StockDoorSensHeat = DrArea*WalkIn(WalkInID)%UValueStockDr(ZoneID)*DelTemp
END IF !have stock doors
IF(GlassDoorArea > 0.d0) THEN
DoorProtectEff = 0.5d0 ! Assume glass doors have air curtain
DrHeight = WalkIn(WalkInID)%HeightGlassDr(ZoneID)
DrArea = GlassDoorArea
! get Glass Door Zone schedule
DoorOpenFactor = DefaultWalkInDoorOpenFactor !default value
IF ( WalkIn( WalkInID)%GlassDoorOpenSchedPtr(ZoneID) > 0) &
DoorOpenFactor = GetCurrentScheduleValue( WalkIn( WalkInID)%GlassDoorOpenSchedPtr(ZoneID))
FullFlowInfLoad = 0.221d0*DrArea*(EnthalpyZoneAir - EnthalpyAirWalkIn)* &
DensityAirWalkIn * DensitySqRtFactor * &
((Gravity*DrHeight)**0.5d0)*DensityFactorFm
GlassDoorInfLoad = FullFlowInfLoad*DoorOpenFactor*DoorFlowFactor*(1.d0 - DoorProtectEff)
GlassDoorSensHeat = DrArea*WalkIn(WalkInID)%UValueGlassDr(ZoneID)*DelTemp
END IF !have Glass doors
!assume mass dry air infiltrating into walk-in == mass out into zone,
! that is, equal air exchange (ASHRAE 2006 Refrigeration)
ZoneInfilLoad = -StockDoorInfLoad - GlassDoorInfLoad
MassDryAirRate = -ZoneInfilLoad/(EnthalpyZoneAir - EnthalpyAirWalkIn)
WaterRemovRate = MassDryAirRate*(HumRatioZoneAir - HumRatioAirWalkIn)
! Just as with cases, we assume no latent credit (water removal = 0) to zone or load on cooler during dripdown
! To be consistent with the treatment of refrigerated cases, latent load
! and latent credit are bothbased on reducing the infiltrating vapor to ice. (This is
! slightly greater than if the latent credit were based upon condensing out the water as liquid.)
! then it would be: ZoneLatentLoad = -WaterRemovRate * WaterToVaporEnthalpy * (1.d0-DefrostDripDownSchedule)
ZoneLatentLoad = -WaterRemovRate * IcetoVaporEnthalpy * (1.d0-DefrostDripDownSchedule)
ZInfilSensLoad = ZoneInfilLoad - (-WaterRemovRate * IcetoVaporEnthalpy) !done to avoid moving latent to sens during dripdown
ZdoorSensLoad = - GlassDoorSensHeat - StockDoorSensHeat
WalkInLatLoad = -ZoneLatentLoad
IF (WalkIn( WalkInID)%TEvapDesign <= 0.d0) THEN ! water turned to ice on coil
WalkInLatLoad = WaterRemovRate*IcetoVaporEnthalpy * (1.d0-DefrostDripDownSchedule)
! 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
FrostChangekg = (WaterRemovRate * TimeStepZone * SecInHour) * (1.0d0-DefrostDripDownSchedule)
WalkIn(WalkInID)%KgFrost = WalkIn(WalkInID)%KgFrost + FrostChangekg
END IF
END IF !water to ice
END IF !No doors
ZoneSensLoad = ZinfilSensLoad + ZdoorSensLoad - UAOtherSurfaces*Deltemp
WalkInSensLoad = -ZoneSensLoad
! Update globals for use in ZoneTemperaturePredictorCorrector (Air Heat Balance) and
! Zone Equipment Manager. Sum walk-in credits to zone using existing 'casecredit' variable
! No return air fractions are applied to walk-ins, and no latent in stocking -
RefrigCaseCredit(ZoneNum)%SenCaseCreditToZone = &
RefrigCaseCredit(ZoneNum)%SenCaseCreditToZone + ZoneSensLoad
RefrigCaseCredit(ZoneNum)%LatCaseCreditToZone = &
RefrigCaseCredit(ZoneNum)%LatCaseCreditToZone + ZoneLatentLoad
! Set up report variables for each zone for this walk-in
! Sensible heat exchange can be positive or negative, split into separate output variables and always report positive value
WalkIn(WalkInID)%SensZoneCreditRate(ZoneID) = ZoneSensLoad
IF(ZoneSensLoad <= 0.0d0) THEN
WalkIn(WalkInID)%SensZoneCreditCoolRate(ZoneID) = -ZoneSensLoad
WalkIn(WalkInID)%SensZoneCreditCool(ZoneID) = -ZoneSensLoad * TimeStepZone * SecInHour
WalkIn(WalkInID)%SensZoneCreditHeatRate(ZoneID) = 0.0d0
WalkIn(WalkInID)%SensZoneCreditHeat(ZoneID) = 0.0d0
ELSE
WalkIn(WalkInID)%SensZoneCreditHeatRate(ZoneID) = ZoneSensLoad
WalkIn(WalkInID)%SensZoneCreditHeat(ZoneID) = ZoneSensLoad * TimeStepZone * SecInHour
WalkIn(WalkInID)%SensZoneCreditCoolRate(ZoneID) = 0.0d0
WalkIn(WalkInID)%SensZoneCreditCool(ZoneID) = 0.0d0
END IF
! This rate should always be negative
WalkIn(WalkInID)%LatZoneCreditRate(ZoneID) = ZoneLatentLoad
WalkIn(WalkInID)%LatZoneCredit(ZoneID) = ZoneLatentLoad * TimeStepZone * SecInHour
!Running total over all zones, use later to dispatch capacity
SensibleLoadTotal = SensibleLoadTotal + WalkInSensLoad
LatentLoadTotal = LatentLoadTotal + WalkInLatLoad
END DO !Do loop over zones for zone-condition-related sensible and latent loads
!cooling coil fan power default is 375W, = 1/2 HP (Tyler showed 1/3 to 3/4 hp)
! CALCULATE AUX LOADS DUE TO LIGHTS, FANS AND HEATERS
LightLoad = DesignLighting * LightingSchedule
! turn coil fan off during defrost/drip - down period
FanLoad = WalkIn(WalkInID)%CircFanPower*CircFanSchedule + &
WalkIn( WalkInID)%CoilFanPower * ( 1.0d0 - DefrostDripDownSchedule )
HeaterLoad = WalkIn(WalkInID)%HeaterPower * HeaterSchedule
! Calculate floor load - using 'GroundTemp' assigned in weather manager (can be entered by user if desired)
! Default value is 18C.
FloorLoad = WalkIn(WalkInID)%FloorArea * WalkIn( WalkInID)%FloorUValue * (GroundTemp - TWalkIn)
!DEFROST CALCULATIONS
IF((DefrostSchedule > 0.0d0).AND. &
(WalkIn(WalkInID)%DefrostType /= WalkInDefrostNone) .AND. &
(WalkIn(WalkInID)%DefrostType /= WalkInDefrostOffCycle)) THEN
DefrostLoad = DefrostCap*DefrostSchedule !W
StartFrostKg = WalkIn(WalkInID)%KgFrost
DefrostEnergy = DefrostLoad * TimeStepZone*SecInHour !Joules
IF (WalkIn(WalkInID)%DefrostControlType == DefrostContTempTerm) THEN
! Need to turn defrost system off early if controlled by temperature and all ice melted
! For temperature termination, need to recognize not all defrost heat goes to melt ice
! Some goes to misc losses (for fluid defrost, some coil areas bare earlier than
! others and xfer heat to environment)
! Assume full ice melting satisfies temperature control.
! (defaults for DefEnergyFraction are :=0.7 for elec, =0.3 for fluids)
DefEnergyFraction = WalkIn(WalkInID)%DefEnergyFraction
AvailDefrostEnergy = DefEnergyFraction * DefrostEnergy !Joules avail to melt ice
IceSensHeatNeeded = 0.d0
IF(StartFrostKg > 0.0d0) THEN
IF(WalkIn(WalkInID)%IceTemp < 0.d0) THEN
StartIceTemp = WalkIn(WalkInID)%IceTemp
IceSensHeatNeeded = StartFrostKg * SpecificHeatIce * (0.0d0 - StartIceTemp)!Joules
IF (AvailDefrostEnergy >= IceSensHeatNeeded) THEN
WalkIn(WalkInID)%IceTemp = 0.d0
AvailDefrostEnergy = AvailDefrostEnergy - IceSensHeatNeeded !Joules
ELSE !DefrostEnergy < IceSensHeatNeeded
WalkIn(WalkInID)%IceTemp = StartIceTemp + AvailDefrostEnergy/(SpecificHeatIce * StartFrostKg)
AvailDefrostEnergy = 0.d0
END IF ! AvailDefrostEnergy >= IceSensHeatNeeded
END IF ! IceTemp < 0, need to raise temperature of ice
!Reduce defrost heat load on walkin by amount of ice melted during time step
FrostChangekg = MIN(AvailDefrostEnergy/IceMeltEnthalpy,StartFrostKg)
IF(FrostChangekg < StartFrostKg) THEN
DefrostLoad = DefrostLoad - FrostChangekg*IceMeltEnthalpy/TimeStepZone/SecInHour
IF(.NOT. WarmUpFlag)WalkIn( WalkInID)%KgFrost = StartFrostKg - FrostChangekg
!DefrostSchedule not changed
ELSE ! all frost melted during time step, so need to terminate defrost
! see Aug 8 page 3 notes
WalkIn( WalkInID)%KgFrost = 0.d0
DefrostEnergyNeeded = (IceSensHeatNeeded + (FrostChangekg*IceMeltEnthalpy))/ &
DefEnergyFraction !Joules - energy needed including E unavail to melt ice
DefrostSchedule = MIN(DefrostSchedule,(DefrostEnergyNeeded/(DefrostCap*TimeStepZone*SecInHour)))
! reduce load on walkin by energy put into ice melting
DefrostLoad = MAX(0.d0,(DefrostSchedule*DefrostCap - &
(IceSensHeatNeeded + (FrostChangekg*IceMeltEnthalpy))/(TimeStepZone*SecInHour)))
WalkIn(WalkInID)%IceTemp = WalkIn(WalkInID)%TEvapDesign
END IF ! frost melted during time step less than amount of ice at start
ELSE ! no frost present so terminate defrost and reset ice temperature for start of next defrost
DefrostLoad = 0.d0
DefrostSchedule = 0.d0
WalkIn(WalkInID)%IceTemp = WalkIn(WalkInID)%TEvapDesign
END IF ! have frost present
ELSE !Not temperature control type
FrostChangekg = MIN(DefrostEnergy/IceMeltEnthalpy,StartFrostKg)
!Reduce defrost heat load on walkin by amount of ice melted during time step
DefrostLoad = DefrostLoad - FrostChangekg*IceMeltEnthalpy/TimeStepZone/SecInHour
IF(.NOT. WarmUpFlag)WalkIn( WalkInID)%KgFrost = StartFrostKg - FrostChangekg
!DefrostSchedule not changed
END IF !Temperature termination control type
ELSE !DefrostSchedule <= 0 or have None or OffCycle
DefrostLoad = 0.0d0
END IF !Defrost calculations
IF(WalkIn(WalkInID)%DefrostType == WalkInDefrostElec) THEN
WalkIn( WalkInID)%ElecDefrostConsumption = DefrostCap*DefrostSchedule*TimeStepZone*SecInHour
WalkIn(WalkInID)%ElecDefrostPower = DefrostCap*DefrostSchedule
ELSE
WalkIn( WalkInID)%ElecDefrostConsumption = 0.d0
WalkIn(WalkInID)%ElecDefrostPower = 0.d0
END IF
! If hot brine or hot gas is used for defrost, need to reduce condenser load by heat reclaimed for defrost
IF(WalkIn(WalkInID)%DefrostType == WalkInDefrostFluid)WalkIn(WalkInID)%HotDefrostCondCredit=DefrostCap*DefrostSchedule
! loads reflects that walk ins continue to accumulate loads, even during defrost
! but cap is used to report portion met by active system while operating
!*** See if capacity meets load and manage accumulated stored energy ***********************************
SensibleLoadTotal = SensibleLoadTotal + LightLoad + HeaterLoad + FanLoad + &
StockingLoad + DefrostLoad + FloorLoad
LoadTotal = SensibleLoadTotal + LatentLoadTotal
!
!Account for difference between load and capacity. Assume rack or system able to provide
! rated capacity. If it can't, that unmet energy will be stored and discharged at the system level.
! Here we are calculating the load the walk-in cooler places on the refrigeration compressor systems.
! Meet current load to the extent possible. If extra capacity available,
! apply it to previously unmet/stored loads. If capacity less than current load,
! (e.g. as it is during defrost cycles) save the unmet/stored load to be met in
! succeeding time steps. This is an artificial way of recognizing that the internal
! temperature will increase by a small amount during defrost and the system will have to
! run full out until the temperature is brought back down.
StoredEnergyRate = WalkIn( WalkInID)%StoredEnergy/TimeStepZone/SecInHour
LoadRequested = LoadTotal + StoredEnergyRate
! prorate available cooling capacity for portion of time off due to drip down.
MaxCap = DesignRatedCap*(1.d0 - DefrostDripDownSchedule)
IF(MaxCap >= LoadRequested) THEN
!Have more at least as much capacity available as needed, even counting stored energy
CapApplied = LoadRequested
SensibleCapApplied = SensibleLoadTotal + StoredEnergyRate
LatentCapApplied = LatentLoadTotal
WalkIn( WalkInID)%StoredEnergy = 0.0d0
ELSE
!Don't have as much capacity as needed (during dripdown or period following dripdown)
CapApplied = MaxCap
LatentCapApplied = MIN(LatentLoadTotal,MaxCap) !Latent load should never be > capavail, but just in case...
SensibleCapApplied = CapApplied - LatentCapApplied
IF(.NOT. WarmUpFlag) &
WalkIn( WalkInID)%StoredEnergy = WalkIn( WalkInID)%StoredEnergy + &
(LoadTotal - MaxCap)*TimeStepZone*SecInHour
END IF !CapAvail vs Load requested
! ReportWalkIn( WalkInID)
WalkIn( WalkInID)%TotalCoolingLoad = CapApplied
WalkIn( WalkInID)%TotalCoolingEnergy = CapApplied * TimeStepZone * SecInHour
WalkIn( WalkInID)%TotSensCoolingEnergyRate = SensibleCapApplied
WalkIn( WalkInID)%TotSensCoolingEnergy = SensibleCapApplied * TimeStepZone * SecInHour
WalkIn( WalkInID)%TotLatCoolingEnergyRate = LatentCapApplied
WalkIn( WalkInID)%TotLatCoolingEnergy = LatentCapApplied * TimeStepZone * SecInHour
WalkIn( WalkInID)%ElecFanPower = FanLoad
WalkIn( WalkInID)%ElecFanConsumption = FanLoad * TimeStepZone * SecInHour
WalkIn( WalkInID)%ElecHeaterPower = HeaterLoad
WalkIn( WalkInID)%ElecHeaterConsumption = HeaterLoad * TimeStepZone * SecInHour
WalkIn( WalkInID)%ElecLightingPower = LightLoad
WalkIn( WalkInID)%ElecLightingConsumption = LightLoad * TimeStepZone * SecInHour
WalkIn( WalkInID)%TotalElecPower = FanLoad + HeaterLoad + LightLoad + WalkIn( WalkInID)%ElecDefrostPower
WalkIn( WalkInID)%TotalElecConsumption = WalkIn( WalkInID)%TotalElecPower * TimeStepZone * SecInHour
!**************************************************************************************************
! 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.
IF( WalkIn( WalkInID)%StoredEnergy > MyLargeNumber) THEN
WalkIn( WalkInID)%StoredEnergy=MyLargeNumber
IF(ShowUnMetWIEnergyWarning(WalkInID)) THEN
CALL ShowWarningError('Refrigeration:WalkIn: '//TRIM( WalkIn( WalkInID)%Name))
CALL ShowContinueError(' This walk-in cooler has insufficient capacity to meet the loads')
CALL ShowContinueError('... Occurrence info = '//TRIM(EnvironmentName)//', '//Trim(CurMnDy)//' '&
//TRIM(CreateSysTimeIntervalString()))
CALL ShowContinueError(' Refer to documentation for further explanation of Total Cooling Capacity.')
ShowUnMetWIEnergyWarning(WalkInID) = .FALSE.
END IF ! ShowStoreEnergyWarning
END IF ! stored energy > large number
IF( WalkIn( WalkInID)%KgFrost > MyLargeNumber) THEN
WalkIn( WalkInID)%KgFrost=MyLargeNumber
IF(ShowWIFrostWarning( WalkInID)) THEN
CALL ShowWarningError('Refrigeration:WalkIn: '//TRIM( WalkIn( WalkInID)%Name))
CALL ShowContinueError(' This walkin cooler has insufficient defrost capacity to remove the excess frost accumulation.')
CALL ShowContinueError(' Check the defrost schedule or defrost capacity. ')
CALL ShowContinueError('... Occurrence info = '//TRIM(EnvironmentName)//', '//Trim(CurMnDy)//' '&
//TRIM(CreateSysTimeIntervalString()))
ShowWIFrostWarning( WalkInID) = .FALSE.
END IF
END IF
RETURN
END SUBROUTINE CalculateWalkIn