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 SimulateDetailedRefrigerationSystems
! SUBROUTINE INFORMATION:
! AUTHOR Therese Stovall, ORNL, Assisted by Hugh Henderson
! DATE WRITTEN Spring 2008
! Based upon ManageRefrigeratedCaseRacks by Richard Raustad, FSEC
! Oct/Nov 2004, and MODIFIED by Shirey, FSEC Dec 2004
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine is called to simulate detailed refrigeration systems
! METHODOLOGY EMPLOYED:
! Each refrigeration system is modeled by first simulating the attached refrigerated cases. The sum
! of the total heat transfer for all attached cases determines the load on the compressor rack.
! Iterations are used here to account for load transfer between independent refrigeration systems
! via mechanical subcoolers.
! The logical variable, UseSysTimeStep, determines whether we are evaluating only systems driven by
! ZoneEquipmentManager on the system time step, or only system driven by HVACManager on the zone time step.
! REFERENCES:
! na
! USE STATEMENTS:
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: SysNum ! Index to the detailed refrigerated system being modeled
LOGICAL :: DeRate = .FALSE. ! If true, need to derate aircoils because load can't be met by system
LOGICAL :: FirstSCLoop =.TRUE. ! Flag first time through multi-system loop used when mech subcoolers present
INTEGER :: StartMechSubcoolLoop = 3 ! if no mechanical subcoolers transfer energy between system,
! don't loop
INTEGER :: LoopNum = 0 ! Index to overall repeat necessary for mechanical subcoolers
INTEGER :: SubcoolID = 0 ! Subcooler ID number
INTEGER :: SubcoolerIndex = 0 ! Subcooler ID number
INTEGER :: CaseID = 0 ! Absolute reference to case
INTEGER :: CaseIndex = 0 ! Index to case
INTEGER :: CoilID = 0 ! Index to a single air chiller/coil
INTEGER :: CoilIndex = 0 ! Index to a single air chiller/coil
INTEGER :: CoilSetID = 0 ! Index to set of coils in a single zone (shared inlet and outlet nodes)
INTEGER :: CoilSetIndex = 0 ! Index to set of coils in a single zone
INTEGER :: CondInletAirZoneNum= 0 ! Index used to assign zone credits
INTEGER :: SecondID = 0 ! Absolute reference to Secondary Loop
INTEGER :: SecondIndex = 0 ! Index to Secondary Loop
INTEGER :: SuctionPipeActualZoneNum = 0 ! Index to zone exchanging heat with suction pipes
INTEGER :: WalkInID = 0 ! Absolute reference to WalkIn
INTEGER :: WalkInIndex = 0 ! Index to WalkIn
INTEGER :: ZoneNum =0 ! counter when assigning zone case credits
INTEGER :: CascadeLoadIndex = 0 ! Index to Cascade Condenser Load
INTEGER :: CascadeLoadID = 0 ! Absolute reference to Cascade Condenser
REAL(r64) :: LoadFrac = 1.d0 ! case load/design case load
REAL(r64) :: LocalTimeStep = 0.0d0 ! Set equal to either TimeStepSys or TimeStepZone
REAL(r64) :: CurrentLoads = 0.0d0 ! current loads on compressor, exclusive of unmet loads from prev time steps
REAL(r64) :: CurrentHiStageLoads = 0.0d0 ! Current loads on high-stage compressor, exclusive of unmet loads from
! prev time steps (two-stage systems only)
REAL(r64) :: MaxTEvap = 0.0d0 ! Maximum evaporating temperature that can still meet load
REAL(r64) :: MaxDelTFloatFrac = 0.5d0 ! max fraction allowed for difference between case and evaporator temperature
! relative to design temperature difference
REAL(r64) :: SuctionPipeZoneTemp ! Temperature for zone identified as environment for suction pipe heat gains, C
LocalTimeStep = TimeStepZone
IF(UseSysTimeStep) LocalTimeStep = TimeStepSys
!Cascade condenser assumes a constant approach delta T (Tcond - Tevap), not f(load)
!Loads for chiller sets are set in call to zone equipment element "SimAirChillerSet"
! (all chiller coils within a set are located in the same zone)
! (note non-zone, such as refrigeration, and zone equip, such as airchillersets, called at diff times)
! Loads are then defined for each chiller coil within the set in "CalculateAirChillerSet"
! In that subroutine, dispatch coils within each set in order specified for each zone
! Below will assign loads to refrigeration system or secondary loop
!Note that this routine will go through all refrigeration systems, but loads for multiple systems
! with interactions will not be known for the intitial calls with first HVAC time step. They will,
! however, be repeated when the last chiller set is called from ZoneEquipmentManager
! that's why important where init goes, don't want to zero out data should keep
IF(UseSysTimeStep) THEN
DO CoilSetIndex=1,NumRefrigChillerSets
CoilSetID = CoilSetIndex
CALL CalculateAirChillerSets(CoilSetID)
END DO
END IF
!Do refrigeration system loop outside of iterative solution to initialize time step and
! calculate case, walk-in, and secondary loop loads (that won't change during balance
! of refrigeration system iterations) and prepare initial estimates for the iterative system solution
DO SysNum = 1, NumRefrigSystems
!Only do those systems appropriate for this analysis, supermarket type on load time step or coil type on sys time step
IF(((.NOT. UseSysTimeStep).AND.(.NOT. System(SysNum)%CoilFlag)).OR.((UseSysTimeStep).AND.(System(SysNum)%CoilFlag)))THEN
IF(System(SysNum)%NumCases > 0) THEN
DO CaseIndex=1,System(SysNum)%NumCases
CaseID=System(Sysnum)%Casenum(CaseIndex)
CALL CalculateCase(CaseID)
! TevapDesign calc in Get Input to meet lowest evap temp of any load on the system.
! Tevap needed is either fixed at this design value,
! or allowed to float to meet lowest T needed among all loads served by the system
! (Floating Tevap = Design Tevap unless load <= Design cap)
IF (System(SysNum)%CompSuctControl == ConstantSuctionTemperature) THEN
System(Sysnum)%TEvapNeeded=System(SysNum)%TEvapDesign
ELSE ! calculate floating T evap
LoadFrac = Min(1.d0,(RefrigCase(CaseID)%TotalCoolingLoad/RefrigCase(CaseID)%DesignRatedCap))
MaxTEvap = RefrigCase(CaseID)%Temperature - &
(RefrigCase(CaseID)%Temperature - RefrigCase(CaseID)%EvapTempDesign)*max(LoadFrac,MaxDelTFloatFrac)
!Compare Tevap for this case to max allowed for all previous cases on this suction group and set at the MINIMUM of the two
IF (CaseIndex == 1)THEN !note use case index, not caseid here to get first case on this suction group/system
System(Sysnum)%TEvapNeeded=MaxTEvap
ELSE
System(Sysnum)%TEvapNeeded=MIN(MaxTEvap,System(Sysnum)%TEvapNeeded)
END IF
END IF !floating or constant evap temperature
! increment TotalCoolingLoad for Compressors/condenser on each system and defrost condenser credits for heat recovery
System(SysNum)%TotalCoolingLoad = System(SysNum)%TotalCoolingLoad + RefrigCase(CaseID)%TotalCoolingLoad
System(SysNum)%TotalCondDefrostCredit=System(SysNum)%TotalCondDefrostCredit + RefrigCase(CaseID)%HotDefrostCondCredit
END DO !NumCases
END IF !Num of cases > 0
IF(System(SysNum)%NumWalkIns > 0) THEN
DO WalkInIndex=1,System(SysNum)%NumWalkIns
WalkInID=System(Sysnum)%WalkInNum(WalkInIndex)
CALL CalculateWalkIn(WalkInID)
IF (System(SysNum)%CompSuctControl == ConstantSuctionTemperature) THEN
System(Sysnum)%TEvapNeeded=System(SysNum)%TEvapDesign
ELSE ! calculate floating T evap
LoadFrac = Min(1.d0,(WalkIn(WalkInID)%TotalCoolingLoad/WalkIn(WalkInID)%DesignRatedCap))
MaxTEvap = WalkIn(WalkInID)%Temperature - &
(WalkIn(WalkInID)%Temperature - WalkIn(WalkInID)%TEvapDesign)*max(LoadFrac,MaxDelTFloatFrac)
! Compare maxTevap for this walk in to max allowed for cases and for all
! previous walk ins on this suction group and set at the MINIMUM of the two
IF (WalkInIndex == 1 .AND. System(SysNum)%NumCases ==0 )THEN
System(Sysnum)%TEvapNeeded=MaxTEvap
ELSE
System(Sysnum)%TEvapNeeded=MIN(MaxTEvap,System(Sysnum)%TEvapNeeded)
END IF
END IF !floating or constant evap temperature
! increment TotalCoolingLoad for Compressors/condenser on each system
System(SysNum)%TotalCoolingLoad = System(SysNum)%TotalCoolingLoad + WalkIn(WalkInID)%TotalCoolingLoad
System(SysNum)%TotalCondDefrostCredit=System(SysNum)%TotalCondDefrostCredit + WalkIn(WalkInID)%HotDefrostCondCredit
END DO !NumWalkIns systems
END IF !System(SysNum)%NumWalkIns > 0
IF(System(SysNum)%NumCoils > 0) THEN
DO CoilIndex=1,System(SysNum)%NumCoils
CoilID=System(Sysnum)%CoilNum(CoilIndex)
! already CALLed CalculateCoil(CoilID) in CoilSet specified order
IF (System(SysNum)%CompSuctControl == ConstantSuctionTemperature) THEN
System(Sysnum)%TEvapNeeded=System(SysNum)%TEvapDesign
ELSE ! calculate floating T evap
! for now, override floating Tevap if coils on system, warning was printed in input to let user know
System(Sysnum)%TEvapNeeded=System(SysNum)%TEvapDesign
END IF !floating or constant evap temperature
! increment TotalCoolingLoad for Compressors/condenser on each system
System(SysNum)%TotalCoolingLoad = System(SysNum)%TotalCoolingLoad + WarehouseCoil(CoilID)%TotalCoolingLoad
System(SysNum)%TotalCondDefrostCredit=System(SysNum)%TotalCondDefrostCredit + WarehouseCoil(CoilID)%HotDefrostCondCredit
END DO !NumCoils systems
END IF !System(SysNum)%NumCoils > 0
IF(System(SysNum)%NumSecondarys > 0) THEN
DO SecondIndex=1,System(SysNum)%NumSecondarys
SecondID=System(Sysnum)%Secondarynum(SecondIndex)
CALL CalculateSecondary(SecondID)
IF (System(SysNum)%CompSuctControl == ConstantSuctionTemperature) THEN
System(Sysnum)%TEvapNeeded=System(SysNum)%TEvapDesign
ELSE ! check for lowest T evap design among the secondary systems and
! Compare Tevap for this second to max allowed for cases, walk ins, and
! for all previous secondary loops on this suction group and set
! at the MINIMUM (note secondary loops control capacity with
! brine flow rate, so don't float above their design evap temperature)
IF (SecondIndex == 1 .AND. System(SysNum)%NumNonCascadeLoads ==0 ) THEN
System(Sysnum)%TEvapNeeded=Secondary(SecondID)%TEvapDesign
ELSE
System(Sysnum)%TEvapNeeded=MIN(Secondary(SecondID)%TEvapDesign,System(Sysnum)%TEvapNeeded)
END IF
END IF !floating or constant evap temperature
! increment TotalCoolingLoad for Compressors/condenser on each system
System(SysNum)%SumSecondaryLoopLoad = System(SysNum)%SumSecondaryLoopLoad + Secondary(SecondID)%TotalCoolingLoad
System(SysNum)%TotalCondDefrostCredit=System(SysNum)%TotalCondDefrostCredit + Secondary(SecondID)%HotDefrostCondCredit
END DO !NumSecondarys systems
END IF !System(SysNum)%NumSecondarys > 0
!add suction pipe heat gains (W) if input by user
!Suction pipe heat gains aren't included in the reported total system load, but are heat gains that must be met in
! condenser and compressor loads. However, secondary dist piping and receiver gains are included
! in the total secondary system loads.
System(SysNum)%PipeHeatLoad = 0.d0
IF(System(SysNum)%SumUASuctionPiping > mysmallnumber) THEN
SuctionPipeZoneTemp = Node(System(SysNum)%SuctionPipeZoneNodeNum)%Temp
System(SysNum)%PipeHeatLoad = System(SysNum)%SumUASuctionPiping * &
(SuctionPipeZoneTemp - System(Sysnum)%TEvapNeeded)
! pipe heat load is a positive number (ie. heat absorbed by pipe, so needs to be subtracted
! from refrigcasecredit (- for cooling zone, + for heating zone)
SuctionPipeActualZoneNum = System(SysNum)%SuctionPipeActualZoneNum
IF(UseSysTimeStep) THEN
CoilSysCredit(SuctionPipeActualZoneNum)%SenCreditToZoneRate = &
CoilSysCredit(SuctionPipeActualZoneNum)%SenCreditToZoneRate - System(SysNum)%PipeHeatLoad
CoilSysCredit(SuctionPipeActualZoneNum)%ReportSenCoolingToZoneRate = &
- CoilSysCredit(SuctionPipeActualZoneNum)%SenCreditToZoneRate
END IF
!Can arrive here when load call to refrigeration looks for cases/walkin systems and usetimestep is .false.
IF((.NOT. UseSysTimeStep).AND.((NumSimulationCases > 0).OR.( NumSimulationWalkIns > 0)))THEN
RefrigCaseCredit(SuctionPipeActualZoneNum)%SenCaseCreditToZone = &
RefrigCaseCredit(SuctionPipeActualZoneNum)%SenCaseCreditToZone - System(SysNum)%PipeHeatLoad
END IF !UseSysTimeStep
END IF
END IF !(((.NOT. UseSysTimeStep).AND.(.NOT. System(SysNum)%CoilFlag)).OR.((UseSysTimeStep).AND.(System(SysNum)%CoilFlag)))
END DO ! SysNum
! Need to know if mechanical subcoolers or cascade condensers or shared condensers
! are present. If so, energy transfer between
! detailed refrigeration systems requires additional iteration at this level.
StartMechSubcoolLoop=3
If ((NumSimulationMechSubcoolers > 0) .OR. (NumSimulationCascadeCondensers > 0) &
.OR. (NumSimulationSharedCondensers > 0) &
.OR. (NumSimulationRefrigAirChillers > 0)) StartMechSubcoolLoop=1
FirstSCLoop=.TRUE.
Do Loopnum= StartMechSubcoolLoop,3 !Note, for cascade cond loads compared requiring 5 iterations to 3, no difference.
DO SysNum = 1, NumRefrigSystems
!Only do those systems appropriate for this analysis, supermarket type on load time step or coil type on sys time step
IF(((.NOT. UseSysTimeStep).AND.(.NOT. System(SysNum)%CoilFlag)).OR.((UseSysTimeStep).AND.(System(SysNum)%CoilFlag))) THEN
System(SysNum)%SumMechSCLoad =0.d0
System(SysNum)%SumCascadeLoad =0.d0
System(SysNum)%SumCascadeCondCredit=0.d0
System(SysNum)%SumMechSCBenefit =0.d0
IF((NumSimulationMechSubcoolers > 0).AND. (.NOT. FirstSCLoop)) THEN
!This loop places load on system providing mechanical subcooling
DO SubCoolID = 1,NumSimulationSubcoolers
IF(Subcooler(SubcoolID)%SubcoolerType == LiquidSuction)CYCLE
IF(Subcooler(SubcoolID)%MechSourceSysID /= SysNum)CYCLE
!don't have summechscload until second subcooler pass, set to zero on first pass
System(SysNum)%SumMechSCLoad=System(SysNum)%SumMechSCLoad+System(SysNum)%MechSCLoad(SubCoolID)
!subcooler should not drive Tevap for supplying system,
! but check to see if T controlled can be met or if Tevap is at a higher temperature
IF(Subcooler(SubcoolID)%MechControlTliqOut < System(SysNum)%TEvapNeeded) THEN
CALL ShowWarningError('Refrigeration:System: '//TRIM(System(SysNum)%Name))
CALL ShowContinueError(' Evaporating temperature greater than the controlled ')
CALL ShowContinueError(' liquid outlet temperature for SUBCOOLER:'//TRIM(Subcooler(SubcoolID)%Name))
END IF
END DO !SubCoolId
IF (System(SysNum)%NumSubcoolers > 0) THEN
DO SubcoolerIndex=1,System(SysNum)%NumSubcoolers
SubcoolID=System(Sysnum)%Subcoolernum(SubcoolerIndex)
IF(Subcooler(SubcoolID)%SubcoolerType == LiquidSuction)CYCLE
System(SysNum)%SumMechSCBenefit = Subcooler(SubcoolID)%MechSCTransLoad
END DO !subcoolerindex
END IF ! system(sysid)%numsubcoolers > 0
END IF !NumSimulationMechSubcoolers > 0 and not first loop
!This loop places load on system absorbing heat from cascade condenser and &
! condenser heat reclaim credits from hot gas/brine defrosts
IF((System(SysNum)%NumCascadeLoads > 0).AND. (.NOT. FirstSCLoop)) THEN
DO CascadeLoadIndex=1,System(SysNum)%NumCascadeLoads
CascadeLoadID=System(Sysnum)%CascadeLoadNum(CascadeLoadIndex)
IF (System(SysNum)%CompSuctControl == ConstantSuctionTemperature) THEN
System(Sysnum)%TEvapNeeded=System(SysNum)%TEvapDesign
ELSE ! check for lowest T evap design among the CascadeLoad systems and
! Compare Tevap for this Cascade to max allowed for cases, walk ins, and
! for all previous CascadeLoad loops on this suction group and set
! at the MINIMUM
IF(Condenser(CascadeLoadID)%CascadeTempControl == CascadeTempSet) THEN
!if float then set tevap based upon other loads
IF (CascadeLoadIndex == 1 .AND. System(SysNum)%NumNonCascadeLoads == 0 )THEN
System(Sysnum)%TEvapNeeded=Condenser(CascadeLoadID)%CascadeRatedEvapTemp
ELSE
System(Sysnum)%TEvapNeeded=MIN(Condenser(CascadeLoadID)%CascadeRatedEvapTemp,System(Sysnum)%TEvapNeeded)
END IF
END IF
END IF !floating or constant system evap temperature
! increment Cascade condenser Loads for Compressors/condenser on each system
! place any defrost credits on the same system absorbing the cascade condenser load
! (CascadeSysID identifies the condenser producing the defrost credits, that is, the lower temp system)
System(SysNum)%SumCascadeLoad = System(SysNum)%SumCascadeLoad + Condenser(CascadeLoadID)%CondLoad
System(SysNum)%SumCascadeCondCredit = System(SysNum)%SumCascadeCondCredit + &
System(Condenser(CascadeLoadID)%CascadeSysID)%TotalCondDefrostCredit
END DO !NumCascadeLoads
END IF !System(SysNum)%NumCascadeLoads > 0
!only calc detailed system if have load (could be zero first time through if only load is cascade condenser)
System(SysNum)%TotalSystemLoad = System(SysNum)%TotalCoolingLoad + System(SysNum)%SumSecondaryLoopLoad + &
System(SysNum)%SumMechSCLoad + System(SysNum)%SumCascadeLoad
IF (System(SysNum)%TotalSystemLoad > 0.d0) THEN
System(SysNum)%CpSatVapEvap = GetSatSpecificHeatRefrig(System(SysNum)%RefrigerantName,System(SysNum)%TEvapNeeded,&
1.0d0,System(SysNum)%RefIndex,'SimulateDetailedRefrigerationSystems')
System(SysNum)%HCaseOut=GetSatEnthalpyRefrig(System(SysNum)%RefrigerantName,System(Sysnum)%TEvapNeeded, &
1.0d0,System(SysNum)%RefIndex,'SimulateDetailedRefrigerationSystems') + &
System(SysNum)%CpSatVapEvap*CaseSuperheat
!Establish estimates to start solution loop
SELECT CASE (Condenser(System(SysNum)%CondenserNum(1))%CondenserType) !only one condenser allowed now
CASE (RefrigCondenserTypeAir)
System(SysNum)%TCondense = OutDryBulbTemp + 16.7d0
!16.7C is delta T at rating point for air-cooled condensers, just estimate, so ok for zone-located condensers
CASE (RefrigCondenserTypeEvap)
System(SysNum)%TCondense = OutDryBulbTemp + 15.0d0
!15C is delta T at rating point for evap-cooled condensers
CASE (RefrigCondenserTypeWater)
!define starting estimate at temperature of water exiting condenser
System(SysNum)%TCondense = Node(Condenser(System(SysNum)%CondenserNum(1))%OutletNode)%Temp
CASE (RefrigCondenserTypeCascade)
!?Don't need estimate for cascade condenser because it doesn't iterate?
END SELECT
!Produce first time step estimates, assume no subcoolers
System(SysNum)%HSatLiqCond=GetSatEnthalpyRefrig(System(SysNum)%RefrigerantName,System(SysNum)%TCondense,0.0d0,&
System(SysNum)%RefIndex,'SimulateDetailedRefrigerationSystems')
System(SysNum)%CpSatLiqCond = GetSatSpecificHeatRefrig(System(SysNum)%RefrigerantName,System(SysNum)%TCondense,&
0.0d0,System(SysNum)%RefIndex,'SimulateDetailedRefrigerationSystems')
System(SysNum)%HCaseIn = System(SysNum)%HSatLiqCond - System(SysNum)%CpSatLiqCond* &
Condenser(System(SysNum)%CondenserNum(1))%RatedSubcool
System(SysNum)%RefMassFlowtoLoads=System(SysNum)%TotalSystemLoad/(System(SysNum)%HCaseOut-System(SysNum)%HCaseIn)
System(SysNum)%RefMassFlowComps=System(SysNum)%RefMassFlowtoLoads
IF(System(SysNum)%NumStages==2) THEN ! Two-stage compression system
! Initial guess for high-stage mass flow rate in two-stage compression systems
System(SysNum)%RefMassFlowHiStageComps=System(SysNum)%RefMassFlowComps/0.65
END IF
CALL CalcDetailedSystem(SysNum)
DeRate = .FALSE.
!With air chiller coils, don't use unmet energy, instead reduce capacity on coils to match avail compressor/cond capacity
CurrentLoads = System(SysNum)%TotalSystemLoad + &
System(SysNum)%LSHXTrans !because compressor capacity rated from txv to comp inlet
IF((System(SysNum)%CoilFlag).AND.(CurrentLoads > (System(SysNum)%TotCompCapacity*1.001d0))) THEN
DeRate = .TRUE.
CALL FinalRateCoils(Derate,DetailedSystem,SysNum,CurrentLoads, &
System(SysNum)%TotCompCapacity)
System(SysNum)%TotalCoolingLoad = 0.d0
System(SysNum)%TotalCondDefrostCredit = 0.d0
DO CoilIndex=1,System(SysNum)%NumCoils
CoilID=System(Sysnum)%CoilNum(CoilIndex)
! already CALLed CalculateCoil(CoilID) in CoilSet specified order
IF (System(SysNum)%CompSuctControl == ConstantSuctionTemperature) THEN
System(Sysnum)%TEvapNeeded=System(SysNum)%TEvapDesign
ELSE ! calculate floating T evap
System(Sysnum)%TEvapNeeded=System(SysNum)%TEvapDesign
CALL ShowWarningError('Refrigeration:System: '//TRIM(System(SysNum)%Name))
CALL ShowContinueError(' Floating evaporator temperature model not yet available for warehouse coil systems. ')
END IF !floating or constant evap temperature
! increment TotalCoolingLoad for Compressors/condenser on each system
System(SysNum)%TotalCoolingLoad = System(SysNum)%TotalCoolingLoad + WarehouseCoil(CoilID)%TotalCoolingLoad
System(SysNum)%TotalCondDefrostCredit=System(SysNum)%TotalCondDefrostCredit + WarehouseCoil(CoilID)%HotDefrostCondCredit
END DO !NumCoils systems
IF(System(SysNum)%NumStages==2 .AND.&
System(SysNum)%TotHiStageCompCapacity < (System(SysNum)%TotalCoolingLoad + System(SysNum)%LSHXTrans + &
System(SysNum)%TotCompPower))THEN
CALL ShowRecurringWarningErrorAtEnd('Refrigeration:System: '//TRIM(System(SysNum)%Name)//&
':The specified high-stage compressors for this system are unable to meet '// &
' the sum of the refrigeration loads, ', System(SysNum)%HiStageWarnIndex1)
CALL ShowRecurringContinueErrorAtEnd(' subcooler loads (if any), and low-stage compressor loads for this sytem.',&
System(SysNum)%HiStageWarnIndex2)
END IF !Hi-stage capacity<(load+LSHX load + lo-stage compressor load)
END IF !CoilFlag (Numcoils > 0) and load > capacity
END IF !System(SysNum)%TotalSystemLoad > 0
END IF !(((.NOT. UseSysTimeStep).AND.(.NOT. System(SysNum)%CoilFlag)).OR.((UseSysTimeStep).AND.(System(SysNum)%CoilFlag)))
END DO !Sysnum over NumRefrigSystems
FirstSCLoop=.FALSE.
END DO !Loopnum, three times for buildings with multiple detailed systems connected with mechanical subcoolers
! or cascade condensers or shared condensers or warehouse coils that might need to be de-rated
! Dealing with unmet load has to be done outside iterative loop
DO SysNum = 1, NumRefrigSystems
!Only do those systems appropriate for this analysis, supermarket type on load time step or coil type on sys time step
IF((((.NOT. UseSysTimeStep).AND.(.NOT. System(SysNum)%CoilFlag)).OR.((UseSysTimeStep).AND.(System(SysNum)%CoilFlag))).AND. &
(.NOT. WarmUpFlag)) THEN
CurrentLoads = System(SysNum)%TotalSystemLoad + &
System(SysNum)%LSHXTrans !because compressor capacity rated from txv to comp inlet
IF(System(SysNum)%NumStages==2) THEN
CurrentHiStageLoads = CurrentLoads + System(SysNum)%TotCompPower
END IF ! NumStages==2
IF(System(SysNum)%CoilFlag) THEN
! don't use 'unmet energy' with air chillers, see 'derate'
System(SysNum)%UnmetEnergy=0.D0
System(SysNum)%UnmetHiStageEnergy=0.0d0
ELSE
! Meeting current and possibly some portion of the previously unmet energy
! perhaps future interest in reporting percent of installed capacity used(or number of compressors) ?
! If the system compressors were unable to meet the current loads, save energy to be met in succeeding time step
! Note the unmet energy is turned into a rate and applied to the system load at the start of calccompressor
System(SysNum)%UnmetEnergy=System(SysNum)%UnmetEnergy + (CurrentLoads - System(SysNum)%TotCompCapacity)* &
TimeStepZone*SecInHour
IF(System(SysNum)%NumStages==2) THEN
System(SysNum)%UnmetHiStageEnergy=System(SysNum)%UnmetHiStageEnergy + (CurrentHiStageLoads - &
System(SysNum)%TotHiStageCompCapacity)*TimeStepZone*SecInHour
END IF
IF(System(SysNum)%UnmetEnergy > MyLargeNumber)THEN
System(SysNum)%UnmetEnergy = MyLargeNumber
IF(ShowUnmetEnergyWarning(SysNum))THEN
CALL ShowWarningError('Refrigeration:System: '//TRIM(System(SysNum)%Name))
CALL ShowContinueError(' The specified compressors for this system are unable to meet ')
CALL ShowContinueError(' the sum of the refrigerated case loads and subcooler loads (if any) for this sytem.')
ShowUnmetEnergyWarning(SysNum) = .FALSE.
END IF !show warning
END IF ! > mylarge number
IF(System(SysNum)%UnmetHiStageEnergy > MyLargeNumber)THEN
System(SysNum)%UnmetHiStageEnergy = MyLargeNumber
IF(ShowHiStageUnmetEnergyWarning(SysNum))THEN
CALL ShowWarningError('Refrigeration:System: '//TRIM(System(SysNum)%Name))
CALL ShowContinueError(' The specified high-stage compressors for this system are unable to meet ')
CALL ShowContinueError(' the sum of the refrigerated case loads, subcooler loads (if any) and ')
CALL ShowContinueError(' low-stage compressor loads for this sytem.')
ShowHiStageUnmetEnergyWarning(SysNum) = .FALSE.
END IF !show warning
END IF ! > mylarge number
END IF ! numcoils > 0
!Zone-located air-cooled condenser reject heat also has to be outside iterative loop
IF (System(SysNum)%SystemRejectHeatToZone)THEN
CondInletAirZoneNum = Condenser(System(SysNum)%CondenserNum(1))%InletAirZoneNum
IF(UseSysTimeStep) THEN
CoilSysCredit(CondInletAirZoneNum)%SenCreditToZoneRate = &
CoilSysCredit(CondInletAirZoneNum)%SenCreditToZoneRate + &
System(SysNum)%NetHeatRejectLoad !Adding heat is positive
CoilSysCredit(CondInletAirZoneNum)%ReportSenCoolingToZoneRate = &
- CoilSysCredit(CondInletAirZoneNum)%SenCreditToZoneRate
END IF
!Can arrive here when load call to refrigeration looks for cases/walkin systems and usetimestep is .false.
IF((.NOT. UseSysTimeStep).AND.((NumSimulationCases > 0).OR.( NumSimulationWalkIns > 0)))THEN
RefrigCaseCredit(CondInletAirZoneNum)%SenCaseCreditToZone = &
RefrigCaseCredit(CondInletAirZoneNum)%SenCaseCreditToZone + &
System(SysNum)%NetHeatRejectLoad !Adding heat is positive
END IF !UseSystimestep
END IF !Reject heat to zone
! Report variables
System(SysNum)%TotTransferLoad = System(SysNum)%SumMechSCLoad - System(SysNum)%SumMechSCBenefit &
+ System(SysNum)%SumSecondaryLoopLoad + System(SysNum)%SumCascadeLoad
System(SysNum)%TotTransferEnergy = System(SysNum)%TotTransferLoad * LocalTimeStep * SecInHour
System(SysNum)%PipeHeatEnergy = System(SysNum)%PipeHeatLoad * LocalTimeStep * SecInHour
System(SysNum)%TotalCoolingEnergy = System(SysNum)%TotalCoolingLoad * LocalTimeStep * SecInHour
END IF !(((.NOT. UseSysTimeStep).AND.(.NOT. System(SysNum)%CoilFlag)).OR.((UseSysTimeStep).AND.(System(SysNum)%CoilFlag))).and.not warmupflag
END DO ! Sysnum = 1,NumRefrigSystems
! Update for sending to zone equipment manager. (note report variables are summed elsewhere)
! LatOutputProvided = CoilSysCredit(ZoneNum)%LatKgPerS_ToZoneRate
! SysOutputProvided = CoilSysCredit(ZoneNum)%SenCreditToZoneRate
! Note that case credit is negative for cooling, thus subtract positive value calculated for coil
! Note this is done whether or not the coils are derated.
IF(UseSysTimeStep) THEN
DO ZoneNum = 1,NumOfZones
DO CoilID = 1,NumSimulationRefrigAirChillers
IF(WarehouseCoil(CoilID)%ZoneNum /= ZoneNum)CYCLE
CoilSysCredit(ZoneNum)%SenCreditToZoneRate = CoilSysCredit(ZoneNum)%SenCreditToZoneRate - &
WarehouseCoil(CoilID)%SensCreditRate
CoilSysCredit(ZoneNum)%SenCreditToZoneEnergy = CoilSysCredit(ZoneNum)%SenCreditToZoneRate &
* LocalTimeStep * SecInHour
CoilSysCredit(ZoneNum)%LatKgPerS_ToZoneRate = CoilSysCredit(ZoneNum)%LatKgPerS_ToZoneRate - &
WarehouseCoil(CoilID)%LatKgPerS_ToZone
CoilSysCredit(ZoneNum)%LatCreditToZoneRate = CoilSysCredit(ZoneNum)%LatCreditToZoneRate - &
WarehouseCoil(CoilID)%LatCreditRate
CoilSysCredit(ZoneNum)%LatCreditToZoneEnergy = CoilSysCredit(ZoneNum)%LatCreditToZoneEnergy - &
WarehouseCoil(CoilID)%LatCreditEnergy
END DO
END DO
END IF
CALL SumZoneImpacts
RETURN
END SUBROUTINE SimulateDetailedRefrigerationSystems