SUBROUTINE GetRefrigerationInput
! SUBROUTINE INFORMATION:
! AUTHOR Richard Raustad, FSEC
! DATE WRITTEN Oct/Nov 2004
! MODIFIED Shirey, FSEC Dec 2004; Hudson, ORNL Feb 2007, July 2007
! MODIFIED Stovall, ORNL April 2008, Assisted by Hugh Henderson
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! GetObjectItem is called to read refrigerated case, rack, compressor, and condenser information
! Lists of cases and compressors are then correlated to the appropriate system.
! The nominal ratings of all components are then compared and a warning is printed if the system is not balanced
! METHODOLOGY EMPLOYED:
! GetObjectItem is called to read refrigerated case information
! REFERENCES:
! na
! USE STATEMENTS:
USE BranchNodeConnections, ONLY: TestCompSet
USE CurveManager, ONLY : GetCurveIndex, GetCurveType, GetCurveMinMaxValues, CurveValue
USE DataHeatBalance, ONLY: Zone, NumRefrigeratedRacks,NumRefrigSystems !, &
!unused IntGainTypeOf_RefrigerationCompressorRack, &
!unused IntGainTypeOf_RefrigerationCase
USE DataZoneEquipment, ONLY: GetSystemNodeNumberForZone, GetReturnAirNodeForZone
USE DataEnvironment, ONLY: StdBaroPress
USE General, ONLY: RoundSigDigits
USE FluidProperties, ONLY: GetSupHeatEnthalpyRefrig
USE PlantUtilities, ONLY: RegisterPlantCompDesignFlow
USE InputProcessor, ONLY: GetNumObjectsFound, GetObjectItem, GetObjectItemNum, VerifyName, &
FindItemInList, SameString, GetObjectDefMaxArgs
USE NodeInputManager, ONLY: GetOnlySingleNode
USE OutAirNodeManager, ONLY: CheckOutAirNodeNumber
USE Psychrometrics, ONLY: PsyWFnTdbRhPb, PsyTdpFnWPb
! USE ScheduleManager, ONLY: CheckScheduleValueMinMax
USE WaterManager, ONLY: SetupTankDemandComponent
USE DataGlobals, ONLY: AnyEnergyManagementSystemInModel
!USE FluidProperties, ONLY: GetDensityGlycol, GetSpecificHeatGlycol
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
! na
! SUBROUTINE PARAMETER DEFINITIONS:
CHARACTER(len=*),Parameter :: TrackMessage = 'from refrigerated case'
CHARACTER(len=*),Parameter :: RoutineName = 'GetRefrigerationInput: '
INTEGER, Parameter :: AlwaysOn = -1 ! -1 pointer sent to schedule manager returns a value of 1.0
!unused INTEGER, Parameter :: InputTypeSecond = 1 ! Indicator that flow used to specify capacity of secondary heat exchanger
!unused INTEGER, Parameter :: InputTypeFirst = 2 ! Indicator that capacity of secondary heat exchanger is input directly
!unused INTEGER, Parameter :: InputTypeBoth = 3 ! Indicator that capacity of secondary heat exchanger is
! input in both watts and flow rate
INTEGER, Parameter :: NumWIAlphaFieldsBeforeZoneInput = 9 ! Used to cycle through zones on input for walk in coolers
INTEGER, Parameter :: NumWIAlphaFieldsPerZone = 4 ! Used to cycle through zones on input for walk in coolers
INTEGER, Parameter :: NumWINumberFieldsBeforeZoneInput = 12 ! Used to cycle through zones on input for walk in coolers
INTEGER, Parameter :: NumWINumberFieldsPerZone = 8 ! Used to cycle through zones on input for walk in coolers
REAL(r64), PARAMETER :: CondARI460DelT = 16.7d0 ! Rated sat cond temp - dry bulb air T for air-cooled Condensers, ARI460
REAL(r64), PARAMETER :: CondARI460Tcond = 51.7d0 ! Rated sat cond temp for air-cooled cond, ARI 460
REAL(r64), PARAMETER :: CondARI490DelT = 15.0d0 ! Rated sat cond temp - wet bulb air T for evap-cooled Cond w R22, ARI490
REAL(r64), PARAMETER :: CondARI490Tcond = 40.6d0 ! Rated sat cond temp for evap-cooled cond with R22, ARI 490
REAL(r64), PARAMETER :: DelEvapTDefault = 5.0d0 ! default difference between case T and evap T (C)
REAL(r64), PARAMETER :: HoursPerDay = 24.d0
REAL(r64), PARAMETER :: SecondsPerHour = 3600.d0
REAL(r64), PARAMETER :: DefaultCascadeCondApproach =3.0d0 !Cascade condenser approach temperature difference (deltaC)
REAL(r64), PARAMETER :: DefaultCircRate = 2.5d0 !Phase change liquid overfeed circulating rate (ASHRAE definition)
!unused REAL(r64), PARAMETER :: DefaultVarSpdCoeffA = 0.9d0 !Variable speed pump power curve coefficients based
!unused REAL(r64), PARAMETER :: DefaultVarSpdCoeffB = -0.1d0 ! upon paper by John Bittner of Hill Phoenix
!unused REAL(r64), PARAMETER :: DefaultVarSpdCoeffC = 0.2d0 ! A is cube term, B square term, C linear term
REAL(r64), Parameter :: DefaultWISurfaceUValue = 0.3154d0 !equiv R18 in Archaic American units (W/m2-delta T)
REAL(r64), Parameter :: DefaultWIUValueGlassDr = 1.136d0 !equiv R5 in Archaic American units (W/m2-delta T)
REAL(r64), Parameter :: DefaultWIUValueStockDr = 0.3785d0 ! equiv R15 in Archaic American units (W/m2-delta T)
REAL(r64), Parameter :: DefaultWIHeightGlassDr = 1.5d0 ! glass door height in walk-in cooler (m)
REAL(r64), Parameter :: DefaultWIHeightStockDr = 3.0d0 ! stock door height in walk-in cooler (m)
REAL(r64), Parameter :: PumpImpellerEfficiency = 0.78d0 ! same as used in pump auto-sizing, dimensionless
REAL(r64), Parameter :: PumpMotorEfficiency = 0.85d0 ! suggested as average value in ITT/Gould pump references,
! dimensionless
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
CHARACTER(len=MaxNameLength), ALLOCATABLE, DIMENSION(:) :: Alphas ! Alpha items for object
CHARACTER(Len=MaxNameLength), ALLOCATABLE, DIMENSION(:) :: cAlphaFieldNames ! Alpha field names (from input processor)
CHARACTER(Len=MaxNameLength), ALLOCATABLE, DIMENSION(:) :: cNumericFieldNames ! Numeric field names (from input processor)
CHARACTER(len=MaxNameLength) :: CurrentModuleObject = ' '! Object type for getting and error messages
LOGICAL, ALLOCATABLE, DIMENSION(:) :: lAlphaBlanks ! Logic array, alpha input blank = .TRUE.
LOGICAL, ALLOCATABLE, DIMENSION(:) :: lNumericBlanks ! Logic array, numeric input blank = .TRUE.
LOGICAL :: CaseLoads = .FALSE. ! Flag to help verify load type with loads served by systems cooled by cascade condensers
LOGICAL :: ErrorsFound = .FALSE. ! Set to true if errors in input, fatal at end of routine
LOGICAL :: IsNotOK = .FALSE. ! Flag to verify name
LOGICAL :: IsBlank = .FALSE. ! Flag for blank name
LOGICAL :: StartCycle = .FALSE. ! Flag for counting defrost cycles
INTEGER :: AlphaListNum = 0 ! Index of Names in Case, Compressor et al Lists
INTEGER :: AlphaNum = 0 ! Used to cycle through input
INTEGER :: AlphaStartList = 0 !
INTEGER :: AStart = 0 ! Used to cycle through zones on input for walk in coolers
!INTEGER :: CascadeCondenserID= 0 ! Used to match load on system to Condenser absolute index
INTEGER :: CascadeLoadNum = 0 ! counters while associating cascade loads with systems
INTEGER :: CascadeLoadIndex = 0 ! Counters while inputting cascade loads
INTEGER :: CaseID = 0 ! ID of refrigerated case in rack
INTEGER :: CaseIndex = 0 ! Index of refrigerated case attached to a system
INTEGER :: CaseNum = 0 ! Index of refrigerated case
INTEGER :: CaseAndWalkInListNum = 0 ! ID of refrigerated CaseAndWalkInList
INTEGER :: ChillerIndex = 0 !
INTEGER :: CoilID = 0 ! Index of warehouse coil attached to a system
INTEGER :: CoilIndex = 0 ! Index of warehouse coil attached to a system
INTEGER :: CoilNum = 0 ! Index of warehouse coil
INTEGER :: CompIndex = 0 ! Index of refrigeration compressor attached to a system
INTEGER :: CompNum = 0 ! Index of refrigeration compressor
INTEGER :: CondID = 0 ! Condenser ID used when associating condenser as a cascade load
INTEGER :: CondIndex = 0 ! Index of refrigeration condenser attached to a system
INTEGER :: CondNum = 0 ! Index of refrigeration condenser
INTEGER :: DefType = 0 ! Local value for case defrost type
!INTEGER :: FlowIndex = 0 ! Index of pump flow numeric field
INTEGER :: GCNum = 0 ! Index of refrigeration gas cooler
INTEGER :: HRNum = 0 ! Counter for hours in day
INTEGER :: IOStatus = 0 ! Used in GetObjectItem
INTEGER :: ListNum = 0 ! Index of Lists of cases, compressors, and subcoolers
INTEGER :: LoadCascadeNum = 0 ! Used to read transfer load list
INTEGER :: LoadCount = 0 ! check for blank case and walkin names in caseand alkinlist
INTEGER :: LoadSecondaryNum = 0 ! Used to read transfer load list
INTEGER :: LoadWalkInNum = 0 ! Used to read CaseAndWalkInList
INTEGER :: LoadCaseNum = 0 ! Used to read CaseAndWalkInList
INTEGER :: LoadCoilNum = 0 ! Used to read CaseAndWalkInList
INTEGER :: MaxNumAlphasRack = 0 ! Maximum number of alphas for rack object
INTEGER :: MaxNumAlphasAirChiller= 0 ! Maximum number of alphas for air chiller
INTEGER :: MaxNumAlphasAll = 0 ! Maximum number of alphas for all objects
INTEGER :: MaxNumAlphasSys = 0 ! Maximum number of alphas for system object
INTEGER :: MaxNumAlphasTransSys = 0 ! Maximum number of alphas for transcritical system object
INTEGER :: MaxNumAlphasChillerSet= 0 ! Maximum number of alphas for chiller set
INTEGER :: MaxNumAlphasConda = 0 ! Maximum number of alphas for air-cooled condenser object
INTEGER :: MaxNumAlphasConde = 0 ! Maximum number of alphas for evap-cooled condenser object
INTEGER :: MaxNumAlphasCondw = 0 ! Maximum number of alphas for water-cooled condenser object
INTEGER :: MaxNumAlphasGasCoolera = 0 ! Maximum number of alphas for air-cooled gas cooler object
INTEGER :: MaxNumAlphasComp = 0 ! Maximum number of alphas for compressor object
INTEGER :: MaxNumAlphasCompressorList = 0 ! Maximum number of alphas for compressor list objects
INTEGER :: MaxNumAlphasCase = 0 ! Maximum number of alphas for case object
INTEGER :: MaxNumAlphasCaseAndWalkInList= 0 ! Maximum number of alphas in CaseAndWalkInList
INTEGER :: MaxNumAlphasWalkIn = 0 ! Maximum number of alphas for walkin object
!INTEGER :: MaxNumAlphasWalkInList = 0 ! Maximum number of alphas for walkin list object
INTEGER :: MaxNumAlphasSecond = 0 ! Maximum number of alphas for air chiller object
INTEGER :: MaxNumNumbersAirChiller= 0 ! Maximum number of numbers for air chiller object
INTEGER :: MaxNumNumbersSecond = 0 ! Maximum number of numbers for secondary system object
INTEGER :: MaxNumNumbersWalkIn = 0 ! Maximum number of numbers for walkin object
INTEGER :: MaxNumNumbersCase = 0 ! Maximum number of numbers for case object
INTEGER :: MaxNumNumbersCaseAndWalkInList= 0 ! Maximum number of numbers in CaseAndWalkInList
INTEGER :: MaxNumNumbersRack = 0 ! Maximum number of numbers for rack object
INTEGER :: MaxNumNumbersAll = 0 ! Maximum number of numeric inputs for all objects
INTEGER :: MaxNumNumbersSys = 0 ! Maximum number of numbers for system object
INTEGER :: MaxNumNumbersTransSys = 0 ! Maximum number of numbers for transcritical system object
INTEGER :: MaxNumNumbersChillerSet= 0 ! Maximum number of numbers for chiller set object
INTEGER :: MaxNumNumbersConda = 0 ! Maximum number of numbers for air-cooled condenser object
INTEGER :: MaxNumNumbersConde = 0 ! Maximum number of numbers for evap-cooled condenser object
INTEGER :: MaxNumNumbersCondw = 0 ! Maximum number of numbers for water-cooled condenser object
INTEGER :: MaxNumNumbersGasCoolera = 0 ! Maximum number of numbers for air-cooled gas cooler object
INTEGER :: MaxNumNumbersComp = 0 ! Maximum number of numbers for compressor object
INTEGER :: MaxNumNumbersCompressorList = 0 ! Maximum number of numbers
INTEGER :: MaxNumArgs = 0 ! Max number of alphas and numbers (arguments) for rack object
INTEGER :: NStart = 0 ! Used to cycle through zones on input for walk in coolers
INTEGER :: NumAlphas = 0 ! Number of Alphas for each GetObjectItem call
INTEGER :: NumCascadeLoad = 0 ! Number of Cascade Loads on current system
INTEGER :: NumCompressorsSys = 0 ! Number of compressors on current system
INTEGER :: NumHiStageCompressorsSys = 0 ! Number of high-stage compressors on current system
INTEGER :: NumCondensers = 0 ! Counter for condensers in GETInput do loop
INTEGER :: NumGasCoolers = 0 ! Counter for gas coolers in GetInput do loop
INTEGER :: NumDefCycles = 0 ! Number of defrost cycles per day
INTEGER :: NumPumps = 0 ! Number of pumps on a secondary loop
INTEGER :: NumCases = 0 ! Number of refrigerated cases for single system
INTEGER :: NumCasesMT = 0 ! Number of medium temperature cases on a single transcritical system
INTEGER :: NumCasesLT = 0 ! Number of low temperature cases on a single transcritical system
INTEGER :: NumCoils = 0 ! Number of warehouse coils for single system
INTEGER :: NumSubcooler = 0 ! Number of subcoolers on current system
INTEGER :: NumNameMatches = 0 ! Used to check for uniqueness of name for transfer loads
INTEGER :: NumNum = 0 ! Used to cycle through input
INTEGER :: NumNumbers = 0 ! Number of Numbers for each GetObjectItem call
INTEGER :: NumCompressorLists=0 ! Total number of Compressor Lists in IDF
INTEGER :: NumDisplayCases = 0 ! Counter for refrigerated cases in GetInput do loop
INTEGER :: NumSecondary = 0 ! Number of secondary loops
INTEGER :: NumWalkIns = 0 ! Number of walk ins
INTEGER :: NumWalkInsMT = 0 ! Number of medium temperature walk-ins on a single transcritical system
INTEGER :: NumWalkInsLT = 0 ! Number of low temperature walk-ins on a single transcritical system
INTEGER :: NumWIFieldsPerZone = 0 ! Used to calculate number of zones exposed to each walkin
INTEGER :: NumWIFieldsTotal = 0 ! Used to calculate number of zones exposed to each walkin
INTEGER :: NumZones = 0 ! Used to cycle through zones on input for walk in coolers
INTEGER :: NumTotalLoadsOnList= 0 ! Used to read transfer load and caseandWalkIn lists
INTEGER :: NumSecondarysOnList = 0 ! Used to read transfer load lists
INTEGER :: NumCascadeLoadsChecked= 0 ! Used when checking for consistency of coil loads/time steps
INTEGER :: NumCascadeLoadsOnList = 0 ! Used to read transfer load lists
INTEGER :: NumLoad = 0 ! Used to read transfer loadand caseandWalkIn lists
INTEGER :: NumCasesOnList = 0 ! Used to read caseandWalkIn lists
INTEGER :: NumChillersInSet = 0 !
INTEGER :: NumCoilsOnList = 0 ! Used to read caseandWalkIn lists
INTEGER :: NumWalkInsOnList = 0 ! Used to read caseandWalkIn lists
INTEGER :: RackNum = 0 ! Index of refrigerated display case compressor rack
INTEGER :: RefrigIndex = 0 ! Index used in fluid property routines
INTEGER :: RefrigSysNum = 0 ! Index of refrigeration system
INTEGER :: TransRefrigSysNum = 0 ! Index of transcritical CO2 refrigeration system
INTEGER :: SecondaryIndex = 0 ! Index of secondary loops
INTEGER :: SecondaryID = 0 ! Index of secondary loops
INTEGER :: SetID = 0 ! Index of refrigerated chilller SETS
INTEGER :: SecondaryNum = 0 ! Index of secondary loops
!INTEGER :: TransferLoadListIndex = 0 ! Index of TransferLoad lists
!INTEGER :: TransferLoadListID = 0 ! Index of TransferLoad lists
INTEGER :: TransferLoadListNum = 0 ! Index of TransferLoad lists
! INTEGER :: InputType = 0 ! Type of inlet, capcity in W or brine flow rate in m3/s
INTEGER :: SubcoolerNum = 0 ! Index of subcooler
INTEGER :: TSNum = 0 ! Counter for time steps in hour
INTEGER :: WalkInIndex = 0 ! Index of walk ins
INTEGER :: WalkInID = 0 ! Index of walk ins
INTEGER :: WalkInNum = 0 ! Index of walk ins
INTEGER :: TotFields = 0 ! Used to calc number of zones on input for walk in coolers
INTEGER :: ZoneID = 0 ! Index to zone
INTEGER :: ZoneIndex = 0 ! Index to zone
INTEGER :: ZoneNum = 0 ! Index to zone
REAL(r64) :: CalcCircRate = 0.0d0 ! Calculted circ rate in secondary phase change loop, dimensionless
REAL(r64) :: CalcTotFlowVol = 0.0d0 ! Secondary loop flow in phase change liquid overfeed system (m3/s)
REAL(r64) :: CaseHeatGain = 0.0d0 ! Case sensible heat gain used for error messages
REAL(r64) :: CapacityAtMaxVolFlow = 0.0d0 ! Secondary loop capacity (W)
REAL(r64) :: CpBrineRated = 0.0d0 ! specific heat of circ fluid in secondary loop
REAL(r64) :: Capmin =0.0d0 ! min heat rej for heat rej curve for air cooled condenser (W)
REAL(r64) :: Capmax =0.0d0 ! max heat rej for heat rej curve for air cooled condenser (W)
REAL(r64) :: DeltaCap1 =0.0d0 ! fraction dif in capacity for input error check
REAL(r64) :: DeltaCap2 =0.0d0 ! fraction dif in capacity for input error check
REAL(r64) :: DeltaHPhaseChange = 0.0d0 ! Secondary loop enthalpy change in condenser w overfeed system (J/g)
REAL(r64) :: DelTempMin =0.0d0 ! min temperature for heat rej curve for air cooled condenser (C)
REAL(r64) :: DelTempMax =0.0d0 ! max temperature for heat rej curve for air cooled condenser (C)
REAL(r64) :: DensityBrineRated = 0.0d0 ! density of circ fluid in secondary loop
REAL(r64) :: DensityPhaseChange = 0.0d0 ! Secondary loop density at condensing temperature w overfeed system (g/m3)
REAL(r64) :: DesignSensibleCap = 0.0d0 ! Case sensible capacity used for error messages
REAL(r64) :: DiffCircRates =0.0d0 ! Difference between calculated and specified circ rates, fraction
REAL(r64) :: ErrSecondPumpPower = 0.0d0 ! Used to check consistency when both head and power input
REAL(r64) :: FlowMassRated =0.0d0 ! Design mass flow rate of circ fluid in secondary loop(kg/s)
REAL(r64) :: GCOutletH = 0.0d0 ! Gas cooler outlet enthalpy (J/kg)
REAL(r64) :: NominalSecondaryCapacity = 0.0d0 ! Rated Capacity from input data, W
REAL(r64) :: NominalSecondaryRefLoad = 0.0d0 ! Load from all connected cases and walkins, W
REAL(r64) :: NominalTotalCascadeLoad = 0.0d0 ! Load from all connected cascade condensers, W
REAL(r64) :: NominalTotalCaseCap=0.0d0 ! Total of nominal case capacities, used for rough input check (W)
REAL(r64) :: NominalTotalCoilCap=0.0d0 ! Total of nominal case capacities, used for rough input check (W)
REAL(r64) :: NominalTotalWalkInCap=0.0d0 ! Total of nominal walk-in capacities, used for rough input check (W)
REAL(r64) :: NominalTotalSecondaryCap=0.0d0 ! Total of nominal secondary capacities, used for rough input check (W)
REAL(r64) :: NominalTotalCaseCapMT=0.0d0 ! Total of nominal medium temperature case capacities, used for rough input check (W) (Transcritical CO2)
REAL(r64) :: NominalTotalCaseCapLT=0.0d0 ! Total of nominal low temperature case capacities, used for rough input check (W) (Transcritical CO2)
REAL(r64) :: NominalTotalWalkInCapMT=0.0d0 ! Total of nominal medium temperature walk-in capacities, used for rough input check (W) (Transcritical CO2)
REAL(r64) :: NominalTotalWalkInCapLT=0.0d0 ! Total of nominal low temperature walk-in capacities, used for rough input check (W) (Transcritical CO2)
REAL(r64) :: NominalTotalCoolingCap=0.0d0 ! Total of nominal load capacities, used for rough input check (W)
REAL(r64) :: NominalTotalCompCap=0.0d0 ! Total of nominal compressor capacities, used for rough input check (W)
REAL(r64) :: NominalTotalHiStageCompCap=0.0d0 ! Total of nominal high-stage compressor capacities, used for rough input check (W)
REAL(r64) :: NominalTotalCompCapHP=0.0d0 ! Total of nominal high pressure compressor capacities, used for rough input check (W) (Transcritical CO2)
REAL(r64) :: NominalTotalCompCapLP=0.0d0 ! Total of nominal low pressure compressor capacities, used for rough input check (W) (Transcritical CO2)
REAL(r64) :: NominalCondCap =0.0d0 ! Nominal Condenser capacity, used for rough input check (W)
REAL(r64) :: Pcond = 0.0d0 ! Condensing Pressure (Pa)
REAL(r64) :: Pevap = 0.0d0 ! Evaporating Pressure (Pa)
REAL(r64) :: PumpTotRatedHead =0.0d0 ! Total pump rated head on secondary loop (Pa)
REAL(r64) :: PumpTotRatedFlowVol = 0.0d0 ! Rated flow from input pump data, m3/s
REAL(r64) :: Rcase = 0.0d0 ! Case thermal resistance used with anti-sweat heater control
REAL(r64) :: RcaseDenom = 0.0d0 ! Denominator of case thermal resistance calculation for anti-sweat
REAL(r64) :: SecondaryFlowVolRated= 0.0d0 ! Rated flow of secondary fluid, used to calculate capacity (m3/s)
REAL(r64) :: TBrineOutRated = 0.0d0 ! Rated temperature of circ fluid LEAVING heat exchanger,C
REAL(r64) :: TBrineInRated = 0.0d0 ! Rated temperature of circ fluid going INTO heat exchanger, C
REAL(r64) :: TBrineAverage = 0.0d0 ! Rated average of inlet and outlet temps, used for property look up, C
REAL(r64) :: TempRAFraction = 0.0d0 ! Temporary sum of Return Air fraction per zone for reporting
REAL(r64) :: TestDelta = 0.0d0 ! Used to compare secondary loop rated capacity to calculated capacity, fraction
REAL(r64), ALLOCATABLE, DIMENSION(:) :: Numbers ! Numeric items for object
REAL(r64), ALLOCATABLE, DIMENSION (:,:) :: DayValues ! Array of schedule values
NumSimulationCascadeCondensers=GetNumObjectsFound('Refrigeration:Condenser:Cascade')
NumSimulationCases=GetNumObjectsFound('Refrigeration:Case')
NumSimulationCaseAndWalkInLists=GetNumObjectsFound('Refrigeration:CaseAndWalkInList')
NumRefrigeratedRacks=GetNumObjectsFound('Refrigeration:CompressorRack')
NumSimulationSecondarySystems=GetNumObjectsFound('Refrigeration:SecondarySystem')
NumSimulationTransferLoadLists=GetNumObjectsFound('Refrigeration:TransferLoadList')
NumSimulationWalkIns=GetNumObjectsFound('Refrigeration:WalkIn')
NumRefrigSystems=GetNumObjectsFound('Refrigeration:System')
NumTransRefrigSystems=GetNumObjectsFound('Refrigeration:TranscriticalSystem')
NumSimulationCondAir=GetNumObjectsFound('Refrigeration:Condenser:AirCooled')
NumSimulationCondEvap=GetNumObjectsFound('Refrigeration:Condenser:EvaporativeCooled')
NumSimulationCondWater=GetNumObjectsFound('Refrigeration:Condenser:WaterCooled')
NumSimulationGasCooler=GetNumObjectsFound('Refrigeration:GasCooler:AirCooled')
NumRefrigCondensers=NumSimulationCondAir + NumSimulationCondEvap + NumSimulationCondWater + &
NumSimulationCascadeCondensers
NumSimulationCompressors=GetNumObjectsFound('Refrigeration:Compressor')
NumSimulationSubcoolers=GetNumObjectsFound('Refrigeration:Subcooler')
NumCompressorLists=GetNumObjectsFound('Refrigeration:CompressorList')
NumRefrigChillerSets=GetNumObjectsFound('ZoneHVAC:RefrigerationChillerSet')
NumSimulationRefrigAirChillers=GetNumObjectsFound('Refrigeration:AirChiller')
! Set flags used later to avoid unnecessary steps.
IF(NumRefrigeratedRacks == 0) HaveRefrigRacks = .FALSE.
IF(NumRefrigSystems == 0) HaveDetailedRefrig = .FALSE.
IF(NumTransRefrigSystems == 0) HaveDetailedTransRefrig = .FALSE.
IF(NumSimulationCases == 0 .AND. NumSimulationWalkIns == 0)HaveCasesOrWalkins = .FALSE.
IF(NumSimulationRefrigAirChillers == 0)HaveChillers = .FALSE.
IF(NumRefrigeratedRacks > 0)THEN
ALLOCATE(RefrigRack(NumRefrigeratedRacks))
ALLOCATE(HeatReclaimRefrigeratedRack(NumRefrigeratedRacks))
ALLOCATE(ShowCOPWarning(NumRefrigeratedRacks))
ShowCOPWarning = .TRUE.
END IF
IF(NumRefrigSystems > 0)THEN
ALLOCATE(System(NumRefrigSystems))
ALLOCATE(ShowUnmetEnergyWarning(NumRefrigSystems))
ALLOCATE(ShowHiStageUnmetEnergyWarning(NumRefrigSystems))
ShowUnmetEnergyWarning = .TRUE.
ShowHiStageUnmetEnergyWarning = .TRUE.
END IF
IF(NumTransRefrigSystems > 0 )THEN
ALLOCATE(TransSystem(NumTransRefrigSystems))
ALLOCATE(ShowUnmetEnergyWarningTrans(NumTransRefrigSystems))
ShowUnmetEnergyWarningTrans = .TRUE.
END IF
IF(NumRefrigChillerSets > 0) ALLOCATE(AirChillerSet(NumRefrigChillerSets))
IF(NumRefrigCondensers > 0)THEN
ALLOCATE(HeatReclaimRefrigCondenser(NumRefrigCondensers))
ALLOCATE(Condenser(NumRefrigCondensers))
END IF
IF(NumSimulationGasCooler > 0) THEN
ALLOCATE(GasCooler(NumSimulationGasCooler))
END IF
IF(NumSimulationCases > 0)THEN
ALLOCATE(CaseRAFraction(NumOfZones))
ALLOCATE(RefrigCase(NumSimulationCases))
ALLOCATE(ShowStockingWarning(NumSimulationCases))
ShowStockingWarning = .TRUE.
ALLOCATE(ShowFrostWarning(NumSimulationCases))
ShowFrostWarning = .TRUE.
ALLOCATE(ShowStoreEnergyWarning(NumSimulationCases))
ShowStoreEnergyWarning = .TRUE.
END IF
IF(NumSimulationWalkIns > 0)THEN
ALLOCATE(WalkIn(NumSimulationWalkIns))
ALLOCATE(ShowUnMetWIEnergyWarning(NumSimulationWalkIns))
ShowUnMetWIEnergyWarning = .TRUE.
ALLOCATE(ShowWIFrostWarning(NumSimulationWalkIns))
ShowWIFrostWarning = .TRUE.
END IF
IF((NumSimulationWalkIns > 0) .OR. (NumSimulationCases > 0))THEN
ALLOCATE(CaseWIZoneReport(NumOfZones))
ELSE
UseSysTimeStep = .TRUE.
!needed to avoid accessing unallocated caseWIZoneReport on early call to SumZones
END IF
IF(NumSimulationSecondarySystems > 0)THEN
ALLOCATE(Secondary(NumSimulationSecondarySystems))
ALLOCATE(ShowUnmetSecondEnergyWarning(NumSimulationSecondarySystems))
ShowUnmetSecondEnergyWarning = .TRUE.
END IF
IF(NumSimulationRefrigAirChillers > 0)THEN
ALLOCATE(WareHouseCoil(NumSimulationRefrigAirChillers))
ALLOCATE(ShowCoilFrostWarning(NumSimulationRefrigAirChillers))
ALLOCATE(CoilSysCredit(NumOfZones))
ShowCoilFrostWarning = .TRUE.
END IF
IF(NumSimulationCompressors > 0)ALLOCATE(Compressor(NumSimulationCompressors))
IF(NumSimulationSubcoolers > 0)ALLOCATE(Subcooler(NumSimulationSubcoolers))
IF(NumSimulationCaseAndWalkInLists > 0)ALLOCATE(CaseAndWalkInList(NumSimulationCaseAndWalkInLists))
IF(NumCompressorLists > 0)ALLOCATE(CompressorLists(NumCompressorLists))
IF(NumSimulationTransferLoadLists > 0)ALLOCATE(TransferLoadList(NumSimulationTransferLoadLists))
ALLOCATE(DayValues(24,NumOfTimeStepInHour))
ALLOCATE(RefrigPresentInZone(NumOfZones))
RefrigPresentInZone = .FALSE.
CALL GetObjectDefMaxArgs('Refrigeration:Case',MaxNumArgs,MaxNumAlphasCase,MaxNumNumbersCase)
CALL GetObjectDefMaxArgs('Refrigeration:CaseAndWalkInList',MaxNumArgs,MaxNumAlphasCaseAndWalkInList, &
MaxNumNumbersCaseAndWalkInList)
CALL GetObjectDefMaxArgs('Refrigeration:CompressorRack',MaxNumArgs,MaxNumAlphasRack,MaxNumNumbersRack)
CALL GetObjectDefMaxArgs('Refrigeration:System',MaxNumArgs,MaxNumAlphasSys,MaxNumNumbersSys)
CALL GetObjectDefMaxArgs('Refrigeration:TranscriticalSystem',MaxNumArgs,MaxNumAlphasTransSys, &
MaxNumNumbersTransSys)
CALL GetObjectDefMaxArgs('Refrigeration:Condenser:AirCooled',MaxNumArgs,MaxNumAlphasConda, &
MaxNumNumbersConda)
CALL GetObjectDefMaxArgs('Refrigeration:Condenser:EvaporativeCooled',MaxNumArgs, &
MaxNumAlphasConde,MaxNumNumbersConde)
CALL GetObjectDefMaxArgs('Refrigeration:Condenser:WaterCooled',MaxNumArgs,MaxNumAlphasCondw, &
MaxNumNumbersCondw)
CALL GetObjectDefMaxArgs('Refrigeration:GasCooler:AirCooled',MaxNumArgs,MaxNumAlphasGasCoolera, &
MaxNumNumbersGasCoolera)
CALL GetObjectDefMaxArgs('Refrigeration:Compressor',MaxNumArgs,MaxNumAlphasComp,MaxNumNumbersComp)
CALL GetObjectDefMaxArgs('Refrigeration:CompressorList',MaxNumArgs, &
MaxNumAlphasCompressorList,MaxNumNumbersCompressorList)
CALL GetObjectDefMaxArgs('Refrigeration:WalkIn',MaxNumArgs,MaxNumAlphasWalkIn, &
MaxNumNumbersWalkIn)
CALL GetObjectDefMaxArgs('Refrigeration:SecondarySystem',MaxNumArgs,MaxNumAlphasSecond, &
MaxNumNumbersSecond)
CALL GetObjectDefMaxArgs('ZoneHVAC:RefrigerationChillerSet',MaxNumArgs,MaxNumAlphasChillerSet, &
MaxNumNumbersChillerSet)
CALL GetObjectDefMaxArgs('Refrigeration:AirChiller',MaxNumArgs,MaxNumAlphasAirChiller, &
MaxNumNumbersAirChiller)
MaxNumAlphasAll = MAX(MaxNumAlphasCase,MaxNumAlphasCaseAndWalkInList,MaxNumAlphasRack,&
MaxNumAlphasSys,MaxNumAlphasTransSys, MaxNumAlphasConda,MaxNumAlphasConde, &
MaxNumAlphasCondw,MaxNumAlphasGasCoolera,MaxNumAlphasComp, &
MaxNumAlphasCompressorList, &
MaxNumAlphasSecond,MaxNumAlphasWalkIn, MaxNumAlphasChillerSet,MaxNumAlphasAirChiller)
MaxNumNumbersAll = MAX(MaxNumNumbersCase,MaxNumNumbersCaseAndWalkInList,MaxNumNumbersRack,&
MaxNumNumbersSys,MaxNumNumbersTransSys, MaxNumNumbersConda,MaxNumNumbersConde, &
MaxNumNumbersCondw,MaxNumNumbersGasCoolera,MaxNumNumbersComp, &
MaxNumNumbersCompressorList,MaxNumNumbersSecond, &
MaxNumNumbersWalkIn, MaxNumNumbersChillerSet, MaxNumNumbersAirChiller)
ALLOCATE(Alphas(MaxNumAlphasAll))
Alphas=' '
ALLOCATE(Numbers(MaxNumNumbersAll))
Numbers=0.0d0
ALLOCATE(cAlphaFieldNames(MaxNumAlphasAll))
cAlphaFieldNames=' '
ALLOCATE(cNumericFieldNames(MaxNumNumbersAll))
cNumericFieldNames=' '
ALLOCATE(lAlphaBlanks(MaxNumAlphasAll))
lAlphaBlanks=.TRUE.
ALLOCATE(lNumericBlanks(MaxNumNumbersAll))
lNumericBlanks=.TRUE.
!bbb stovall note for future - for all curve entries, see if need fail on type or if can allow table input
IF(NumSimulationCases > 0 ) THEN
CurrentModuleObject='Refrigeration:Case'
DO CaseNum=1,NumSimulationCases
CALL GetObjectItem(CurrentModuleObject,CaseNum,Alphas,NumAlphas,Numbers,NumNumbers,IOStatus, &
NumBlank=lNumericBlanks,AlphaBlank=lAlphaBlanks, &
AlphaFieldNames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
NumDisplayCases = NumDisplayCases+1
IsNotOK =.FALSE.
IsBlank =.FALSE.
AlphaNum=1
CALL VerifyName(Alphas(AlphaNum),RefrigCase%Name,CaseNum-1,IsNotOK,IsBlank,CurrentModuleObject//' Name')
IF (IsNotOK) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Alphas(AlphaNum))//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//'+"'//TRIM(Alphas(AlphaNum)))
IF (IsBlank) Alphas(1)='xxxxx'
ErrorsFound=.TRUE.
ENDIF
RefrigCase(CaseNum)%Name = Alphas(AlphaNum)
AlphaNum=2
IF (.NOT. lAlphaBlanks(AlphaNum)) THEN
RefrigCase(CaseNum)%SchedPtr = GetScheduleIndex(Alphas(AlphaNum)) ! convert schedule name to pointer
IF (RefrigCase(CaseNum)%SchedPtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//' not found: '//TRIM(Alphas(AlphaNum)))
ErrorsFound=.TRUE.
END IF ! ptr == 0
ELSE ! no schedule specified
RefrigCase(CaseNum)%SchedPtr = AlwaysOn
END IF ! not blank
! check availability schedule for values between 0 and 1
IF (RefrigCase(CaseNum)%SchedPtr > 0)THEN
IF (.NOT. CheckScheduleValueMinMax(RefrigCase(CaseNum)%SchedPtr,'>=',0.0d0,'<=',1.0d0)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//'"')
CALL ShowContinueError('Error found in '//TRIM(cAlphaFieldNames(AlphaNum))//' = '//TRIM(Alphas(AlphaNum)))
CALL ShowContinueError('schedule values must be (>=0., <=1.)')
ErrorsFound=.TRUE.
END IF
END IF
!Get the Zone node number from the zone name entered by the user
RefrigCase(CaseNum)%ZoneName = Alphas(3)
RefrigCase(CaseNum)%ActualZoneNum = FindItemInList(Alphas(3),Zone%Name,NumOfZones)
IF (RefrigCase(CaseNum)%ActualZoneNum == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)// &
'", invalid '//TRIM(cAlphaFieldNames(3))//' not valid: '//TRIM(Alphas(3)))
ErrorsFound=.TRUE.
ELSE
RefrigPresentInZone(RefrigCase(CaseNum)%ActualZoneNum) = .TRUE.
ENDIF
RefrigCase(CaseNum)%ZoneNodeNum = GetSystemNodeNumberForZone(RefrigCase(CaseNum)%ZoneName)
RefrigCase(CaseNum)%ZoneRANode = GetReturnAirNodeForZone(RefrigCase(CaseNum)%ZoneName)
IF (RefrigCase(CaseNum)%ActualZoneNum >= 0) THEN
IF (RefrigCase(CaseNum)%ZoneNodeNum == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)// &
'", System Node Number not found for '//TRIM(cAlphaFieldNames(3))//' = '//TRIM(Alphas(3)))
CALL ShowContinueError('..Refrigerated cases must reference a controlled Zone (appear'// &
' in a ZoneHVAC:EquipmentConnections object).')
ErrorsFound=.TRUE.
ENDIF
ENDIF
RefrigCase(CaseNum)%RatedAmbientTemp = Numbers(1)
IF(Numbers(1) <= 0.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", '//TRIM(cNumericFieldNames(1))//' must be greater than 0 C')
ErrorsFound = .TRUE.
END IF
RefrigCase(CaseNum)%RatedAmbientRH = Numbers(2)
IF(Numbers(2) <= 0.0d0 .OR. Numbers(2) >= 100.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", '//TRIM(cNumericFieldNames(2))//' must be greater than 0% and less than 100%')
ErrorsFound = .TRUE.
END IF
RefrigCase(CaseNum)%RatedAmbientDewPoint = &
PsyTdpFnWPb(PsyWFnTdbRhPb(RefrigCase(CaseNum)%RatedAmbientTemp, &
(RefrigCase(CaseNum)%RatedAmbientRH / 100.0d0), &
StdBaroPress),StdBaroPress)
RefrigCase(CaseNum)%RateTotCapPerLength = Numbers(3)
IF(Numbers(3) <= 0.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", '//TRIM(cNumericFieldNames(3))//' must be greater than 0 W/m')
ErrorsFound = .TRUE.
END IF
RefrigCase(CaseNum)%RatedLHR = Numbers(4)
IF(Numbers(4) < 0.0d0 .OR. Numbers(4) > 1.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", '//TRIM(cNumericFieldNames(4))//' must be >= 0 and <= 1')
ErrorsFound = .TRUE.
END IF
RefrigCase(CaseNum)%RatedRTF = Numbers(5)
IF(Numbers(5) <= 0.0d0 .OR. Numbers(5) > 1.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", '//TRIM(cNumericFieldNames(5))//' must be > 0 and <= to 1')
ErrorsFound = .TRUE.
END IF
RefrigCase(CaseNum)%Length = Numbers(6)
IF(Numbers(6) <= 0.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", '//TRIM(cNumericFieldNames(6))//' must be greater than 0 m')
ErrorsFound = .TRUE.
END IF
RefrigCase(CaseNum)%Temperature = Numbers(7)
IF(RefrigCase(CaseNum)%Temperature >= RefrigCase(CaseNum)%RatedAmbientTemp) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", '//TRIM(cNumericFieldNames(7))//' must be below '//trim(cNumericFieldNames(1)))
ErrorsFound=.TRUE.
END IF
IF (SameString(Alphas(4),'CaseTemperatureMethod')) THEN
RefrigCase(CaseNum)%LatentEnergyCurveType = CaseTemperatureMethod
ELSEIF (SameString(Alphas(4),'RelativeHumidityMethod')) THEN
RefrigCase(CaseNum)%LatentEnergyCurveType = RHCubic
ELSEIF (SameString(Alphas(4),'DewpointMethod')) THEN
RefrigCase(CaseNum)%LatentEnergyCurveType = DPCubic
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(4))//'="'//TRIM(Alphas(4))//'".')
ErrorsFound=.TRUE.
END IF
RefrigCase(CaseNum)%LatCapCurvePtr = GetCurveIndex(Alphas(5)) ! convert curve name to number
IF (RefrigCase(CaseNum)%LatCapCurvePtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(5))//' not found:'//TRIM(Alphas(5)))
ErrorsFound = .TRUE.
END IF
IF(.NOT. SameString(GetCurveType(RefrigCase(CaseNum)%LatCapCurvePtr),'CUBIC')) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(5))//' object must be of type Cubic.')
ErrorsFound = .TRUE.
END IF
NumNum = 8
IF (.NOT. lNumericBlanks(NumNum)) THEN
RefrigCase(CaseNum)%STDFanPower = Numbers(NumNum)
IF(Numbers(NumNum) < 0.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be greater than or equal to 0 W/m')
ErrorsFound = .TRUE.
END IF
ELSE !blank use default of 75 W/m
RefrigCase(CaseNum)%STDFanPower = 75.d0
END IF ! blank input
NumNum = 9
IF (.NOT. lNumericBlanks(NumNum)) THEN
RefrigCase(CaseNum)%OperatingFanPower = Numbers(NumNum)
IF(Numbers(NumNum) < 0.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be greater than or equal to 0 W/m')
ErrorsFound = .TRUE.
END IF
ELSE ! if blank set = to std fan power
RefrigCase(CaseNum)%OperatingFanPower = RefrigCase(CaseNum)%STDFanPower
END IF ! if blank
NumNum = 10
IF (.NOT. lNumericBlanks(NumNum)) THEN
RefrigCase(CaseNum)%RatedLightingPower = Numbers(NumNum)
IF(Numbers(NumNum) < 0.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be greater than or equal to 0 W/m')
ErrorsFound = .TRUE.
END IF
ELSE !blank input - use default of 90 W/m
RefrigCase(CaseNum)%RatedLightingPower = 90.d0
END IF ! blank input
NumNum = 11
IF (.NOT. lNumericBlanks(NumNum)) THEN
RefrigCase(CaseNum)%LightingPower = Numbers(NumNum)
IF(Numbers(NumNum) < 0.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be greater than or equal to 0 W/m')
ErrorsFound = .TRUE.
END IF
ELSE ! blank input so set lighting power equal to rated/std lighting power
RefrigCase(CaseNum)%LightingPower = RefrigCase(CaseNum)%RatedLightingPower
END IF ! blank input
IF (.NOT. lAlphaBlanks(6)) THEN
RefrigCase(CaseNum)%LightingSchedPtr = GetScheduleIndex(Alphas(6)) ! convert schedule name to pointer
IF (RefrigCase(CaseNum)%LightingSchedPtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(6))//' not found: '//TRIM(Alphas(6)))
ErrorsFound=.TRUE.
END IF ! ptr == 0
ELSE ! no schedule specified
RefrigCase(CaseNum)%LightingSchedPtr = AlwaysOn
END IF ! not blank
! check lighting schedule for values between 0 and 1
IF (RefrigCase(CaseNum)%LightingSchedPtr > 0)THEN
IF (.NOT. CheckScheduleValueMinMax(RefrigCase(CaseNum)%LightingSchedPtr,'>=',0.0d0,'<=',1.0d0)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//'"')
CALL ShowContinueError('Error found in '//TRIM(cAlphaFieldNames(6))//' = '//TRIM(Alphas(6)))
CALL ShowContinueError('schedule values must be (>=0., <=1.)')
ErrorsFound=.true.
END IF
END IF
NumNum = 12
RefrigCase(CaseNum)%LightingFractionToCase = 1.d0 !default value
IF (.NOT. lNumericBlanks(NumNum)) THEN
RefrigCase(CaseNum)%LightingFractionToCase = Numbers(NumNum)
END IF ! blank input lighting fraction to case
! check lighting fraction to case input
IF (RefrigCase(CaseNum)%LightingFractionToCase < 0.0d0 .OR. &
RefrigCase(CaseNum)%LightingFractionToCase > 1.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' has a value outside the valid range')
CALL ShowContinueError(' Minimum should be >= 0.0 and Maximum should be <= 1.0')
ErrorsFound=.TRUE.
END IF
NumNum = 13
RefrigCase(CaseNum)%AntiSweatPower = Numbers(NumNum)
IF(Numbers(NumNum) < 0.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be greater than or equal to 0 W/m')
ErrorsFound = .TRUE.
END IF
NumNum = 14
RefrigCase(CaseNum)%MinimumASPower = Numbers(NumNum)
IF(Numbers(NumNum) < 0.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be greater than or equal to 0 W/m')
ErrorsFound = .TRUE.
END IF
IF (SameString(Alphas(7),'None')) THEN
RefrigCase(CaseNum)%AntiSweatControlType = ASNone
RefrigCase(CaseNum)%AntiSweatPower = 0.0d0
ELSEIF (SameString(Alphas(7),'Constant')) THEN
RefrigCase(CaseNum)%AntiSweatControlType = ASConstant
ELSEIF (SameString(Alphas(7),'Linear')) THEN
RefrigCase(CaseNum)%AntiSweatControlType = ASLinear
ELSEIF (SameString(Alphas(7),'DewpointMethod')) THEN
RefrigCase(CaseNum)%AntiSweatControlType = ASDewPoint
ELSEIF (SameString(Alphas(7),'HeatBalanceMethod')) THEN
RefrigCase(CaseNum)%AntiSweatControlType = ASHeatBalance
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(7))//'="'//TRIM(Alphas(7))//'".')
ErrorsFound=.TRUE.
END IF
! Assure that case temperature is below the rated dew point when anti-sweat heater control type is dew point method
IF(RefrigCase(CaseNum)%Temperature >= RefrigCase(CaseNum)%RatedAmbientDewPoint .AND. &
RefrigCase(CaseNum)%AntiSweatControlType == ASDewPoint) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", '//TRIM(cNumericFieldNames(7))//' must be below the Rated Ambient Dew Point when '//&
TRIM(cAlphaFieldNames(7))//' is Dew Point Method')
ErrorsFound=.TRUE.
END IF
NumNum = 15
! negative values for minimum humidity are allowed
RefrigCase(CaseNum)%HumAtZeroAS = Numbers(NumNum)
! check minimum humidity when linear AS control type is used
IF (RefrigCase(CaseNum)%HumAtZeroAS >= &
RefrigCase(CaseNum)%RatedAmbientRH .AND. &
RefrigCase(CaseNum)%AntiSweatControlType == ASLinear) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be less than '//TRIM(cNumericFieldNames(2)))
CALL ShowContinueError(' for Linear '//TRIM(cAlphaFieldNames(7))//'.')
ErrorsFound=.TRUE.
END IF
NumNum = 16
RefrigCase(CaseNum)%Height = Numbers(NumNum)
IF(Numbers(NumNum) < 0.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be greater than or equal to 0 m')
ErrorsFound = .TRUE.
END IF
IF (RefrigCase(CaseNum)%Height <= 0.0d0 .AND. &
RefrigCase(CaseNum)%AntiSweatControlType == ASHeatBalance) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be greater than 0 when '//TRIM(cAlphaFieldNames(7))// &
' is Heat Balance Method.')
CALL ShowContinueError('..given '//TRIM(cNumericFieldNames(NumNum))//' was: '//&
TRIM(RoundSigDigits(RefrigCase(CaseNum)%Height,3)))
ErrorsFound=.TRUE.
END IF
! initialize case resistance for anti-sweat heater control type = Heat Balance Method
IF(RefrigCase(CaseNum)%AntiSweatControlType == ASHeatBalance) THEN
IF(RefrigCase(CaseNum)%Height == 0.0d0) THEN
Rcase = 0.0d0
ELSE
RcaseDenom = ((RefrigCase(CaseNum)%AntiSweatPower / &
RefrigCase(CaseNum)%Height) - &
(RefrigCase(CaseNum)%RatedAmbientDewPoint- &
RefrigCase(CaseNum)%RatedAmbientTemp)/Rair)
Rcase = (RefrigCase(CaseNum)%RatedAmbientDewPoint - &
RefrigCase(CaseNum)%Temperature) / RcaseDenom
END IF
RefrigCase(CaseNum)%Rcase = MAX(0.0d0,Rcase)
IF(RefrigCase(CaseNum)%Rcase == 0.0d0) THEN
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'" A case thermal resistance of 0 was calculated for anti-sweat heater performance using the')
CALL ShowContinueError(' Heat Balance Method control type. Anti-sweat heater performance cannot be calculated '// &
'and '//TRIM(cAlphaFieldNames(7))//' will be set to None and simulation continues.')
CALL ShowContinueError(' See Engineering Documentation for anti-sweat heater control of refrigerated cases.')
END IF
END IF
NumNum = 17
RefrigCase(CaseNum)%ASHeaterFractionToCase = Numbers(NumNum)
IF(Numbers(NumNum) < 0.0d0 .OR. Numbers(NumNum) > 1.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be >= 0 and <= 1')
ErrorsFound = .TRUE.
END IF
IF (SameString(Alphas(8),'None')) THEN
RefrigCase(CaseNum)%DefrostType = DefNone
ELSEIF (SameString(Alphas(8),'OffCycle')) THEN
RefrigCase(CaseNum)%DefrostType = DefOffCycle
ELSEIF ((SameString(Alphas(8),'HotFluid')) .OR. &
(SameString(Alphas(8),'HotGas' ))) THEN
RefrigCase(CaseNum)%DefrostType = DefHotFluid
ELSEIF ((SameString(Alphas(8),'HotFluidWithTemperatureTermination')) .OR. &
(SameString(Alphas(8),'HotGasWithTemperatureTermination' ))) THEN
RefrigCase(CaseNum)%DefrostType = DefHotFluidTerm
! ELSEIF (SameString(Alphas(8),'Hot-Fluid On Demand')) THEN
! RefrigCase(CaseNum)%DefrostType = DefHotFluidOnDemand
ELSEIF (SameString(Alphas(8),'Electric')) THEN
RefrigCase(CaseNum)%DefrostType = DefElectric
ELSEIF (SameString(Alphas(8),'ElectricWithTemperatureTermination')) THEN
RefrigCase(CaseNum)%DefrostType = DefElectricTerm
! ELSEIF (SameString(Alphas(8),'Electric On Demand')) THEN
! RefrigCase(CaseNum)%DefrostType = DefElectricOnDemand
ELSE
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(8))//'="'//TRIM(Alphas(8))//'".')
CALL ShowContinueError('Simulation will default to '//TRIM(cAlphaFieldNames(8))//'="None" and continue.')
RefrigCase(CaseNum)%DefrostType = DefNone
END IF
DefType = RefrigCase(CaseNum)%DefrostType
NumNum = 18
IF (.NOT. lNumericBlanks(NumNum)) THEN
RefrigCase(CaseNum)%DefrostPower = Numbers(NumNum)
IF(Numbers(NumNum) < 0.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be greater than or equal to 0 W/m')
ErrorsFound = .TRUE.
END IF
! disregard defrost power for Off-Cycle or None defrost types
IF((DefType==DefOffCycle .OR. DefType==DefOffCycle) .AND.(RefrigCase(CaseNum)%DefrostPower > 0.0d0)) THEN
RefrigCase(CaseNum)%DefrostPower=0.0d0
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' for '//TRIM(cAlphaFieldNames(8))// &
' None or Off-Cycle will be set to 0 and simulation continues.')
END IF
ELSE
RefrigCase(CaseNum)%DefrostPower = 0.0d0
END IF
!defrost power needed to calculate heat gain to case even if not needed for electric consumption
IF((DefType==DefHotFluid .OR. DefType==DefHotFluidTerm .OR. &
DefType==DefElectric .OR. DefType==DefElectricTerm ) .AND. &
RefrigCase(CaseNum)%DefrostPower <= 0.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be greater than 0 W/m'//' for '//&
TRIM(cAlphaFieldNames(8))//' '//TRIM(Alphas(8)))
ErrorsFound = .TRUE.
END IF
RefrigCase(CaseNum)%DefrostSchedPtr = GetScheduleIndex(Alphas(9)) ! convert schedule name to pointer
IF (RefrigCase(CaseNum)%DefrostSchedPtr == 0 .AND. &
RefrigCase(CaseNum)%DefrostType /= DefNone) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(9))//' not found: '//TRIM(Alphas(9)))
CALL ShowContinueError('required when '//trim(cAlphaFieldNames(8))//'="'//trim(Alphas(8))//'".')
ErrorsFound=.TRUE.
END IF
! check defrost schedule for values between 0 and 1
IF (RefrigCase(CaseNum)%DefrostSchedPtr > 0)THEN
IF (.NOT. CheckScheduleValueMinMax(RefrigCase(CaseNum)%DefrostSchedPtr,'>=',0.0d0,'<=',1.0d0)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//'".')
CALL ShowContinueError('Error found in '//TRIM(cAlphaFieldNames(9))//' = '//TRIM(Alphas(9)))
CALL ShowContinueError('schedule values must be (>=0., <=1.)')
ErrorsFound=.true.
END IF
END IF
! Note that next section counting number cycles and setting maxkgfrost not used now, but may be in the future.
! count the number of defrost cycles
StartCycle = .FALSE.
NumDefCycles = 0
DayValues = 0.0d0
CALL GetScheduleValuesForDay(RefrigCase(CaseNum)%DefrostSchedPtr,DayValues,1)
DO HRNum = 1,24
DO TSNum = 1,NumOfTimeStepInHour
IF(DayValues(HRNum,TSNum) > 0.0d0) THEN
IF(.NOT. StartCycle) THEN
NumDefCycles = NumDefCycles + 1
StartCycle = .TRUE.
END IF
ELSE
StartCycle = .FALSE.
END IF
END DO
END DO
IF(NumDefCycles > 0) THEN
! calculate maximum frost formation based on defrost schedule, heat of vaporization+fusion for water = 2833.0 kJ/kg
RefrigCase(CaseNum)%MaxKgFrost = (RefrigCase(CaseNum)%RateTotCapPerLength * RefrigCase(CaseNum)%RatedLHR * &
RefrigCase(CaseNum)%RatedRTF * SecondsPerHour * HoursPerDay / 1000.0d0 / 2833.0d0) &
/(NumDefCycles)
ELSE
RefrigCase(CaseNum)%MaxKgFrost = 9999999.9d0
END IF
! some defrost types do not use drip-down schedules, use same defrost schedule pointer in that case
IF (.NOT. lAlphaBlanks(10)) THEN
RefrigCase(CaseNum)%DefrostDripDownSchedPtr = GetScheduleIndex(Alphas(10)) ! convert schedule name to pointer
IF (RefrigCase(CaseNum)%DefrostDripDownSchedPtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(10))//' not found: '//TRIM(Alphas(10)))
ErrorsFound=.TRUE.
END IF
ELSE
RefrigCase(CaseNum)%DefrostDripDownSchedPtr = RefrigCase(CaseNum)%DefrostSchedPtr
END IF
! check defrost drip-down schedule for values between 0 and 1
IF (RefrigCase(CaseNum)%DefrostDripDownSchedPtr > 0 .AND. (.NOT. lAlphaBlanks(10)))THEN
IF (.NOT. CheckScheduleValueMinMax(RefrigCase(CaseNum)%DefrostDripDownSchedPtr,'>=',0.0d0,'<=',1.0d0)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//'".')
CALL ShowContinueError('Error found in '//TRIM(cAlphaFieldNames(10))//' = '//TRIM(Alphas(10)))
CALL ShowContinueError('schedule values must be (>=0., <=1.)')
ErrorsFound=.TRUE.
END IF
END IF
IF (SameString(Alphas(11),'CaseTemperatureMethod')) THEN
RefrigCase(CaseNum)%DefrostEnergyCurveType = CaseTemperatureMethod
ELSEIF (SameString(Alphas(11),'RelativeHumidityMethod')) THEN
RefrigCase(CaseNum)%DefrostEnergyCurveType = RHCubic
ELSEIF (SameString(Alphas(11),'DewpointMethod')) THEN
RefrigCase(CaseNum)%DefrostEnergyCurveType = DPCubic
ELSEIF (SameString(Alphas(11),'None')) THEN
RefrigCase(CaseNum)%DefrostEnergyCurveType = None
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(11))//'="'//TRIM(Alphas(11))//'".')
ErrorsFound=.TRUE.
END IF
RefrigCase(CaseNum)%DefCapCurvePtr = GetCurveIndex(Alphas(12)) ! convert curve name to number
IF((RefrigCase(CaseNum)%DefrostType == DefElectricTerm .OR. &
RefrigCase(CaseNum)%DefrostType == DefHotFluidTerm) .AND. &
(RefrigCase(CaseNum)%DefCapCurvePtr == 0)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(12))//' not found:'//TRIM(Alphas(12)))
ErrorsFound = .TRUE.
END IF
IF (RefrigCase(CaseNum)%DefCapCurvePtr > 0) THEN
IF(.NOT. SameString(GetCurveType(RefrigCase(CaseNum)%DefCapCurvePtr),'CUBIC')) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(12))//' must be of type Cubic.')
ErrorsFound = .TRUE.
END IF
END IF
! warn user if defrost energy curve is entered that it is only used for temperature termination types
IF(RefrigCase(CaseNum)%DefCapCurvePtr > 0)THEN
IF( RefrigCase(CaseNum)%DefrostType /= DefElectricTerm .AND. &
RefrigCase(CaseNum)%DefrostType /= DefHotFluidTerm ) THEN
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(12))// &
' is only applicable to Defrost Temperature Termination types.')
CALL ShowContinueError(TRIM(cAlphaFieldNames(12))//' will be disregarded and simulation continues.')
END IF
END IF
NumNum = 19
RefrigCase(CaseNum)%RAFrac = Numbers(NumNum)
IF(Numbers(NumNum) < 0.0d0 .OR. Numbers(NumNum) > 1.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be >= 0 or <= 1 ')
ErrorsFound = .TRUE.
END IF
! set flag in Zone Data if RAFrac > 0
IF (RefrigCase(CaseNum)%RAFrac > 0.0d0) THEN
Zone(RefrigCase(CaseNum)%ActualZoneNum)%RefrigCaseRA = .TRUE.
END IF
! Make sure RA node exists for display cases with under case HVAC returns
IF(RefrigCase(CaseNum)%ZoneRANode == 0 .AND. &
RefrigCase(CaseNum)%RAFrac > 0.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", '//TRIM(cNumericFieldNames(18))//' not applicable to zones without return air systems.')
ErrorsFound=.TRUE.
END IF
IF(RefrigCase(CaseNum)%ActualZoneNum /= 0) THEN
CaseRAFraction(RefrigCase(CaseNum)%ActualZoneNum)%TotalCaseRAFraction = &
CaseRAFraction(RefrigCase(CaseNum)%ActualZoneNum)%TotalCaseRAFraction + &
RefrigCase(CaseNum)%RAFrac
CaseRAFraction(RefrigCase(CaseNum)%ActualZoneNum)%ZoneName = &
RefrigCase(CaseNum)%ZoneName
END IF
RefrigCase(CaseNum)%StockingSchedPtr = GetScheduleIndex(Alphas(13)) ! convert schedule name to pointer
IF (.NOT. lAlphaBlanks(13)) THEN
IF (RefrigCase(CaseNum)%StockingSchedPtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(13))//' not found: '//TRIM(Alphas(13)))
ErrorsFound=.TRUE.
END IF
ELSE
RefrigCase(CaseNum)%StockingSchedPtr = 0
END IF
! calculate sensible case load at design conditions
DesignSensibleCap = RefrigCase(CaseNum)%RateTotCapPerLength * &
(1.0d0-RefrigCase(CaseNum)%RatedLHR) * &
RefrigCase(CaseNum)%RatedRTF * &
RefrigCase(CaseNum)%Length
! calculate case heat gain = lights + fans + anti-sweat
CaseHeatGain = ((RefrigCase(CaseNum)%RatedLightingPower * &
RefrigCase(CaseNum)%LightingFractionToCase) + &
(RefrigCase(CaseNum)%AntiSweatPower * &
RefrigCase(CaseNum)%ASHeaterFractionToCase) + &
RefrigCase(CaseNum)%STDFanPower) * &
RefrigCase(CaseNum)%Length
! sensible case credits are calculated as the difference between the design sensible capacity and the case heat gain
RefrigCase(CaseNum)%DesignSensCaseCredit = DesignSensibleCap - CaseHeatGain
! compare case loads to design capacity
IF (DesignSensibleCap < CaseHeatGain) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//&
TRIM(RefrigCase(CaseNum)%Name)//'", the sum of '//&
'lighting, fan, and anti-sweat heater energy is greater than refrigerated case sensible capacity')
ErrorsFound=.TRUE.
END IF
RefrigCase(CaseNum)%CaseCreditFracSchedPtr = GetScheduleIndex(Alphas(14)) ! convert schedule name to pointer
IF (.NOT. lAlphaBlanks(14)) THEN
IF (RefrigCase(CaseNum)%CaseCreditFracSchedPtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(14))//' not found: '//TRIM(Alphas(14)))
ErrorsFound=.TRUE.
END IF
ELSE
RefrigCase(CaseNum)%CaseCreditFracSchedPtr = 0
END IF
! check case credit fraction schedule for values between 0 and 1
IF (RefrigCase(CaseNum)%CaseCreditFracSchedPtr > 0) THEN
IF (.NOT. CheckScheduleValueMinMax(RefrigCase(CaseNum)%CaseCreditFracSchedPtr,'>=',0.0d0,'<=',1.0d0)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//'".')
CALL ShowContinueError('Error found in '//TRIM(cAlphaFieldNames(14))//' = '//TRIM(Alphas(14)))
CALL ShowContinueError('schedule values must be (>=0., <=1.)')
ErrorsFound=.true.
END IF
END IF
RefrigCase(CaseNum)%DesignRatedCap = RefrigCase(CaseNum)%RateTotCapPerLength * RefrigCase(CaseNum)%Length
RefrigCase(CaseNum)%DesignLatentCap = RefrigCase(CaseNum)%DesignRatedCap * RefrigCase(CaseNum)%RatedLHR *&
RefrigCase(CaseNum)%RatedRTF
RefrigCase(CaseNum)%DesignDefrostCap= RefrigCase(CaseNum)%DefrostPower * RefrigCase(CaseNum)%Length
RefrigCase(CaseNum)%DesignLighting = RefrigCase(CaseNum)%LightingPower * RefrigCase(CaseNum)%Length
RefrigCase(CaseNum)%DesignFanPower = RefrigCase(CaseNum)%OperatingFanPower * RefrigCase(CaseNum)%Length
!Design evaporating temperature: for a DX system, saturated temperature for pressure leaving case
! : for a liquid system, liquid temperature entering case
NumNum = 20
IF (.NOT. lNumericBlanks(NumNum)) THEN
RefrigCase(CaseNum)%EvapTempDesign = Numbers(NumNum)
IF(RefrigCase(CaseNum)%EvapTempDesign >= RefrigCase(CaseNum)%Temperature) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'" '//TRIM(cNumericFieldNames(NumNum))//' must be below '//TRIM(cNumericFieldNames(7)))
ErrorsFound=.TRUE.
END IF
ELSE
RefrigCase(CaseNum)%EvapTempDesign = RefrigCase(CaseNum)%Temperature - DelEvapTDefault
! default 5C less than case operating temperature
END IF
NumNum = 21
IF (.NOT. lNumericBlanks(NumNum)) THEN
RefrigCase(Casenum)%RefrigInventory = Numbers(NumNum)
RefrigCase(Casenum)%DesignRefrigInventory =RefrigCase(Casenum)%RefrigInventory * RefrigCase(CaseNum)%Length
IF(RefrigCase(Casenum)%RefrigInventory < 0.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigCase(CaseNum)%Name)//&
'" '//TRIM(cNumericFieldNames(NumNum))//' must be a positive number.')
ErrorsFound = .TRUE.
END IF
ELSE
RefrigCase(Casenum)%RefrigInventory = 0.0d0
END IF
ENDDO !Individual refrigerated cases
END IF !(NumSimulationCases > 0 )
!************ START WALK IN COOLER INPUT **************
IF(NumSimulationWalkIns > 0 ) THEN
CurrentModuleObject='Refrigeration:WalkIn'
DO WalkInID=1,NumSimulationWalkIns
CALL GetObjectItem(CurrentModuleObject, WalkInID,Alphas,NumAlphas,Numbers,NumNumbers,IOStatus, &
NumBlank=lNumericBlanks,AlphaBlank=lAlphaBlanks, &
AlphaFieldNames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
IsNotOK =.FALSE.
IsBlank =.FALSE.
CALL VerifyName(Alphas(1), WalkIn%Name, WalkInID-1,IsNotOK,IsBlank,CurrentModuleObject//' Name')
IF (IsNotOK) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//', has an invalid or undefined name="'//&
TRIM(Alphas(1))//'".')
IF (IsBlank) Alphas(1)='xxxxx'
ErrorsFound=.TRUE.
ENDIF
WalkIn( WalkInID)%Name = Alphas(1)
IF (.NOT. lAlphaBlanks(2)) THEN
WalkIn( WalkInID)%SchedPtr = GetScheduleIndex(Alphas(2)) ! convert schedule name to pointer
IF ( WalkIn( WalkInID)%SchedPtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(2))//' not found: '//TRIM(Alphas(2)))
ErrorsFound=.TRUE.
END IF ! ptr == 0
ELSE ! no schedule specified
WalkIn( WalkInID)%SchedPtr = AlwaysOn
END IF ! not blank
! check availability schedule for values between 0 and 1
IF ( WalkIn( WalkInID)%SchedPtr > 0)THEN
IF (.NOT. CheckScheduleValueMinMax( WalkIn( WalkInID)%SchedPtr,'>=',0.0d0,'<=',1.0d0)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)//'"')
CALL ShowContinueError('Error found in '//TRIM(cAlphaFieldNames(2))//' = '//TRIM(Alphas(2)))
CALL ShowContinueError('schedule values must be (>=0., <=1.)')
ErrorsFound=.TRUE.
END IF
END IF
WalkIn(WalkInID)%DesignRatedCap = Numbers(1)
IF(Numbers(1) <= 0.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)//&
'", '//TRIM(cNumericFieldNames(1))//' must be greater than 0 W')
ErrorsFound = .TRUE.
END IF
IF (.NOT. lNumericBlanks(2))THEN
WalkIn( WalkInID)%Temperature = Numbers(2)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)//&
'", '//TRIM(cNumericFieldNames(2))//' must be input ')
ErrorsFound=.TRUE.
END IF
IF (.NOT. lNumericBlanks(3))THEN
WalkIn( WalkInID)%TEvapDesign = Numbers(3)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)//&
'", '//TRIM(cNumericFieldNames(3))//' must be input')
ErrorsFound=.TRUE.
END IF
IF (.NOT. lNumericBlanks(4))THEN
WalkIn( WalkInID)%HeaterPower = Numbers(4)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)//&
'", '//TRIM(cNumericFieldNames(4))//' must be input ')
ErrorsFound=.TRUE.
END IF
AlphaNum=3
IF (.NOT. lAlphaBlanks(AlphaNum)) THEN
WalkIn( WalkInID)%HeaterSchedPtr = GetScheduleIndex(Alphas(AlphaNum)) ! convert heater schedule name to pointer
IF ( WalkIn( WalkInID)%HeaterSchedPtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//' not found: '//TRIM(Alphas(AlphaNum)))
ErrorsFound=.TRUE.
END IF ! ptr == 0
ELSE ! no schedule specified
WalkIn( WalkInID)%HeaterSchedPtr = AlwaysOn
END IF ! not blank
! check heater schedule for values between 0 and 1
IF ( WalkIn( WalkInID)%HeaterSchedPtr > 0)THEN
IF (.NOT. CheckScheduleValueMinMax( WalkIn( WalkInID)%HeaterSchedPtr,'>=',0.0d0,'<=',1.0d0)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)//'"')
CALL ShowContinueError('Error found in '//TRIM(cAlphaFieldNames(AlphaNum))//' = '//TRIM(Alphas(AlphaNum)))
CALL ShowContinueError('schedule values must be (>=0., <=1.)')
ErrorsFound=.TRUE.
END IF
END IF
IF (.NOT. lNumericBlanks(5) .AND. Numbers(5) > 0.d0)THEN
WalkIn( WalkInID)%CoilFanPower = Numbers(5)
ELSE
CALL ShowWarningError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)//&
'", '//TRIM(cNumericFieldNames(5))//' was not input or was less than 0 and default of 375.0 W will be used ')
WalkIn( WalkInID)%CoilFanPower = 375.d0 !default value = 1/2 hp
END IF
IF (lNumericBlanks(6))THEN
WalkIn( WalkInID)%CircFanPower = 0.0d0
ELSE
WalkIn( WalkInID)%CircFanPower = Numbers(6)
IF(Numbers(7) < 0.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)//&
'", '//TRIM(cNumericFieldNames(6))//' must be greater than >= 0 W')
ErrorsFound = .TRUE.
END IF
END IF
IF (.NOT. lNumericBlanks(7))THEN
WalkIn( WalkInID)%DesignLighting = Numbers(7)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)//&
'" '//TRIM(cNumericFieldNames(7))//' must be input ')
ErrorsFound=.TRUE.
END IF
AlphaNum=4
IF (.NOT. lAlphaBlanks(AlphaNum)) THEN
WalkIn( WalkInID)%LightingSchedPtr = GetScheduleIndex(Alphas(AlphaNum)) ! convert lighting schedule name to pointer
IF ( WalkIn( WalkInID)%LightingSchedPtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//' not found: '//TRIM(Alphas(AlphaNum)))
ErrorsFound=.TRUE.
END IF ! ptr == 0
ELSE ! no schedule specified
WalkIn( WalkInID)%LightingSchedPtr = AlwaysOn
END IF ! schedule name not blank
! check Lighting schedule for values between 0 and 1
IF ( WalkIn( WalkInID)%LightingSchedPtr > 0)THEN
IF (.NOT. CheckScheduleValueMinMax( WalkIn( WalkInID)%LightingSchedPtr,'>=',0.0d0,'<=',1.0d0)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)//'"')
CALL ShowContinueError('Error found in '//TRIM(cAlphaFieldNames(AlphaNum))//' = '//TRIM(Alphas(AlphaNum)))
CALL ShowContinueError('schedule values must be (>=0., <=1.)')
ErrorsFound=.TRUE.
END IF
END IF
!Input walk-in cooler defrost information
AlphaNum=5
IF(lAlphaBlanks(AlphaNum)) THEN
WalkIn( WalkInID)%DefrostType = WalkInDefrostElec
ELSEIF (SameString(Alphas(AlphaNum),'Electric')) THEN
WalkIn( WalkInID)%DefrostType = WalkInDefrostElec
ELSEIF (SameString(Alphas(AlphaNum),'HotFluid')) THEN
WalkIn( WalkInID)%DefrostType = WalkInDefrostFluid
ELSEIF (SameString(Alphas(AlphaNum),'None')) THEN
WalkIn( WalkInID)%DefrostType = WalkInDefrostNone
ELSEIF (SameString(Alphas(AlphaNum),'OffCycle')) THEN
WalkIn( WalkInID)%DefrostType = WalkInDefrostOffCycle
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//'="'//TRIM(Alphas(AlphaNum))//'".')
ErrorsFound=.TRUE.
END IF
AlphaNum=6
IF(lAlphaBlanks(AlphaNum)) THEN
WalkIn( WalkInID)%DefrostControlType = DefrostControlSched
ELSEIF (SameString(Alphas(AlphaNum),'TimeSchedule'))THEN
WalkIn( WalkInID)%DefrostControlType = DefrostControlSched
ELSEIF (SameString(Alphas(AlphaNum),'TemperatureTermination')) THEN
WalkIn( WalkInID)%DefrostControlType = DefrostContTempTerm
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//' not found: '//TRIM(Alphas(AlphaNum)))
ErrorsFound=.TRUE.
END IF ! defrost control type
! convert defrost schedule name to pointer
AlphaNum=7
WalkIn( WalkInID)%DefrostSchedPtr = GetScheduleIndex(Alphas(AlphaNum))
IF ( WalkIn( WalkInID)%DefrostSchedPtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//' not found: '//TRIM(Alphas(AlphaNum)))
ErrorsFound=.TRUE.
END IF
! check defrost schedule for values between 0 and 1
IF ( WalkIn( WalkInID)%DefrostSchedPtr > 0)THEN
IF (.NOT. CheckScheduleValueMinMax( WalkIn( WalkInID)%DefrostSchedPtr,'>=',0.0d0,'<=',1.0d0)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//' = "'//TRIM( WalkIn( WalkInID)%Name)//'"')
CALL ShowContinueError('Error found in '//TRIM(cAlphaFieldNames(AlphaNum))//'='//TRIM(Alphas(AlphaNum)))
CALL ShowContinueError('schedule values must be (>=0., <=1.)')
ErrorsFound=.TRUE.
END IF
END IF
! convert defrost drip-down schedule name to pointer
! some defrost types do not use drip-down schedules, use same defrost schedule pointer in that case
AlphaNum=8
IF (.NOT. lAlphaBlanks(AlphaNum)) THEN
WalkIn( WalkInID)%DefrostDripDownSchedPtr = GetScheduleIndex(Alphas(AlphaNum))
IF ( WalkIn( WalkInID)%DefrostDripDownSchedPtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(WalkIn( WalkInID)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//' not found: '//TRIM(Alphas(AlphaNum)))
ErrorsFound=.TRUE.
END IF
! check schedule for values between 0 and 1
IF ( WalkIn( WalkInID)%DefrostDripDownSchedPtr > 0)THEN
IF (.NOT. CheckScheduleValueMinMax( WalkIn( WalkInID)%DefrostDripDownSchedPtr,'>=',0.0d0,'<=',1.0d0)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)//'"')
CALL ShowContinueError('Error found in '//TRIM(cAlphaFieldNames(AlphaNum))//' = '//TRIM(Alphas(AlphaNum)))
CALL ShowContinueError('schedule values must be (>=0., <=1.)')
ErrorsFound=.TRUE.
END IF
END IF
ELSE !blank input so use drip down schedule for defrost
WalkIn( WalkInID)%DefrostDripDownSchedPtr = WalkIn( WalkInID)%DefrostSchedPtr
END IF
IF (WalkIn( WalkInID)%DefrostType == WalkInDefrostOffCycle .OR. &
WalkIn( WalkInID)%DefrostType == WalkInDefrostNone) THEN
WalkIn( WalkInID)%DefrostCapacity = 0.d0
!Don't even need to read N8 or N9 for those two defrost types.
ELSE !have electric or hot gas/brine defrost
IF ((lNumericBlanks(8)) .OR. (Numbers(8) <= 0.0d0))THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)//&
'", '//TRIM(cNumericFieldNames(8))//' must be input and greater than or equal to 0 W'//' for '//&
TRIM(cAlphaFieldNames(5))//' '//TRIM(Alphas(5)))
ErrorsFound = .TRUE.
ELSE
WalkIn( WalkInID)%DefrostCapacity = Numbers(8)
END IF !Blank or negative N8
!defaults for defrost energy fraction are 0.7 for elec defrost and 0.3 for warm fluid
!note this value is only used for temperature terminated defrost control type
IF (WalkIn( WalkInID)%DefrostType == WalkInDefrostElec) WalkIn(WalkInID)%DefEnergyFraction = 0.7d0
IF (WalkIn( WalkInID)%DefrostType == WalkInDefrostFluid) WalkIn(WalkInID)%DefEnergyFraction = 0.3d0
IF (.NOT. lNumericBlanks (9)) THEN
IF ((Numbers(9) > 1.0d0) .OR. (Numbers(9) < 0.0d0))THEN
CALL ShowWarningError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(WalkIn( WalkInID)%Name)//&
'", '//TRIM(cNumericFieldNames(9))//' must be between 0 and 1, default values will be used.')
ELSE
WalkIn(WalkInID)%DefEnergyFraction = Numbers(9)
END IF ! number out of range
END IF !lnumericblanks
END IF ! defrost type
! convert restocking schedule name to pointer, default of 0.1 is assigned inside walkin subroutine if blank
AlphaNum=9
IF (lAlphaBlanks(AlphaNum)) THEN
WalkIn( WalkInID)%StockingSchedPtr = 0
ELSE
WalkIn( WalkInID)%StockingSchedPtr = GetScheduleIndex(Alphas(AlphaNum))
IF ( WalkIn( WalkInID)%StockingSchedPtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(WalkIn( WalkInID)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//' not found: '//TRIM(Alphas(AlphaNum)))
ErrorsFound=.TRUE.
END IF
END IF !blank
WalkIn( WalkInID)%DesignRefrigInventory = 0.0d0
IF (.NOT. lNumericBlanks(10)) WalkIn( WalkInID)%DesignRefrigInventory = Numbers(10)
IF (.NOT. lNumericBlanks(11))THEN
WalkIn(WalkInID)%FloorArea = Numbers(11)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(WalkIn( WalkInID)%Name)//&
'", '//TRIM(cNumericFieldNames(11))//' must be input' )
ErrorsFound=.TRUE.
END IF
IF (lNumericBlanks(12))THEN
WalkIn( WalkInID)%FloorUValue = DefaultWISurfaceUValue
ELSE
WalkIn( WalkInID)%FloorUValue = Numbers(12)
IF(Numbers(12) <= 0.d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)//&
'", '//TRIM(cNumericFieldNames(12))//' must be > 0.')
ErrorsFound=.TRUE.
END IF
END IF
!Calculate the number of zones exposed to walk-in based on number of input fields, all integer math,
! This approach used because last zone could have less than NumWIFieldsPerZone due to optional values
TotFields = NumNumbers + NumAlphas
NumWIFieldsPerZone = NumWIAlphaFieldsPerZone + NumWINumberFieldsPerZone
NumWIFieldsTotal = TotFields - NumWIAlphaFieldsBeforeZoneInput - NumWINumberfieldsBeforeZoneInput
NumZones = 1
IF (NumWIFieldsTotal > NumWIFieldsPerZone) NumZones = 2
IF (NumWIFieldsTotal > (2 * NumWIFieldsPerZone)) NumZones = 3
IF (NumWIFieldsTotal > (3 * NumWIFieldsPerZone)) NumZones = 4
IF (NumWIFieldsTotal > (4 * NumWIFieldsPerZone)) NumZones = 5
IF (NumWIFieldsTotal > (5 * NumWIFieldsPerZone)) NumZones = 6
WalkIn(WalkInID)%NumZones = NumZones
! All variables for walk-in/zone interactions need to be allocated after know number of zones
IF(.NOT. ALLOCATED(WalkIn( WalkInID)%ZoneName))ALLOCATE(WalkIn( WalkInID)%ZoneName(NumZones))
IF(.NOT. ALLOCATED(WalkIn( WalkInID)%ZoneNum))ALLOCATE(WalkIn( WalkInID)%ZoneNum(NumZones))
IF(.NOT. ALLOCATED(WalkIn( WalkInID)%ZoneNodeNum))ALLOCATE(WalkIn( WalkInID)%ZoneNodeNum(NumZones))
IF(.NOT. ALLOCATED(WalkIn( WalkInID)%SurfaceArea))ALLOCATE(WalkIn( WalkInID)%SurfaceArea(NumZones))
IF(.NOT. ALLOCATED(WalkIn( WalkInID)%UValue))ALLOCATE(WalkIn( WalkInID)%UValue(NumZones))
IF(.NOT. ALLOCATED(WalkIn( WalkInID)%UValueGlassDr))ALLOCATE(WalkIn( WalkInID)%UValueGlassDr(NumZones))
IF(.NOT. ALLOCATED(WalkIn( WalkInID)%GlassDoorOpenSchedPtr))ALLOCATE(WalkIn( WalkInID)%GlassDoorOpenSchedPtr(NumZones))
IF(.NOT. ALLOCATED(WalkIn( WalkInID)%AreaGlassDr))ALLOCATE(WalkIn( WalkInID)%AreaGlassDr(NumZones))
IF(.NOT. ALLOCATED(WalkIn( WalkInID)%HeightGlassDr))ALLOCATE(WalkIn( WalkInID)%HeightGlassDr(NumZones))
IF(.NOT. ALLOCATED(WalkIn( WalkInID)%UValueStockDr))ALLOCATE(WalkIn( WalkInID)%UValueStockDr(NumZones))
IF(.NOT. ALLOCATED(WalkIn( WalkInID)%StockDoorOpenSchedPtr))ALLOCATE(WalkIn( WalkInID)%StockDoorOpenSchedPtr(NumZones))
IF(.NOT. ALLOCATED(WalkIn( WalkInID)%StockDoorProtectType))ALLOCATE(WalkIn( WalkInID)%StockDoorProtectType(NumZones))
IF(.NOT. ALLOCATED(WalkIn( WalkInID)%AreaStockDr))ALLOCATE(WalkIn( WalkInID)%AreaStockDr(NumZones))
IF(.NOT. ALLOCATED(WalkIn( WalkInID)%HeightStockDr))ALLOCATE(WalkIn( WalkInID)%HeightStockDr(NumZones))
IF(.NOT. ALLOCATED(WalkIn( WalkInID)%SensZoneCreditRate))ALLOCATE(WalkIn( WalkInID)%SensZoneCreditRate(NumZones))
IF(.NOT. ALLOCATED(WalkIn( WalkInID)%SensZoneCreditCoolRate))ALLOCATE(WalkIn( WalkInID)%SensZoneCreditCoolRate(NumZones))
IF(.NOT. ALLOCATED(WalkIn( WalkInID)%SensZoneCreditCool))ALLOCATE(WalkIn( WalkInID)%SensZoneCreditCool(NumZones))
IF(.NOT. ALLOCATED(WalkIn( WalkInID)%SensZoneCreditHeatRate))ALLOCATE(WalkIn( WalkInID)%SensZoneCreditHeatRate(NumZones))
IF(.NOT. ALLOCATED(WalkIn( WalkInID)%SensZoneCreditHeat))ALLOCATE(WalkIn( WalkInID)%SensZoneCreditHeat(NumZones))
IF(.NOT. ALLOCATED(WalkIn( WalkInID)%LatZoneCreditRate))ALLOCATE(WalkIn( WalkInID)%LatZoneCreditRate(NumZones))
IF(.NOT. ALLOCATED(WalkIn( WalkInID)%LatZoneCredit))ALLOCATE(WalkIn( WalkInID)%LatZoneCredit(NumZones))
AStart = NumWIAlphaFieldsBeforeZoneInput +1
NStart = NumWINumberFieldsBeforeZoneInput +1
DO ZoneID = 1,NumZones
!Get the Zone node number from the zone name
!The Zone Node is needed to get the zone's ambient conditions, NumOfZones from dataglobals
WalkIn( WalkInID)%ZoneName(ZoneID)= Alphas(AStart)
WalkIn( WalkInID)%ZoneNum(ZoneID) = FindItemInList(Alphas(AStart),Zone%Name,NumOfZones)
IF ( WalkIn( WalkInID)%ZoneNum(ZoneID) == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)// &
'", invalid '//TRIM(cAlphaFieldNames(AStart))//' not valid: '//TRIM(Alphas(AStart)))
ErrorsFound=.TRUE.
ELSE
RefrigPresentInZone(WalkIn( WalkInID)%ZoneNum(ZoneID)) = .TRUE.
ENDIF
WalkIn( WalkInID)%ZoneNodeNum(ZoneID) = &
GetSystemNodeNumberForZone( WalkIn( WalkInID)%ZoneName(ZoneID))
IF ( WalkIn( WalkInID)%ZoneNum(ZoneID) >= 0) THEN
IF ( WalkIn( WalkInID)%ZoneNodeNum(ZoneID) == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)// &
'" System Node Number not found for '//TRIM(cAlphaFieldNames(AStart))// &
' = '//TRIM(Alphas(AStart)))
CALL ShowContinueError('.. Walk Ins must reference a controlled Zone (appear'// &
' in a ZoneHVAC:EquipmentConnections object.')
ErrorsFound=.TRUE.
ENDIF
ENDIF
IF (.NOT. lNumericBlanks(NStart))THEN
WalkIn( WalkInID)%SurfaceArea(ZoneID) = Numbers(NStart)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)//&
'", '//TRIM(cNumericFieldNames(NStart))//' must be input for Zone: ' &
//TRIM( WalkIn( WalkInID)%ZoneName(ZoneID)))
ErrorsFound=.TRUE.
END IF
IF (lNumericBlanks(NStart+1))THEN
WalkIn( WalkInID)%UValue(ZoneID) = DefaultWISurfaceUValue
ELSE
WalkIn( WalkInID)%UValue(ZoneID) = Numbers(NStart+1)
IF(Numbers(Nstart + 1) <= 0.d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)//&
'", Zone="'//TRIM( WalkIn( WalkInID)%ZoneName(ZoneID))//'", '//&
TRIM(cNumericFieldNames(NStart+1))//' must be > 0.')
ErrorsFound=.TRUE.
END IF
END IF
!start IF set for glass doors in this zone
WalkIn( WalkInID)%AreaGlassDr(ZoneID) = 0.0d0
WalkIn( WalkInID)%HeightGlassDr(ZoneID) = 0.0d0
WalkIn( WalkInID)%UValueGlassDr(ZoneID) = 0.0d0
IF (.NOT. lNumericBlanks(NStart+2))THEN
WalkIn( WalkInID)%AreaGlassDr(ZoneID) = Numbers(NStart+2)
WalkIn( WalkInID)%HeightGlassDr(ZoneID) = DefaultWIHeightGlassDr
IF (.NOT. lNumericBlanks(NStart+3)) WalkIn( WalkInID)%HeightGlassDr(ZoneID) = Numbers(NStart+3)
WalkIn( WalkInID)%UValueGlassDr(ZoneID) = DefaultWIUValueGlassDr
IF (.NOT. lNumericBlanks(NStart+4))WalkIn( WalkInID)%UValueGlassDr(ZoneID) = Numbers(NStart+4)
! convert door opening schedule name to pointer, default of 0.1 is assigned inside walkin subroutine if blank
IF (lAlphaBlanks(AStart + 1)) THEN
WalkIn( WalkInID)%GlassDoorOpenSchedPtr(ZoneID) = 0
ELSE
WalkIn( WalkInID)%GlassDoorOpenSchedPtr(ZoneID) = GetScheduleIndex(Alphas(AStart + 1))
IF ( WalkIn( WalkInID)%GlassDoorOpenSchedPtr(ZoneID) == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(WalkIn( WalkInID)%Name)//&
'", Zone="'//TRIM( WalkIn( WalkInID)%ZoneName(ZoneID))// &
'", invalid '//TRIM(cAlphaFieldNames(AStart + 1))//' not found: '//TRIM(Alphas(AStart + 1)))
ErrorsFound=.TRUE.
ELSE
! check schedule for values between 0 and 1
IF (.NOT. CheckScheduleValueMinMax( WalkIn( WalkInID)%GlassDoorOpenSchedPtr(ZoneID),'>=',0.0d0,'<=',1.0d0)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(WalkIn( WalkInID)%Name)//&
'", Zone="'//TRIM( WalkIn( WalkInID)%ZoneName(ZoneID))//'"')
CALL ShowContinueError('Error found in '//TRIM(cAlphaFieldNames(AStart + 1))// &
' = '//TRIM(Alphas(AStart + 1)))
CALL ShowContinueError('schedule values must be (>=0., <=1.)')
ErrorsFound=.TRUE.
END IF !schedule values outside range
END IF ! have schedule pointer
END IF !blank on door opening schedule (AStart + 1)
END IF ! have glassdoor area facing zone (blank on lNumericBlanks(NStart+2))
!start IF set for stock doors in this zone
WalkIn( WalkInID)%AreaStockDr(ZoneID) = 0.0d0
WalkIn( WalkInID)%HeightStockDr(ZoneID) = 0.0d0
WalkIn( WalkInID)%UValueStockDr(ZoneID) = 0.0d0
IF (.NOT. lNumericBlanks(NStart+5))THEN
WalkIn( WalkInID)%AreaStockDr(ZoneID) = Numbers(NStart+5)
WalkIn( WalkInID)%HeightStockDr(ZoneID) = DefaultWIHeightStockDr
IF (.NOT. lNumericBlanks(NStart+6)) WalkIn( WalkInID)%HeightStockDr(ZoneID) = Numbers(NStart+6)
WalkIn( WalkInID)%UValueStockDr(ZoneID) = DefaultWIUValueStockDr
IF (.NOT. lNumericBlanks(NStart+7)) WalkIn( WalkInID)%UValueStockDr(ZoneID) = Numbers(NStart+7)
! convert door opening schedule name to pointer, default of 0.1 is assigned inside walkin subroutine if blank
IF (lAlphaBlanks(AStart + 2)) THEN
WalkIn( WalkInID)%StockDoorOpenSchedPtr(ZoneID) = 0
ELSE
WalkIn( WalkInID)%StockDoorOpenSchedPtr(ZoneID) = GetScheduleIndex(Alphas(AStart + 2))
IF ( WalkIn( WalkInID)%StockDoorOpenSchedPtr(ZoneID) == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)//&
'", Zone="'//TRIM( WalkIn( WalkInID)%ZoneName(ZoneID))// &
'", invalid '//TRIM(cAlphaFieldNames(AStart + 2))//' not found: '//TRIM(Alphas(AStart + 2)))
ErrorsFound=.TRUE.
ELSE
! check schedule for values between 0 and 1
IF (.NOT. CheckScheduleValueMinMax( WalkIn( WalkInID)%StockDoorOpenSchedPtr(ZoneID),'>=',0.0d0,'<=',1.0d0)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)//&
'", Zone="'//TRIM( WalkIn( WalkInID)%ZoneName(ZoneID))//'"')
CALL ShowContinueError('Error found in '//TRIM(cAlphaFieldNames(AStart + 2))// &
' = '//TRIM(Alphas(AStart + 2)))
CALL ShowContinueError('schedule values must be (>=0., <=1.)')
ErrorsFound=.TRUE.
END IF !schedule values outside range
END IF ! have schedule pointer
END IF !blank on door opening schedule (AStart + 2)
IF(lAlphaBlanks(AStart + 3)) THEN
!default air curtain
WalkIn( WalkInID)%StockDoorProtectType(ZoneID) = WIStockDoorAirCurtain
ELSEIF (SameString(Alphas(AStart + 3),'None')) THEN
WalkIn( WalkInID)%StockDoorProtectType(ZoneID) = WIStockDoorNone
ELSEIF (SameString(Alphas(AStart + 3),'AirCurtain')) THEN
WalkIn( WalkInID)%StockDoorProtectType(ZoneID) = WIStockDoorAirCurtain
ELSEIF (SameString(Alphas(AStart + 3),'StripCurtain')) THEN
WalkIn( WalkInID)%StockDoorProtectType(ZoneID) = WIStockDoorStripCurtain
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WalkIn( WalkInID)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AStart + 3))//'="'//TRIM(Alphas(AStart + 3))//'".')
ErrorsFound=.TRUE.
END IF !stock door protection (AStart + 3) blank
END IF ! have Stockdoor area facing zone
AStart = AStart + NumWIAlphaFieldsPerZone
NStart = NStart + NumWINumberFieldsPerZone
END DO !Zones for Walk Ins
END DO !Individual Walk Ins
END IF !(NumSimulationWalkIns > 0 )
!************* Start Indiv Refrig Air Chillers
IF(NumSimulationRefrigAirChillers > 0 ) THEN
CurrentModuleObject='Refrigeration:AirChiller'
DO CoilID=1,NumSimulationRefrigAirChillers
!A1
AlphaNum = 1
CALL GetObjectItem(CurrentModuleObject, CoilID,Alphas,NumAlphas,Numbers,NumNumbers,IOStatus, &
NumBlank=lNumericBlanks,AlphaBlank=lAlphaBlanks, &
AlphaFieldNames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
IsNotOK =.FALSE.
IsBlank =.FALSE.
CALL VerifyName(Alphas(AlphaNum), WarehouseCoil%Name, CoilID-1,IsNotOK,IsBlank,CurrentModuleObject//' Name')
IF (IsNotOK) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//', has an invalid or undefined name="'//&
TRIM(Alphas(AlphaNum))//'".')
IF (IsBlank) Alphas(AlphaNum)='xxxxx'
ErrorsFound=.TRUE.
ENDIF
WarehouseCoil(CoilID)%Name = Alphas(AlphaNum)
!A2
AlphaNum = AlphaNum + 1
IF (.NOT. lAlphaBlanks(AlphaNum)) THEN
WarehouseCoil(CoilID)%SchedPtr = GetScheduleIndex(Alphas(AlphaNum)) ! convert schedule name to pointer
IF ( WarehouseCoil(CoilID)%SchedPtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//' not found: '//TRIM(Alphas(AlphaNum)))
ErrorsFound=.TRUE.
END IF ! ptr == 0
ELSE ! no schedule specified
WarehouseCoil(CoilID)%SchedPtr = AlwaysOn
END IF ! not blank
! check availability schedule for values between 0 and 1
IF ( WarehouseCoil(CoilID)%SchedPtr > 0)THEN
IF (.NOT. CheckScheduleValueMinMax( WarehouseCoil(CoilID)%SchedPtr,'>=',0.0d0,'<=',1.0d0)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//'"')
CALL ShowContinueError('Error found in '//TRIM(cAlphaFieldNames(AlphaNum))//' = '//TRIM(Alphas(AlphaNum)))
CALL ShowContinueError('schedule values must be (>=0., <=1.)')
ErrorsFound=.TRUE.
END IF
END IF
!Input capacity rating type
!bbbbb input values (DT1 or DTM type)translate DT1 to DTm here because node will give avg temp?
! ask whether ceiling or floor mounted? - effects translation from DT1 to DTM
! input coil condition, wet or dry OR input rating basis, European SC1, SC2 etc., have to combine with refrigerant factor)
! rated capacity, BAC give W/C, European gives W
! fin material factor, default 1
! refrigerant factor (factor of both refrigerant and Tevap)
!A3
AlphaNum = AlphaNum + 1
IF (lAlphaBlanks(AlphaNum)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
TRIM(cAlphaFieldNames(AlphaNum))//' is required and not found.')
ErrorsFound=.TRUE.
ELSEIF (SameString(Alphas(AlphaNum),'UnitLoadFactorSensibleOnly')) THEN
WarehouseCoil(CoilID)%RatingType = UnitLoadFactorSens
ELSEIF (SameString(Alphas(AlphaNum),'CapacityTotalSpecificConditions')) THEN
WarehouseCoil(CoilID)%RatingType = RatedCapacityTotal
ELSEIF (SameString(Alphas(AlphaNum),'EuropeanSC1Standard')) THEN
WarehouseCoil(CoilID)%RatingType = EuropeanSC1Std
ELSEIF (SameString(Alphas(AlphaNum),'EuropeanSC1NominalWet')) THEN
WarehouseCoil(CoilID)%RatingType = EuropeanSC1Nom
ELSEIF (SameString(Alphas(AlphaNum),'EuropeanSC2Standard')) THEN
WarehouseCoil(CoilID)%RatingType = EuropeanSC2Std
ELSEIF (SameString(Alphas(AlphaNum),'EuropeanSC2NominalWet')) THEN
WarehouseCoil(CoilID)%RatingType = EuropeanSC2Nom
ELSEIF (SameString(Alphas(AlphaNum),'EuropeanSC3Standard')) THEN
WarehouseCoil(CoilID)%RatingType = EuropeanSC3Std
ELSEIF (SameString(Alphas(AlphaNum),'EuropeanSC3NominalWet')) THEN
WarehouseCoil(CoilID)%RatingType = EuropeanSC3Nom
ELSEIF (SameString(Alphas(AlphaNum),'EuropeanSC4Standard')) THEN
WarehouseCoil(CoilID)%RatingType = EuropeanSC4Std
ELSEIF (SameString(Alphas(AlphaNum),'EuropeanSC4NominalWet')) THEN
WarehouseCoil(CoilID)%RatingType = EuropeanSC4Nom
ELSEIF (SameString(Alphas(AlphaNum),'EuropeanSC5Standard')) THEN
WarehouseCoil(CoilID)%RatingType = EuropeanSC5Std
ELSEIF (SameString(Alphas(AlphaNum),'EuropeanSC5NominalWet')) THEN
WarehouseCoil(CoilID)%RatingType = EuropeanSC5Nom
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//'="'//TRIM(Alphas(AlphaNum))//'".')
ErrorsFound=.TRUE.
END IF
!Here have to do select case with one numeric field with units of W and the second with units of W/deltaC,
! (RatedRH field only used for RatedCapacityTotal type)
SELECTCASE (WarehouseCoil(CoilID)%RatingType)
CASE (UnitLoadFactorSens)
!N1
NumNum = 1
IF(.NOT. lNumericBlanks(NumNum) .AND. Numbers(NumNum) > 0.0d0) THEN
WarehouseCoil(CoilID)%UnitLoadFactorSens = Numbers(NumNum)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be input and be greater than 0 W/C')
ErrorsFound = .TRUE.
END IF
CASE (RatedCapacityTotal)
!N2
NumNum = 2 !advance past rating in W/C to N2 with rating in W
IF(.NOT. lNumericBlanks(NumNum) .AND. Numbers(NumNum) > 0.0d0) THEN
WarehouseCoil(CoilID)%RatedCapTotal = Numbers(NumNum)
!N3
NumNum = 3 !read rated RH only for this type of rating at N3
IF(lNumericBlanks(NumNum)) THEN
WarehouseCoil(CoilID)%RatedRH = 0.85d0
ELSE
IF(Numbers(NumNum) <= 0.0d0 .OR. Numbers(NumNum) >= 100.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(WarehouseCoil(CoilID)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be greater than 0% and less than 100%')
ErrorsFound = .TRUE.
END IF
WarehouseCoil(CoilID)%RatedRH = Numbers(NumNum)/100.d0
END IF
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be input and be greater than 0 W')
ErrorsFound = .TRUE.
END IF
CASE (EuropeanSC1Std)
!N2
NumNum = 2 !advance past rating in W/C to rating in W at N2
IF(.NOT. lNumericBlanks(NumNum) .AND. Numbers(NumNum) > 0.0d0) THEN
WarehouseCoil(CoilID)%RatedSensibleCap = Numbers(NumNum)
WarehouseCoil(CoilID)%SCIndex = 1
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be input and be greater than 0 W')
ErrorsFound = .TRUE.
END IF
CASE (EuropeanSC1Nom)
!N2
NumNum = 2 !advance past rating in W/C to rating in W at N2
IF(.NOT. lNumericBlanks(NumNum) .AND. Numbers(NumNum) > 0.0d0) THEN
WarehouseCoil(CoilID)%RatedCapTotal = Numbers(NumNum)
WarehouseCoil(CoilID)%RatedSensibleCap = Numbers(NumNum)/EuropeanWetCoilFactor(1)
WarehouseCoil(CoilID)%SCIndex = 1
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be input and be greater than 0 W')
ErrorsFound = .TRUE.
END IF
CASE (EuropeanSC2Std)
!N2
NumNum = 2 !advance past rating in W/C to rating in W at N2
IF(.NOT. lNumericBlanks(NumNum) .AND. Numbers(NumNum) > 0.0d0) THEN
WarehouseCoil(CoilID)%RatedSensibleCap = Numbers(NumNum)
WarehouseCoil(CoilID)%SCIndex = 2
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be input and be greater than 0 W')
ErrorsFound = .TRUE.
END IF
CASE (EuropeanSC2Nom)
!N2
NumNum = 2 !advance past rating in W/C to rating in W at N2
IF(.NOT. lNumericBlanks(NumNum) .AND. Numbers(NumNum) > 0.0d0) THEN
WarehouseCoil(CoilID)%RatedCapTotal = Numbers(NumNum)
WarehouseCoil(CoilID)%RatedSensibleCap = Numbers(NumNum)/EuropeanWetCoilFactor(2)
WarehouseCoil(CoilID)%SCIndex = 2
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be input and be greater than 0 W')
ErrorsFound = .TRUE.
END IF
CASE (EuropeanSC3Std)
!N2
NumNum = 2 !advance past rating in W/C to rating in W at N2
IF(.NOT. lNumericBlanks(NumNum) .AND. Numbers(NumNum) > 0.0d0) THEN
WarehouseCoil(CoilID)%RatedSensibleCap = Numbers(NumNum)
WarehouseCoil(CoilID)%SCIndex = 3
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be input and be greater than 0 W')
ErrorsFound = .TRUE.
END IF
CASE (EuropeanSC3Nom)
!N2
NumNum = 2 !advance past rating in W/C to rating in W at N2
IF(.NOT. lNumericBlanks(NumNum) .AND. Numbers(NumNum) > 0.0d0) THEN
WarehouseCoil(CoilID)%RatedCapTotal = Numbers(NumNum)
WarehouseCoil(CoilID)%RatedSensibleCap = Numbers(NumNum)/EuropeanWetCoilFactor(3)
WarehouseCoil(CoilID)%SCIndex = 3
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be input and be greater than 0 W')
ErrorsFound = .TRUE.
END IF
CASE (EuropeanSC4Std)
!N2
NumNum = 2 !advance past rating in W/C to rating in W at N2
IF(.NOT. lNumericBlanks(NumNum) .AND. Numbers(NumNum) > 0.0d0) THEN
WarehouseCoil(CoilID)%RatedSensibleCap = Numbers(NumNum)
WarehouseCoil(CoilID)%SCIndex = 4
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be input and be greater than 0 W')
ErrorsFound = .TRUE.
END IF
CASE (EuropeanSC4Nom)
!N2
NumNum = 2 !advance past rating in W/C to rating in W at N2
IF(.NOT. lNumericBlanks(NumNum) .AND. Numbers(NumNum) > 0.0d0) THEN
WarehouseCoil(CoilID)%RatedCapTotal = Numbers(NumNum)
WarehouseCoil(CoilID)%RatedSensibleCap = Numbers(NumNum)/EuropeanWetCoilFactor(4)
WarehouseCoil(CoilID)%SCIndex = 4
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be input and be greater than 0 W')
ErrorsFound = .TRUE.
END IF
CASE (EuropeanSC5Std)
!N2
NumNum = 2 !advance past rating in W/C to rating in W at N2
IF(.NOT. lNumericBlanks(NumNum) .AND. Numbers(NumNum) > 0.0d0) THEN
WarehouseCoil(CoilID)%RatedSensibleCap = Numbers(NumNum)
WarehouseCoil(CoilID)%SCIndex = 5
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be input and be greater than 0 W')
ErrorsFound = .TRUE.
END IF
CASE (EuropeanSC5Nom)
!N2
NumNum = 2 !advance past rating in W/C to rating in W at N2
IF(.NOT. lNumericBlanks(NumNum) .AND. Numbers(NumNum) > 0.0d0) THEN
WarehouseCoil(CoilID)%RatedCapTotal = Numbers(NumNum)
WarehouseCoil(CoilID)%RatedSensibleCap = Numbers(NumNum)/EuropeanWetCoilFactor(5)
WarehouseCoil(CoilID)%SCIndex = 5
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be input and be greater than 0 W')
ErrorsFound = .TRUE.
END IF
END SELECT !WarehouseCoil(CoilID)%RatingType
!N4
NumNum = 4
IF (.NOT. lNumericBlanks(NumNum))THEN
WarehouseCoil(CoilID)%TEvapDesign = Numbers(NumNum) !also used to rep inlet brine T later when add that option
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be input')
ErrorsFound=.TRUE.
END IF
NumNum = NumNum + 1 !N5
IF (.NOT. lNumericBlanks(NumNum))THEN
WarehouseCoil(CoilID)%RatedTemperatureDif = Numbers(NumNum)
! INLET temperature - evaporating temperature, NOT room temp - evap temp
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be input')
ErrorsFound=.TRUE.
END IF
NumNum = NumNum + 1 !N6
IF (.NOT. lNumericBlanks(NumNum))THEN
WarehouseCoil(CoilID)%MaxTemperatureDif = Numbers(NumNum)
! Maximum difference between INLET temperature - evaporating temperature, NOT room temp - evap temp
! Important when cooling down space at start of environment or if large stocking loads imposed.
ELSE
WarehouseCoil(CoilID)%MaxTemperatureDif = 1.3d0 * WarehouseCoil(CoilID)%RatedTemperatureDif
CALL ShowWarningError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(WarehouseCoil(CoilID)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' not entered, default 1.3 times rated temperature difference will be used.')
END IF
! Correction factor from manufacturer's rating for coil material, default 1.0
NumNum = NumNum + 1 !N7
WarehouseCoil(CoilID)%CorrMaterial = 1.d0 !default value
IF (.NOT. lNumericBlanks(NumNum)) WarehouseCoil(CoilID)%CorrMaterial = Numbers(NumNum)
! Correction factor from manufacturer's rating for refrigerant, default 1.0
NumNum = NumNum + 1 !N8
WarehouseCoil(CoilID)%CorrRefrigerant = 1.0d0 !default value
IF (.NOT. lNumericBlanks(NumNum)) WarehouseCoil(CoilID)%CorrRefrigerant = Numbers(NumNum)
!ONLY used if the Capacity Rating Type is CapacityTotalSpecificConditions
!Convert all European sensible capacities to sensible load factors
IF((WarehouseCoil(CoilID)%RatingType /= UnitLoadFactorSens) .AND. &
(WarehouseCoil(CoilID)%RatingType /= RatedCapacityTotal)) &
WarehouseCoil(CoilID)%UnitLoadFactorSens = WarehouseCoil(CoilID)%RatedSensibleCap/ &
WarehouseCoil(CoilID)%RatedTemperatureDif
!Now have UnitLoadFactorSens for all except RatingType == RatedCapacityTotal
!Apply material and refrigerant correction factors to sensible load factors
IF((WarehouseCoil(CoilID)%RatingType /= RatedCapacityTotal)) &
WarehouseCoil(CoilID)%UnitLoadFactorSens = WarehouseCoil(CoilID)%UnitLoadFactorSens * &
WarehouseCoil(CoilID)%CorrMaterial * &
WarehouseCoil(CoilID)%CorrRefrigerant
!First calc of ratedsensiblecap for type type unitloadfactorsens
WarehouseCoil(CoilID)%RatedSensibleCap = WarehouseCoil(CoilID)%UnitLoadFactorSens * &
WarehouseCoil(CoilID)%RatedTemperatureDif
!A4 Enter capacity correction curve type
AlphaNum = 4
IF((lAlphaBlanks(AlphaNum)) .AND. (WarehouseCoil(CoilID)%RatingType /= RatedCapacityTotal)) THEN
! For all except RatedCapacityTotal - default to linear capacity factor approximating Nelson August 2010 ASHRAE journal
WarehouseCoil(CoilID)%SHRCorrectionType = SHR60
ELSEIF (WarehouseCoil(CoilID)%RatingType == RatedCapacityTotal) THEN
! For RatedCapacityTotal, the manufacturer's coil performance map is required
! Specify the performance map with TabularRHxDT1xTRoom
WarehouseCoil(CoilID)%SHRCorrectionType = TabularRH_DT1_TRoom
IF (.NOT.(SameString(Alphas(AlphaNum),'TabularRHxDT1xTRoom'))) THEN
CALL ShowWarningError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(WarehouseCoil(CoilID)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//'="'//TRIM(Alphas(AlphaNum))//'".')
CALL ShowContinueError('The "CapacityTotalSpecificConditions" Capacity Rating Type has been specified '//&
'for this air chiller. This rating type requires ')
CALL ShowContinueError('the "TabularRHxDT1xTRoom" correction curve. Verify that a valid '//&
'"TabularRHxDT1xTRoom" curve is specified in "'//TRIM(cAlphaFieldNames(AlphaNum+1))//'".')
ENDIF
ELSEIF (SameString(Alphas(AlphaNum),'LinearSHR60')) THEN
WarehouseCoil(CoilID)%SHRCorrectionType = SHR60
ELSEIF (SameString(Alphas(AlphaNum),'QuadraticSHR')) THEN
WarehouseCoil(CoilID)%SHRCorrectionType = QuadraticSHR
ELSEIF (SameString(Alphas(AlphaNum),'European')) THEN
WarehouseCoil(CoilID)%SHRCorrectionType = European
ELSEIF (SameString(Alphas(AlphaNum),'TabularRHxDT1xTRoom')) THEN
WarehouseCoil(CoilID)%SHRCorrectionType = TabularRH_DT1_TRoom
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//'="'//TRIM(Alphas(AlphaNum))//'".')
ErrorsFound=.TRUE.
END IF
AlphaNum = AlphaNum + 1 !A5
NumNum = NumNum + 1 !N9
SELECT CASE (WarehouseCoil(CoilID)%SHRCorrectionType)
CASE (SHR60)
WarehouseCoil(CoilID)%SHRCorrection60 = 1.48d0 ! reference Nelson, ASHRAE journal August 2010 Fig 2
IF (.NOT. lNumericBlanks(NumNum)) WarehouseCoil(CoilID)%SHRCorrection60 = Numbers(NumNum)
!(1.66667 would be a perfect effectiveness, 1.0 would be artificial coil that does only sensible)
IF (WarehouseCoil(CoilID)%SHRCorrection60 > 1.67d0)THEN
WarehouseCoil(CoilID)%SHRCorrection60 = 1.67d0
CALL ShowWarningError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(WarehouseCoil(CoilID)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be between 1 and 1.67, 1.67 will be used.')
END IF
IF (WarehouseCoil(CoilID)%SHRCorrection60 < 1.d0) THEN
WarehouseCoil(CoilID)%SHRCorrection60 = 1.0d0
CALL ShowWarningError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(WarehouseCoil(CoilID)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be between 1 and 1.67, 1.00 will be used.')
END IF
CASE (European)
!WarehouseCoil(CoilID)%SHRCorrectionCurvePtr = GetCurveIndex('ChillerEuropeanWetCoilFactor')
! This is a place holder, currently use embedded constants for European ratings, future may want a curve
CASE (QuadraticSHR)
WarehouseCoil(CoilID)%SHRCorrectionCurvePtr = GetCurveIndex(Alphas(AlphaNum)) ! convert curve name to number
IF (lAlphaBlanks(AlphaNum)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(WarehouseCoil(CoilID)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//' is blank, required.')
ErrorsFound=.true.
ELSEIF (WarehouseCoil(CoilID)%SHRCorrectionCurvePtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(WarehouseCoil(CoilID)%Name)//&
'", invalid ')
CALL ShowContinueError('...invalid curve '//TRIM(cAlphaFieldNames(AlphaNum))//'="'//trim(Alphas(AlphaNum))//'".')
ErrorsFound=.true.
ENDIF
!error checks for curve type entered and curve name
IF(.NOT. SameString(GetCurveType(WarehouseCoil(CoilID)%SHRCorrectionCurvePtr),'QUADRATIC')) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(WarehouseCoil(CoilID)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//' must be of type Quadratic.')
ErrorsFound = .TRUE.
END IF
CASE (TabularRH_DT1_TRoom)
WarehouseCoil(CoilID)%SHRCorrectionCurvePtr = GetCurveIndex(Alphas(AlphaNum)) ! convert curve name to number
IF (lAlphaBlanks(AlphaNum)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(WarehouseCoil(CoilID)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//' is blank, required.')
ErrorsFound=.true.
ELSEIF (WarehouseCoil(CoilID)%SHRCorrectionCurvePtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(WarehouseCoil(CoilID)%Name)//&
'", invalid ')
CALL ShowContinueError('...invalid curve '//TRIM(cAlphaFieldNames(AlphaNum))//'="'//trim(Alphas(AlphaNum))//'".')
ErrorsFound=.true.
ENDIF
! IF(WarehouseCoil(CoilID)%SHRCorrectionCurvePtr == 0) THEN
! CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(WarehouseCoil(CoilID)%Name)//&
! '", not found '//TRIM(cAlphaFieldNames(AlphaNum)))
! ErrorsFound = .TRUE.
! END IF !valid table name
END SELECT !SHRCorrectionType
NumNum = NumNum + 1 !N10
IF (.NOT. lNumericBlanks(NumNum))THEN
WarehouseCoil(CoilID)%HeaterPower = Numbers(NumNum)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be input ')
ErrorsFound=.TRUE.
END IF
AlphaNum = AlphaNum + 1 !A6
IF (.NOT. lAlphaBlanks(AlphaNum)) THEN
WarehouseCoil(CoilID)%HeaterSchedPtr = GetScheduleIndex(Alphas(AlphaNum)) ! convert heater schedule name to pointer
IF ( WarehouseCoil(CoilID)%HeaterSchedPtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//' not found: '//TRIM(Alphas(AlphaNum)))
ErrorsFound=.TRUE.
ELSE ! check heater schedule for values between 0 and 1
IF (.NOT. CheckScheduleValueMinMax( WarehouseCoil(CoilID)%HeaterSchedPtr,'>=',0.0d0,'<=',1.0d0)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//'"')
CALL ShowContinueError('Error found in '//TRIM(cAlphaFieldNames(AlphaNum))//' = '//TRIM(Alphas(AlphaNum)))
CALL ShowContinueError('schedule values must be (>=0., <=1.)')
ErrorsFound=.TRUE.
END IF !heater schedule ptr == 0
END IF !htr sched == 0
ELSE ! lalphaBlanks, no schedule specified
WarehouseCoil(CoilID)%HeaterSchedPtr = AlwaysOn
END IF ! not blank
!Input fan control type
AlphaNum = AlphaNum + 1 !A7
IF(lAlphaBlanks(AlphaNum)) THEN
WarehouseCoil(CoilID)%FanType = FanConstantSpeed
ELSEIF (SameString(Alphas(AlphaNum),'Fixed')) THEN
WarehouseCoil(CoilID)%FanType = FanConstantSpeed
ELSEIF (SameString(Alphas(AlphaNum),'FixedLinear')) THEN
WarehouseCoil(CoilID)%FanType = FanConstantSpeedLinear
ELSEIF (SameString(Alphas(AlphaNum),'VariableSpeed')) THEN
WarehouseCoil(CoilID)%FanType = FanVariableSpeed
ELSEIF (SameString(Alphas(AlphaNum),'TwoSpeed')) THEN
WarehouseCoil(CoilID)%FanType = FanTwoSpeed
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//'="'//TRIM(Alphas(AlphaNum))//'".')
ErrorsFound=.TRUE.
END IF !fan control type
NumNum = NumNum + 1 !N11
IF (.NOT. lNumericBlanks(NumNum) .AND. Numbers(NumNum) > 0.d0)THEN
WarehouseCoil(CoilID)%RatedFanPower = Numbers(NumNum)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' was not input or was less than 0 ')
ErrorsFound=.TRUE.
END IF !coil fan power
NumNum = NumNum + 1 !N12
IF (.NOT. lNumericBlanks(NumNum) .AND. Numbers(NumNum) > 0.d0)THEN
WarehouseCoil(CoilID)%RatedAirVolumeFlow = Numbers(NumNum)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' is required and was not input or was less than 0 ')
END IF !air volume flow
NumNum = NumNum + 1 !N13
WarehouseCoil(CoilID)%FanMinAirFlowRatio = 0.2d0 !default value
IF(.NOT. lNumericBlanks(NumNum) .AND. Numbers(NumNum) > 0.d0) WarehouseCoil(CoilID)%FanMinAirFlowRatio = Numbers(NumNum)
!Input defrost type
AlphaNum = AlphaNum + 1 !A8
IF(lAlphaBlanks(AlphaNum)) THEN
WarehouseCoil(CoilID)%DefrostType = DefrostElec
ELSEIF (SameString(Alphas(AlphaNum),'Electric')) THEN
WarehouseCoil(CoilID)%DefrostType = DefrostElec
ELSEIF (SameString(Alphas(AlphaNum),'HotFluid')) THEN
WarehouseCoil(CoilID)%DefrostType = DefrostFluid
ELSEIF (SameString(Alphas(AlphaNum),'None')) THEN
WarehouseCoil(CoilID)%DefrostType = DefrostNone
ELSEIF (SameString(Alphas(AlphaNum),'OffCycle')) THEN
WarehouseCoil(CoilID)%DefrostType = DefrostOffCycle
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//'="'//TRIM(Alphas(AlphaNum))//'".')
ErrorsFound=.TRUE.
END IF !defrost type
AlphaNum = AlphaNum + 1 !A9
IF(lAlphaBlanks(AlphaNum)) THEN
WarehouseCoil(CoilID)%DefrostControlType = DefrostControlSched
ELSEIF (SameString(Alphas(AlphaNum),'TimeSchedule'))THEN
WarehouseCoil(CoilID)%DefrostControlType = DefrostControlSched
ELSEIF (SameString(Alphas(AlphaNum),'TemperatureTermination')) THEN
WarehouseCoil(CoilID)%DefrostControlType = DefrostContTempTerm
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//' not found: '//TRIM(Alphas(AlphaNum)))
ErrorsFound=.TRUE.
END IF ! defrost control type
! convert defrost schedule name to pointer
AlphaNum = AlphaNum + 1 !A10
WarehouseCoil(CoilID)%DefrostSchedPtr = GetScheduleIndex(Alphas(AlphaNum))
IF ( WarehouseCoil(CoilID)%DefrostSchedPtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//' not found: '//TRIM(Alphas(AlphaNum)))
ErrorsFound=.TRUE.
ELSE ! check defrost schedule for values between 0 and 1
IF (.NOT. CheckScheduleValueMinMax( WarehouseCoil(CoilID)%DefrostSchedPtr,'>=',0.0d0,'<=',1.0d0)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//' = "'//TRIM( WarehouseCoil(CoilID)%Name)//'"')
CALL ShowContinueError('Error found in '//TRIM(cAlphaFieldNames(AlphaNum))//'='//TRIM(Alphas(AlphaNum)))
CALL ShowContinueError('schedule values must be (>=0., <=1.)')
ErrorsFound=.TRUE.
END IF !checkschedulevalueMinMax
END IF !check for valid schedule name
! convert defrost drip-down schedule name to pointer
! some defrost types do not use drip-down schedules, use same defrost schedule pointer in that case
AlphaNum = AlphaNum + 1 !A11
IF (.NOT. lAlphaBlanks(AlphaNum)) THEN
WarehouseCoil(CoilID)%DefrostDripDownSchedPtr = GetScheduleIndex(Alphas(AlphaNum))
IF ( WarehouseCoil(CoilID)%DefrostDripDownSchedPtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(WarehouseCoil(CoilID)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//' not found: '//TRIM(Alphas(AlphaNum)))
ErrorsFound=.TRUE.
ELSE ! check schedule for values between 0 and 1
IF (.NOT. CheckScheduleValueMinMax( WarehouseCoil(CoilID)%DefrostDripDownSchedPtr,'>=',0.0d0,'<=',1.0d0)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//'"')
CALL ShowContinueError('Error found in '//TRIM(cAlphaFieldNames(AlphaNum))//' = '//TRIM(Alphas(AlphaNum)))
CALL ShowContinueError('schedule values must be (>=0., <=1.)')
ErrorsFound=.TRUE.
END IF !Check schedule value between 0 and 1
END IF ! Check if drip down schedule name is valid
ELSE ! .not. lAlphaBlanks so use drip down schedule for defrost
WarehouseCoil(CoilID)%DefrostDripDownSchedPtr = WarehouseCoil(CoilID)%DefrostSchedPtr
END IF ! .not. lAlphaBlanks
NumNum = NumNum + 1 !N14
IF (WarehouseCoil(CoilID)%DefrostType == DefrostOffCycle .OR. &
WarehouseCoil(CoilID)%DefrostType == DefrostNone) THEN
WarehouseCoil(CoilID)%DefrostCapacity = 0.d0
!Don't even need to read Defrost capacity for those two defrost types.
ELSE !have electric or hot gas/brine defrost
IF ((lNumericBlanks(NumNum)) .OR. (Numbers(NumNum) <= 0.0d0))THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be input and greater than or equal to 0 W'//' for '//&
TRIM(cAlphaFieldNames(AlphaNum))//' '//TRIM(Alphas(AlphaNum)))
ErrorsFound = .TRUE.
ELSE
WarehouseCoil(CoilID)%DefrostCapacity = Numbers(NumNum)
END IF !Blank or negative Defrost Capacity
!defaults for defrost energy fraction are 0.7 for elec defrost and 0.3 for warm fluid
!note this value is only used for temperature terminated defrost control type
IF (WarehouseCoil(CoilID)%DefrostType == DefrostElec) WarehouseCoil(CoilID)%DefEnergyFraction = 0.7d0
IF (WarehouseCoil(CoilID)%DefrostType == DefrostFluid) WarehouseCoil(CoilID)%DefEnergyFraction = 0.3d0
NumNum = NumNum + 1 !N15
IF (.NOT. lNumericBlanks (NumNum)) THEN
IF ((Numbers(NumNum) > 1.0d0) .OR. (Numbers(NumNum) < 0.0d0))THEN
CALL ShowWarningError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(WarehouseCoil(CoilID)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be between 0 and 1, default values will be used.')
ELSE
WarehouseCoil(CoilID)%DefEnergyFraction = Numbers(NumNum)
END IF ! number out of range
END IF !lnumericblanks
END IF ! defrost type
AlphaNum = AlphaNum + 1 !A12
IF(lAlphaBlanks(AlphaNum)) THEN
WarehouseCoil(CoilID)%VerticalLocation = Middle !default position
ELSEIF (SameString(Alphas(AlphaNum),'Ceiling'))THEN
WarehouseCoil(CoilID)%VerticalLocation = Ceiling
ELSEIF (SameString(Alphas(AlphaNum),'Middle')) THEN
WarehouseCoil(CoilID)%VerticalLocation = Middle
ELSEIF (SameString(Alphas(AlphaNum),'Floor')) THEN
WarehouseCoil(CoilID)%VerticalLocation = Floor
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( WarehouseCoil(CoilID)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//' not found: '//TRIM(Alphas(AlphaNum)))
ErrorsFound=.TRUE.
END IF ! Vertical location class
NumNum = NumNum + 1 !N16
WarehouseCoil(CoilID)%DesignRefrigInventory = 0.0d0
IF (.NOT. lNumericBlanks(NumNum)) WarehouseCoil(CoilID)%DesignRefrigInventory = Numbers(NumNum)
END DO !NumRefrigAirChillers
END IF !NumRefrigerationAirChillers > 0
!************ START Warehouse Coil SET INPUT **************
! One Set allowed per zone, but indiv coils within zone can be served by different compressor/condenser systems
IF(NumRefrigChillerSets > 0 ) THEN
ALLOCATE(CheckChillerSetName(NumRefrigChillerSets))
CheckChillerSetName=.true.
CurrentModuleObject='ZoneHVAC:RefrigerationChillerSet'
DO SetID=1,NumRefrigChillerSets
CALL GetObjectItem(CurrentModuleObject, SetID,Alphas,NumAlphas,Numbers,NumNumbers,IOStatus, &
NumBlank=lNumericBlanks,AlphaBlank=lAlphaBlanks, &
AlphaFieldNames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
IsNotOK =.FALSE.
IsBlank =.FALSE.
AlphaNum = 1
CALL VerifyName(Alphas(AlphaNum), AirChillerSet%Name, SetID-1,IsNotOK,IsBlank,CurrentModuleObject//' Name')
IF (IsNotOK) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//', has an invalid or undefined name="'//&
TRIM(Alphas(AlphaNum))//'".')
IF (IsBlank) Alphas(AlphaNum)='xxxxx'
ErrorsFound=.TRUE.
ENDIF
AirChillerSet(SetID)%Name = Alphas(AlphaNum)
AlphaNum = 2
IF (.NOT. lAlphaBlanks(AlphaNum)) THEN
AirChillerSet(SetID)%SchedPtr = GetScheduleIndex(Alphas(AlphaNum)) ! convert schedule name to pointer
IF ( AirChillerSet(SetID)%SchedPtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( AirChillerSet(SetID)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//' not found: '//TRIM(Alphas(AlphaNum)))
ErrorsFound=.TRUE.
END IF ! ptr == 0
ELSE ! no schedule specified
AirChillerSet(SetID)%SchedPtr = AlwaysOn
END IF ! not blank
! check availability schedule for values between 0 and 1
IF ( AirChillerSet(SetID)%SchedPtr > 0)THEN
IF (.NOT. CheckScheduleValueMinMax( AirChillerSet(SetID)%SchedPtr,'>=',0.0d0,'<=',1.0d0)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( AirChillerSet(SetID)%Name)//'"')
CALL ShowContinueError('Error found in '//TRIM(cAlphaFieldNames(AlphaNum))//' = '//TRIM(Alphas(AlphaNum)))
CALL ShowContinueError('schedule values must be (>=0., <=1.)')
ErrorsFound=.TRUE.
END IF
END IF
AlphaNum = AlphaNum + 1
AirChillerSet(SetID)%ZoneName= Alphas(AlphaNum)
AirChillerSet(SetID)%ZoneNum = FindItemInList(Alphas(AlphaNum),Zone%Name,NumOfZones)
IF ( AirChillerSet(SetID)%ZoneNum == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( AirChillerSet(SetID)%Name)// &
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//' not valid: '//TRIM(Alphas(AlphaNum)))
ErrorsFound=.TRUE.
ENDIF
AirChillerSet(SetID)%ZoneNodeNum = GetSystemNodeNumberForZone( AirChillerSet(SetID)%ZoneName)
IF ( AirChillerSet(SetID)%ZoneNodeNum == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( AirChillerSet(SetID)%Name)// &
'" System Node Number not found for '//TRIM(cAlphaFieldNames(AlphaNum))// &
' = '//TRIM(Alphas(AlphaNum)))
CALL ShowContinueError('.. Refrigeration chillers must reference a controlled Zone (appear'// &
' in a ZoneHVAC:EquipmentConnections object.')
ErrorsFound=.TRUE.
ENDIF
RefrigPresentInZone(AirChillerSet(SetID)%ZoneNum) = .TRUE.
AlphaNum = AlphaNum + 1
IF (.NOT. lAlphaBlanks(AlphaNum)) THEN
CALL ShowMessage(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( AirChillerSet(SetID)%Name)// &
'" '//TRIM(cAlphaFieldNames(AlphaNum))//' is not used. This is not an error. '// &
' Energy is exchanged directly with the zone independent of any air system. ')
! Node identification reserved for future use. Currently exchange energy directly with zone outside any air system
!AirChillerSet(SetID)%NodeNumInlet = &
! GetOnlySingleNode(Alphas(AlphaNum),ErrorsFound,TRIM(CurrentModuleObject), &
! AirChillerSet(SetID)%Name,NodeType_Air,NodeConnectionType_Inlet,1,ObjectIsNotParent)
END IF
AlphaNum = AlphaNum + 1
IF (.NOT. lAlphaBlanks(AlphaNum)) THEN
CALL ShowMessage(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM( AirChillerSet(SetID)%Name)// &
'" '//TRIM(cAlphaFieldNames(AlphaNum))//' is not used. This is not an error. '// &
' Energy is exchanged directly with the zone independent of any air system. ')
! Node identification reserved for future use. Currently exchange energy directly with zone outside any air system
!AirChillerSet(SetID)%NodeNumOutlet = &
! GetOnlySingleNode(Alphas(AlphaNum),ErrorsFound,TRIM(CurrentModuleObject), &
! AirChillerSet(SetID)%Name,NodeType_Air,NodeConnectionType_Outlet,1,ObjectIsNotParent)
END IF
!An extensible list is used to enter the individual names of each chiller in the set.
!These chillers will be dispatched in this list order to meet the required zone load
NumChillersInSet = NumAlphas - AlphaNum
AlphaStartList = AlphaNum !+ 1
AirChillerSet(SetID)%NumCoils = NumChillersInSet
IF(.NOT. ALLOCATED(AirChillerSet(SetID)%CoilNum))ALLOCATE(AirChillerSet(SetID)%CoilNum(NumChillersInSet))
DO ChillerIndex = 1,NumChillersInSet
AlphaListNum = AlphaStartList + ChillerIndex
IF(.NOT. lAlphaBlanks(AlphaListNum)) THEN
CoilNum = FindItemInList(Alphas(AlphaListNum),WarehouseCoil%Name,NumSimulationRefrigAirChillers)
IF(CoilNum == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)// &
'="'//TRIM(AirChillerSet(SetID)%Name)//'", has an invalid '//&
TRIM(cAlphaFieldNames(AlphaListNum))//' defined as '//TRIM(Alphas(AlphaListNum)))
ErrorsFound = .TRUE.
END IF ! == 0
AirChillerSet(SetID)%CoilNum(ChillerIndex)= CoilNum
WarehouseCoil(CoilNum)%ZoneName = AirChillerSet(SetID)%ZoneName
WarehouseCoil(CoilNum)%ZoneNum = AirChillerSet(SetID)%ZoneNum
WarehouseCoil(CoilNum)%ZoneNodeNum = AirChillerSet(SetID)%ZoneNodeNum
END IF ! ! = alphablanks
END DO !CoilID over NumChillersInSet
END DO ! NumChillerSets
END IF ! NumChillerSets > 0
!************* End Air Chiller Sets
!**** Read CaseAndWalkIn Lists **********************************************************
IF(NumSimulationCaseAndWalkInLists > 0) THEN
CurrentModuleObject='Refrigeration:CaseAndWalkInList'
DO ListNum=1,NumSimulationCaseAndWalkInLists
CALL GetObjectItem(CurrentModuleObject,ListNum,Alphas,NumAlphas,Numbers,NumNumbers,IOStatus, &
NumBlank=lNumericBlanks,AlphaBlank=lAlphaBlanks, &
AlphaFieldNames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
IsNotOK =.FALSE.
IsBlank =.FALSE.
CALL VerifyName(Alphas(1),CaseAndWalkInList%Name,ListNum-1,IsNotOK,IsBlank,CurrentModuleObject//' Name')
IF (IsNotOK) THEN
IF (IsBlank) Alphas(1)='xxxxx'
ErrorsFound=.TRUE.
ENDIF
CaseAndWalkInList(ListNum)%Name=Alphas(1)
! CaseAndWalkInList alphas include CaseAndWalkInList name and one name for each Case or WalkIn in list
! below allocates larger than needed (each allocated to sum of both), but avoids two loops through input fields
NumTotalLoadsOnList = NumAlphas - 1
IF(.NOT. ALLOCATED(CaseAndWalkInList(ListNum)%WalkInItemNum)) &
ALLOCATE(CaseAndWalkInList(ListNum)%WalkInItemNum(NumTotalLoadsOnList))
IF(.NOT. ALLOCATED(CaseAndWalkInList(ListNum)%CaseItemNum)) &
ALLOCATE(CaseAndWalkInList(ListNum)%CaseItemNum(NumTotalLoadsOnList))
IF(.NOT. ALLOCATED(CaseAndWalkInList(ListNum)%CoilItemNum)) &
ALLOCATE(CaseAndWalkInList(ListNum)%CoilItemNum(NumTotalLoadsOnList))
NumCasesOnList = 0
NumCoilsOnList = 0
NumWalkInsOnList = 0
LoadCount = 0
DO NumLoad = 1, NumTotalLoadsOnList
AlphaListNum= 1 + NumLoad
IF (.NOT. lAlphaBlanks(alphalistnum)) THEN
LoadCount = Loadcount + 1
LoadWalkInNum = 0
LoadCaseNum = 0
LoadCoilNum = 0
IF(NumSimulationWalkIns > 0) &
LoadWalkInNum = FindItemInList(Alphas(AlphaListNum),WalkIn%Name,NumSimulationWalkIns)
IF(NumSimulationCases > 0) &
LoadCaseNum = FindItemInList(Alphas(AlphaListNum),RefrigCase%Name,NumSimulationCases)
IF(NumSimulationRefrigAirChillers > 0) &
LoadCoilNum = FindItemInList(Alphas(AlphaListNum),WarehouseCoil%Name,NumSimulationRefrigAirChillers)
IF((LoadWalkInNum == 0) .AND. (LoadCaseNum == 0).AND. (LoadCoilNum == 0)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//&
TRIM(cAlphaFieldNames(AlphaListNum))//'", has an invalid '//&
'value of '//TRIM(Alphas(AlphaListNum)))
ErrorsFound = .TRUE.
ELSEIF((LoadWalkInNum /= 0) .AND. (LoadCaseNum /= 0).AND. (LoadCoilNum /= 0)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(cAlphaFieldNames(AlphaListNum))//&
'", '//TRIM(Alphas(AlphaListNum))// &
' Case and WalkIns and Refrigerated Coils cannot have the same name.')
ErrorsFound = .TRUE.
ELSEIF (LoadWalkInNum /= 0) THEN
NumWalkInsOnList = NumWalkInsOnList + 1
CaseAndWalkInList(ListNum)%WalkInItemNum(NumWalkInsOnList) = LoadWalkInNum
ELSEIF (LoadCaseNum /= 0) THEN
NumCasesOnList = NumCasesOnList + 1
CaseAndWalkInList(ListNum)%CaseItemNum(NumCasesOnList) = LoadCaseNum
ELSEIF (LoadCoilNum /= 0) THEN
NumCoilsOnList = NumCoilsOnList + 1
CaseAndWalkInList(ListNum)%CoilItemNum(NumCoilsOnList) = LoadCoilNum
END IF
END IF !lalphablanks
END DO !Num Total Loads on List
IF(LoadCount == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)// &
', "'//TRIM(CaseAndWalkInList(ListNum)%Name)//'" : degenerate list '//&
'All entries were blank.')
ErrorsFound = .TRUE.
END IF !loadcount == 0
CaseAndWalkInList(ListNum)%NumCases = NumCasesOnList
CaseAndWalkInList(ListNum)%NumCoils = NumCoilsOnList
CaseAndWalkInList(ListNum)%NumWalkIns = NumWalkInsOnList
END DO !ListNum=1,NumSimulationCaseAndWalkInLists
END IF !(NumSimulationCaseAndWalkInLists > 0)
!**** End read CaseAndWalkIn Lists **********************************************************
!************** Start RefrigerationRacks
IF(NumRefrigeratedRacks > 0) THEN
CurrentModuleObject='Refrigeration:CompressorRack'
DO RackNum=1,NumRefrigeratedRacks
CALL GetObjectItem(CurrentModuleObject,RackNum,Alphas,NumAlphas,Numbers,NumNumbers,IOStatus, &
NumBlank=lNumericBlanks,AlphaBlank=lAlphaBlanks, &
AlphaFieldNames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
IsNotOK =.FALSE.
IsBlank =.FALSE.
CALL VerifyName(Alphas(1),RefrigRack%Name,RackNum-1,IsNotOK,IsBlank,CurrentModuleObject//' Name')
IF (IsNotOK) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//', has an invalid or undefined '// &
TRIM(cAlphaFieldNames(1))//'="'//TRIM(Alphas(1))//'".')
IF (IsBlank) Alphas(1)='xxxxx'
ErrorsFound=.TRUE.
ENDIF
RefrigRack(RackNum)%Name = Alphas(1)
HeatReclaimRefrigeratedRack(RackNum)%Name = Alphas(1)
HeatReclaimRefrigeratedRack(RackNum)%SourceType = CurrentModuleObject
IF (SameString(Alphas(2),'Outdoors')) THEN
RefrigRack(RackNum)%HeatRejectionLocation = LocationOutdoors
ELSEIF (SameString(Alphas(2),'Zone')) THEN
RefrigRack(RackNum)%HeatRejectionLocation = LocationZone
! don't need to set RefrigPresentInZone to .TRUE. here because only allowed to reject heat to zone
! holding all served cases, so already set when case read in
ELSE
RefrigRack(RackNum)%HeatRejectionLocation = LocationOutdoors
CALL ShowWarningError(TRIM(CurrentModuleObject)//', '//TRIM(cAlphaFieldNames(1))//' = "'//TRIM(RefrigRack(RackNum)%Name)// &
'": '//TRIM(cAlphaFieldNames(2))//' defined as '//TRIM(Alphas(2))// &
' not found. Will assume '//TRIM(cAlphaFieldNames(2))//' is OUTDOORS and simulation continues.')
END IF
RefrigRack(RackNum)%RatedCOP = Numbers(1)
IF(RefrigRack(RackNum)%RatedCOP <= 0.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigRack(RackNum)%Name)//&
'" '//TRIM(cNumericFieldNames(1))//' must be greater than 0.0')
ErrorsFound = .TRUE.
END IF
RefrigRack(RackNum)%COPFTempPtr = GetCurveIndex(Alphas(3)) ! convert curve name to number
IF (RefrigRack(RackNum)%COPFTempPtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigRack(RackNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(3))//' not found:'//TRIM(Alphas(3)))
ErrorsFound = .TRUE.
END IF
IF(.NOT. SameString(GetCurveType(RefrigRack(RackNum)%COPFTempPtr),'CUBIC')) THEN
IF(.NOT. SameString(GetCurveType(RefrigRack(RackNum)%COPFTempPtr),'QUADRATIC')) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigRack(RackNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(3))//' object must be of type cubic or quadratic.')
ErrorsFound = .TRUE.
END IF
END IF
RefrigRack(RackNum)%CondenserFanPower = Numbers(2)
IF(Numbers(2) < 0.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigRack(RackNum)%Name)//&
'" '//TRIM(cNumericFieldNames(2))//' must be greater than or equal to 0 Watts.')
ErrorsFound = .TRUE.
END IF
RefrigRack(RackNum)%TotCondFTempPtr = GetCurveIndex(Alphas(4)) ! convert curve name to number
IF ((.NOT. lAlphaBlanks(4)) .AND. RefrigRack(RackNum)%TotCondFTempPtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigRack(RackNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(4))//' not found:'//TRIM(Alphas(4)))
ErrorsFound = .TRUE.
END IF
IF (.NOT. lAlphaBlanks(4)) THEN
IF(.NOT. SameString(GetCurveType(RefrigRack(RackNum)%TotCondFTempPtr),'CUBIC')) THEN
IF(.NOT. SameString(GetCurveType(RefrigRack(RackNum)%TotCondFTempPtr),'QUADRATIC')) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigRack(RackNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(4))//' object must be of type cubic or quadratic.')
ErrorsFound = .TRUE.
END IF
END IF
END IF
IF (SameString(Alphas(5),'EvaporativelyCooled')) THEN
RefrigRack(RackNum)%CondenserType = RefrigCondenserTypeEvap
IF (RefrigRack(RackNum)%HeatRejectionLocation==LocationZone) THEN
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(RefrigRack(RackNum)%Name)//&
'" Evap cooled '//TRIM(cAlphaFieldNames(5))//' not available with '//TRIM(cAlphaFieldNames(2))//' = Zone.')
CALL ShowContinueError(TRIM(cAlphaFieldNames(5))//' reset to Air Cooled and simulation continues.')
RefrigRack(RackNum)%CondenserType = RefrigCondenserTypeAir
END IF
ELSEIF (SameString(Alphas(5),'WaterCooled')) THEN
RefrigRack(RackNum)%CondenserType = RefrigCondenserTypeWater
IF (RefrigRack(RackNum)%HeatRejectionLocation==LocationZone) THEN
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(RefrigRack(RackNum)%Name)//&
'" Water cooled '//TRIM(cAlphaFieldNames(5))//' not available with '//TRIM(cAlphaFieldNames(2))//' = Zone.')
CALL ShowContinueError(TRIM(cAlphaFieldNames(5))//' reset to Air Cooled and simulation continues.')
RefrigRack(RackNum)%CondenserType = RefrigCondenserTypeAir
END IF
ELSE
RefrigRack(RackNum)%CondenserType = RefrigCondenserTypeAir
END IF
! Get water-cooled condenser input, if applicable
IF (RefrigRack(RackNum)%CondenserType == RefrigCondenserTypeWater) THEN
RefrigRack(RackNum)%InletNode = GetOnlySingleNode(Alphas(6),ErrorsFound,CurrentModuleObject, &
Alphas(1),NodeType_Water,NodeConnectionType_Inlet, 1, ObjectIsNotParent)
RefrigRack(RackNum)%OutletNode = GetOnlySingleNode(Alphas(7),ErrorsFound,CurrentModuleObject, &
Alphas(1),NodeType_Water,NodeConnectionType_Outlet, 1, ObjectIsNotParent)
! Check node connections
CALL TestCompSet(CurrentModuleObject,Alphas(1),Alphas(6),Alphas(7),'RefrigRack Nodes')
! Get loop flow type
IF (SameString(Alphas(8),'VariableFlow')) THEN
RefrigRack(RackNum)%FlowType = VariableFlow
ELSE IF (SameString(Alphas(8),'ConstantFlow')) THEN
RefrigRack(RackNum)%FlowType = ConstantFlow
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigRack(RackNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(8))//' not recognized: '//TRIM(Alphas(8)))
CALL ShowContinueError('Check input value choices.')
ErrorsFound=.TRUE.
END IF
! Get outlet temperature schedule for variable flow case
IF (RefrigRack(RackNum)%FlowType==VariableFlow) THEN
IF (lAlphaBlanks(9)) THEN
RefrigRack(RackNum)%OutletTempSchedPtr = 0
ELSE
RefrigRack(RackNum)%OutletTempSchedPtr = GetScheduleIndex(Alphas(9)) ! convert schedule name to pointer
END IF
IF (RefrigRack(RackNum)%OutletTempSchedPtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigRack(RackNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(9))//' : '//TRIM(Alphas(9)))
CALL ShowContinueError('A schedule with this name is not defined in this input data file.')
ErrorsFound=.TRUE.
END IF
END IF
! Get volumetric flow rate if applicable
IF (RefrigRack(RackNum)%FlowType==ConstantFlow) THEN
RefrigRack(RackNum)%DesVolFlowRate = Numbers(3)
RefrigRack(RackNum)%VolFlowRate = Numbers(3)
END IF
! Get maximum flow rates
RefrigRack(RackNum)%VolFlowRateMax = Numbers(4)
! Check constant flow for max violation, if applicable
IF (RefrigRack(RackNum)%FlowType==ConstantFlow .AND. RefrigRack(RackNum)%VolFlowRate>Numbers(4)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigRack(RackNum)%Name)//&
'" '//TRIM(cNumericFieldNames(3))//' > '//TRIM(cNumericFieldNames(4))//'.')
CALL ShowContinueError('Revise flow rates.')
ErrorsFound=.TRUE.
END IF
! Get max/min allowed water temps
RefrigRack(RackNum)%OutletTempMax = Numbers(5)
RefrigRack(RackNum)%InletTempMin = Numbers(6)
! set hardware limits on Node data structure for plant interactions
!Node(RefrigRack(RackNum)%InletNode)%MassFlowRateMax = RefrigRack(RackNum)%MassFlowRateMax !CR7425
!Node(RefrigRack(RackNum)%InletNode)%MassFlowRateMin = 0.0D0 !CR7435
! set flow request for plant sizing.
CALL RegisterPlantCompDesignFlow(RefrigRack(RackNum)%InletNode, RefrigRack(RackNum)%VolFlowRateMax)
END IF !Water cooled condenser data
! Get evaporative cooled condenser input
IF (lAlphaBlanks(10)) THEN
RefrigRack(RackNum)%EvapSchedPtr = 0
ELSE
RefrigRack(RackNum)%EvapSchedPtr = GetScheduleIndex(Alphas(10)) ! convert schedule name to pointer
! check availability schedule for values >= 0
IF (RefrigRack(RackNum)%EvapSchedPtr > 0)THEN
IF (.NOT. CheckScheduleValueMinMax(RefrigRack(RackNum)%EvapSchedPtr,'>=',0.0d0)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigRack(RackNum)%Name)//'" .')
CALL ShowContinueError('Error found in '//TRIM(cAlphaFieldNames(10))//' = '//TRIM(Alphas(10)))
CALL ShowContinueError('schedule values must be (>=0.).')
ErrorsFound=.TRUE.
END IF
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigRack(RackNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(10))//' = '//TRIM(Alphas(10)))
CALL ShowContinueError('A schedule with this name is not defined in this input data file.')
ErrorsFound=.TRUE.
END IF
END IF
RefrigRack(RackNum)%EvapEffect= Numbers(7)
IF (RefrigRack(RackNum)%EvapEffect < 0.0d0 .OR. RefrigRack(RackNum)%EvapEffect > 1.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigRack(RackNum)%Name)//&
'" '//TRIM(cNumericFieldNames(7))//' cannot be less than zero or greater than 1.0.')
ErrorsFound = .TRUE.
END IF
RefrigRack(RackNum)%CondenserAirFlowRate = Numbers(8)
IF (RefrigRack(RackNum)%CondenserType == RefrigCondenserTypeEvap .AND. RefrigRack(RackNum)%CondenserAirFlowRate <= 0.0d0 &
.AND. RefrigRack(RackNum)%CondenserAirFlowRate /= AutoCalculate) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigRack(RackNum)%Name)//&
'", '//TRIM(cNumericFieldNames(8))//' cannot be less than or equal to zero.')
ErrorsFound = .TRUE.
END IF
! Basin heater power as a function of temperature must be greater than or equal to 0
RefrigRack(RackNum)%BasinHeaterPowerFTempDiff = Numbers(9)
IF(RefrigRack(RackNum)%CondenserType == RefrigCondenserTypeEvap .AND. Numbers(9) < 0.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="' //TRIM(RefrigRack(RackNum)%Name)//&
'", '//TRIM(cNumericFieldNames(9))//' must be >= 0')
ErrorsFound = .TRUE.
END IF
RefrigRack(RackNum)%BasinHeaterSetPointTemp = Numbers(10)
IF(RefrigRack(RackNum)%CondenserType == RefrigCondenserTypeEvap .AND. RefrigRack(RackNum)%BasinHeaterSetPointTemp < 2.0d0) THEN
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(RefrigRack(RackNum)%Name)//&
'", '//TRIM(cNumericFieldNames(10))//' is less than 2 deg C. Freezing could occur.')
END IF
RefrigRack(RackNum)%EvapPumpPower = Numbers(11)
IF(RefrigRack(RackNum)%CondenserType == RefrigCondenserTypeEvap .AND. RefrigRack(RackNum)%EvapPumpPower < 0.0d0 &
.AND. RefrigRack(RackNum)%EvapPumpPower /= AutoCalculate) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigRack(RackNum)%Name)//&
'", '//TRIM(cNumericFieldNames(11))//' cannot be less than zero.')
ErrorsFound = .TRUE.
END IF
! Get Water System tank connections
RefrigRack(RackNum)%SupplyTankName = Alphas(11)
IF (lAlphaBlanks(11)) THEN
RefrigRack(RackNum)%EvapWaterSupplyMode = WaterSupplyFromMains
ELSE
RefrigRack(RackNum)%EvapWaterSupplyMode = WaterSupplyFromTank
CALL SetupTankDemandComponent(RefrigRack(RackNum)%Name, CurrentModuleObject, &
RefrigRack(RackNum)%SupplyTankName, ErrorsFound, RefrigRack(RackNum)%EvapWaterSupTankID, &
RefrigRack(RackNum)%EvapWaterTankDemandARRID)
ENDIF
! Check condenser air inlet node connection
IF (lAlphaBlanks(12)) THEN
RefrigRack(RackNum)%OutsideAirNodeNum = 0
ELSE
RefrigRack(RackNum)%OutsideAirNodeNum = &
GetOnlySingleNode(Alphas(12),ErrorsFound,CurrentModuleObject,Alphas(1), &
NodeType_Air,NodeConnectionType_OutsideAirReference,1,ObjectIsParent)
IF(.not. CheckOutAirNodeNumber(RefrigRack(RackNum)%OutsideAirNodeNum))THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigRack(RackNum)%Name)//&
'", '//TRIM(cAlphaFieldNames(12))//' not found: '//TRIM(Alphas(12)))
CALL ShowContinueError('...does not appear in an OutdoorAir:NodeList or as an OutdoorAir:Node.')
ErrorsFound = .TRUE.
END IF
ENDIF
IF (.NOT. lAlphaBlanks(13)) RefrigRack(RackNum)%EndUseSubcategory = Alphas(13)
!Read all loads on this rack: cases and walk-ins and coils
NumCases = 0
NumCoils = 0
NumWalkIns = 0
RefrigRack(RackNum)%NumCases = 0
RefrigRack(RackNum)%NumCoils = 0
RefrigRack(RackNum)%NumWalkIns = 0
RefrigRack(RackNum)%TotalRackLoad = 0.0d0
! Read display case and walkin assignments for this rack
AlphaNum = 14
IF(lAlphaBlanks(AlphaNum) ) THEN
!No cases or walkins or coils specified, ie, rack has no load
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigRack(RackNum)%Name)// &
'" : has no loads, must have at least one of: '//TRIM(cAlphaFieldNames(14)))
ErrorsFound = .TRUE.
ELSE ! (.NOT. lAlphaBlanks(AlphaNum))
! Entry for Alphas(AlphaNum) can be either a Case, WalkIn, Coil, or CaseAndWalkInList name
CaseAndWalkInListNum=0
CaseNum=0
WalkInNum=0
CoilNum=0
IF(NumSimulationCaseAndWalkInLists > 0) &
CaseAndWalkInListNum=FindItemInList(Alphas(AlphaNum),CaseAndWalkInList%Name,NumSimulationCaseAndWalkInLists)
IF(NumSimulationCases > 0)CaseNum=FindItemInList(Alphas(AlphaNum),RefrigCase%Name,NumSimulationCases)
IF(NumSimulationWalkIns > 0)WalkInNum=FindItemInList(Alphas(AlphaNum),WalkIn%Name,NumSimulationWalkIns)
IF(NumSimulationRefrigAirChillers > 0) &
CoilNum=FindItemInList(Alphas(AlphaNum),WarehouseCoil%Name,NumSimulationRefrigAirChillers)
NumNameMatches = 0
IF(CaseAndWalkInListNum /= 0)NumNameMatches = NumNameMatches +1
IF(CaseNum /= 0) NumNameMatches = NumNameMatches +1
IF(WalkInNum /= 0) NumNameMatches = NumNameMatches +1
IF(CoilNum /= 0) NumNameMatches = NumNameMatches +1
IF (NumNameMatches /= 1) THEN !name must uniquely point to a list or a single case or walkin
ErrorsFound = .TRUE.
IF(NumNameMatches == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigRack(RackNum)%Name)//&
'" : has an invalid '//TRIM(cAlphaFieldNames(AlphaNum))//': '//TRIM(Alphas(AlphaNum)))
ELSEIF(NumNameMatches > 1) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//&
TRIM(RefrigRack(RackNum)%Name)//'" : has a non-unique name '//&
'that could be either a '//TRIM(cAlphaFieldNames(AlphaNum))//': '//TRIM(Alphas(AlphaNum)))
END IF !num matches = 0 or > 1
ELSEIF(CaseAndWalkInListNum /= 0) THEN !Name points to a CaseAndWalkInList
NumCoils = CaseAndWalkInList(CaseAndWalkInListNum)%NumCoils
NumCases = CaseAndWalkInList(CaseAndWalkInListNum)%NumCases
NumWalkIns = CaseAndWalkInList(CaseAndWalkInListNum)%NumWalkIns
RefrigRack(RackNum)%NumCoils = NumCoils
RefrigRack(RackNum)%NumCases = NumCases
RefrigRack(RackNum)%NumWalkIns = NumWalkIns
IF(.NOT. ALLOCATED(RefrigRack(RackNum)%CoilNum))ALLOCATE(RefrigRack(RackNum)%CoilNum(NumCoils))
RefrigRack(RackNum)%CoilNum(1:NumCoils) = CaseAndWalkInList(CaseAndWalkInListNum)%CoilItemNum(1:NumCoils)
IF(.NOT. ALLOCATED(RefrigRack(RackNum)%CaseNum))ALLOCATE(RefrigRack(RackNum)%CaseNum(NumCases))
RefrigRack(RackNum)%CaseNum(1:NumCases) = CaseAndWalkInList(CaseAndWalkInListNum)%CaseItemNum(1:NumCases)
IF(.NOT. ALLOCATED(RefrigRack(RackNum)%WalkInNum))ALLOCATE(RefrigRack(RackNum)%WalkInNum(NumWalkIns))
RefrigRack(RackNum)%WalkInNum(1:NumWalkIns) = CaseAndWalkInList(CaseAndWalkInListNum)%WalkInItemNum(1:NumWalkIns)
ELSEIF (CoilNum /= 0) THEN !Name points to a coil
NumCoils = 1
RefrigRack(RackNum)%NumCoils = 1
IF(.NOT. ALLOCATED(RefrigRack(RackNum)%CoilNum)) ALLOCATE(RefrigRack(RackNum)%CoilNum(NumCoils))
RefrigRack(RackNum)%CoilNum(NumCoils)=CoilNum
ELSEIF (CaseNum /= 0) THEN !Name points to a case
NumCases = 1
RefrigRack(RackNum)%NumCases = 1
IF(.NOT. ALLOCATED(RefrigRack(RackNum)%CaseNum)) ALLOCATE(RefrigRack(RackNum)%CaseNum(NumCases))
RefrigRack(RackNum)%CaseNum(NumCases)=CaseNum
ELSEIF (WalkInNum /= 0) THEN !Name points to a walkin
NumWalkIns = 1
RefrigRack(RackNum)%NumWalkIns = 1
IF(.NOT. ALLOCATED(RefrigRack(RackNum)%WalkInNum)) &
ALLOCATE(RefrigRack(RackNum)%WalkInNum(NumWalkIns))
RefrigRack(RackNum)%WalkInNum(NumWalkIns)=WalkInNum
END IF !NumNameMatches /= 1
END IF !blank input for loads on rack
IF (NumCases > 0) THEN
DO CaseIndex = 1, NumCases
CaseID=RefrigRack(RackNum)%CaseNum(CaseIndex)
!mark all cases on rack as used by this system (checking for unused or non-unique cases)
RefrigCase(CaseID)%NumSysAttach = RefrigCase(CaseID)%NumSysAttach + 1
!determine total capacity on rack
RefrigRack(RackNum)%TotalRackLoad = RefrigRack(RackNum)%TotalRackLoad + RefrigCase(CaseID)%DesignRatedCap
END DO !CaseIndex=1,NumCases
! check that all refrigerated cases attached to a rack are to the same zone if heat rejection location is "Zone"
! however, won't matter if walk-in specified
IF(RefrigRack(RackNum)%HeatRejectionLocation == LocationZone .AND. RefrigRack(RackNum)%NumCases > 1 .AND. &
RefrigCase(RefrigRack(RackNum)%CaseNum(1))%ActualZoneNum /= 0 .AND. NumWalkIns < 1 .AND. &
NumCoils < 1 ) THEN
ZoneNum = RefrigCase(RefrigRack(RackNum)%CaseNum(1))%ActualZoneNum
DO CaseIndex = 2,RefrigRack(RackNum)%NumCases
IF(RefrigCase(RefrigRack(RackNum)%CaseNum(CaseIndex))%ActualZoneNum == ZoneNum)CYCLE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//&
TRIM(RefrigRack(RackNum)%Name)//'" : All cases '//&
'attached to a rack must be in the same zone when '//TRIM(cAlphaFieldNames(2))//&
' equals "Zone".')
ErrorsFound = .TRUE.
EXIT
END DO
END IF ! heat rejection location is zone
END IF ! numcases > 0
IF (NumCoils > 0) THEN
RefrigRack(RackNum)%CoilFlag = .TRUE.
DO CoilIndex = 1, NumCoils
CoilNum=RefrigRack(RackNum)%CoilNum(CoilIndex)
!mark all Coils on rack as used by this system (checking for unused or non-unique Coils)
WarehouseCoil(CoilNum)%NumSysAttach = WarehouseCoil(CoilNum)%NumSysAttach + 1
!determine total capacity on rack
RefrigRack(RackNum)%TotalRackLoad = RefrigRack(RackNum)%TotalRackLoad + WarehouseCoil(CoilNum)%RatedSensibleCap
END DO !CoilIndex=1,NumCoils
END IF !numcoils > 0
IF (NumWalkIns > 0) THEN
DO WalkInIndex = 1, NumWalkIns
WalkInID=RefrigRack(RackNum)%WalkInNum(WalkInIndex)
!mark all WalkIns on rack as used by this system (checking for unused or non-unique WalkIns)
WalkIn(WalkInID)%NumSysAttach = WalkIn(WalkInID)%NumSysAttach + 1
!determine total capacity on rack
RefrigRack(RackNum)%TotalRackLoad = RefrigRack(RackNum)%TotalRackLoad + WalkIn(WalkInID)%DesignRatedCap
END DO !WalkInIndex=1,NumWalkIns
END IF !NumWalkins
IF (NumWalkIns > 0 .OR. NumCoils > 0) THEN
!Get the heat rejection Zone node number from the zone name entered by the user (if heatrej location = zone)
IF (RefrigRack(RackNum)%HeatRejectionLocation==LocationZone) THEN
IF ( lalphablanks(15)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigRack(RackNum)%Name)// &
TRIM(cAlphaFieldNames(15))//&
' must be input if walkins or AirChillers connected to rack and heat rejection location = zone.')
ErrorsFound=.TRUE.
ELSE ! alpha (15) not blank
RefrigRack(RackNum)%HeatRejectionZoneNum = FindItemInList(Alphas(15),Zone%Name,NumOfZones)
RefrigRack(RackNum)%HeatRejectionZoneNodeNum = GetSystemNodeNumberForZone(Alphas(15))
IF (RefrigRack(RackNum)%HeatRejectionZoneNum == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(RefrigRack(RackNum)%Name)// &
'", invalid '//TRIM(cAlphaFieldNames(15))//' not valid: '//TRIM(Alphas(15)))
ErrorsFound=.TRUE.
ELSE
RefrigPresentInZone(RefrigRack(RackNum)%HeatRejectionZoneNum) = .TRUE.
END IF !zonenum == 0
END IF ! alpha 15 blank
END IF ! zone heat rej and walk-ins or coils present, must input heat rejection zone
END IF !numwalkins or coils > 0
! set condenser air flow and evap water pump power if autocalculated
! autocalculate condenser evap water pump if needed
IF(RefrigRack(RackNum)%CondenserType==RefrigCondenserTypeEvap .AND. RefrigRack(RackNum)%EvapPumpPower==AutoCalculate) THEN
RefrigRack(RackNum)%EvapPumpPower = CondPumpRatePower * RefrigRack(RackNum)%TotalRackLoad
END IF
! autocalculate evap condenser air volume flow rate if needed
IF(RefrigRack(RackNum)%CondenserType==RefrigCondenserTypeEvap .AND. &
RefrigRack(RackNum)%CondenserAirFlowRate==AutoCalculate) THEN
RefrigRack(RackNum)%CondenserAirFlowRate = AirVolRateEvapCond * RefrigRack(RackNum)%TotalRackLoad
END IF
END DO !RackNum=1,NumRefrigeratedRacks
ALLOCATE(CheckEquipNameRackWaterCondenser(NumRefrigeratedRacks))
CheckEquipNameRackWaterCondenser = .TRUE.
END IF !(NumRefrigeratedRacks > 0)
IF(NumRefrigSystems > 0 .OR. NumTransRefrigSystems >0) THEN
IF(NumRefrigSystems > 0 .AND. NumRefrigCondensers == 0) THEN
CALL ShowSevereError('Refrigeration:System objects were found during input processing, however '// &
'no Rrefrigeration condenser objects (which may be either: ')
CALL ShowContinueError(' Refrigeration:Condenser:AirCooled, Refrigeration:Condenser:WaterCooled, '// &
' Refrigeration:Condenser:EvaporativeCooled,or Refrigeration:Condenser:CascadeCooled) were found.')
ErrorsFound = .TRUE.
END IF
IF(NumTransRefrigSystems > 0 .AND. NumSimulationGasCooler == 0) THEN
CALL ShowSevereError('Refrigeration:TranscriticalSystem objects were found during input processing, however '// &
'no Refrigeration gas cooler objects (Refrigeration:GasCooler:AirCooled) were found.')
ErrorsFound = .TRUE.
END IF
IF(NumSimulationCompressors == 0) THEN
CALL ShowSevereError('Refrigeration:System objects were found during input processing, however '// &
'no Refrigeration:Compressor objects were found.')
ErrorsFound = .TRUE.
END IF
!************ START CONDENSER INPUT **************
IF(NumSimulationCondAir > 0) THEN
CurrentModuleObject='Refrigeration:Condenser:AirCooled'
DO CondNum=1,NumSimulationCondAir
CALL GetObjectItem(CurrentModuleObject,CondNum,Alphas,NumAlphas,Numbers,NumNumbers,IOStatus, &
NumBlank=lNumericBlanks,AlphaBlank=lAlphaBlanks, &
AlphaFieldNames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
IsNotOK =.FALSE.
IsBlank =.FALSE.
CALL VerifyName(Alphas(1),Condenser%Name,CondNum-1,IsNotOK,IsBlank,CurrentModuleObject//' Name')
IF (IsNotOK) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//', has an invalid or undefined '// &
TRIM(cAlphaFieldNames(1))//' = '//TRIM(Alphas(1)))
IF (IsBlank) Alphas(1)='xxxxx'
ErrorsFound=.TRUE.
ENDIF !IsNotOK on Verify Name
Condenser(CondNum)%Name = Alphas(1)
HeatReclaimRefrigCondenser(CondNum)%Name=Alphas(1)
Condenser(CondNum)%CapCurvePtr = GetCurveIndex(Alphas(2)) ! convert curve name to number
IF (Condenser(CondNum)%CapCurvePtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(2))//' not found:'//TRIM(Alphas(2)))
ErrorsFound = .TRUE.
END IF
!set start of count for number of systems attached to this condenser
Condenser(CondNum)%NumSysAttach = 0
IF(.NOT. ALLOCATED(Condenser(CondNum)%SysNum))&
ALLOCATE(Condenser(CondNum)%SysNum(NumRefrigSystems))
!set CondenserType and rated temperature difference (51.7 - 35)C per ARI 460
Condenser(CondNum)%CondenserType = RefrigCondenserTypeAir
HeatReclaimRefrigCondenser(CondNum)%SourceType=RefrigCondenserTypeAir
Condenser(CondNum)%RatedDelT = CondARI460DelT != 16.7d0 ,Rated sat cond temp - dry bulb air T for air-cooled Condensers, ARI460
Condenser(CondNum)%RatedTCondense= CondARI460Tcond
if (Condenser(CondNum)%CapCurvePtr > 0) then
Condenser(CondNum)%RatedCapacity=CurveValue(Condenser(CondNum)%CapCurvePtr,CondARI460DelT)
endif
!elevation capacity correction on air-cooled condensers, Carrier correlation more conservative than Trane
Condenser(CondNum)%RatedCapacity = Condenser(CondNum)%RatedCapacity*(1.d0 - 7.17D-5*Elevation)
IF(Condenser(CondNum)%RatedCapacity > 0.d0) THEN
CALL GetCurveMinMaxValues(Condenser(CondNum)%CapCurvePtr,DelTempMin,DelTempMax)
Capmin=CurveValue(Condenser(CondNum)%CapCurvePtr,DelTempMin)*(1.d0 - 7.17D-5*Elevation)!Mar 2011 bug fix
Capmax=CurveValue(Condenser(CondNum)%CapCurvePtr,DelTempMax)*(1.d0 - 7.17D-5*Elevation)!Mar 2011 bug
Condenser(CondNum)%TempSlope=(DelTempMax-DelTempMin)/((Capmax-Capmin))!*(1.d0 - 7.17D-5*Elevation))!Mar 2011 bug fix
Condenser(CondNum)%MinCondLoad=Capmax-DelTempMax/Condenser(CondNum)%TempSlope
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'" Condenser capacity curve per ARI 460 must be input and must be greater than 0 Watts at 16.7C'// &
' temperature difference.')
ErrorsFound = .TRUE.
END IF
Condenser(CondNum)%RatedSubcool = 0.0d0 !default value
IF(.NOT. lNumericBlanks(1)) Condenser(CondNum)%RatedSubcool = Numbers(1)
! Get fan control type
IF (SameString(Alphas(3),'Fixed')) THEN
Condenser(CondNum)%FanSpeedControlType = FanConstantSpeed
ELSE IF (SameString(Alphas(3),'FixedLinear')) THEN
Condenser(CondNum)%FanSpeedControlType = FanConstantSpeedLinear
ELSE IF (SameString(Alphas(3),'VariableSpeed')) THEN
Condenser(CondNum)%FanSpeedControlType = FanVariableSpeed
ELSE IF (SameString(Alphas(3),'TwoSpeed')) THEN
Condenser(CondNum)%FanSpeedControlType = FanTwoSpeed
ELSE
Condenser(CondNum)%FanSpeedControlType = FanConstantSpeed !default
END IF !Set fan control type
IF(.NOT. lNumericBlanks(2)) Condenser(CondNum)%RatedFanPower = Numbers(2)
IF((lNumericBlanks(2)) .OR. (Numbers(2) < 0.0d0)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'" '//TRIM(cNumericFieldNames(2))//' must be input greater than or equal to 0 Watts.')
ErrorsFound = .TRUE.
END IF
Condenser(CondNum)%FanMinAirFlowRatio = 0.2d0 !default value
IF(.NOT. lNumericBlanks(3)) Condenser(CondNum)%FanMinAirFlowRatio = Numbers(3)
! Check condenser air inlet node connection
! Jan 2011 - added ability to reject heat to a zone from air-cooled condenser
Condenser(CondNum)%CondenserRejectHeatToZone = .FALSE.
IF (lAlphaBlanks(4)) THEN
Condenser(CondNum)%InletAirNodeNum = 0
ELSE !see if it's an outside air node name or an indoor zone name,
!have to check inside first because outside check automatically generates an error message
Condenser(CondNum)%InletAirZoneNum = FindItemInList(Alphas(4),Zone%Name,NumOfZones)
!need to clearly id node number for air inlet conditions and zone number for casecredit assignment
IF(Condenser(CondNum)%InletAirZoneNum /= 0) THEN
!set condenser flag (later used to set system flag) and zone flag
Condenser(CondNum)%InletAirNodeNum = GetSystemNodeNumberForZone(Alphas(4))
Condenser(CondNum)%CondenserRejectHeatToZone = .TRUE.
RefrigPresentInZone(Condenser(CondNum)%InletAirZoneNum) = .TRUE.
ELSE ! not in a conditioned zone, so see if it's outside
Condenser(CondNum)%InletAirNodeNum = &
GetOnlySingleNode(Alphas(4),ErrorsFound,CurrentModuleObject,Alphas(1), &
NodeType_Air,NodeConnectionType_OutsideAirReference,1,ObjectIsParent)
IF(.NOT. CheckOutAirNodeNumber(Condenser(CondNum)%InletAirNodeNum))THEN
! not outside and not a zone
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'", '//TRIM(cAlphaFieldNames(4))//' not found: '//TRIM(Alphas(4)))
CALL ShowContinueError('...does not appear in an OutdoorAir:NodeList or as an OutdoorAir:Node or as a Zone.')
ErrorsFound = .TRUE.
END IF !checkoutairnodenumber
END IF !InletAirZoneNum \=0
END IF ! Condenser air inlet node connection
Condenser(CondNum)%EndUseSubcategory =' '
IF (.NOT. lAlphaBlanks(5)) Condenser(CondNum)%EndUseSubcategory = Alphas(5)
Condenser(CondNum)%RefOpCharge = 0.0d0
Condenser(CondNum)%RefReceiverInventory = 0.0d0
Condenser(CondNum)%RefPipingInventory = 0.0d0
IF (.NOT. lNumericBlanks(4)) Condenser(CondNum)%RefOpCharge = Numbers(4)
IF (.NOT. lNumericBlanks(5)) Condenser(CondNum)%RefReceiverInventory = Numbers(5)
IF (.NOT. lNumericBlanks(6)) Condenser(CondNum)%RefPipingInventory = Numbers(6)
END DO ! Read input for REFRIGERATION:Condenser:AirCooled
END IF ! NumSimulationCondAir > 0
IF(NumSimulationCondEvap > 0)THEN
CurrentModuleObject='Refrigeration:Condenser:EvaporativeCooled'
DO CondIndex=1,NumSimulationCondEvap
CondNum=CondIndex + NumSimulationCondAir
CALL GetObjectItem(CurrentModuleObject,CondIndex,Alphas,NumAlphas,Numbers,NumNumbers,IOStatus, &
NumBlank=lNumericBlanks,AlphaBlank=lAlphaBlanks, &
AlphaFieldNames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
IsNotOK =.FALSE.
IsBlank =.FALSE.
CALL VerifyName(Alphas(1),Condenser%Name,CondNum-1,IsNotOK,IsBlank,CurrentModuleObject//' Name')
IF (IsNotOK) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//', has an invalid or undefined '// &
TRIM(cAlphaFieldNames(1))//'="'//TRIM(Alphas(1))//'".')
IF (IsBlank) Alphas(1)='xxxxx'
ErrorsFound=.TRUE.
ENDIF !IsNotOK on Verify Name
Condenser(CondNum)%Name = Alphas(1)
HeatReclaimRefrigCondenser(CondNum)%Name=Alphas(1)
!set start of count for number of systems attached to this condenser
Condenser(CondNum)%NumSysAttach = 0
IF(.NOT. ALLOCATED(Condenser(CondNum)%SysNum))&
ALLOCATE(Condenser(CondNum)%SysNum(NumRefrigSystems))
!set CondenserType and rated Heat Rejection per ARI 490 rating
Condenser(CondNum)%CondenserType = RefrigCondenserTypeEvap
HeatReclaimRefrigCondenser(CondNum)%SourceType=RefrigCondenserTypeEvap
Condenser(CondNum)%RatedTCondense= CondARI490Tcond
Condenser(CondNum)%RatedDelT = CondARI490DelT
IF ((.NOT. lNumericBlanks(1)).AND.(Numbers(1)> 0.0d0)) THEN
Condenser(CondNum)%RatedCapacity = Numbers(1)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'" '//TRIM(cNumericFieldNames(1))//' per ARI 490 must be input and must be greater than 0 Watts.')
ErrorsFound = .TRUE.
END IF
!Calculate capacity elevation derate factor per ARI 490 barometric pressure correction factor
Condenser(CondNum)%EvapElevFact=1.d0-3.074D-5*Elevation
Condenser(CondNum)%RatedSubcool = 0.0d0 !default value
IF((.NOT. lNumericBlanks(2)).AND.(Numbers(2)> 0.0d0)) Condenser(CondNum)%RatedSubcool = Numbers(2)
! Get fan control type
IF (SameString(Alphas(2),'Fixed')) THEN
Condenser(CondNum)%FanSpeedControlType = FanConstantSpeed
ELSE IF (SameString(Alphas(3),'FixedLinear')) THEN
Condenser(CondNum)%FanSpeedControlType = FanConstantSpeedLinear
ELSE IF (SameString(Alphas(2),'VariableSpeed')) THEN
Condenser(CondNum)%FanSpeedControlType = FanVariableSpeed
ELSE IF (SameString(Alphas(2),'TwoSpeed')) THEN
Condenser(CondNum)%FanSpeedControlType = FanTwoSpeed
ELSE
Condenser(CondNum)%FanSpeedControlType = FanConstantSpeed !default
END IF !Set fan control type
Condenser(CondNum)%RatedFanPower = Numbers(3)
IF(Numbers(3) < 0.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'" '//TRIM(cNumericFieldNames(3))//' must be greater than or equal to 0 Watts.')
ErrorsFound = .TRUE.
END IF
Condenser(CondNum)%FanMinAirFlowRatio = 0.2d0 !default value
IF(.NOT. lNumericBlanks(4)) Condenser(CondNum)%FanMinAirFlowRatio = Numbers(4)
!Enter min and max and default coefficients for evap condenser HRCF correlation
!Defaults taken from 2008 BAC equipment for R22, R134a, series CXV
!Correlation coefficients for other manufacturers are very similar per Hugh Henderson's work
Condenser(CondNum)%EvapCoeff1=6.63d0
Condenser(CondNum)%EvapCoeff2=0.468d0
Condenser(CondNum)%EvapCoeff3=17.93d0
Condenser(CondNum)%EvapCoeff4=-.322d0
Condenser(CondNum)%MinCapFacEvap=0.5d0
Condenser(CondNum)%MaxCapFacEvap=5.0d0
NumNum = 5 !added warnings if below not blank but unused due to limits
IF(.NOT. lNumericBlanks(NumNum)) THEN
IF(Numbers(NumNum)>= 0.0d0) THEN
Condenser(CondNum)%EvapCoeff1=Numbers(NumNum)
ELSE
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' is less than 0 and was not used. Default was used.')
ENDIF
ENDIF
NumNum = 6 ! EvapCoeff2 can't be equal to 0 because used in a denominator
IF(.NOT. lNumericBlanks(NumNum)) THEN
IF (Numbers(NumNum)> 0.0d0) THEN
Condenser(CondNum)%EvapCoeff2=Numbers(NumNum)
ELSE
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' is less than or equal to 0 and was not used. Default was used.')
ENDIF
ENDIF
NumNum = 7
IF(.NOT. lNumericBlanks(NumNum)) THEN
IF(Numbers(NumNum)>= 0.0d0) THEN
Condenser(CondNum)%EvapCoeff3=Numbers(NumNum)
ELSE
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' is less than 0 and was not used. Default was used.')
ENDIF
ENDIF
NumNum = 8
IF(.NOT. lNumericBlanks(NumNum)) THEN
IF(Numbers(NumNum)>= -20.0d0) THEN
Condenser(CondNum)%EvapCoeff4=Numbers(NumNum)
ELSE
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' is less than -20 and was not used. Default was used.')
ENDIF
ENDIF
NumNum = 9
IF(.NOT. lNumericBlanks(NumNum)) THEN
IF(Numbers(NumNum)>= 0.0d0)THEN
Condenser(CondNum)%MinCapFacEvap=Numbers(NumNum)
ELSE
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' is less than 0 and was not used. Default was used.')
ENDIF
ENDIF
NumNum = 10
IF(.NOT. lNumericBlanks(NumNum)) THEN
IF(Numbers(NumNum)>= 0.0d0) THEN
Condenser(CondNum)%MaxCapFacEvap=Numbers(NumNum)
ELSE
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' is less than 0 and was not used. Default was used.')
ENDIF
ENDIF
! Check condenser air inlet node connection
IF (lAlphaBlanks(3)) THEN
Condenser(CondNum)%InletAirNodeNum = 0
ELSE
Condenser(CondNum)%InletAirNodeNum = &
GetOnlySingleNode(Alphas(3),ErrorsFound,CurrentModuleObject,Alphas(1), &
NodeType_Air,NodeConnectionType_OutsideAirReference,1,ObjectIsParent)
IF(.not. CheckOutAirNodeNumber(Condenser(CondNum)%InletAirNodeNum))THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'", '//TRIM(cAlphaFieldNames(3))//' not found: '//TRIM(Alphas(3)))
CALL ShowContinueError('...does not appear in an OutdoorAir:NodeList or as an OutdoorAir:Node.')
ErrorsFound = .TRUE.
END IF
END IF ! Condenser air inlet node connection
NumNum = 11
Condenser(CondNum)%RatedAirFlowRate = Numbers(NumNum)
! Note the autocalculate feature for this value takes place in the system section because
! it is a function of the total cooling capacity of the cases served by the condenser
! Evaporative condensers basin heater power as a function of temperature must be greater than or equal to 0
NumNum = 12
Condenser(CondNum)%BasinHeaterPowerFTempDiff = Numbers(NumNum)
IF(Numbers(NumNum) < 0.0d0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="' //TRIM(Condenser(CondNum)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' must be >= 0')
ErrorsFound = .TRUE.
END IF
NumNum = 13
Condenser(CondNum)%BasinHeaterSetPointTemp = 2.0d0 !default
IF(.NOT. lNumericBlanks(NumNum)) Condenser(CondNum)%BasinHeaterSetPointTemp = Numbers(NumNum)
IF(Condenser(CondNum)%BasinHeaterSetPointTemp < 2.0d0) THEN
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'", '//TRIM(cNumericFieldNames(NumNum))//' is less than 2 deg C. Freezing could occur.')
END IF
NumNum = 14
Condenser(CondNum)%EvapPumpPower = 1000.d0 !default
IF(.NOT. lNumericBlanks(NumNum)) Condenser(CondNum)%EvapPumpPower = Numbers(NumNum)
! Note the autocalculate feature for this value takes place in the system section because
! it is a function of the total cooling capacity of the cases served by the condenser
! Get Evaporative Water System tank connections
Condenser(CondNum)%SupplyTankName = Alphas(4)
IF (lAlphaBlanks(4)) THEN
Condenser(CondNum)%EvapWaterSupplyMode = WaterSupplyFromMains
ELSE
Condenser(CondNum)%EvapWaterSupplyMode = WaterSupplyFromTank
CALL SetupTankDemandComponent(Condenser(CondNum)%Name,CurrentModuleObject, &
Condenser(CondNum)%SupplyTankName, ErrorsFound, Condenser(CondNum)%EvapWaterSupTankID, &
Condenser(CondNum)%EvapWaterTankDemandARRID)
END IF
IF (lAlphaBlanks(5)) THEN
Condenser(CondNum)%EvapSchedPtr = 0
ELSE
Condenser(CondNum)%EvapSchedPtr = GetScheduleIndex(Alphas(5)) ! convert schedule name to pointer
! check availability schedule for values >= 0
IF (Condenser(CondNum)%EvapSchedPtr > 0)THEN
IF (.NOT. CheckScheduleValueMinMax(Condenser(CondNum)%EvapSchedPtr,'>=',0.0d0)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'" .')
CALL ShowContinueError('Error found in '//TRIM(cAlphaFieldNames(5))//' = '//TRIM(Alphas(5)))
CALL ShowContinueError('schedule values must be (>=0.).')
ErrorsFound=.TRUE.
END IF
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(5))//' = '//TRIM(Alphas(5)))
CALL ShowContinueError('A schedule with this name is not defined in this input data file.')
ErrorsFound=.TRUE.
END IF
END IF ! Set Evap Schedule Pointer
Condenser(CondNum)%EndUseSubcategory =' '
IF (.NOT. lAlphaBlanks(6)) Condenser(CondNum)%EndUseSubcategory = Alphas(6)
Condenser(CondNum)%RefOpCharge = 0.0d0
Condenser(CondNum)%RefReceiverInventory = 0.0d0
Condenser(CondNum)%RefPipingInventory = 0.0d0
NumNum = 15
IF (.NOT. lNumericBlanks(NumNum)) Condenser(CondNum)%RefOpCharge = Numbers(NumNum)
NumNum = 16
IF (.NOT. lNumericBlanks(NumNum)) Condenser(CondNum)%RefReceiverInventory = Numbers(NumNum)
NumNum = 17
IF (.NOT. lNumericBlanks(NumNum)) Condenser(CondNum)%RefPipingInventory = Numbers(NumNum)
END DO ! Read input for CONDENSER:REFRIGERATION:EVAPorativeCooled
END IF ! If NumSimulationCondEvap > 0
IF(NumSimulationCondWater > 0)THEN
CurrentModuleObject='Refrigeration:Condenser:WaterCooled'
DO CondIndex=1,NumSimulationCondWater
CondNum=CondIndex + NumSimulationCondAir + NumSimulationCondEvap
CALL GetObjectItem(CurrentModuleObject,CondIndex,Alphas,NumAlphas,Numbers,NumNumbers,IOStatus,&
NumBlank=lNumericBlanks,AlphaBlank=lAlphaBlanks, &
AlphaFieldNames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
IsNotOK =.FALSE.
IsBlank =.FALSE.
CALL VerifyName(Alphas(1),Condenser%Name,CondNum-1,IsNotOK,IsBlank,CurrentModuleObject//' Name')
IF (IsNotOK) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//', has an invalid or undefined '// &
TRIM(cAlphaFieldNames(1))//'="'//TRIM(Alphas(1))//'".')
IF (IsBlank) Alphas(1)='xxxxx'
ErrorsFound=.TRUE.
ENDIF !IsNotOK on Verify Name
Condenser(CondNum)%Name = Alphas(1)
HeatReclaimRefrigCondenser(CondNum)%Name=Alphas(1)
!set start of count for number of systems attached to this condenser
Condenser(CondNum)%NumSysAttach = 0
IF(.NOT. ALLOCATED(Condenser(CondNum)%SysNum))&
ALLOCATE(Condenser(CondNum)%SysNum(NumRefrigSystems))
!set CondenserType and rated Heat Rejection per ARI 450 rating
Condenser(CondNum)%CondenserType = RefrigCondenserTypeWater
HeatReclaimRefrigCondenser(CondNum)%SourceType=RefrigCondenserTypeWater
IF ((.NOT. lNumericBlanks(1)).AND.(Numbers(1)> 0.0d0)) THEN
Condenser(CondNum)%RatedCapacity = Numbers(1)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'" '//TRIM(cNumericFieldNames(1))//' per ARI 450 must be input and must be greater than 0 Watts.')
ErrorsFound = .TRUE.
END IF
IF ((.NOT. lNumericBlanks(2)).AND.(Numbers(2)> 0.0d0)) THEN
Condenser(CondNum)%RatedTCondense = Numbers(2)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'" '//TRIM(cNumericFieldNames(2))//' per ARI 450 must be input and must be greater than 0 C.')
ErrorsFound = .TRUE.
END IF
IF (.NOT. lNumericBlanks(3)) THEN
IF(Numbers(3)>=0.0d0)THEN
Condenser(CondNum)%RatedSubcool = Numbers(3)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'" '//TRIM(cNumericFieldNames(3))//' must be greater than or equal to zero.')
ErrorsFound = .TRUE.
END IF
ELSE
Condenser(CondNum)%RatedSubcool = 0.0d0 !default value
END IF
IF ((.NOT. lNumericBlanks(4)).AND.(Numbers(4)> 0.0d0)) THEN
Condenser(CondNum)%RatedWaterInletT = Numbers(4)
Condenser(CondNum)%RatedApproachT = Condenser(CondNum)%RatedTCondense-Numbers(4)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'" '//TRIM(cNumericFieldNames(4))//' must be input and greater than zero.')
ErrorsFound = .TRUE.
END IF
Condenser(CondNum)%InletNode = GetOnlySingleNode(Alphas(2),&
ErrorsFound,CurrentModuleObject, &
Alphas(1),NodeType_Water,NodeConnectionType_Inlet,&
1, ObjectIsNotParent)
Condenser(CondNum)%OutletNode = GetOnlySingleNode(Alphas(3),&
ErrorsFound,CurrentModuleObject, &
Alphas(1),NodeType_Water,NodeConnectionType_Outlet, &
1, ObjectIsNotParent)
! Check node connections
CALL TestCompSet(CurrentModuleObject,Alphas(1),Alphas(2),Alphas(3),&
'Water Cooled Condenser Nodes')
! Get loop flow type
IF (SameString(Alphas(4),'VariableFlow')) THEN !set FlowType
Condenser(CondNum)%FlowType = VariableFlow
ELSE IF (SameString(Alphas(4),'ConstantFlow')) THEN
Condenser(CondNum)%FlowType = ConstantFlow
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(4))//' not recognized: '//TRIM(Alphas(4)))
CALL ShowContinueError('Check input value choices.')
ErrorsFound=.TRUE.
END IF !Set FlowType
! Get outlet temperature schedule for variable flow case
IF (Condenser(CondNum)%FlowType==VariableFlow) THEN
IF (lAlphaBlanks(5)) THEN
Condenser(CondNum)%OutletTempSchedPtr = 0
ELSE
Condenser(CondNum)%OutletTempSchedPtr = GetScheduleIndex(Alphas(5)) ! convert schedule name to pointer
END IF
IF (Condenser(CondNum)%OutletTempSchedPtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(5))//' = '//TRIM(Alphas(5)))
CALL ShowContinueError('A schedule with this name is not defined in this input data file.')
ErrorsFound=.TRUE.
END IF
END IF ! Outlet temperature schedule
! Get volumetric flow rate if applicable
IF (Condenser(CondNum)%FlowType==ConstantFlow) THEN
IF((.NOT. lNumericBlanks(5)).AND.(Numbers(5) > 0.0d0))THEN
Condenser(CondNum)%DesVolFlowRate = Numbers(5)
Condenser(CondNum)%VolFlowRate = Numbers(5)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'" '//TRIM(cNumericFieldNames(5))//' must be greater than zero.')
CALL ShowContinueError('Revise flow rates.')
ErrorsFound=.TRUE.
END IF
END IF
! Get maximum flow rates
IF(Numbers(6) > 0.0d0)THEN
Condenser(CondNum)%VolFlowRateMax = Numbers(6)
! Check constant flow for max violation, if applicable
IF (Condenser(CondNum)%FlowType==ConstantFlow .AND. Condenser(CondNum)%VolFlowRate>Numbers(6)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'" '//TRIM(cNumericFieldNames(5))//' > '//TRIM(cNumericFieldNames(6))//' .')
CALL ShowContinueError('Revise flow rates.')
ErrorsFound=.TRUE.
END IF !Error check on max flow rate
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'" '//TRIM(cNumericFieldNames(6))//' must be greater than zero.')
ErrorsFound=.TRUE.
END IF
! Get max/min allowed water temps
Condenser(CondNum)%OutletTempMax = Numbers(7)
Condenser(CondNum)%InletTempMin = Numbers(8)
Condenser(CondNum)%EndUseSubcategory =' '
IF (.NOT. lAlphaBlanks(6)) Condenser(CondNum)%EndUseSubcategory = Alphas(6)
Condenser(CondNum)%RefOpCharge = 0.0d0
Condenser(CondNum)%RefReceiverInventory = 0.0d0
Condenser(CondNum)%RefPipingInventory = 0.0d0
IF (.NOT. lNumericBlanks(9)) Condenser(CondNum)%RefOpCharge = Numbers(9)
IF (.NOT. lNumericBlanks(10)) Condenser(CondNum)%RefReceiverInventory = Numbers(10)
IF (.NOT. lNumericBlanks(11)) Condenser(CondNum)%RefPipingInventory = Numbers(11)
END DO ! Read input for CONDENSER:REFRIGERATION:WaterCooled
ALLOCATE(CheckEquipNameWaterCondenser(NumRefrigCondensers))
CheckEquipNameWaterCondenser = .TRUE.
END IF ! NumSimulationCondWater > 0
!cascade condensers assumed to provide zero subcooling
IF(NumSimulationCascadeCondensers > 0)THEN
CurrentModuleObject='Refrigeration:Condenser:Cascade'
DO CondIndex=1,NumSimulationCascadeCondensers
CondNum=CondIndex + NumSimulationCondAir + NumSimulationCondEvap + NumSimulationCondWater
CALL GetObjectItem(CurrentModuleObject,CondIndex,Alphas,NumAlphas,Numbers,NumNumbers,IOStatus,&
NumBlank=lNumericBlanks,AlphaBlank=lAlphaBlanks, &
AlphaFieldNames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
IsNotOK =.FALSE.
IsBlank =.FALSE.
CALL VerifyName(Alphas(1),Condenser%Name,CondNum-1,IsNotOK,IsBlank,CurrentModuleObject//' Name')
IF (IsNotOK) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//', has an invalid or undefined '// &
TRIM(cAlphaFieldNames(1))//'="'//TRIM(Alphas(1))//'".')
IF (IsBlank) Alphas(1)='xxxxx'
ErrorsFound=.TRUE.
ENDIF !IsNotOK on Verify Name
Condenser(CondNum)%Name = Alphas(1)
HeatReclaimRefrigCondenser(CondNum)%Name=Alphas(1)
!set start of count for number of systems attached to this condenser
Condenser(CondNum)%NumSysAttach = 0
IF(.NOT. ALLOCATED(Condenser(CondNum)%SysNum))&
ALLOCATE(Condenser(CondNum)%SysNum(NumRefrigSystems))
!set CondenserType
Condenser(CondNum)%CondenserType = RefrigCondenserTypeCascade
IF (.NOT. lNumericBlanks(1)) THEN
Condenser(CondNum)%RatedTCondense = Numbers(1)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'" '//TRIM(cNumericFieldNames(1))//' must be input.')
ErrorsFound = .TRUE.
END IF
IF (.NOT. lNumericBlanks(2)) THEN
IF(Numbers(2)>=0.0d0)THEN
Condenser(CondNum)%RatedApproachT = Numbers(2)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'" '//TRIM(cNumericFieldNames(2))//' must be greater than or equal to zero.')
ErrorsFound = .TRUE.
END IF
ELSE
Condenser(CondNum)%RatedApproachT = DefaultCascadeCondApproach
END IF
IF ((.NOT. lNumericBlanks(3)).AND.(Numbers(3)> 0.0d0)) THEN
Condenser(CondNum)%RatedCapacity = Numbers(3)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'" '//TRIM(cNumericFieldNames(3))//' must be in put and must be greater than or equal to zero.')
ErrorsFound = .TRUE.
END IF
! Get condensing temperature type, either fixed by design or allowed to float to match other loads on supply system
IF (.NOT. lAlphaBlanks(2)) THEN
IF (SameString(Alphas(2),'Fixed')) THEN !set Condenser Temperature Control Type
Condenser(CondNum)%CascadeTempControl = CascadeTempSet
ELSE IF (SameString(Alphas(2),'Float')) THEN
Condenser(CondNum)%CascadeTempControl = CascadeTempFloat
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(2))//' not recognized: '//TRIM(Alphas(2)))
CALL ShowContinueError('Check input value choices.')
ErrorsFound=.TRUE.
END IF !string comparison to key choices
ELSE ! default is fixed/cascadetempset
Condenser(CondNum)%CascadeTempControl = CascadeTempSet
END IF ! not blank
Condenser(CondNum)%CascadeRatedEvapTemp = Condenser(CondNum)%RatedTCondense - Condenser(CondNum)%RatedApproachT
!future - add refrigerant inventory on system side accepting reject heat (as was done for secondary)
Condenser(CondNum)%RefOpCharge = 0.0d0
Condenser(CondNum)%RefReceiverInventory = 0.0d0
Condenser(CondNum)%RefPipingInventory = 0.0d0
IF (.NOT. lNumericBlanks(4)) Condenser(CondNum)%RefOpCharge = Numbers(4)
IF (.NOT. lNumericBlanks(5)) Condenser(CondNum)%RefReceiverInventory = Numbers(5)
IF (.NOT. lNumericBlanks(6)) Condenser(CondNum)%RefPipingInventory = Numbers(6)
END DO ! Read input for CONDENSER:REFRIGERATION:Cascade
END IF ! NumSimulationCascadeCondensers > 0
!************ END CONDENSER INPUT **************
!********** START GAS COOLER INPUT **********
IF(NumSimulationGasCooler > 0) THEN
CurrentModuleObject='Refrigeration:GasCooler:AirCooled'
DO GCNum=1,NumSimulationGasCooler
CALL GetObjectItem(CurrentModuleObject,GCNum,Alphas,NumAlphas,Numbers,NumNumbers,IOStatus, &
NumBlank=lNumericBlanks,AlphaBlank=lAlphaBlanks, &
AlphaFieldNames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
IsNotOK =.FALSE.
IsBlank =.FALSE.
CALL VerifyName(Alphas(1),GasCooler%Name,GCNum-1,IsNotOK,IsBlank,TRIM(CurrentModuleObject)//' Name')
IF (IsNotOK) THEN
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)// &
', has an invalid or undefined '// &
TRIM(cAlphaFieldNames(1))//' = '//TRIM(Alphas(1)))
IF (IsBlank) Alphas(1)='xxxxx'
ErrorsFound=.TRUE.
ENDIF !IsNotOK on Verify Name
GasCooler(GCNum)%Name = Alphas(1)
GasCooler(GCNum)%CapCurvePtr = GetCurveIndex(Alphas(2)) ! convert curve name to number
IF (GasCooler(GCNum)%CapCurvePtr == 0) THEN
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(GasCooler(GCNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(2))//' not found:'//TRIM(Alphas(2)))
ErrorsFound = .TRUE.
END IF
!set start of count for number of systems attached to this gas cooler
GasCooler(GCNum)%NumSysAttach = 0
IF(.NOT. ALLOCATED(GasCooler(GCNum)%SysNum))&
ALLOCATE(GasCooler(GCNum)%SysNum(NumTransRefrigSystems))
GasCooler(GCNum)%RatedApproachT = 3.0d0 ! rated CO2 gas cooler approach temperature
if (GasCooler(GCNum)%CapCurvePtr > 0) then
GasCooler(GCNum)%RatedCapacity=CurveValue(GasCooler(GCNum)%CapCurvePtr,GasCooler(GCNum)%RatedApproachT)
endif
! elevation capacity correction on air-cooled condensers, Carrier correlation more conservative than Trane
GasCooler(GCNum)%RatedCapacity = GasCooler(GCNum)%RatedCapacity*(1.d0 - 7.17D-5*Elevation)
IF(GasCooler(GCNum)%RatedCapacity > 0.0d0) THEN
CALL GetCurveMinMaxValues(GasCooler(GCNum)%CapCurvePtr,DelTempMin,DelTempMax)
Capmin=CurveValue(GasCooler(GCNum)%CapCurvePtr,DelTempMin)*(1.d0 - 7.17D-5*Elevation)
Capmax=CurveValue(GasCooler(GCNum)%CapCurvePtr,DelTempMax)*(1.d0 - 7.17D-5*Elevation)
GasCooler(GCNum)%TempSlope=(DelTempMax-DelTempMin)/((Capmax-Capmin))
GasCooler(GCNum)%MinCondLoad=Capmax-DelTempMax/GasCooler(GCNum)%TempSlope
ELSE
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(GasCooler(GCNum)%Name)//&
'" Gas Cooler capacity curve must be input and must be greater than 0 Watts at 3C'// &
' temperature difference.')
ErrorsFound = .TRUE.
END IF
! Get fan control type
IF (SameString(Alphas(3),'Fixed')) THEN
GasCooler(GCNum)%FanSpeedControlType = FanConstantSpeed
ELSE IF (SameString(Alphas(3),'FixedLinear')) THEN
GasCooler(GCNum)%FanSpeedControlType = FanConstantSpeedLinear
ELSE IF (SameString(Alphas(3),'VariableSpeed')) THEN
GasCooler(GCNum)%FanSpeedControlType = FanVariableSpeed
ELSE IF (SameString(Alphas(3),'TwoSpeed')) THEN
GasCooler(GCNum)%FanSpeedControlType = FanTwoSpeed
ELSE
GasCooler(GCNum)%FanSpeedControlType = FanConstantSpeed !default
END IF !Set fan control type
! Gas cooler fan power
GasCooler(GCNum)%RatedFanPower = 5000.0d0 ! default value
IF(.NOT. lNumericBlanks(1)) GasCooler(GCNum)%RatedFanPower = Numbers(1)
IF(Numbers(1) < 0.0d0) THEN
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(GasCooler(GCNum)%Name)//&
'" '//TRIM(cNumericFieldNames(1))//' must be input greater than or equal to 0 Watts.')
ErrorsFound = .TRUE.
END IF
! Gas cooler minimum fan air flow ratio
GasCooler(GCNum)%FanMinAirFlowRatio = 0.2d0 !default value
IF(.NOT. lNumericBlanks(2)) GasCooler(GCNum)%FanMinAirFlowRatio = Numbers(2)
IF((GasCooler(GCNum)%FanMinAirFlowRatio < 0.0d0).OR.(GasCooler(GCNum)%FanMinAirFlowRatio > 1.0d0)) THEN
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(GasCooler(GCNum)%Name)//&
'" '//TRIM(cNumericFieldNames(2))//' must be a value between zero and one. The default value (0.2) '//&
'will be used.')
GasCooler(GCNum)%FanMinAirFlowRatio = 0.2d0
END IF
! Gas cooler transition temperature
GasCooler(GCNum)%TransitionTemperature = 2.7d1 ! default value
IF(.NOT. lNumericBlanks(3)) GasCooler(GCNum)%TransitionTemperature = Numbers(3)
IF(GasCooler(GCNum)%TransitionTemperature < 2.5d1) THEN
CALL ShowWarningError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(GasCooler(GCNum)%Name)//&
'" '//TRIM(cNumericFieldNames(3))//' is low (less than 25C). Consider raising the '//&
'transition temperature to operate for longer periods of time in the subcritical region.')
END IF
IF(GasCooler(GCNum)%TransitionTemperature > 30.978d0) THEN
CALL ShowWarningError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(GasCooler(GCNum)%Name)//&
'" '//TRIM(cNumericFieldNames(3))//' is greater than the critical temperature of carbon '//&
'dioxide. The default value (27C) will be used.')
GasCooler(GCNum)%TransitionTemperature = 2.7d1
END IF
! Gas cooler approach temperature for transcritical operation
GasCooler(GCNum)%GasCoolerApproachT = 3.0d0 ! default value
IF(.NOT. lNumericBlanks(4)) GasCooler(GCNum)%GasCoolerApproachT = Numbers(4)
IF(GasCooler(GCNum)%GasCoolerApproachT < 0.0d0) THEN
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(GasCooler(GCNum)%Name)//&
'" '//TRIM(cNumericFieldNames(4))//' must be greater than 0C.')
ErrorsFound = .TRUE.
END IF
! Gas cooler temperature difference for subcritical operation
GasCooler(GCNum)%SubcriticalTempDiff = 1.0d1 ! default value
IF(.NOT. lNumericBlanks(5)) GasCooler(GCNum)%SubcriticalTempDiff = Numbers(5)
IF(GasCooler(GCNum)%SubcriticalTempDiff < 0.0d0) THEN
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(GasCooler(GCNum)%Name)//&
'" '//TRIM(cNumericFieldNames(5))//' must be greater than 0C.')
ErrorsFound = .TRUE.
END IF
! Gas cooler minimum condensing temperature for subcritical operation
GasCooler(GCNum)%MinCondTemp = 1.0d1 ! default value
IF(.NOT. lNumericBlanks(6)) GasCooler(GCNum)%MinCondTemp = Numbers(6)
IF(GasCooler(GCNum)%MinCondTemp > 30.9d0) THEN
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(GasCooler(GCNum)%Name)//&
'" '//TRIM(cNumericFieldNames(6))//' must be less than the critical temperature of carbon '//&
'dioxide (31C).')
ErrorsFound = .TRUE.
END IF
! Check GasCooler air inlet node connection
GasCooler(GCNum)%GasCoolerRejectHeatToZone = .FALSE.
IF (lAlphaBlanks(4)) THEN
GasCooler(GCNum)%InletAirNodeNum = 0
ELSE !see if it's an outside air node name or an indoor zone name,
!have to check inside first because outside check automatically generates an error message
GasCooler(GCNum)%InletAirZoneNum = FindItemInList(Alphas(4),Zone%Name,NumOfZones)
!need to clearly id node number for air inlet conditions and zone number for casecredit assignment
IF(GasCooler(GCNum)%InletAirZoneNum /= 0) THEN
!set condenser flag (later used to set system flag) and zone flag
GasCooler(GCNum)%InletAirNodeNum = GetSystemNodeNumberForZone(Alphas(4))
GasCooler(GCNum)%GasCoolerRejectHeatToZone = .TRUE.
RefrigPresentInZone(GasCooler(GCNum)%InletAirZoneNum) = .TRUE.
ELSE ! not in a conditioned zone, so see if it's outside
GasCooler(GCNum)%InletAirNodeNum = &
GetOnlySingleNode(Alphas(4),ErrorsFound,CurrentModuleObject,Alphas(1), &
NodeType_Air,NodeConnectionType_OutsideAirReference,1,ObjectIsParent)
IF(.NOT. CheckOutAirNodeNumber(GasCooler(GCNum)%InletAirNodeNum))THEN
! not outside and not a zone
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(GasCooler(GCNum)%Name)//&
'", '//TRIM(cAlphaFieldNames(4))//' not found: '//TRIM(Alphas(4)))
CALL ShowContinueError('...does not appear in an OutdoorAir:NodeList or as an OutdoorAir:Node or as a Zone.')
ErrorsFound = .TRUE.
END IF !checkoutairnodenumber
END IF !InletAirZoneNum \=0
END IF ! Gas cooler air inlet node connection
GasCooler(GCNum)%EndUseSubcategory =' '
IF (.NOT. lAlphaBlanks(5)) GasCooler(GCNum)%EndUseSubcategory = Alphas(5)
GasCooler(GCNum)%RefOpCharge = 0.0d0
GasCooler(GCNum)%RefReceiverInventory = 0.0d0
GasCooler(GCNum)%RefPipingInventory = 0.0d0
IF (.NOT. lNumericBlanks(7)) GasCooler(GCNum)%RefOpCharge = Numbers(7)
IF (.NOT. lNumericBlanks(8)) GasCooler(GCNum)%RefReceiverInventory = Numbers(8)
IF (.NOT. lNumericBlanks(9)) GasCooler(GCNum)%RefPipingInventory = Numbers(9)
END DO ! Read input for REFRIGERATION:GasCooler:AirCooled
END IF ! NumSimulationGasCooler > 0
!********** END GAS COOLER INPUT **********
!************ START SECONDARY LOOP INPUT (before system input) **************
IF (NumSimulationSecondarySystems > 0) THEN
CurrentModuleObject='Refrigeration:SecondarySystem'
DO SecondaryNum=1,NumSimulationSecondarySystems
CALL GetObjectItem(CurrentModuleObject,SecondaryNum,Alphas,NumAlphas,Numbers,NumNumbers,IOStatus, &
NumBlank=lNumericBlanks,AlphaBlank=lAlphaBlanks, &
AlphaFieldNames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
IsNotOK =.FALSE.
IsBlank =.FALSE.
CALL VerifyName(Alphas(1),Secondary%Name,SecondaryNum-1,IsNotOK,IsBlank,CurrentModuleObject//' Name')
IF (IsNotOK) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//', has an invalid or undefined '// &
TRIM(cAlphaFieldNames(1))//'="'//TRIM(Alphas(1))//'".')
IF (IsBlank) Alphas(1)='xxxxx'
ErrorsFound=.TRUE.
ENDIF
Secondary(SecondaryNum)%Name = Alphas(1)
! Find the loads on the secondary loop: can be input in form of case or walkin or CaseAndWalkInList names
NominalTotalCaseCap = 0.0d0
NumCases = 0
NominalTotalCoilCap = 0.0d0
NumCoils = 0
NumWalkIns = 0
NominalTotalWalkInCap = 0.0d0
Secondary(SecondaryNum)%RefInventory=0.0d0
! Read display case and walkin assignments for this secondary
AlphaNum = 2
IF(lAlphaBlanks(AlphaNum) ) THEN
!No cases or walkins specified, ie, secondary has no load
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)// &
'", has no loads, must have at least one of: '//TRIM(cAlphaFieldNames(Alphanum)))
ErrorsFound = .TRUE.
ELSE ! (.NOT. lAlphaBlanks(AlphaNum))
! Entry for Alphas(AlphaNum) can be either a Case, WalkIn Coil, or CaseAndWalkInList name
CaseAndWalkInListNum=0
CaseNum=0
WalkInNum=0
CoilNum = 0
IF(NumSimulationCaseAndWalkInLists > 0) &
CaseAndWalkInListNum=FindItemInList(Alphas(AlphaNum),CaseAndWalkInList%Name,NumSimulationCaseAndWalkInLists)
IF(NumSimulationCases > 0)CaseNum=FindItemInList(Alphas(AlphaNum),RefrigCase%Name,NumSimulationCases)
IF(NumSimulationWalkIns > 0)WalkInNum=FindItemInList(Alphas(AlphaNum),WalkIn%Name,NumSimulationWalkIns)
IF(NumSimulationRefrigAirChillers > 0) &
CoilNum=FindItemInList(Alphas(AlphaNum),WarehouseCoil%Name,NumSimulationRefrigAirChillers)
NumNameMatches = 0
IF(CaseAndWalkInListNum /= 0)NumNameMatches = NumNameMatches +1
IF(CaseNum /= 0) NumNameMatches = NumNameMatches +1
IF(WalkInNum /= 0) NumNameMatches = NumNameMatches +1
IF(CoilNum /= 0) NumNameMatches = NumNameMatches +1
IF (NumNameMatches /= 1) THEN !name must uniquely point to a list or a single case or walkin or coil
ErrorsFound = .TRUE.
IF(NumNameMatches == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
'", has an invalid '//TRIM(cAlphaFieldNames(AlphaNum))//': '//TRIM(Alphas(AlphaNum)))
ELSEIF(NumNameMatches > 1) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//&
TRIM(Secondary(SecondaryNum)%Name)//'", has a non-unique name '//&
'that could be either a '//TRIM(cAlphaFieldNames(AlphaNum))//': '//TRIM(Alphas(AlphaNum)))
END IF !num matches = 0 or > 1
ELSEIF(CaseAndWalkInListNum /= 0) THEN !Name points to a CaseAndWalkInList
NumCoils = CaseAndWalkInList(CaseAndWalkInListNum)%NumCoils
NumCases = CaseAndWalkInList(CaseAndWalkInListNum)%NumCases
NumWalkIns = CaseAndWalkInList(CaseAndWalkInListNum)%NumWalkIns
Secondary(SecondaryNum)%NumCases = NumCases
Secondary(SecondaryNum)%NumCoils = NumCoils
Secondary(SecondaryNum)%NumWalkIns = NumWalkIns
IF(.NOT. ALLOCATED(Secondary(SecondaryNum)%CaseNum))ALLOCATE(Secondary(SecondaryNum)%CaseNum(NumCases))
Secondary(SecondaryNum)%CaseNum(1:NumCases) = CaseAndWalkInList(CaseAndWalkInListNum)%CaseItemNum(1:NumCases)
IF(.NOT. ALLOCATED(Secondary(SecondaryNum)%CoilNum))ALLOCATE(Secondary(SecondaryNum)%CoilNum(NumCoils))
Secondary(SecondaryNum)%CoilNum(1:NumCoils) = CaseAndWalkInList(CaseAndWalkInListNum)%CoilItemNum(1:NumCoils)
IF(.NOT. ALLOCATED(Secondary(SecondaryNum)%WalkInNum))ALLOCATE(Secondary(SecondaryNum)%WalkInNum(NumWalkIns))
Secondary(SecondaryNum)%WalkInNum(1:NumWalkIns) = CaseAndWalkInList(CaseAndWalkInListNum)%WalkInItemNum(1:NumWalkIns)
ELSEIF (CaseNum /= 0) THEN !Name points to a case
NumCases = 1
Secondary(SecondaryNum)%NumCases = 1
IF(.NOT. ALLOCATED(Secondary(SecondaryNum)%CaseNum)) ALLOCATE(Secondary(SecondaryNum)%CaseNum(NumCases))
Secondary(SecondaryNum)%CaseNum(NumCases)=CaseNum
ELSEIF (CoilNum /= 0) THEN !Name points to a coil
NumCoils = 1
Secondary(SecondaryNum)%NumCoils = 1
IF(.NOT. ALLOCATED(Secondary(SecondaryNum)%CoilNum)) ALLOCATE(Secondary(SecondaryNum)%CoilNum(NumCoils))
Secondary(SecondaryNum)%CoilNum(NumCoils)=CoilNum
ELSEIF (WalkInNum /= 0) THEN !Name points to a walkin
NumWalkIns = 1
Secondary(SecondaryNum)%NumWalkIns = 1
IF(.NOT. ALLOCATED(Secondary(SecondaryNum)%WalkInNum)) &
ALLOCATE(Secondary(SecondaryNum)%WalkInNum(NumWalkIns))
Secondary(SecondaryNum)%WalkInNum(NumWalkIns)=WalkInNum
END IF !NumNameMatches /= 1
END IF !blank input for loads on secondary
IF (NumCases > 0) THEN
! Find lowest design T loop fluid out of secondary chiller
! Sum rated capacity of all cases on Secondary
DO CaseIndex = 1, NumCases
!mark all cases on Secondary as used by this Secondary - checking for unused or non-unique cases
CaseNum=Secondary(SecondaryNum)%CaseNum(CaseIndex)
RefrigCase(CaseNum)%NumSysAttach = RefrigCase(CaseNum)%NumSysAttach + 1
NominalTotalCaseCap = NominalTotalCaseCap + RefrigCase(CaseNum)%DesignRatedCap*RefrigCase(CaseNum)%RatedRTF
Secondary(SecondaryNum)%RefInventory=Secondary(SecondaryNum)%RefInventory + &
RefrigCase(Casenum)%DesignRefrigInventory
IF(CaseIndex == 1) THEN !look for lowest case design evap T for Secondary
Secondary(SecondaryNum)%TMinNeeded=RefrigCase(CaseNum)%EvapTempDesign
ELSE
Secondary(SecondaryNum)%TMinNeeded = &
MIN(RefrigCase(CaseNum)%EvapTempDesign,Secondary(SecondaryNum)%TMinNeeded)
END IF
END DO !CaseIndex=1,NumCases
END IF !Numcases > 0
IF (NumCoils > 0) THEN
! Find lowest design T loop fluid out of secondary chiller
! Sum rated capacity of all Coils on Secondary
DO CoilIndex = 1, NumCoils
!mark all Coils on Secondary as used by this Secondary - checking for unused or non-unique Coils
CoilNum=Secondary(SecondaryNum)%CoilNum(CoilIndex)
WarehouseCoil(CoilNum)%NumSysAttach = WarehouseCoil(CoilNum)%NumSysAttach + 1
NominalTotalCoilCap = NominalTotalCoilCap + WarehouseCoil(CoilNum)%RatedSensibleCap
Secondary(SecondaryNum)%RefInventory=Secondary(SecondaryNum)%RefInventory + &
WarehouseCoil(Coilnum)%DesignRefrigInventory
IF((CoilIndex == 1).AND. (NumCases == 0)) THEN !look for lowest Coil design evap T for Secondary
Secondary(SecondaryNum)%TMinNeeded=WarehouseCoil(CoilNum)%TEvapDesign
ELSE
Secondary(SecondaryNum)%TMinNeeded = &
MIN(WarehouseCoil(CoilNum)%TEvapDesign,Secondary(SecondaryNum)%TMinNeeded)
END IF
END DO !CoilIndex=1,NumCoils
END IF !NumCoils > 0
IF(NumWalkIns > 0) THEN
! Find lowest design T loop fluid out of secondary chiller
! Sum rated capacity of all WalkIns on Secondary
DO WalkInIndex = 1, NumWalkIns
!mark all WalkIns on Secondary as used by this Secondary - checking for unused or non-unique WalkIns
WalkInID=Secondary(SecondaryNum)%WalkInNum(WalkInIndex)
WalkIn(WalkInID)%NumSysAttach = WalkIn(WalkInID)%NumSysAttach + 1
NominalTotalWalkInCap = NominalTotalWalkInCap + WalkIn(WalkInID)%DesignRatedCap
Secondary(SecondaryNum)%RefInventory=Secondary(SecondaryNum)%RefInventory + &
WalkIn(WalkInID)%DesignRefrigInventory
IF((WalkInIndex == 1).AND. (NumCases == 0) .AND. (NumCoils == 0)) THEN !look for lowest load design evap T for Secondary
Secondary(SecondaryNum)%TMinNeeded=WalkIn(WalkInID)%TEvapDesign
ELSE
Secondary(SecondaryNum)%TMinNeeded = &
MIN(Secondary(SecondaryNum)%TMinNeeded,WalkIn(WalkInID)%TEvapDesign)
END IF
END DO !WalkInIndex=1,NumWalkIns
END IF ! Numwalkins > 0
! Get circulating fluid type
AlphaNum=3
IF (.NOT. lAlphaBlanks(AlphaNum)) THEN
IF (SameString(Alphas(AlphaNum),'FluidAlwaysLiquid')) THEN
Secondary(SecondaryNum)%FluidType = SecFluidTypeAlwaysLiquid
ELSE IF (SameString(Alphas(AlphaNum),'FluidPhaseChange')) THEN
Secondary(SecondaryNum)%FluidType = SecFluidTypePhaseChange
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
'" '//TRIM(cAlphaFieldNames(AlphaNum))//' not recognized = '//TRIM(Alphas(AlphaNum)))
CALL ShowContinueError('Input value choices should be FluidAlwaysLiquid or FluidPhaseChange.')
ErrorsFound=.TRUE.
END IF !Set FluidType
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
'" '//TRIM(cAlphaFieldNames(AlphaNum))//' must be specified.')
ErrorsFound = .TRUE.
END IF ! blank on cir fluid type
AlphaNum=4
Secondary(SecondaryNum)%FluidName = Alphas(AlphaNum)
! Error messages for refrigerants and glycols already found in fluidproperties
! Note remainder of inputs for secondary don't follow IDD input order because of different interpretations
! and intermediate calculations used to assign default values for brine type vs. liquid overfeed/phase change loops
IF (.NOT. lNumericBlanks(3)) THEN
Secondary(SecondaryNum)%TEvapDesign = Numbers(3)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
'" '//TRIM(cNumericFieldNames(3))//' must be specified.')
ErrorsFound = .TRUE.
END IF ! blank on N3
IF (.NOT. lNumericBlanks(4)) THEN
Secondary(SecondaryNum)%TApproachDifRated = Numbers(4)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
'" '//TRIM(cNumericFieldNames(4))//' must be specified.')
ErrorsFound = .TRUE.
END IF ! blank on N4
!^^^^^^^Now look at input and once-only calculations required only for liquid/brine secondary loops^^^^^^^^^^^^^^^^^^^^^^
! Ensure that required input data is not missing prior to performing the following once-only calculations
IF (ErrorsFound) THEN
CALL ShowFatalError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
'", Program terminated due to previous condition(s).')
END IF ! ErrorsFound
IF( Secondary(SecondaryNum)%FluidType == SecFluidTypeAlwaysLiquid) THEN
IF (.NOT. lNumericBlanks(5)) THEN
Secondary(SecondaryNum)%TRangeDifRated = Numbers(5)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
'", '//TRIM(cNumericFieldNames(5))//' must be specified.')
CALL ShowContinueError('...when '//trim(cAlphaFieldNames(3))//'="FluidAlwaysLiquid".')
ErrorsFound = .TRUE.
END IF ! blank on N5
! Get fluid properties at rated conditions, will be used to calculate ht exchgr effectiveness
TBrineOutRated = Secondary(SecondaryNum)%TEvapDesign + Secondary(SecondaryNum)%TApproachDifRated
TBrineInRated = TBrineOutRated + Secondary(SecondaryNum)%TRangeDifRated
TBrineAverage= (TbrineOutRated + TBrineInRated)/2.0d0
Secondary(SecondaryNum)%TBrineAverage = TBrineAverage
DensityBrineRated = GetDensityGlycol(Secondary(SecondaryNum)%FluidName,&
TBrineAverage,Secondary(SecondaryNum)%FluidID,TrackMessage)
Secondary(SecondaryNum)%DensityBrineRated = DensityBrineRated
CpBrineRated = GetSpecificHeatGlycol(Secondary(SecondaryNum)%FluidName,&
TBrineAverage,Secondary(SecondaryNum)%FluidID,TrackMessage)
Secondary(SecondaryNum)%CpBrineRated = CpBrineRated
!Users can input either design brine flow (m3/s), or capacity in W, or both. Now have
! temperatures needed to calculate either the loop cooling capacity or fluid flow rate, if one was not input
! Don't need to save as a flow vol as a permanent var because calc whichever is missing here
IF ((.NOT. lNumericBlanks(1)) .AND. (.NOT. lNumericBlanks(2))) THEN
!Both values input, check for approximate agreement
Secondary(SecondaryNum)%CoolingLoadRated = Numbers(1)
SecondaryFlowVolRated = Numbers(2)
FlowMassRated = SecondaryFlowVolRated*DensityBrineRated
NominalSecondaryCapacity = FlowMassRated * CpBrineRated * Secondary(SecondaryNum)%TRangeDifRated
TestDelta = (NominalSecondaryCapacity-Secondary(SecondaryNum)%CoolingLoadRated)/NominalSecondaryCapacity
IF (ABS(TestDelta) > 0.2d0) THEN
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
' You may wish to check the system definition. Based upon the design flow rate'//&
' and range temperature difference, '//&
' The nominal secondary loop heat exchanger capacity is, '// &
TRIM(RoundSigDigits(NominalSecondaryCapacity,0))// &
' but the specified design capacity is, '//&
TRIM(RoundSigDigits(Secondary(SecondaryNum)%CoolingLoadRated,0)))
END IF
ELSEIF (.NOT. lNumericBlanks(1)) THEN
Secondary(SecondaryNum)%CoolingLoadRated = Numbers(1)
!Calc flow vol rated
FlowMassRated=Secondary(SecondaryNum)%CoolingLoadRated/(CpBrineRated* &
Secondary(SecondaryNum)%TRangeDifRated)
SecondaryFlowVolRated=FlowMassRated/DensityBrineRated
ELSEIF (.NOT. lNumericBlanks(2)) THEN
SecondaryFlowVolRated = Numbers(2)
!Calc rated load
FlowMassRated=SecondaryFlowVolRated*DensityBrineRated
Secondary(SecondaryNum)%CoolingLoadRated=FlowMassRated*CpBrineRated* &
Secondary(SecondaryNum)%TRangeDifRated
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
'", Either "'//TRIM(cNumericFieldNames(1))//'" OR "'// &
TRIM(cNumericFieldNames(2))//'" must be input.')
ErrorsFound=.TRUE.
END IF ! Capacity Input via either or both options
IF (.not. ErrorsFound) THEN
!Calculate heat exchanger effectiveness based on rated flow and temperature differences
Secondary(SecondaryNum)%HeatExchangeEta = Secondary(SecondaryNum)%CoolingLoadRated / &
(FlowMassRated*CpBrineRated* (TBrineInRated - Secondary(SecondaryNum)%TEvapDesign))
Secondary(SecondaryNum)%TBrineInRated = TBrineInRated
IF (Secondary(SecondaryNum)%HeatExchangeEta > 0.99d0) THEN
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
' You may wish to check the system definition. '//&
' The heat exchanger effectiveness is, '// &
TRIM(RoundSigDigits(Secondary(SecondaryNum)%HeatExchangeEta,2)))
Secondary(SecondaryNum)%HeatExchangeEta = 0.99d0
END IF
ELSE
CALL ShowContinueError('...remainder of this object input skipped due to previous errors')
CYCLE
ENDIF
PumpTotRatedFlowVol=SecondaryFlowVolRated
IF (.NOT. lNumericBlanks(7)) PumpTotRatedFlowVol = Numbers(7)
ELSE !FluidType = FluidTypePhaseChange ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
IF (.NOT. lNumericBlanks(1)) THEN
Secondary(SecondaryNum)%CoolingLoadRated = Numbers(1)
ELSE
Secondary(SecondaryNum)%CoolingLoadRated = NominalTotalCaseCap + NominalTotalWalkInCap
! first estimate, will later be adjusted to include pump power
END IF !input capacity
Secondary(SecondaryNum)%TCondense = Secondary(SecondaryNum)%TEvapDesign + &
Secondary(SecondaryNum)%TApproachDifRated
Secondary(SecondaryNum)%CircRate = DefaultCircRate
IF (.NOT. lNumericBlanks(10)) Secondary(SecondaryNum)%CircRate = Numbers(10)
DensityPhaseChange = GetSatDensityRefrig(Secondary(SecondaryNum)%FluidName,&
Secondary(SecondaryNum)%TCondense,0.0d0, &
Secondary(SecondaryNum)%FluidID, &
'GetInput in RefrigeratedCase')
DeltaHPhaseChange = GetSatEnthalpyRefrig(Secondary(SecondaryNum)%FluidName,&
Secondary(SecondaryNum)%TCondense, 1.0d0, &
Secondary(SecondaryNum)%FluidID, &
'GetInput in RefrigeratedCase') - &
GetSatEnthalpyRefrig(Secondary(SecondaryNum)%FluidName,&
Secondary(SecondaryNum)%TCondense, 0.0d0, &
Secondary(SecondaryNum)%FluidID, &
'GetInput in RefrigeratedCase')
!TotRatedFlowVol= capacity*circrate/deltahphasechange/density
CalcTotFlowVol = Secondary(SecondaryNum)%CoolingLoadRated * Secondary(SecondaryNum)%CircRate / &
(DensityPhaseChange * DeltaHPhaseChange)
PumpTotRatedFlowVol = CalcTotFlowVol
IF (.NOT. lNumericBlanks(7)) THEN
PumpTotRatedFlowVol = Numbers(7)
CalcCircRate = DensityPhaseChange * DeltaHPhaseChange * PumpTotRatedFlowVol / &
Secondary(SecondaryNum)%CoolingLoadRated
DiffCircRates = (CalcCircRate - Secondary(SecondaryNum)%CircRate)/Secondary(SecondaryNum)%CircRate
IF(ABS(DiffCircRates) > .3d0)THEN
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
' '//TRIM(cNumericFieldNames(7))//' Produces a circulating rate of '//&
TRIM(RoundSigDigits(CalcCircRate,2))//' ; '//' A circulating rate of '//&
TRIM(RoundSigDigits(Secondary(SecondaryNum)%CircRate,2))//' would need a '//&
' '//TRIM(cNumericFieldNames(7))//' of '//TRIM(RoundSigDigits(CalcTotFlowVol,2))//&
' m3/s')
END IF ! warning check on pump flow rate vs circ rate input
END IF !blank pump flow rate
SecondaryFlowVolRated = PumpTotRatedFlowVol
END IF !fluid type AlwaysLiquid or PhaseChange ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
!Read number of pumps (or pump stages) in secondary loop
NumPumps = 1 !default value
IF ((.NOT. lNumericBlanks(6)) .AND. (Numbers(6) >= 1) ) NumPumps = Numbers(6)
Secondary(SecondaryNum)%NumPumps = NumPumps
! Get pump power (users can input either power in W or head in Pa or both)
! Assume pump impeller efficiency is 0.78 (consistent with E+ Pump auto sizing assumption)
! Assume pump motor efficiency is 0.85 (Goulds Pumps motor data sheet)
! It is important that tot rated head must be for specific fluid
IF ((.NOT. lNumericBlanks(8)) .AND. (.NOT. lNumericBlanks(9))) THEN
Secondary(SecondaryNum)%PumpTotRatedPower = Numbers(8)
PumpTotRatedHead = Numbers(9)
ErrSecondPumpPower = (Secondary(SecondaryNum)%PumpTotRatedPower - &
PumpTotRatedFlowVol*PumpTotRatedHead/(PumpImpellerEfficiency*PumpMotorEfficiency))/ &
Secondary(SecondaryNum)%PumpTotRatedPower
IF (ABS(ErrSecondPumpPower) > 0.35d0) & !generous diff allowed because comparing to my assumed impeller and motor effs
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
' Input value for '//TRIM(cNumericFieldNames(9))//' not consistent with input value for '//&
TRIM(cNumericFieldNames(8))//'. '//TRIM(cNumericFieldNames(8))//' will be used')
ELSEIF (.NOT. lNumericBlanks(8)) THEN
Secondary(SecondaryNum)%PumpTotRatedPower = Numbers(8)
ELSEIF (.NOT. lNumericBlanks(9)) THEN
PumpTotRatedHead = Numbers(9)
Secondary(SecondaryNum)%PumpTotRatedPower = PumpTotRatedFlowVol*PumpTotRatedHead/(PumpImpellerEfficiency*PumpMotorEfficiency)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)// &
'", Either "'//TRIM(cNumericFieldNames(8))//'" OR "'// &
TRIM(cNumericFieldNames(9))//'" must be input.')
ErrorsFound=.TRUE.
END IF !Either or pump power Input variations (head or power)
! Get pump drive type
AlphaNum=5
Secondary(SecondaryNum)%PumpControlType = SecPumpControlConstant !default
IF (.NOT. lAlphaBlanks(AlphaNum)) THEN
IF (SameString(Alphas(AlphaNum),'Constant')) THEN
Secondary(SecondaryNum)%PumpControlType = SecPumpControlConstant
ELSE IF (SameString(Alphas(AlphaNum),'Variable')) THEN
Secondary(SecondaryNum)%PumpControlType = SecPumpControlVariable
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
'" '//TRIM(cAlphaFieldNames(AlphaNum))//' not recognized = '//TRIM(Alphas(AlphaNum)))
CALL ShowContinueError('Check input value choices.')
ErrorsFound=.TRUE.
END IF !Set PumpControlType
END IF ! blank on pump drive control type
! Print warning if Pump Control = Constant and Variable Speed Curve is specified.
IF ((Secondary(SecondaryNum)%PumpControlType == SecPumpControlConstant) .AND. &
(.NOT. lAlphaBlanks(AlphaNum+1))) THEN
CALL ShowWarningError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
'", A '//TRIM(cAlphaFieldNames(AlphaNum+1))//' is specified even though '//TRIM(cAlphaFieldNames(AlphaNum))//&
' is "CONSTANT".')
CALL ShowContinueError('The secondary loop pump(s) will be modeled as constant speed and the '//&
TRIM(cAlphaFieldNames(AlphaNum+1))//' will be ignored.')
END IF
IF(Secondary(SecondaryNum)%PumpControlType == SecPumpControlConstant) THEN
!Set incremental flow and power amounts for pump dispatch
Secondary(SecondaryNum)%PumpIncrementFlowVol = PumpTotRatedFlowVol/NumPumps
Secondary(SecondaryNum)%PumpIncrementPower = Secondary(SecondaryNum)%PumpTotRatedPower/NumPumps
ELSE !Variable speed drive need to read in power curve
AlphaNum = 6
Secondary(SecondaryNum)%VarSpeedCurvePtr = GetCurveIndex(Alphas(AlphaNum)) ! convert curve name to number
IF (Secondary(SecondaryNum)%VarSpeedCurvePtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//' not found:'//TRIM(Alphas(AlphaNum)))
ErrorsFound = .TRUE.
END IF
IF(.NOT. SameString(GetCurveType(Secondary(SecondaryNum)%VarSpeedCurvePtr),'CUBIC')) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//' object must be of type cubic.')
ErrorsFound = .TRUE.
END IF
END IF ! input power conditions/levels for constant or variable speed pump drives
!Default non-hermetic motor eff at 85% and all shaft power goes to heat in fluid
! In a semi-hermetic motor, assume all power to motor goes to heat in fluid
Secondary(SecondaryNum)%PumpPowerToHeat=PumpMotorEfficiency
NumNum = 11
IF(.NOT. lNumericBlanks(NumNum))THEN
IF((0.5d0 <= Numbers(NumNum)).AND.(1.0d0 >= Numbers(NumNum)))THEN
Secondary(SecondaryNum)%PumpPowerToHeat=Numbers(NumNum)
ELSE
CALL ShowWarningError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
'" '//TRIM(cNumericFieldNames(NumNum))//&
' must be between 0.5 and 1.0. Default value of : '//TRIM(RoundSigDigits(PumpMotorEfficiency,3))//&
' will be used')
END IF !range of pump moter heat to fluid
END IF !blank input for pumppowertoheat
!Distribution piping heat gain - optional
! Input UA and Zone containing the bulk of the secondary coolant distribution piping
! This Zone ID will be used to determine the temperature used for distribution piping heat gain.
! Zone Id is only required if Sum UA Distribution Piping >0.0
! Get the Zone node number from the zone name entered by the user
Secondary(SecondaryNum)%SumUADistPiping=0.d0
AlphaNum=7
NumNum = 12
IF(.NOT. lNumericBlanks(NumNum) .AND. .NOT. lAlphaBlanks(AlphaNum)) THEN
Secondary(SecondaryNum)%SumUADistPiping= Numbers(NumNum)
Secondary(SecondaryNum)%DistPipeZoneNum = FindItemInList(Alphas(AlphaNum),Zone%Name,NumOfZones)
Secondary(SecondaryNum)%DistPipeZoneNodeNum = GetSystemNodeNumberForZone(Alphas(AlphaNum))
IF (Secondary(SecondaryNum)%DistPipeZoneNum == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//&
TRIM(Secondary(SecondaryNum)%Name)// &
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//' not valid: '//TRIM(Alphas(AlphaNum)))
ErrorsFound=.TRUE.
ELSE
RefrigPresentInZone(Secondary(SecondaryNum)%DistPipeZoneNum) = .TRUE.
ENDIF
IF ( Secondary(SecondaryNum)%DistPipeZoneNodeNum == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
'" System Node Number not found for '//TRIM(cAlphaFieldNames(AlphaNum))// &
' = '//TRIM(Alphas(AlphaNum))//' even though '//TRIM(cNumericFieldNames(NumNum))//&
' is greater than zero. Distribution piping heat gain cannot be calculated unless a '//&
' controlled Zone (appear in a ZoneHVAC:EquipmentConnections object.)'//&
' is defined to determine the environmental temperature surrounding the piping.')
ErrorsFound=.TRUE.
ENDIF
ELSEIF(.NOT. lNumericBlanks(NumNum) .AND. lAlphaBlanks(AlphaNum)) THEN
CALL ShowWarningError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
'", '//TRIM(cAlphaFieldNames(AlphaNum))//' not found even though '//TRIM(cNumericFieldNames(NumNum))//&
' is greater than zero. Distribution piping heat gain will not be calculated unless a Zone'//&
' is defined to deterimine the environmental temperature surrounding the piping.')
ELSEIF(lNumericBlanks(NumNum) .AND. .NOT. lAlphaBlanks(AlphaNum)) THEN
CALL ShowWarningError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
'", '//TRIM(cAlphaFieldNames(AlphaNum))//' will not be used and distribution piping heat gain will'//&
' not be calculated because '//TRIM(cNumericFieldNames(NumNum))//&
' was blank.')
END IF !distribution piping
!Separator/receiver heat gain - optional
! Input UA and Zone containing the Separator/receiver
! This Zone ID will be used to determine the temperature used for Separator/receiver heat gain.
! Zone Id is only required if Sum UA Separator/receiver >0.0
! Get the Zone node number from the zone name entered by the user
Secondary(SecondaryNum)%SumUAReceiver=0.d0
AlphaNum=8
NumNum = 13
IF(.NOT. lNumericBlanks(NumNum) .AND. .NOT. lAlphaBlanks(AlphaNum)) THEN
Secondary(SecondaryNum)%SumUAReceiver= Numbers(NumNum)
Secondary(SecondaryNum)%ReceiverZoneNum = FindItemInList(Alphas(AlphaNum),Zone%Name,NumOfZones)
Secondary(SecondaryNum)%ReceiverZoneNodeNum = GetSystemNodeNumberForZone(Alphas(AlphaNum))
IF (Secondary(SecondaryNum)%ReceiverZoneNum == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//&
TRIM(Secondary(SecondaryNum)%Name)// &
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//' not valid: '//TRIM(Alphas(AlphaNum)))
ErrorsFound=.TRUE.
ELSE
RefrigPresentInZone(Secondary(SecondaryNum)%ReceiverZoneNum) = .TRUE.
ENDIF
IF ( Secondary(SecondaryNum)%ReceiverZoneNodeNum == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
'" System Node Number not found for '//TRIM(cAlphaFieldNames(AlphaNum))// &
' = '//TRIM(Alphas(AlphaNum))//' even though '//TRIM(cNumericFieldNames(NumNum))//&
' is greater than zero. Receiver heat gain cannot be calculated unless a '//&
' controlled Zone (appear in a ZoneHVAC:EquipmentConnections object.)'//&
' is defined to determine the environmental temperature surrounding the Receiver.')
ErrorsFound=.TRUE.
ENDIF
ELSEIF(.NOT. lNumericBlanks(NumNum) .AND. lAlphaBlanks(AlphaNum)) THEN
CALL ShowWarningError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
'", '//TRIM(cAlphaFieldNames(AlphaNum))//' not found even though '//TRIM(cNumericFieldNames(NumNum))//&
' is greater than zero. Receiver heat gain will not be calculated unless a Zone'//&
' is defined to deterimine the environmental temperature surrounding the Receiver.')
ELSEIF(lNumericBlanks(NumNum) .AND. .NOT. lAlphaBlanks(AlphaNum)) THEN
CALL ShowWarningError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
'", '//TRIM(cAlphaFieldNames(AlphaNum))//' will not be used and Receiver heat gain will'//&
' not be calculated because '//TRIM(cNumericFieldNames(NumNum))//&
' was blank.')
END IF !Receiver
NumNum = 14
Secondary(SecondaryNum)%ChillerRefInventory = 0.d0
IF (.NOT. lNumericBlanks(NumNum))Secondary(SecondaryNum)%ChillerRefInventory = Numbers(NumNum)
IF (Secondary(SecondaryNum)%ChillerRefInventory < 0.0d0) THEN
Secondary(SecondaryNum)%ChillerRefInventory = 0.d0
CALL ShowWarningError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
'", The value specified for '//TRIM(cNumericFieldNames(NumNum))//' is less than zero. The default'//&
' value of zero will be used.')
END IF
AlphaNum=9
IF (.NOT. lAlphaBlanks(AlphaNum)) Secondary(SecondaryNum)%EndUseSubcategory = Alphas(AlphaNum)
!Error checks on secondary loop:
! Note, rated capacities can be far off from operating capacities, but rough checks here
! (don't include dist piping or receiver heat gains).
! Load limit logic here (maxvolflow and maxload used in calcs later)
Secondary(SecondaryNum)%MaxVolFlow = MIN(SecondaryFlowVolRated,PumpTotRatedFlowVol)
NominalSecondaryRefLoad = NominalTotalCaseCap + NominalTotalWalkInCap + &
Secondary(SecondaryNum)%PumpTotRatedPower
IF( Secondary(SecondaryNum)%FluidType == SecFluidTypeAlwaysLiquid) THEN
IF(TBrineOutRated > (Secondary(SecondaryNum)%TMinNeeded + 0.5d0)) THEN
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
' The design brine temperature to the refrigeration loads: '//&
TRIM(RoundSigDigits(TBrineOutRated,1))//' ;')
CALL ShowContinueError(' is greater than the design inlet temperature for at least one of the cases or walkins: '//&
TRIM(RoundSigDigits(Secondary(SecondaryNum)%TMinNeeded,1)))
CALL ShowContinueError(' Compare your Approach and Evaporating Temperature to'//&
' the design inlet temperatures needed for the loads.')
!ErrorsFound = .TRUE.
END IF !Tbrine out warning
CapacityAtMaxVolFlow = Secondary(SecondaryNum)%MaxVolFlow * Secondary(SecondaryNum)%HeatExchangeEta* &
(cpBrineRated * DensityBrineRated) * &
(TbrineInRated - Secondary(SecondaryNum)%TEvapDesign)
Secondary(SecondaryNum)%MaxLoad = MIN(Secondary(SecondaryNum)%CoolingLoadRated,CapacityAtMaxVolFlow)
DeltaCap1 = ABS((Secondary(SecondaryNum)%CoolingLoadRated -CapacityAtMaxVolFlow)/&
Secondary(SecondaryNum)%CoolingLoadRated)
IF(DeltaCap1 > (0.3d0))THEN !diff between chiller rating and capacity at max flow > 30%
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
'" You may wish to check the system sizing. '//&
' The nominal secondary loop heat exchanger capacity is '//&
TRIM(RoundSigDigits(Secondary(SecondaryNum)%CoolingLoadRated,0))// &
' But the capacity based upon the maximum flow rate is '//&
TRIM(RoundSigDigits(CapacityAtMaxVolFlow,0)))
END IF ! DeltaCap1 > .3
ELSE ! Fluid type phase change !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
IF(lNumericBlanks(1)) THEN ! Chiller/evaporator capacity was not specified
IF(lNumericBlanks(7)) THEN ! Pump power was not input, calc based on flow and head
!need to refine because capacity calculated, but needs to include pump power (which was prev
! estimated based upon capacity which had been estimated as sum of case and walk-in capacities)
PumpTotRatedFlowVol = NominalSecondaryRefLoad * Secondary(SecondaryNum)%CircRate / &
(DensityPhaseChange * DeltaHPhaseChange)
Secondary(SecondaryNum)%PumpTotRatedPower = PumpTotRatedFlowVol*PumpTotRatedHead/&
(PumpImpellerEfficiency*PumpMotorEfficiency)
!need to recalc nominal load with new pump power value
NominalSecondaryRefLoad = NominalTotalCaseCap + NominalTotalWalkInCap + &
Secondary(SecondaryNum)%PumpTotRatedPower
IF(Secondary(SecondaryNum)%PumpControlType == SecPumpControlConstant) THEN
!Set incremental flow and power amounts for pump dispatch
Secondary(SecondaryNum)%PumpIncrementFlowVol = PumpTotRatedFlowVol/NumPumps
Secondary(SecondaryNum)%PumpIncrementPower = Secondary(SecondaryNum)%PumpTotRatedPower/NumPumps
END IF ! constant speed pump
END IF ! Pump power was not specified
Secondary(SecondaryNum)%CoolingLoadRated = NominalSecondaryRefLoad
END IF ! Chiller/evap capacity was not specified
Secondary(SecondaryNum)%MaxLoad = Secondary(SecondaryNum)%CoolingLoadRated
END IF ! SecFluidType
DeltaCap2 = ABS((Secondary(SecondaryNum)%CoolingLoadRated -NominalSecondaryRefLoad)/&
Secondary(SecondaryNum)%CoolingLoadRated)
IF(DeltaCap2 > (0.3d0))THEN !diff between chiller rating and sum of nominal loads > 30%
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
'" You may wish to check the system sizing. Total nominal refrigerating load is '//&
TRIM(RoundSigDigits(NominalSecondaryRefLoad,0))// &
' (Including cases, walk-ins, and pump heat). '//&
' The nominal secondary loop heat exchanger capacity is '// &
TRIM(RoundSigDigits(Secondary(SecondaryNum)%CoolingLoadRated,0)))
END IF
!compare rated xt xchanger brine flow to the total rated pump flow
IF(SecondaryFlowVolRated > (1.1d0 * PumpTotRatedFlowVol)) THEN
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(Secondary(SecondaryNum)%Name)//&
'" You may wish to check the pump sizing. Total nominal brine flow is '//&
TRIM(RoundSigDigits(SecondaryFlowVolRated,0))// &
' m3/s, but the total nominal pump flow rate is: '//&
TRIM(RoundSigDigits(PumpTotRatedFlowVol,0))// &
' m3/s. ')
END IF
END DO ! Secondary Loops
END IF !( IF (NumSimulationSecondarySystems > 0)
!************ END SECONDARY SYSTEM INPUT **************
!************ START Compressor INPUT **************
CurrentModuleObject='Refrigeration:Compressor'
DO CompNum=1,NumSimulationCompressors
CALL GetObjectItem(CurrentModuleObject,CompNum,Alphas,NumAlphas,Numbers,NumNumbers,IOStatus,&
NumBlank=lNumericBlanks,AlphaBlank=lAlphaBlanks, &
AlphaFieldNames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
IsNotOK =.FALSE.
IsBlank =.FALSE.
CALL VerifyName(Alphas(1),Compressor%Name,CompNum-1,IsNotOK,IsBlank,CurrentModuleObject//' Name')
IF (IsNotOK) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//', has an invalid or undefined '// &
TRIM(cAlphaFieldNames(1))//'="'//TRIM(Alphas(1))//'".')
IF (IsBlank) Alphas(1)='xxxxx'
ErrorsFound=.TRUE.
ENDIF
Compressor(CompNum)%Name = Alphas(1)
Compressor(CompNum)%ElecPowerCurvePtr = GetCurveIndex(Alphas(2)) ! convert curve name to number
IF ((.NOT. lAlphaBlanks(2)) .AND. Compressor(CompNum)%ElecPowerCurvePtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Compressor(CompNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(2))//' not found = '//TRIM(Alphas(2)))
ErrorsFound = .TRUE.
END IF
Compressor(CompNum)%CapacityCurvePtr = GetCurveIndex(Alphas(3)) ! convert curve name to number
IF ((.NOT. lAlphaBlanks(3)) .AND. Compressor(CompNum)%CapacityCurvePtr == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Compressor(CompNum)%Name)//&
'", invalid '//TRIM(cAlphaFieldNames(3))//' not found = '//TRIM(Alphas(3)))
ErrorsFound = .TRUE.
END IF
! Get superheat rating type (Either N1 or N2 Must be input)
IF ( ((.NOT. lNumericBlanks(1)) .AND. (.NOT. lNumericBlanks(2))) .OR. &
(lNumericBlanks(1) .AND. lNumericBlanks(2)) ) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Compressor(CompNum)%Name)//&
'"One, and Only One of '//TRIM(cNumericFieldNames(1))//' or '//TRIM(cNumericFieldNames(2)))
CALL ShowContinueError('Must Be Entered. Check input value choices.')
ErrorsFound=.TRUE.
ELSE IF (.NOT. lNumericBlanks(1))THEN
Compressor(CompNum)%SuperheatRatingType = RatedSuperheat
Compressor(CompNum)%RatedSuperheat = Numbers(1)
ELSE IF (.NOT. lNumericBlanks(2))THEN
Compressor(CompNum)%SuperheatRatingType = RatedReturnGasTemperature
Compressor(CompNum)%RatedSuperheat = Numbers(2)
END IF !Set SuperheatRatingType
! Get subcool rating type (Either N3 or N4 Must be input)
IF ( ((.NOT. lNumericBlanks(3)) .AND. (.NOT. lNumericBlanks(4))) .OR. &
(lNumericBlanks(3) .AND. lNumericBlanks(4)) ) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Compressor(CompNum)%Name)//&
'" One, and Only One of '//TRIM(cNumericFieldNames(3))//' or '//TRIM(cNumericFieldNames(4)))
CALL ShowContinueError('Must Be Entered. Check input value choices.')
ErrorsFound=.TRUE.
ELSE IF (.NOT. lNumericBlanks(3))THEN
Compressor(CompNum)%SubcoolRatingType = RatedLiquidTemperature
Compressor(CompNum)%RatedSubcool = Numbers(3)
ELSE IF (.NOT. lNumericBlanks(4))THEN
Compressor(CompNum)%SubcoolRatingType = RatedSubcooling
Compressor(CompNum)%RatedSubcool = Numbers(4)
END IF !Set SubcoolRatingType
Compressor(CompNum)%EndUseSubcategory ='General'
IF (.NOT. lAlphaBlanks(4)) Compressor(CompNum)%EndUseSubcategory = Alphas(4)
! If the compressor is a transcritical CO compressor, get transcritical power and capacity curves
IF (SameString(Alphas(5),'Transcritical')) THEN ! Mode of Operation = Transcritical
Compressor(CompNum)%TransFlag = .TRUE.
Compressor(CompNum)%TransElecPowerCurvePtr = GetCurveIndex(Alphas(6)) ! convert curve name to number
IF (lAlphaBlanks(6) .AND. Compressor(CompNum)%TransElecPowerCurvePtr == 0) THEN
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'='//TRIM(Compressor(CompNum)%Name)//': ' &
//TRIM(cAlphaFieldNames(6))//' not found.')
ErrorsFound = .TRUE.
END IF
Compressor(CompNum)%TransCapacityCurvePtr = GetCurveIndex(Alphas(7)) ! convert curve name to number
IF (lAlphaBlanks(7) .AND. Compressor(CompNum)%TransCapacityCurvePtr == 0) THEN
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'='//TRIM(Compressor(CompNum)%Name)//': ' &
//TRIM(cAlphaFieldNames(7))//' not found.')
ErrorsFound = .TRUE.
END IF
ELSE IF ((SameString(Alphas(5),'Subcritical')).OR.(lAlphaBlanks(5))) THEN ! Mode of Operation = Subcritical
Compressor(CompNum)%TransFlag = .FALSE.
IF ((.NOT.lAlphaBlanks(6)).OR.(.NOT.lAlphaBlanks(7))) THEN ! Transcritical compressor curves specified for subcritical compressor
CALL ShowWarningError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'='//TRIM(Compressor(CompNum)%Name)// &
' is specified to be a subcritical compressor, however transcritical compressor curve(s) are given.')
CALL ShowContinueError('The compressor will be modeled as a subcritical compressor and the transcritical '// &
'compressor curve(s) will be ignored.')
END IF
ELSE ! Invalid Mode of Operation
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//': '//TRIM(cAlphaFieldNames(5))// &
' for '//TRIM(Compressor(CompNum)%Name)//'='//TRIM(Alphas(5))// &
' is invalid. Valid choices are "Subcritical" or "Transcritical".')
ErrorsFound = .TRUE.
END IF
END DO ! RefrigCompressor
!************ END Compressor INPUT **************
!************ START Subcooler INPUT **************
IF (NumSimulationSubcoolers > 0) THEN
CurrentModuleObject='Refrigeration:Subcooler'
NumSimulationMechSubcoolers=0
DO SubcoolerNum=1,NumSimulationSubcoolers
CALL GetObjectItem(CurrentModuleObject,SubcoolerNum,Alphas,NumAlphas,Numbers,NumNumbers,IOStatus, &
NumBlank=lNumericBlanks,AlphaBlank=lAlphaBlanks, &
AlphaFieldNames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
IsNotOK =.FALSE.
IsBlank =.FALSE.
CALL VerifyName(Alphas(1),Subcooler%Name,SubcoolerNum-1,IsNotOK,IsBlank,CurrentModuleObject//' Name')
IF (IsNotOK) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//', has an invalid or undefined '// &
TRIM(cAlphaFieldNames(1))//'="'//TRIM(Alphas(1))//'".')
IF (IsBlank) Alphas(1)='xxxxx'
ErrorsFound=.TRUE.
ENDIF
Subcooler(SubcoolerNum)%Name = Alphas(1)
! Get subcooler type
Subcooler(SubcoolerNum)%subcoolertype = LiquidSuction !default subcooler type
IF (SameString(Alphas(2),'Mechanical')) THEN !set subcooler type
Subcooler(SubcoolerNum)%subcoolertype = Mechanical
NumSimulationMechSubcoolers=NumSimulationMechSubcoolers + 1
ELSE IF (SameString(Alphas(2),'LiquidSuction')) THEN
Subcooler(SubcoolerNum)%subcoolertype = LiquidSuction
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Subcooler(SubcoolerNum)%Name)//&
'", '//TRIM(cAlphaFieldNames(2))//' not recognized = '//TRIM(Alphas(2)))
CALL ShowContinueError('Check input value choices.')
ErrorsFound=.TRUE.
END IF !Set Subcooler Type
SELECT CASE(Subcooler(SubcoolerNum)%subcoolertype)
CASE (LiquidSuction)
Subcooler(SubcoolerNum)%LiqSuctDesignDelT=10.d0 !default value
IF (.NOT. lNumericBlanks(1))Subcooler(SubcoolerNum)%LiqSuctDesignDelT= Numbers(1)
IF (Subcooler(SubcoolerNum)%LiqSuctDesignDelT < 0.0d0 ) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Subcooler(SubcoolerNum)%Name)//&
'" '//TRIM(cNumericFieldNames(1))//' cannot be less than zero.')
ErrorsFound = .TRUE.
END IF
IF (.NOT. lNumericBlanks(2)) THEN
Subcooler(SubcoolerNum)%LiqSuctDesignTliqIn= Numbers(2)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Subcooler(SubcoolerNum)%Name)//&
'" '//TRIM(cNumericFieldNames(2))//' must be specified.')
ErrorsFound = .TRUE.
END IF
IF (.NOT. lNumericBlanks(3)) THEN
Subcooler(SubcoolerNum)%LiqSuctDesignTvapIn= Numbers(3)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Subcooler(SubcoolerNum)%Name)//&
'" '//TRIM(cNumericFieldNames(3))//' must be specified.')
ErrorsFound = .TRUE.
END IF
IF (Subcooler(SubcoolerNum)%LiqSuctDesignTvapIn > Subcooler(SubcoolerNum)%LiqSuctDesignTliqIn) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Subcooler(SubcoolerNum)%Name)//&
'" '//TRIM(cNumericFieldNames(3))//' cannot be greater than '//TRIM(cNumericFieldNames(2))//'.')
ErrorsFound = .TRUE.
END IF !error check
CASE (Mechanical)
Subcooler(SubcoolerNum)%MechSourceSys=Alphas(3)
!Error check on system name comes later after systems have been read
IF (.NOT. lNumericBlanks(4)) THEN
Subcooler(SubcoolerNum)%MechControlTliqOut= Numbers(4)
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Subcooler(SubcoolerNum)%Name)//&
'" '//TRIM(cNumericFieldNames(4))//' must be specified.')
ErrorsFound = .TRUE.
END IF !error check
END SELECT
END DO ! Subcooler Input
END IF ! If there are subcoolers
! ********END SUBCOOLER INPUTS ************
!**** Read TransferLoad Lists **********************************************************
IF(NumSimulationTransferLoadLists > 0) THEN
CurrentModuleObject='Refrigeration:TransferLoadList'
DO ListNum=1,NumSimulationTransferLoadLists
CALL GetObjectItem(CurrentModuleObject,ListNum,Alphas,NumAlphas,Numbers,NumNumbers,IOStatus, &
NumBlank=lNumericBlanks,AlphaBlank=lAlphaBlanks, &
AlphaFieldNames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
IsNotOK =.FALSE.
IsBlank =.FALSE.
CALL VerifyName(Alphas(1),TransferLoadList%Name,ListNum-1,IsNotOK,IsBlank,CurrentModuleObject//' Name')
IF (IsNotOK) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//', has an invalid or undefined '// &
TRIM(cAlphaFieldNames(1))//'="'//TRIM(Alphas(1))//'".')
IF (IsBlank) Alphas(1)='xxxxx'
ErrorsFound=.TRUE.
ENDIF
TransferLoadList(ListNum)%Name=Alphas(1)
! Transfer load list alphas include TransferLoadList name and one name for each Secondary or Cascade Condenser in list
! below allocates larger than needed (each allocated to sum of both), but avoids two loops through input fields
NumTotalLoadsOnList = NumAlphas - 1
IF(.NOT. ALLOCATED(TransferLoadList(ListNum)%CascadeLoadItemNum))&
ALLOCATE(TransferLoadList(ListNum)%CascadeLoadItemNum(NumTotalLoadsOnList))
IF(.NOT. ALLOCATED(TransferLoadList(ListNum)%SecondaryItemNum))&
ALLOCATE(TransferLoadList(ListNum)%SecondaryItemNum(NumTotalLoadsOnList))
NumSecondarysOnList = 0
NumCascadeLoadsOnList = 0
DO NumLoad = 1, NumTotalLoadsOnList
AlphaListNum= 1 + NumLoad
LoadCascadeNum = 0
LoadSecondaryNum = 0
IF(NumRefrigCondensers > 0) &
LoadCascadeNum = FindItemInList(Alphas(AlphaListNum),Condenser%Name,NumRefrigCondensers)
IF(NumSimulationSecondarySystems > 0) &
LoadSecondaryNum = FindItemInList(Alphas(AlphaListNum),Secondary%Name,NumSimulationSecondarySystems)
IF((LoadCascadeNum == 0) .AND. (LoadSecondaryNum == 0)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//&
TRIM(cAlphaFieldNames(AlphaListNum))//'" : has an invalid '//&
'value of '//TRIM(Alphas(AlphaListNum)))
ErrorsFound = .TRUE.
ELSEIF((LoadCascadeNum /= 0) .AND. (LoadSecondaryNum /= 0)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//&
TRIM(cAlphaFieldNames(AlphaListNum))//'" : has a non-unique name '//&
': '//TRIM(Alphas(AlphaListNum)))
ErrorsFound = .TRUE.
ELSEIF (LoadCascadeNum /= 0) THEN
IF(Condenser(LoadCascadeNum)%CondenserType /= RefrigCondenserTypeCascade) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(System(RefrigSysNum)%Name)&
//'" : has a condenser listed as a transfer load that is not a cascade condenser: '//&
TRIM(Alphas(AlphaListNum)))
ErrorsFound = .TRUE.
ELSE
NumCascadeLoadsOnList = NumCascadeLoadsOnList + 1
TransferLoadList(ListNum)%CascadeLoadItemNum(NumCascadeLoadsOnList) = LoadCascadeNum
END IF ! /= condenser cascade type
ELSEIF (LoadSecondaryNum /= 0) THEN
NumSecondarysOnList = NumSecondarysOnList + 1
TransferLoadList(ListNum)%SecondaryItemNum(NumSecondarysOnList) = LoadSecondaryNum
END IF
TransferLoadList(ListNum)%NumSecondarys = NumSecondarysOnList
TransferLoadList(ListNum)%NumCascadeLoads = NumCascadeLoadsOnList
END DO !Num Total Loads on List
END DO !ListNum=1,NumSimulationTransferLoadLists
END IF !(NumSimulationTransferLoadLists > 0)
!**** End read transfer load Lists **********************************************************
!**** Read Compressor Lists **********************************************************
CurrentModuleObject='Refrigeration:CompressorList'
DO ListNum=1,NumCompressorLists
CALL GetObjectItem(CurrentModuleObject,ListNum,Alphas,NumAlphas,Numbers,NumNumbers,IOStatus, &
NumBlank=lNumericBlanks,AlphaBlank=lAlphaBlanks, &
AlphaFieldNames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
IsNotOK =.FALSE.
IsBlank =.FALSE.
CompressorLists(ListNum)%NumCompressors=NumAlphas - 1
CALL VerifyName(Alphas(1),CompressorLists%Name,ListNum-1,IsNotOK,IsBlank,CurrentModuleObject//' Name')
IF (IsNotOK) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//', has an invalid or undefined '// &
TRIM(cAlphaFieldNames(1))//'="'//TRIM(Alphas(1))//'".')
IF (IsBlank) Alphas(1)='xxxxx'
ErrorsFound=.TRUE.
ENDIF
CompressorLists(ListNum)%Name=Alphas(1)
IF(.NOT. ALLOCATED(CompressorLists(ListNum)%CompItemNum))&
ALLOCATE(CompressorLists(ListNum)%CompItemNum(CompressorLists(ListNum)%NumCompressors))
DO CompIndex = 1, CompressorLists(ListNum)%NumCompressors
AlphaListNum = CompIndex+1 !same as do loop from 2 to end of list
IF(.NOT. lAlphaBlanks(AlphaListNum)) THEN
CompressorLists(ListNum)%CompItemNum(CompIndex)= &
FindItemInList(Alphas(AlphaListNum),Compressor%Name,NumSimulationCompressors)
IF(CompressorLists(ListNum)%CompItemNum(CompIndex) == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)// &
'="'//TRIM(CompressorLists(ListNum)%Name)//'", has an invalid '//&
TRIM(cAlphaFieldNames(AlphaListNum))//' defined as '//TRIM(Alphas(AlphaListNum)))
ErrorsFound = .TRUE.
END IF
END IF
END DO !NumCompressors in CompressorList
END DO !NumCompressorLists
! ********READ REFRIGERATION SYSTEMS ***********
CurrentModuleObject='Refrigeration:System'
DO RefrigSysNum=1,NumRefrigSystems
CALL GetObjectItem(CurrentModuleObject,RefrigSysNum,Alphas,NumAlphas,Numbers,NumNumbers,IOStatus, &
NumBlank=lNumericBlanks,AlphaBlank=lAlphaBlanks, &
AlphaFieldNames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
IsNotOK =.FALSE.
IsBlank =.FALSE.
CALL VerifyName(Alphas(1),System%Name,RefrigSysNum-1,IsNotOK,IsBlank,CurrentModuleObject//' Name')
IF (IsNotOK) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//', has an invalid or undefined '// &
TRIM(cAlphaFieldNames(1))//'="'//TRIM(Alphas(1))//'".')
IF (IsBlank) Alphas(1)='xxxxx'
ErrorsFound=.TRUE.
ENDIF
System(RefrigSysNum)%Name = Alphas(1)
!Read all loads on this System: cases, walk-ins, cascade loads, and secondary loops
IF(lAlphaBlanks(2) .AND. lAlphaBlanks(3) ) THEN
!No cases, walkins, cascade loads, or secondary loops specified, ie, System has no load
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(System(RefrigSysNum)%Name)// &
'", has no loads, must have at least one of: '//TRIM(cAlphaFieldNames(2))// &
' or '//TRIM(cAlphaFieldNames(3))//' objects attached.')
ErrorsFound = .TRUE.
END IF
NumCases = 0
System(RefrigSysNum)%NumCases = 0
NumCoils = 0
System(RefrigSysNum)%NumCoils = 0
NumWalkIns = 0
System(RefrigSysNum)%NumWalkIns = 0
NumSecondary = 0
System(RefrigSysNum)%NumSecondarys = 0
NumCascadeLoad = 0
System(RefrigSysNum)%NumCascadeLoads = 0
System(RefrigSysNum)%NumNonCascadeLoads = 0
NominalTotalCaseCap = 0.0d0
NominalTotalCoilCap = 0.0d0
NominalTotalWalkInCap = 0.0d0
NominalTotalSecondaryCap = 0.0d0
NominalTotalCoolingCap = 0.0d0
NominalTotalCascadeLoad = 0.0d0
System(RefrigSysNum)%RefInventory=0.0d0
! Check for case or walkin or CaseAndWalkInList names
AlphaNum = 2
IF (.NOT. lAlphaBlanks(AlphaNum)) THEN
! Entry for Alphas(AlphaNum) can be either a Case, WalkIn or CaseAndWalkInList name
CaseAndWalkInListNum=0
CaseNum=0
WalkInNum=0
CoilNum=0
IF(NumSimulationCaseAndWalkInLists > 0) &
CaseAndWalkInListNum=FindItemInList(Alphas(AlphaNum),CaseAndWalkInList%Name,NumSimulationCaseAndWalkInLists)
IF(NumSimulationCases > 0) CaseNum= FindItemInList(Alphas(AlphaNum),RefrigCase%Name,NumSimulationCases)
IF(NumSimulationWalkIns > 0)WalkInNum=FindItemInList(Alphas(AlphaNum),WalkIn%Name,NumSimulationWalkIns)
IF(NumSimulationRefrigAirChillers > 0) &
CoilNum= FindItemInList(Alphas(AlphaNum),WarehouseCoil%Name,NumSimulationRefrigAirChillers)
NumNameMatches = 0
IF(CaseAndWalkInListNum /= 0)NumNameMatches = NumNameMatches +1
IF(CaseNum /= 0) NumNameMatches = NumNameMatches +1
IF(WalkInNum /= 0) NumNameMatches = NumNameMatches +1
IF(CoilNum /= 0) NumNameMatches = NumNameMatches +1
IF (NumNameMatches /= 1) THEN !name must uniquely point to a list or a single case or walkin or coil
ErrorsFound = .TRUE.
IF(NumNameMatches == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(System(RefrigSysNum)%Name)//&
'", has an invalid '//TRIM(cAlphaFieldNames(AlphaNum))//': '//TRIM(Alphas(AlphaNum)))
ELSEIF(NumNameMatches > 1) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//&
TRIM(System(RefrigSysNum)%Name)//'", has a non-unique name '//&
'that could be either a '//TRIM(cAlphaFieldNames(AlphaNum))//': '//TRIM(Alphas(AlphaNum)))
END IF !num matches = 0 or > 1
ELSEIF(CaseAndWalkInListNum /= 0) THEN !Name points to a CaseAndWalkInList
NumCases = CaseAndWalkInList(CaseAndWalkInListNum)%NumCases
NumWalkIns = CaseAndWalkInList(CaseAndWalkInListNum)%NumWalkIns
NumCoils = CaseAndWalkInList(CaseAndWalkInListNum)%NumCoils
System(RefrigSysNum)%NumCases = NumCases
System(RefrigSysNum)%NumWalkIns = NumWalkIns
System(RefrigSysNum)%NumCoils = NumCoils
IF(NumCases > 0) THEN
IF(.NOT. ALLOCATED(System(RefrigSysNum)%CaseNum))ALLOCATE(System(RefrigSysNum)%CaseNum(NumCases))
System(RefrigSysNum)%CaseNum(1:NumCases) = CaseAndWalkInList(CaseAndWalkInListNum)%CaseItemNum(1:NumCases)
END IF
IF(NumCoils > 0) THEN
IF(.NOT. ALLOCATED(System(RefrigSysNum)%CoilNum))ALLOCATE(System(RefrigSysNum)%CoilNum(NumCoils))
System(RefrigSysNum)%CoilNum(1:NumCoils) = CaseAndWalkInList(CaseAndWalkInListNum)%CoilItemNum(1:NumCoils)
END IF
IF(NumWalkIns > 0) THEN
IF(.NOT. ALLOCATED(System(RefrigSysNum)%WalkInNum))ALLOCATE(System(RefrigSysNum)%WalkInNum(NumWalkIns))
System(RefrigSysNum)%WalkInNum(1:NumWalkIns) = CaseAndWalkInList(CaseAndWalkInListNum)%WalkInItemNum(1:NumWalkIns)
END IF
ELSEIF (CaseNum /= 0) THEN !Name points to a case
NumCases = 1
System(RefrigSysNum)%NumCases = 1
IF(.NOT. ALLOCATED(System(RefrigSysNum)%CaseNum)) ALLOCATE(System(RefrigSysNum)%CaseNum(NumCases))
System(RefrigSysNum)%CaseNum(NumCases)=CaseNum
ELSEIF (CoilNum /= 0) THEN !Name points to a coil
NumCoils = 1
System(RefrigSysNum)%NumCoils = 1
IF(.NOT. ALLOCATED(System(RefrigSysNum)%CoilNum)) ALLOCATE(System(RefrigSysNum)%CoilNum(NumCoils))
System(RefrigSysNum)%CoilNum(NumCoils)=CoilNum
ELSEIF (WalkInNum /= 0) THEN !Name points to a walkin
NumWalkIns = 1
System(RefrigSysNum)%NumWalkIns = 1
IF(.NOT. ALLOCATED(System(RefrigSysNum)%WalkInNum)) &
ALLOCATE(System(RefrigSysNum)%WalkInNum(NumWalkIns))
System(RefrigSysNum)%WalkInNum(NumWalkIns)=WalkInNum
END IF !NumNameMatches /= 1
END IF !blank input for cases, walkins, or caseandwalkinlist
IF(NumCases > 0) THEN
! Find lowest design evap T
! Sum rated capacity of all cases on system
DO CaseIndex = 1, NumCases
!mark all cases on system as used by this system - checking for unused or non-unique cases
CaseNum=System(RefrigSysNum)%CaseNum(CaseIndex)
RefrigCase(CaseNum)%NumSysAttach = RefrigCase(CaseNum)%NumSysAttach + 1
NominalTotalCaseCap = NominalTotalCaseCap + RefrigCase(CaseNum)%DesignRatedCap
System(RefrigSysNum)%RefInventory=System(RefrigSysNum)%RefInventory + &
RefrigCase(Casenum)%DesignRefrigInventory
IF(CaseIndex == 1) THEN !look for lowest case design evap T for system
System(RefrigSysNum)%TEvapDesign=RefrigCase(CaseNum)%EvapTempDesign
ELSE
System(RefrigSysNum)%TEvapDesign = &
MIN(RefrigCase(CaseNum)%EvapTempDesign,System(RefrigSysNum)%TEvapDesign)
END IF
END DO !CaseIndex=1,NumCases
System(RefrigSysNum)%NumNonCascadeLoads = System(RefrigSysNum)%NumNonCascadeLoads + System(RefrigSysNum)%NumCases
END IF !Numcases > 0
IF(NumCoils > 0) THEN
! Find lowest design evap T
! Sum rated capacity of all Coils on system
DO CoilIndex = 1, NumCoils
!mark all Coils on system as used by this system - checking for unused or non-unique Coils
CoilNum=System(RefrigSysNum)%CoilNum(CoilIndex)
WarehouseCoil(CoilNum)%NumSysAttach = WarehouseCoil(CoilNum)%NumSysAttach + 1
NominalTotalCoilCap = NominalTotalCoilCap + WarehouseCoil(CoilNum)%RatedSensibleCap
System(RefrigSysNum)%RefInventory=System(RefrigSysNum)%RefInventory + &
WarehouseCoil(Coilnum)%DesignRefrigInventory
IF((CoilIndex == 1) .AND. (System(RefrigSysNum)%NumCases ==0)) THEN !look for lowest Coil design evap T for system
System(RefrigSysNum)%TEvapDesign=WarehouseCoil(CoilNum)%TEvapDesign
ELSE
System(RefrigSysNum)%TEvapDesign = &
MIN(WarehouseCoil(CoilNum)%TEvapDesign,System(RefrigSysNum)%TEvapDesign)
END IF
END DO !CoilIndex=1,NumCoils
System(RefrigSysNum)%NumNonCascadeLoads = System(RefrigSysNum)%NumNonCascadeLoads + System(RefrigSysNum)%NumCoils
END IF !NumCoils > 0
IF (NumWalkIns > 0) THEN
DO WalkInIndex = 1, NumWalkIns
WalkInID=System(RefrigSysNum)%WalkInNum(WalkInIndex)
!mark all WalkIns on rack as used by this system (checking for unused or non-unique WalkIns)
WalkIn(WalkInID)%NumSysAttach = WalkIn(WalkInID)%NumSysAttach + 1
NominalTotalWalkInCap = NominalTotalWalkInCap + WalkIn(WalkInID)%DesignRatedCap
System(RefrigSysNum)%RefInventory=System(RefrigSysNum)%RefInventory + &
WalkIn(WalkInID)%DesignRefrigInventory
!Defrost capacity is treated differently by compressor racks and detailed systems,
! so this value may be adjusted (or warnings issued) after the walkin is assigned
! to either the rack or system.
!for walkins served by detailed system, need capacity for both fluid and electric types.
IF (WalkIn( WalkInID)%DefrostCapacity <= -98.d0) THEN
! - 99 used as a flag for blank input error message for detailed systems
CALL ShowSevereError(RoutineName//'Refrigeration:WalkIn="'//TRIM( WalkIn( WalkInID)%Name)//&
'", Defrost capacity must be greater than or equal to 0 W' //&
' for electric and hotfluid defrost types')
ErrorsFound = .TRUE.
END IF
! Find design evaporating temperature for system by getting min design evap for ALL loads
IF ((WalkInIndex == 1) .AND. (System(RefrigSysNum)%NumCases ==0) .AND. &
(System(RefrigSysNum)%NumCoils ==0) )THEN
!note use walk in index, not walkinid here to get
!first walkin on this suction group/system
System(RefrigSysNum)%TEvapDesign=WalkIn(WalkInID)%TEvapDesign
ELSE
System(RefrigSysNum)%TEvapDesign=MIN(WalkIn(WalkInID)%TEvapDesign,System(RefrigSysNum)%TEvapDesign)
END IF
END DO !WalkInIndex=1,NumWalkIns
System(RefrigSysNum)%NumNonCascadeLoads = System(RefrigSysNum)%NumNonCascadeLoads + System(RefrigSysNum)%NumWalkIns
END IF !numwalkins > 0
AlphaNum = 3
! Read Transfer Loads (Secondary and Cascade) assignments for this System ,
! already allow more than one mech subcooler to load onto a system so they don't need to go in list
IF (.NOT. lAlphaBlanks(AlphaNum)) THEN
! Entry for Alphas(AlphaNum) can be either a Secondary, CascadeLoad name or a TransferLoadList name
TransferLoadListNum=0
SecondaryNum=0
CascadeLoadNum=0
IF(NumSimulationTransferLoadLists > 0) &
TransferLoadListNum=FindItemInList(Alphas(AlphaNum),TransferLoadList%Name,NumSimulationTransferLoadLists)
IF(NumSimulationSecondarySystems > 0) &
SecondaryNum=FindItemInList(Alphas(AlphaNum),Secondary%Name,NumSimulationSecondarySystems)
IF(NumRefrigCondensers > 0) &
CascadeLoadNum=FindItemInList(Alphas(AlphaNum),Condenser%Name,NumRefrigCondensers)
NumNameMatches = 0
IF(TransferLoadListNum /= 0)NumNameMatches = NumNameMatches +1
IF(SecondaryNum /= 0) NumNameMatches = NumNameMatches +1
IF(CascadeLoadNum /= 0) NumNameMatches = NumNameMatches +1
IF (NumNameMatches /= 1) THEN !name must uniquely point to a list or a single transfer load
ErrorsFound = .TRUE.
IF(NumNameMatches == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(System(RefrigSysNum)%Name)//&
'", has an invalid '//TRIM(cAlphaFieldNames(AlphaNum))//': '//TRIM(Alphas(AlphaNum)))
ELSEIF(NumNameMatches > 1) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//&
TRIM(System(RefrigSysNum)%Name)//'", has a non-unique name '//&
'that could be either a '//TRIM(cAlphaFieldNames(AlphaNum))//': '//TRIM(Alphas(AlphaNum)))
END IF !num matches = 0 or > 1
ELSEIF(TransferLoadListNum /= 0) THEN !Name points to a transferLoad list
NumSecondary = TransferLoadList(TransferLoadListNum)%NumSecondarys
NumCascadeLoad = TransferLoadList(TransferLoadListNum)%NumCascadeLoads
System(RefrigSysNum)%NumSecondarys = NumSecondary
System(RefrigSysNum)%NumCascadeLoads = NumCascadeLoad
IF(.NOT. ALLOCATED(System(RefrigSysNum)%SecondaryNum))ALLOCATE(System(RefrigSysNum)%SecondaryNum(NumSecondary))
System(RefrigSysNum)%SecondaryNum(1:NumSecondary) = TransferLoadList(TransferLoadListNum)%SecondaryItemNum(1:NumSecondary)
IF(.NOT. ALLOCATED(System(RefrigSysNum)%CascadeLoadNum))ALLOCATE(System(RefrigSysNum)%CascadeLoadNum(NumCascadeLoad))
System(RefrigSysNum)%CascadeLoadNum(1:NumCascadeLoad) = &
TransferLoadList(TransferLoadListNum)%CascadeLoadItemNum(1:NumCascadeLoad)
ELSEIF (SecondaryNum /= 0) THEN !Name points to a secondary loop load
NumSecondary = 1
System(RefrigSysNum)%NumSecondarys = 1
IF(.NOT. ALLOCATED(System(RefrigSysNum)%SecondaryNum)) ALLOCATE(System(RefrigSysNum)%SecondaryNum(NumSecondary))
System(RefrigSysNum)%Secondarynum(NumSecondary)=SecondaryNum
ELSEIF (CascadeLoadNum /= 0) THEN !Name points to a cascade condenser load
NumCascadeLoad = 1
System(RefrigSysNum)%NumCascadeLoads = 1
IF(.NOT. ALLOCATED(System(RefrigSysNum)%CascadeLoadNum)) &
ALLOCATE(System(RefrigSysNum)%CascadeLoadNum(NumCascadeLoad))
System(RefrigSysNum)%CascadeLoadnum(NumCascadeLoad)=CascadeLoadNum
END IF !NumNameMatches /= 1
System(RefrigSysNum)%CoilFlag = .FALSE.
! Now need to loop through all transfer loads to see if they change the minimum required system evaporating temperature
IF (NumSecondary > 0) THEN
DO SecondaryIndex = 1, NumSecondary
SecondaryID=System(RefrigSysNum)%SecondaryNum(SecondaryIndex)
IF(SecondaryIndex == 1)THEN ! check for consistency of loads (coils calc on sys time step, all others on zone time step)
IF(Secondary(SecondaryID)%CoilFlag)System(RefrigSysNum)%CoilFlag = .TRUE.
ELSEIF(Secondary(SecondaryID)%CoilFlag .neqv. System(RefrigSysNum)%CoilFlag) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)// &
'="'//TRIM(System(RefrigSysNum)%Name)//&
'", Serves an inconsistent mixture of loads. Coil-type loads are served on a '//&
' different time step than case or walkin loads. Compare loads on system served by '//&
' secondary loop "'//&
TRIM(Secondary(SecondaryID)%Name))
ErrorsFound = .TRUE.
ENDIF ! check for consistency of loads (coils calc on sys time step, all others on zone time step)
!mark all Secondarys on system as used by this system (checking for unused or non-unique Secondarys)
Secondary(SecondaryID)%NumSysAttach = Secondary(SecondaryID)%NumSysAttach + 1
NominalTotalSecondaryCap = NominalTotalSecondaryCap + Secondary(SecondaryID)%CoolingLoadRated
System(RefrigSysNum)%RefInventory=System(RefrigSysNum)%RefInventory + &
Secondary(SecondaryID)%ChillerRefInventory
! Find design evaporating temperature for system by getting min design evap for ALL loads
IF ((SecondaryIndex == 1) .AND. (System(RefrigSysNum)%NumCases ==0) .AND. &
(System(RefrigSysNum)%NumCoils ==0) .AND. (System(RefrigSysNum)%NumWalkIns == 0 ))THEN
!note use secondary index above, not secondaryid here to get
!first secondary on this suction group/system
!note - TMinNeeded on secondary defined by cases and walkins served by secondary, not by
! the secondary's rated evaporating temperature (which is used to calc secondary heat
! exchanger effectiveness with other rated values)
System(RefrigSysNum)%TEvapDesign=Secondary(SecondaryID)%TMinNeeded
ELSE
System(RefrigSysNum)%TEvapDesign=MIN(Secondary(SecondaryID)%TMinNeeded,System(RefrigSysNum)%TEvapDesign)
END IF
END DO !SecondaryIndex=1,NumSecondary
System(RefrigSysNum)%NumNonCascadeLoads = System(RefrigSysNum)%NumNonCascadeLoads + System(RefrigSysNum)%NumSecondarys
END IF !numsecondary > 0
IF (NumCascadeLoad > 0 ) THEN
DO CascadeLoadIndex = 1, NumCascadeLoad
CondID=System(RefrigSysNum)%CascadeLoadNum(CascadeLoadIndex)
IF(Condenser(CondID)%CondenserType /= RefrigCondenserTypeCascade) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(System(RefrigSysNum)%Name)&
//'", has a '//&
TRIM(cAlphaFieldNames(AlphaNum))//': '//TRIM(Alphas(AlphaNum))//&
' cascade load that is not a cascade condenser.')
ErrorsFound = .TRUE.
END IF
! For a cascade condenser, need to identify the system absorbing the heat
Condenser(CondID)%CascadeSinkSystemID=RefrigSysNum
NominalTotalCascadeLoad = NominalTotalCascadeLoad + Condenser(CondID)%RatedCapacity
! Find design evaporating temperature for system by getting min design evap for ALL loads
IF (System(RefrigSysNum)%NumNonCascadeLoads == 0 ) THEN
IF (CascadeLoadIndex == 1) THEN
!note use cascadeload index above, not condid here to get
!first cascade condenser served by this suction group/system
System(RefrigSysNum)%TEvapDesign=Condenser(CondID)%CascadeRatedEvapTemp
ELSE
System(RefrigSysNum)%TEvapDesign=MIN(Condenser(CondID)%CascadeRatedEvapTemp,System(RefrigSysNum)%TEvapDesign)
END IF ! CascadeLoadIndex == 1
ELSE ! (NumNonCascadeLoads > 0 so initial TEvapDesign set above with those other loads)
IF (Condenser(CondID)%CascadeTempControl == CascadeTempSet) & ! other wise TEvapDesign set by other loads
System(RefrigSysNum)%TEvapDesign=MIN(Condenser(CondID)%CascadeRatedEvapTemp,System(RefrigSysNum)%TEvapDesign)
END IF
END DO !CascadeLoadIndex=1,NumCascadeLoad
END IF !CascadeLoadNum > 0
END IF !yes/no blank input for transfer loads
! check for consistency of loads (coils calc on sys time step, all others on zone time step, so can't mix on one system)
IF(System(RefrigSysNum)%CoilFlag) THEN !could already be true if serving secondary that serves coils
IF ((System(RefrigSysNum)%NumCases > 0) .OR.(System(RefrigSysNum)%NumWalkIns > 0))THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)// &
'="'//TRIM(System(RefrigSysNum)%Name)//&
'", Serves an inconsistent mixture of loads. Coil-type loads are served on a '//&
' different time step than case or walkin loads.')
ErrorsFound = .TRUE.
END IF
ELSE !no coils on secondary or no secondary
IF(System(RefrigSysNum)%NumCoils > 0) THEN !(note, coilflag set to .false. for all systems as default above
System(RefrigSysNum)%CoilFlag = .TRUE.
IF((System(RefrigSysNum)%NumCases > 0) .OR.(System(RefrigSysNum)%NumWalkIns > 0))THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)// &
'="'//TRIM(System(RefrigSysNum)%Name)//&
'", Serves an inconsistent mixture of loads. Coil-type loads are served on a '//&
' different time step than case or walkin loads.')
ErrorsFound = .TRUE.
END IF
END IF ! NumCoils > 0
END IF !Coil flag already true due to secondary coil loads
NominalTotalCoolingCap = NominalTotalCaseCap + NominalTotalWalkInCap + NominalTotalSecondaryCap + &
NominalTotalCascadeLoad
! read condenser
! currently assumes one condenser per refrigeration system and but multiple systems allowed per condenser
AlphaNum = 4
NumCondensers = 1
IF(.NOT. ALLOCATED(System(RefrigSysNum)%CondenserNum)) &
ALLOCATE(System(RefrigSysNum)%CondenserNum(NumCondensers))
System(RefrigSysNum)%NumCondensers = 1
!Find condenser number, note condensers were read in one of four objects, but all read into same list
CondNum = FindItemInList(Alphas(AlphaNum),Condenser%Name,NumRefrigCondensers)
IF(CondNum == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(System(RefrigSysNum)%Name)//&
'", has an invalid '// &
TRIM(cAlphaFieldNames(AlphaNum))//' defined as '//TRIM(Alphas(AlphaNum)))
ErrorsFound = .TRUE.
ELSE
System(RefrigSysNum)%CondenserNum(NumCondensers) = CondNum
!Now take care of case where multiple systems share a condenser
Condenser(CondNum)%NumSysAttach = Condenser(CondNum)%NumSysAttach + 1
Condenser(CondNum)%SysNum(Condenser(CondNum)%NumSysAttach) = RefrigSysNum
END IF
System(RefrigSysNum)%RefInventory=System(RefrigSysNum)%RefInventory + Condenser(CondNum)%RefReceiverInventory + &
Condenser(CondNum)%RefPipingInventory + Condenser(CondNum)%RefOpCharge
IF(Condenser(CondNum)%CondenserType == RefrigCondenserTypeCascade)Condenser(CondNum)%CascadeSysID=RefrigSysNum
IF((Condenser(Condnum)%CondenserType==RefrigCondenserTypeAir).AND. &
( Condenser(Condnum)%CondenserRejectHeatToZone))System(RefrigSysNum)%SystemRejectHeatToZone = .TRUE.
!Now do evaporative condenser auto sizing because it is a function of the system's cooling load
IF(Condenser(CondNum)%CondenserType == RefrigCondenserTypeEvap)THEN
IF(Condenser(CondNum)%RatedAirFlowRate==AutoCalculate) THEN
Condenser(CondNum)%RatedAirFlowRate = AirVolRateEvapCond * Condenser(CondNum)%RatedCapacity
END IF
IF (Condenser(CondNum)%RatedAirFlowRate <= 0.0d0 ) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'", Evaporative Condenser Air Volume Flow Rate cannot be less than or equal to zero.')
ErrorsFound = .TRUE.
END IF
IF(Condenser(CondNum)%EvapPumpPower==AutoCalculate) THEN
Condenser(CondNum)%EvapPumpPower = CondPumpRatePower * Condenser(CondNum)%RatedCapacity
END IF
IF(Condenser(CondNum)%EvapPumpPower < 0.0d0 ) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(Condenser(CondNum)%Name)//&
'", Design Evaporative Condenser Water Pump Power cannot be less than zero.')
ErrorsFound = .TRUE.
END IF
END IF
! Read the compressor data.
! If the system consists of two stages of compression, these compressors will be the low-stage compressors.
AlphaNum=5
NumCompressorsSys = 0
IF(lAlphaBlanks(AlphaNum)) THEN
!blank input where must have compressor or compressor list input.
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//' '//TRIM(cAlphaFieldNames(AlphaNum))//'" : '//&
'must be input.')
ErrorsFound = .TRUE.
ELSE ! Entry for Alphas(AlphaNum) can be either a compressor name or a compressorlist name
IF (NumCompressorLists > 0 ) THEN
ListNum=FindItemInList(Alphas(AlphaNum),CompressorLists%Name,NumCompressorLists)
ELSE
ListNum=0
ENDIF
IF (NumSimulationCompressors > 0) THEN
CompNum=FindItemInList(Alphas(AlphaNum),Compressor%Name,NumSimulationCompressors)
ELSE
CompNum=0
ENDIF
IF((ListNum == 0) .AND. (CompNum == 0)) THEN ! name doesn't match either a compressor or a compressor list
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//' '//&
TRIM(cAlphaFieldNames(AlphaNum))//', has an invalid '//&
'or undefined value="'//TRIM(Alphas(AlphaNum))//'".')
ErrorsFound = .TRUE.
ELSEIF((ListNum /= 0) .AND. (CompNum /= 0)) THEN !have compressor list and compressor with same name
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//' '//&
TRIM(cAlphaFieldNames(AlphaNum))//', has a non-unique name '//&
' used for both Compressor and CompressorList name: "'//TRIM(Alphas(AlphaNum))//'".')
ErrorsFound = .TRUE.
ELSE IF(ListNum /= 0) THEN
NumCompressorsSys = CompressorLists(ListNum)%NumCompressors
System(RefrigSysNum)%NumCompressors = NumCompressorsSys
IF(.NOT. ALLOCATED(System(RefrigSysNum)%CompressorNum))&
ALLOCATE(System(RefrigSysNum)%CompressorNum(NumCompressorsSys))
System(RefrigSysNum)%CompressorNum(1:NumCompressorsSys) = CompressorLists(ListNum)%CompItemNum(1:NumCompressorsSys)
ELSEIF (CompNum /= 0) THEN
NumCompressorsSys = 1
System(RefrigSysNum)%NumCompressors = 1
IF(.NOT. ALLOCATED(System(RefrigSysNum)%CompressorNum))&
ALLOCATE(System(RefrigSysNum)%CompressorNum(NumCompressorsSys))
System(RefrigSysNum)%CompressorNum(NumCompressorsSys)=CompNum
END IF
ENDIF
IF (.NOT. lNumericBlanks(1)) THEN
System(RefrigSysNum)%TCondenseMin= Numbers(1)
System(RefrigSysNum)%TCondenseMinInput = System(RefrigSysNum)%TCondenseMin
IF (AnyEnergyManagementSystemInModel) THEN
CALL SetupEMSActuator('Refrigeration:System', System(RefrigSysNum)%Name, &
'Minimum Condensing Temperature' , '[C]', &
System(RefrigSysNum)%EMSOverrideOnTCondenseMin, &
System(RefrigSysNum)%EMSOverrideValueTCondenseMin )
ENDIF
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(System(RefrigSysNum)%Name)//&
'", '//TRIM(cNumericFieldNames(1))//' must be defined.')
ErrorsFound = .TRUE.
END IF
IF ((Condenser(CondNum)%CondenserType == RefrigCondenserTypeCascade).AND. &
(System(RefrigSysNum)%TCondenseMin > Condenser(CondNum)%RatedTCondense)) &
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(System(RefrigSysNum)%Name)//&
'", The system specified minimum condensing temperature is greater than '//&
' the rated condensing temperature for the cascade condenser. ')
AlphaNum=6
System(RefrigSysNum)%RefrigerantName = Alphas(AlphaNum)
!error messages for refrigerants already found in fluidproperties
AlphaNum=7
IF(.NOT. lAlphaBlanks(AlphaNum)) THEN
IF (SameString(Alphas(AlphaNum),'ConstantSuctionTemperature')) THEN
System(RefrigSysNum)%CompSuctControl = ConstantSuctionTemperature
ELSEIF (SameString(Alphas(AlphaNum),'FloatSuctionTemperature')) THEN
System(RefrigSysNum)%CompSuctControl = FloatSuctionTemperature
IF(System(RefrigSysNum)%CoilFlag)THEN
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(System(RefrigSysNum)%Name)//&
'", The system specified a FloatSuctionTemperature, but that is not '//&
'available with air chiller loads so ConstantSuctionTemperature will be used. ')
END IF !coilflag
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(System(RefrigSysNum)%Name)// &
'", invalid '//TRIM(cAlphaFieldNames(AlphaNum))//' not found = '//TRIM(Alphas(AlphaNum)))
ErrorsFound=.TRUE.
END IF
ELSE
System(RefrigSysNum)%CompSuctControl = ConstantSuctionTemperature !Default for blank
END IF
!Count subcoolers on system and allocate
AlphaNum=8
System(RefrigSysNum)%NumSubcoolers=0
IF(.NOT. lAlphaBlanks(AlphaNum)) THEN
System(RefrigSysNum)%NumSubcoolers = System(RefrigSysNum)%NumSubcoolers + 1
END IF
IF(.NOT. lAlphaBlanks(AlphaNum+1)) THEN
System(RefrigSysNum)%NumSubcoolers = System(RefrigSysNum)%NumSubcoolers + 1
END IF
IF(System(RefrigSysNum)%NumSubcoolers > 0)THEN
IF(.NOT. ALLOCATED(System(RefrigSysNum)%SubcoolerNum)) &
ALLOCATE(System(RefrigSysNum)%SubcoolerNum(System(RefrigSysNum)%NumSubcoolers))
NumSubcooler=1
IF(.NOT. lAlphaBlanks(AlphaNum)) THEN
System(RefrigSysNum)%SubcoolerNum(NumSubcooler)= GetObjectItemNum('Refrigeration:Subcooler',Alphas(AlphaNum))
IF(System(RefrigSysNum)%SubcoolerNum(NumSubcooler) <= 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(System(RefrigSysNum)%Name)//&
'", has an invalid '//TRIM(cAlphaFieldNames(AlphaNum))//' defined as "'//TRIM(Alphas(AlphaNum))//'".')
ErrorsFound = .TRUE.
ELSE
Subcooler(System(RefrigSysNum)%SubcoolerNum(NumSubcooler))%CoilFlag=System(RefrigSysNum)%CoilFlag
END IF
NumSubcooler=NumSubcooler+1
END IF
IF(.NOT. lAlphaBlanks(AlphaNum+1)) THEN
System(RefrigSysNum)%SubcoolerNum(NumSubcooler)= GetObjectItemNum('Refrigeration:Subcooler',Alphas(AlphaNum+1))
IF(System(RefrigSysNum)%SubcoolerNum(NumSubcooler) <= 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(System(RefrigSysNum)%Name)//&
'", has an invalid '//TRIM(cAlphaFieldNames(AlphaNum+1))//' defined as "'//TRIM(Alphas(AlphaNum+1))//'".')
ErrorsFound = .TRUE.
ELSE
Subcooler(System(RefrigSysNum)%SubcoolerNum(NumSubcooler))%CoilFlag=System(RefrigSysNum)%CoilFlag
END IF
END IF
END IF
!Suction piping heat gain - optional
! Input UA and identify the Zone containing the bulk of the suction piping
! This Zone ID will be used to determine the temperature used for suction piping heat gain.
! The pipe heat gains are also counted as cooling credit for the zone.
! Zone Id is only required if Sum UA Suction Piping >0.0
! Get the Zone and zone node numbers from the zone name entered by the user
AlphaNum=10
System(RefrigSysNum)%SumUASuctionPiping=0.d0
IF(.NOT. lNumericBlanks(2) .AND. .NOT. lAlphaBlanks(AlphaNum)) THEN
System(RefrigSysNum)%SumUASuctionPiping= Numbers(2)
System(RefrigSysNum)%SuctionPipeActualZoneNum = FindItemInList(Alphas(AlphaNum),Zone%Name,NumOfZones)
System(RefrigSysNum)%SuctionPipeZoneNodeNum = GetSystemNodeNumberForZone(Alphas(AlphaNum))
IF ( System(RefrigSysNum)%SuctionPipeZoneNodeNum == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(System(RefrigSysNum)%Name)//&
'", System Node Number not found for '//TRIM(cAlphaFieldNames(AlphaNum))// &
' = '//TRIM(Alphas(AlphaNum))//' even though '//TRIM(cNumericFieldNames(2))//&
' is greater than zero. Suction piping heat gain cannot be calculated unless a Zone'//&
' is defined to deterimine the environmental temperature surrounding the piping.')
ErrorsFound=.TRUE.
ELSE
RefrigPresentInZone(System(RefrigSysNum)%SuctionPipeActualZoneNum) = .TRUE.
ENDIF
ELSEIF(.NOT. lNumericBlanks(2) .AND. lAlphaBlanks(AlphaNum)) THEN
CALL ShowWarningError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(System(RefrigSysNum)%Name)//&
'" '//TRIM(cAlphaFieldNames(AlphaNum))//' not found even though '//TRIM(cNumericFieldNames(2))//&
' is greater than zero. Suction piping heat gain will not be calculated unless a Zone'//&
' is defined to determine the environmental temperature surrounding the piping.')
ELSEIF(lNumericBlanks(2) .AND. .NOT. lAlphaBlanks(AlphaNum)) THEN
CALL ShowWarningError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(System(RefrigSysNum)%Name)//&
'" '//TRIM(cAlphaFieldNames(AlphaNum))//' will not be used and suction piping heat gain will '//&
' not be calculated because '//TRIM(cNumericFieldNames(2))//&
' was blank.')
END IF !suction piping heat gains
AlphaNum=11
IF (.NOT. lAlphaBlanks(AlphaNum)) System(RefrigSysNum)%EndUseSubcategory = Alphas(AlphaNum)
! Single-stage or two-stage compression system
IF(.NOT. lNumericBlanks(3)) THEN
System(RefrigSysNum)%NumStages = Numbers(3)
IF(System(RefrigSysNum)%NumStages<1 .OR. System(RefrigSysNum)%NumStages>2) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(System(RefrigSysNum)%Name)//&
'", '//TRIM(cNumericFieldNames(3))//' has an invalid '//&
'value. Only "1" or "2" compressor stages are allowed.')
ErrorsFound=.TRUE.
END IF
ELSE
System(RefrigSysNum)%NumStages = 1 !Default for blank
END IF
! Intercooler type
! None (0) for single-stage compression systems
! Flash intercooler (1) or coil-and-shell intercooler (2) for two-stage compression systems
AlphaNum=12
IF (.NOT. lAlphaBlanks(AlphaNum)) THEN
IF (SameString(Alphas(AlphaNum),'None')) THEN
System(RefrigSysNum)%IntercoolerType = 0
ELSEIF (SameString(Alphas(AlphaNum),'Flash Intercooler')) THEN
System(RefrigSysNum)%IntercoolerType = 1
ELSEIF (SameString(Alphas(AlphaNum),'Shell-and-Coil Intercooler')) THEN
System(RefrigSysNum)%IntercoolerType = 2
ELSE
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(System(RefrigSysNum)%Name)//&
'", Invalid '//TRIM(cAlphaFieldNames(AlphaNum))//' specified.')
CALL ShowContinueError('"'//TRIM(Alphas(AlphaNum))//'" is not a recognized intercooler type.')
ErrorsFound=.TRUE.
END IF
ELSE
System(RefrigSysNum)%IntercoolerType = 0 !Default for blank
END IF
IF (System(RefrigSysNum)%NumStages==1 .AND. &
(System(RefrigSysNum)%IntercoolerType==1 .OR. System(RefrigSysNum)%IntercoolerType==2)) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(System(RefrigSysNum)%Name)//&
'", A single-stage compression system')
CALL ShowContinueError('has been specified with an intercooler. Verify that the number of compressor stages')
CALL ShowContinueError('and the intercooler type are consistent.')
ErrorsFound=.TRUE.
ELSEIF (System(RefrigSysNum)%NumStages==2 .AND. System(RefrigSysNum)%IntercoolerType==0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(System(RefrigSysNum)%Name)//&
'", A two-stage compression system')
CALL ShowContinueError('has been specified without an intercooler. Verify that the number of compressor stages')
CALL SHowContinueError('and the intercooler type are consistent.')
ErrorsFound=.TRUE.
END IF
! Shell-and-coil intercooler effectiveness
IF(.NOT. lNumericBlanks(4)) THEN
System(RefrigSysNum)%IntercoolerEffectiveness = Numbers(4)
IF(System(RefrigSysNum)%IntercoolerEffectiveness<0.0d0 .OR. System(RefrigSysNum)%IntercoolerEffectiveness>1.0d0) THEN
CALL ShowWarningError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(System(RefrigSysNum)%Name)//&
'", The specified value for the')
CALL ShowContinueError(TRIM(cNumericFieldNames(4))//' = '//&
TRIM(RoundSigDigits(System(RefrigSysNum)%IntercoolerEffectiveness,2))//' is invalid. This value must be')
CALL ShowContinueError('between 0.0 and 1.0. The default value of 0.8 will be used.')
System(RefrigSysNum)%IntercoolerEffectiveness = 0.8d0
END IF
ELSE
System(RefrigSysNum)%IntercoolerEffectiveness = 0.8d0
END IF
! Read the high-stage compressor info, if two-stage compression has been specified.
AlphaNum=13
NumHiStageCompressorsSys = 0
IF(System(RefrigSysNum)%NumStages==2) THEN
IF(lAlphaBlanks(AlphaNum)) THEN
!blank input where must have high-stage compressor or compressor list input.
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(System(RefrigSysNum)%Name)//&
'", '//TRIM(cAlphaFieldNames(AlphaNum))//' must be input for two-stage compression systems.')
ErrorsFound = .TRUE.
ELSE ! Entry for Alphas(AlphaNum) can be either a compressor name or a compressorlist name
ListNum=FindItemInList(Alphas(AlphaNum),CompressorLists%Name,NumCompressorLists)
CompNum=FindItemInList(Alphas(AlphaNum),Compressor%Name,NumSimulationCompressors)
IF((ListNum == 0) .AND. (CompNum == 0)) THEN ! name doesn't match either a compressor or a compressor list
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(System(RefrigSysNum)%Name)//&
'", '//TRIM(cAlphaFieldNames(AlphaNum))//' has an invalid or undefined value="'//&
TRIM(Alphas(AlphaNum))//'".')
ErrorsFound = .TRUE.
ELSEIF((ListNum /= 0) .AND. (CompNum /= 0)) THEN !have compressor list and compressor with same name
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)//'="'//TRIM(System(RefrigSysNum)%Name)//&
'", '//TRIM(cAlphaFieldNames(AlphaNum))//' has a non-unique name used for both Compressor '//&
'and CompressorList name: "'//TRIM(Alphas(AlphaNum))//'".')
ErrorsFound = .TRUE.
ELSE IF(ListNum /= 0) THEN
NumHiStageCompressorsSys = CompressorLists(ListNum)%NumCompressors
System(RefrigSysNum)%NumHiStageCompressors = NumHiStageCompressorsSys
IF(.NOT. ALLOCATED(System(RefrigSysNum)%HiStageCompressorNum))&
ALLOCATE(System(RefrigSysNum)%HiStageCompressorNum(NumHiStageCompressorsSys))
System(RefrigSysNum)%HiStageCompressorNum(1:NumHiStageCompressorsSys) = &
CompressorLists(ListNum)%CompItemNum(1:NumHiStageCompressorsSys)
ELSEIF (CompNum /= 0) THEN
NumHiStageCompressorsSys = 1
System(RefrigSysNum)%NumHiStageCompressors = 1
IF(.NOT. ALLOCATED(System(RefrigSysNum)%HiStageCompressorNum))&
ALLOCATE(System(RefrigSysNum)%HiStageCompressorNum(NumHiStageCompressorsSys))
System(RefrigSysNum)%HiStageCompressorNum(NumHiStageCompressorsSys)=CompNum
END IF
ENDIF
ENDIF
! Determine intercooler pressure and temperature at design conditions
IF(System(RefrigSysNum)%NumStages==2) THEN
Pcond=GetSatPressureRefrig(System(RefrigSysNum)%RefrigerantName, &
Condenser(System(RefrigSysNum)%CondenserNum(1))%RatedTCondense, &
System(RefrigSysNum)%RefIndex, TRIM(RoutineName))
Pevap=GetSatPressureRefrig(System(RefrigSysNum)%RefrigerantName, &
System(RefrigSysNum)%TEvapDesign, &
System(RefrigSysNum)%RefIndex, TRIM(RoutineName))
System(RefrigSysNum)%PIntercooler=SQRT(Pcond*Pevap)
System(RefrigSysNum)%TIntercooler=GetSatTemperatureRefrig(System(RefrigSysNum)%RefrigerantName, &
System(RefrigSysNum)%PIntercooler, &
System(RefrigSysNum)%RefIndex, TRIM(RoutineName))
END IF ! NumStages
! Sum capacity of single-stage compressors or low-stage compressors if two-stage system
NominalTotalCompCap = 0.0d0
DO CompIndex=1,NumCompressorsSys
CompNum = System(RefrigSysNum)%CompressorNum(CompIndex)
IF (.NOT. Compressor(CompNum)%TransFlag) THEN ! Subcritical Compressor
IF (System(RefrigSysNum)%NumStages==1) THEN ! Single-stage compression
Compressor(CompNum)%NomCap = CurveValue(Compressor(CompNum)%CapacityCurvePtr,&
System(RefrigSysNum)%TEvapDesign,Condenser(System(RefrigSysNum)%CondenserNum(1))%RatedTCondense)
NominalTotalCompCap = NominalTotalCompCap + Compressor(CompNum)%NomCap
Compressor(CompNum)%NumSysAttach = Compressor(CompNum)%NumSysAttach + 1
ELSE ! Two-stage compression, low-stage compressors
Compressor(CompNum)%NomCap = CurveValue(Compressor(CompNum)%CapacityCurvePtr,&
System(RefrigSysNum)%TEvapDesign,System(RefrigSysNum)%TIntercooler)
NominalTotalCompCap = NominalTotalCompCap + Compressor(CompNum)%NomCap
Compressor(CompNum)%NumSysAttach = Compressor(CompNum)%NumSysAttach + 1
END IF ! NumStages
ELSE ! Transcritical compressor attached to subcritical refigeration cycle
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'. '//&
'A transcritical compressor is attached to a subcritical refrigeration system.')
CALL ShowContinueError('Check input to ensure that subcritical compressors are '// &
'connected only to subcritical systems and'// &
' transcritical compressors are connected only to transcritical systems.')
ErrorsFound = .TRUE.
END IF ! .NOT. Compressor(CompNum)%TransFlag
END DO
! Sum capacity of high-stage compressors if two stage system
IF (System(RefrigSysNum)%NumStages==2) THEN
DO CompIndex=1,NumHiStageCompressorsSys
CompNum = System(RefrigSysNum)%HiStageCompressorNum(CompIndex)
IF (.NOT. Compressor(CompNum)%TransFlag) THEN ! Subcritical Compressor
Compressor(CompNum)%NomCap = CurveValue(Compressor(CompNum)%CapacityCurvePtr,&
System(RefrigSysNum)%TIntercooler,Condenser(System(RefrigSysNum)%CondenserNum(1))%RatedTCondense)
NominalTotalHiStageCompCap = NominalTotalHiStageCompCap + Compressor(CompNum)%NomCap
Compressor(CompNum)%NumSysAttach = Compressor(CompNum)%NumSysAttach + 1
ELSE ! Transcritical compressor attached to subcritical refigeration cycle
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'. '//&
'A transcritical compressor is attached to a subcritical refrigeration system.')
CALL ShowContinueError('Check input to ensure that subcritical compressors are '// &
'connected only to subcritical systems and'// &
' transcritical compressors are connected only to transcritical systems.')
ErrorsFound = .TRUE.
END IF
END DO
ENDIF ! NumStages
!Compare the rated capacity of compressor, condenser, and cases.
! Note, rated capacities can be far off from operating capacities, but rough check.
NominalCondCap=Condenser(System(RefrigSysNum)%CondenserNum(1))%RatedCapacity
IF(System(RefrigSysNum)%SystemRejectHeatToZone)NominalCondCap=NominalCondCap*2.d0
IF(System(RefrigSysNum)%NumStages==1) THEN ! Single-stage system
IF((NominalTotalCompCap < (0.7d0*NominalTotalCoolingCap)) .OR. &
(NominalCondCap < (1.3d0*NominalTotalCoolingCap))) THEN
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(System(RefrigSysNum)%Name)//&
'", You may wish to check the system sizing. Total nominal cooling capacity is '//&
TRIM(RoundSigDigits(NominalTotalCoolingCap,0))//'W. Condenser capacity is '//&
TRIM(RoundSigDigits(NominalCondCap,0))//'W. Nominal compressor capacity is '//&
TRIM(RoundSigDigits(NominalTotalCompCap,0))//'W.')
END IF
ELSE IF (System(RefrigSysNum)%NumStages==2) THEN ! Two-stage system
IF((NominalTotalHiStageCompCap < (0.7d0*NominalTotalCoolingCap)) .OR. &
(NominalCondCap < (1.3d0*NominalTotalCoolingCap))) THEN
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(System(RefrigSysNum)%Name)//&
'", You may wish to check the system sizing. Total nominal cooling capacity is '//&
TRIM(RoundSigDigits(NominalTotalCoolingCap,0))//'W. Condenser capacity is '//&
TRIM(RoundSigDigits(NominalCondCap,0))//'W. Nominal compressor capacity is '//&
TRIM(RoundSigDigits(NominalTotalCompCap,0))//'W.')
END IF
END IF ! NumStages
END DO ! Refrigeration systems
! Assign coilflags to compressors, condensers, and subcoolers (coils calc on sys time step, all other refrig loads on zone time step, so can't mix on one system)
! need to do here once again after all cascade condensers and cascade sink systems have been identified
DO RefrigSysNum=1,NumRefrigSystems
!assign flags to all condensers to match system below condenser (system rejecting heat to cascade condenser)
CondNum = System(RefrigSysNum)%CondenserNum(1) ! right now only have one condenser per system
Condenser(CondNum)%CoilFlag = System(RefrigSysNum)%CoilFlag
DO CompIndex=1,System(RefrigSysNum)%NumCompressors
CompNum = System(RefrigSysNum)%CompressorNum(CompIndex)
Compressor(CompNum)%CoilFlag = System(RefrigSysNum)%CoilFlag
END DO
END DO !assign coil flags to all condensers
!Finished setting cascade condenser coilflags to match system rejecting heat to the cascade condenser
! Now have to see if there's a mismatch in the coilflag with the system absorbing heat from the cascade condenser
! Note a system can cool multiple cascade condensers. If so, need to be sure all are consistent - all coil or all non-coil(called case here)
! check for consistency of loads (coils calc on sys time step, all others on zone time step, so can't mix on one system)
DO RefrigSysNum=1,NumRefrigSystems !check flags for systems reflect all cascade loads
IF (System(RefrigSysNum)%NumCascadeLoads == 0) CYCLE
IF(System(RefrigSysNum)%CoilFlag) THEN !system already identified as serving coils
DO CondID = 1,NumRefrigCondensers
IF (Condenser(CondID)%CondenserType /= RefrigCondenserTypeCascade)CYCLE
IF (RefrigSysNum /= Condenser(CondID)%CascadeSinkSystemID) CYCLE !this condenser is not a cascade load on this system
IF (.NOT. Condenser(CondID)%CoilFlag )THEN
!would mean system already serving coil loads and this condenser cooling system with case-type loads
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)// &
'="'//TRIM(System(RefrigSysNum)%Name)//&
'", Serves an inconsistent mixture of loads. Coil-type loads are served on a '//&
' different time step than case or walkin loads. Compare loads on system served by '//&
' cascade condenser "'//&
TRIM(Condenser(CondID)%Name))
ErrorsFound = .TRUE.
END IF
END DO !CondID
ELSE ! %coilflag == false, so no coil loads prev identified directly or through secondary loop
CaseLoads = .FALSE.
NumCascadeLoadsChecked = 0
DO CondID = 1,NumRefrigCondensers !look at All cascade condenser loads on system
IF (Condenser(CondID)%CondenserType /= RefrigCondenserTypeCascade)CYCLE
IF (RefrigSysNum /= Condenser(CondID)%CascadeSinkSystemID)CYCLE !this condenser is not a cascade load on this system
NumCascadeLoadsChecked = NumCascadeLoadsChecked + 1
IF ((CaseLoads) .AND. (.NOT. Condenser(CondID)%CoilFlag).AND.(.NOT. System(RefrigSysNum)%CoilFlag)) CYCLE
!all loads to date are case-type and properly flagged with consistent coilflags
!(note caseloads could be true if prev cascade load checked is serving a case-type system)
IF (NumCascadeLoadsChecked == 1)THEN
IF (Condenser(CondID)%CoilFlag) THEN
System(RefrigSysNum)%CoilFlag = .TRUE.
!setting system coilflag if 1st cascade condenser served has coils (system has no case-type loads up to this point)
ELSE !condenser is not serving coils, but case-type loads
CaseLoads = .TRUE.
!system coilflag already set to false
END IF !Condenser%CoilFlag
ELSE !numcascadeloadschecked > 1
IF(System(RefrigSysNum)%CoilFlag .neqv. Condenser(CondID)%CoilFlag)THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)// &
'="'//TRIM(System(RefrigSysNum)%Name)//&
'", Serves an inconsistent mixture of loads. Coil-type loads are served on a '//&
' different time step than case or walkin loads. Compare loads on system served by '//&
' cascade condenser "'//&
TRIM(Condenser(CondID)%Name))
ErrorsFound = .TRUE.
END IF
END IF !numcascadeloadschecked > 1
END DO ! CondID
END IF !(System%coilflag)
END DO ! Refrigeration systems checking coilflag consistency with cascade condenser loads
END IF !(NumRefrigSystems > 0)
!after the systems have been read, can finish the mechanical subcooler/system interactions
!System%NumMechSCServed=0
IF (NumSimulationSubcoolers > 0) THEN
DO SubcoolerNum=1, NumSimulationSubcoolers
IF(Subcooler(SubcoolerNum)%Subcoolertype == LiquidSuction)CYCLE
Subcooler(SubcoolerNum)%MechSourceSysID = &
GetObjectItemNum('Refrigeration:System',Subcooler(SubcoolerNum)%MechSourceSys)
IF (Subcooler(SubcoolerNum)%MechSourceSysID == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)// &
'="'//TRIM(Subcooler(SubcoolerNum)%Name)//&
'", Mechanical Subcooler has an invalid Source Refrigeration:System="'//&
TRIM(Subcooler(SubcoolerNum)%MechSourceSys)//'".')
ErrorsFound = .TRUE.
ELSE
IF (System(Subcooler(SubcoolerNum)%MechSourceSysID)%CoilFlag .neqv. Subcooler(SubcoolerNum)%CoilFlag )THEN
CALL ShowSevereError(RoutineName//TRIM(CurrentModuleObject)// &
'="'//TRIM(System(RefrigSysNum)%Name)//&
'", Serves an inconsistent mixture of loads. Coil-type loads are served on a '//&
' different time step than case or walkin loads. Compare loads on system served by '//&
' mechanical subcooler "'//&
TRIM(Subcooler(SubcoolerNum)%Name))
ErrorsFound = .TRUE.
END IF
END IF !error check
END DO ! numsubcoolers
DO RefrigSysNum=1,NumRefrigSystems
DO SubcoolerNum=1,NumSimulationSubcoolers
IF(Subcooler(SubcoolerNum)%Subcoolertype == LiquidSuction)CYCLE
IF(Subcooler(SubcoolerNum)%MechSourceSysID == RefrigSysNum)THEN
System(RefrigSysNum)%NumMechSCServed=System(RefrigSysNum)%NumMechSCServed + 1
END IF
END DO
IF(System(RefrigSysNum)%NumMechSCServed > 0) THEN
IF(.NOT. ALLOCATED(System(RefrigSysNum)%MechSCLoad)) &
ALLOCATE(System(RefrigSysNum)%MechSCLoad(NumSimulationSubcoolers))
END IF
END DO
END IF ! NumSimulationSubcoolers > 0
! ********** READ TRANSCRITICAL REFRIGERATION SYSTEMS **********
IF (NumTransRefrigSystems >0) THEN
CurrentModuleObject='Refrigeration:TranscriticalSystem'
DO TransRefrigSysNum=1,NumTransRefrigSystems
CALL GetObjectItem(CurrentModuleObject,TransRefrigSysNum,Alphas,NumAlphas,Numbers,NumNumbers,IOStatus, &
NumBlank=lNumericBlanks,AlphaBlank=lAlphaBlanks, &
AlphaFieldNames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
IsNotOK =.FALSE.
IsBlank =.FALSE.
CALL VerifyName(Alphas(1),TransSystem%Name,RefrigSysNum-1,IsNotOK,IsBlank,CurrentModuleObject//' Name')
IF (IsNotOK) THEN
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//', has an invalid or undefined '// &
TRIM(cAlphaFieldNames(1))//'="'//TRIM(Alphas(1))//'".')
IF (IsBlank) Alphas(1)='xxxxx'
ErrorsFound=.TRUE.
ENDIF
TransSystem(TransRefrigSysNum)%Name = Alphas(1)
! Read refrigerant for this system
AlphaNum=8
TransSystem(TransRefrigSysNum)%RefrigerantName = Alphas(AlphaNum)
!error messages for refrigerants already found in fluidproperties
! Read Transcritical System Type: SingleStage or TwoStage
IF(lAlphaBlanks(2)) THEN
! No system type specified
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(TransSystem(TransRefrigSysNum)%Name)// &
'", has no system type specified.')
CALL ShowContinueError(' System type must be specified as "SingleStage" or "TwoStage".')
ErrorsFound = .TRUE.
END IF
IF (SameString(Alphas(2),'SingleStage')) THEN
TransSystem(TransRefrigSysNum)%TransSysType = 1
ELSE IF (SameString(Alphas(2),'TwoStage')) THEN
TransSystem(TransRefrigSysNum)%TransSysType = 2
ELSE
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(TransSystem(TransRefrigSysNum)%Name)// &
'", has an incorrect System Type specified as "'//TRIM(Alphas(2))//'".')
CALL ShowContinueError(' System type must be specified as "SingleStage" or "TwoStage".')
ErrorsFound = .TRUE.
END IF
! Read all loads (display cases and walk-ins) on this Transcritical System
IF(lAlphaBlanks(3) .AND. lAlphaBlanks(4)) THEN
! No loads specified - display error
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(TransSystem(TransRefrigSysNum)%Name)// &
'", has no loads.')
CALL ShowContinueError(' The system must have at least one of: '//TRIM(cAlphaFieldNames(3))//' or '// &
TRIM(cAlphaFieldNames(4))//' objects attached.')
ErrorsFound = .TRUE.
ELSE IF (lAlphaBlanks(3) .AND. TransSystem(TransRefrigSysNum)%TransSysType == 1) THEN
! No medium temperature loads specified for a SingleStage system - display error
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(TransSystem(TransRefrigSysNum)%Name)// &
'", is a "SingleStage" system but no medium temperature loads are specified.')
CALL ShowContinueError(' The system must have at least one '//TRIM(cAlphaFieldNames(3))//' object attached.')
ErrorsFound = .TRUE.
ELSE IF (lAlphaBlanks(4) .AND. TransSystem(TransRefrigSysNum)%TransSysType == 2) THEN
! No low temperature loads specified for a TwoStage system - display error
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(TransSystem(TransRefrigSysNum)%Name)// &
'", is a "TwoStage" system but no low temperature loads are specified.')
CALL ShowContinueError(' The system must have at least one '//TRIM(cAlphaFieldNames(4))//' object attached.')
ErrorsFound = .TRUE.
END IF
NumCasesMT = 0
TransSystem(TransRefrigSysNum)%NumCasesMT = 0
NumCasesLT = 0
TransSystem(TransRefrigSysNum)%NumCasesLT = 0
NumWalkInsMT = 0
TransSystem(TransRefrigSysNum)%NumWalkInsMT = 0
NumWalkInsLT = 0
TransSystem(TransRefrigSysNum)%NumWalkInsLT = 0
NominalTotalCaseCapMT = 0.0d0
NominalTotalCaseCapLT = 0.0d0
NominalTotalWalkInCapMT = 0.0d0
NominalTotalWalkInCapLT = 0.0d0
NominalTotalCoolingCap = 0.0d0
TransSystem(TransRefrigSysNum)%RefInventory = 0.0d0
! Check for Medium Temperature Case or Walk-In or CaseAndWalkInList names
AlphaNum = 3
IF (.NOT. lAlphaBlanks(AlphaNum)) THEN
! Entry for Alphas(AlphaNum) can be either a Case, WalkIn or CaseAndWalkInList name
CaseAndWalkInListNum=0
CaseNum=0
WalkInNum=0
IF(NumSimulationCaseAndWalkInLists > 0) &
CaseAndWalkInListNum=FindItemInList(Alphas(AlphaNum),CaseAndWalkInList%Name,NumSimulationCaseAndWalkInLists)
IF(NumSimulationCases > 0) CaseNum= FindItemInList(Alphas(AlphaNum),RefrigCase%Name,NumSimulationCases)
IF(NumSimulationWalkIns > 0)WalkInNum=FindItemInList(Alphas(AlphaNum),WalkIn%Name,NumSimulationWalkIns)
NumNameMatches = 0
IF(CaseAndWalkInListNum /= 0)NumNameMatches = NumNameMatches +1
IF(CaseNum /= 0) NumNameMatches = NumNameMatches +1
IF(WalkInNum /= 0) NumNameMatches = NumNameMatches +1
IF (NumNameMatches /= 1) THEN !name must uniquely point to a list or a single case or walkin or coil
ErrorsFound = .TRUE.
IF(NumNameMatches == 0) THEN
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(TransSystem(TransRefrigSysNum)%Name)//&
'", has an invalid '//TRIM(cAlphaFieldNames(AlphaNum))//': '//TRIM(Alphas(AlphaNum)))
ELSEIF(NumNameMatches > 1) THEN
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//&
TRIM(TransSystem(TransRefrigSysNum)%Name)//'", has a non-unique name '//&
'that could be either a '//TRIM(cAlphaFieldNames(AlphaNum))//': '//TRIM(Alphas(AlphaNum)))
END IF !num matches = 0 or > 1
ELSEIF(CaseAndWalkInListNum /= 0) THEN !Name points to a CaseAndWalkInList
NumCasesMT = CaseAndWalkInList(CaseAndWalkInListNum)%NumCases
NumWalkInsMT = CaseAndWalkInList(CaseAndWalkInListNum)%NumWalkIns
TransSystem(TransRefrigSysNum)%NumCasesMT = NumCasesMT
TransSystem(TransRefrigSysNum)%NumWalkInsMT = NumWalkInsMT
IF(NumCasesMT > 0) THEN
IF(.NOT. ALLOCATED(TransSystem(TransRefrigSysNum)%CaseNumMT)) &
ALLOCATE(TransSystem(TransRefrigSysNum)%CaseNumMT(NumCasesMT))
TransSystem(TransRefrigSysNum)%CaseNumMT(1:NumCasesMT) = &
CaseAndWalkInList(CaseAndWalkInListNum)%CaseItemNum(1:NumCasesMT)
END IF
IF(NumWalkInsMT > 0) THEN
IF(.NOT. ALLOCATED(TransSystem(TransRefrigSysNum)%WalkInNumMT)) &
ALLOCATE(TransSystem(TransRefrigSysNum)%WalkInNumMT(NumWalkInsMT))
TransSystem(TransRefrigSysNum)%WalkInNumMT(1:NumWalkInsMT) = &
CaseAndWalkInList(CaseAndWalkInListNum)%WalkInItemNum(1:NumWalkInsMT)
END IF
ELSEIF (CaseNum /= 0) THEN !Name points to a case
NumCasesMT = 1
TransSystem(TransRefrigSysNum)%NumCasesMT = 1
IF(.NOT. ALLOCATED(TransSystem(TransRefrigSysNum)%CaseNumMT)) &
ALLOCATE(TransSystem(TransRefrigSysNum)%CaseNumMT(NumCasesMT))
TransSystem(TransRefrigSysNum)%CaseNumMT(NumCases)=CaseNum
ELSEIF (WalkInNum /= 0) THEN !Name points to a walkin
NumWalkInsMT = 1
TransSystem(TransRefrigSysNum)%NumWalkInsMT = 1
IF(.NOT. ALLOCATED(TransSystem(TransRefrigSysNum)%WalkInNumMT)) &
ALLOCATE(TransSystem(TransRefrigSysNum)%WalkInNumMT(NumWalkInsMT))
TransSystem(TransRefrigSysNum)%WalkInNumMT(NumWalkIns)=WalkInNum
END IF !NumNameMatches /= 1
END IF !blank input for cases, walkins, or caseandwalkinlist
IF(NumCasesMT > 0) THEN
! Find lowest design evap T
! Sum rated capacity of all MT cases on system
DO CaseIndex = 1, NumCasesMT
!mark all cases on system as used by this system - checking for unused or non-unique cases
CaseNum=TransSystem(TransRefrigSysNum)%CaseNumMT(CaseIndex)
RefrigCase(CaseNum)%NumSysAttach = RefrigCase(CaseNum)%NumSysAttach + 1
NominalTotalCaseCapMT = NominalTotalCaseCapMT + RefrigCase(CaseNum)%DesignRatedCap
TransSystem(TransRefrigSysNum)%RefInventory=TransSystem(TransRefrigSysNum)%RefInventory + &
RefrigCase(Casenum)%DesignRefrigInventory
IF(CaseIndex == 1) THEN !look for lowest case design evap T for system
TransSystem(TransRefrigSysNum)%TEvapDesignMT=RefrigCase(CaseNum)%EvapTempDesign
ELSE
TransSystem(TransRefrigSysNum)%TEvapDesignMT = &
MIN(RefrigCase(CaseNum)%EvapTempDesign,TransSystem(TransRefrigSysNum)%TEvapDesignMT)
END IF
END DO !CaseIndex=1,NumCases
END IF !NumcasesMT > 0
IF (NumWalkInsMT > 0) THEN
DO WalkInIndex = 1, NumWalkInsMT
WalkInID=TransSystem(TransRefrigSysNum)%WalkInNumMT(WalkInIndex)
!mark all WalkIns on rack as used by this system (checking for unused or non-unique WalkIns)
WalkIn(WalkInID)%NumSysAttach = WalkIn(WalkInID)%NumSysAttach + 1
NominalTotalWalkInCapMT = NominalTotalWalkInCapMT + WalkIn(WalkInID)%DesignRatedCap
TransSystem(TransRefrigSysNum)%RefInventory=TransSystem(TransRefrigSysNum)%RefInventory + &
WalkIn(WalkInID)%DesignRefrigInventory
!Defrost capacity is treated differently by compressor racks and detailed systems,
! so this value may be adjusted (or warnings issued) after the walkin is assigned
! to either the rack or system.
!for walkins served by detailed system, need capacity for both fluid and electric types.
IF (WalkIn(WalkInID)%DefrostCapacity <= -98.d0) THEN
! - 99 used as a flag for blank input error message for detailed systems
CALL ShowSevereError(RoutineName//'Refrigeration:WalkIn="'//TRIM(WalkIn(WalkInID)%Name)//&
'", Defrost capacity must be greater than or equal to 0 W' //&
' for electric and hotfluid defrost types')
ErrorsFound = .TRUE.
END IF
! Find design evaporating temperature for system by getting min design evap for ALL loads
IF ((WalkInIndex == 1) .AND. (TransSystem(TransRefrigSysNum)%NumCasesMT ==0)) THEN
!note use walk in index, not walkinid here to get
!first walkin on this suction group/system
TransSystem(TransRefrigSysNum)%TEvapDesignMT=WalkIn(WalkInID)%TEvapDesign
ELSE
TransSystem(TransRefrigSysNum)%TEvapDesignMT= &
MIN(WalkIn(WalkInID)%TEvapDesign,TransSystem(TransRefrigSysNum)%TEvapDesignMT)
END IF
END DO !WalkInIndex=1,NumWalkIns
END IF !NumWalkInsMT > 0
! Check for Low Temperature Case or Walk-In or CaseAndWalkInList names
AlphaNum = 4
IF (.NOT. lAlphaBlanks(AlphaNum)) THEN
! Entry for Alphas(AlphaNum) can be either a Case, WalkIn or CaseAndWalkInList name
CaseAndWalkInListNum=0
CaseNum=0
WalkInNum=0
IF(NumSimulationCaseAndWalkInLists > 0) &
CaseAndWalkInListNum=FindItemInList(Alphas(AlphaNum),CaseAndWalkInList%Name,NumSimulationCaseAndWalkInLists)
IF(NumSimulationCases > 0) CaseNum= FindItemInList(Alphas(AlphaNum),RefrigCase%Name,NumSimulationCases)
IF(NumSimulationWalkIns > 0)WalkInNum=FindItemInList(Alphas(AlphaNum),WalkIn%Name,NumSimulationWalkIns)
NumNameMatches = 0
IF(CaseAndWalkInListNum /= 0)NumNameMatches = NumNameMatches +1
IF(CaseNum /= 0) NumNameMatches = NumNameMatches +1
IF(WalkInNum /= 0) NumNameMatches = NumNameMatches +1
IF (NumNameMatches /= 1) THEN !name must uniquely point to a list or a single case or walkin or coil
ErrorsFound = .TRUE.
IF(NumNameMatches == 0) THEN
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(TransSystem(TransRefrigSysNum)%Name)//&
'", has an invalid '//TRIM(cAlphaFieldNames(AlphaNum))//': '//TRIM(Alphas(AlphaNum)))
ELSEIF(NumNameMatches > 1) THEN
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//&
TRIM(TransSystem(TransRefrigSysNum)%Name)//'", has a non-unique name '//&
'that could be either a '//TRIM(cAlphaFieldNames(AlphaNum))//': '//TRIM(Alphas(AlphaNum)))
END IF !num matches = 0 or > 1
ELSEIF(CaseAndWalkInListNum /= 0) THEN !Name points to a CaseAndWalkInList
NumCasesLT = CaseAndWalkInList(CaseAndWalkInListNum)%NumCases
NumWalkInsLT = CaseAndWalkInList(CaseAndWalkInListNum)%NumWalkIns
TransSystem(TransRefrigSysNum)%NumCasesLT = NumCasesLT
TransSystem(TransRefrigSysNum)%NumWalkInsLT = NumWalkInsLT
IF(NumCasesLT > 0) THEN
IF(.NOT. ALLOCATED(TransSystem(TransRefrigSysNum)%CaseNumLT)) &
ALLOCATE(TransSystem(TransRefrigSysNum)%CaseNumLT(NumCasesLT))
TransSystem(TransRefrigSysNum)%CaseNumLT(1:NumCasesLT) = &
CaseAndWalkInList(CaseAndWalkInListNum)%CaseItemNum(1:NumCasesLT)
END IF
IF(NumWalkInsLT > 0) THEN
IF(.NOT. ALLOCATED(TransSystem(TransRefrigSysNum)%WalkInNumLT)) &
ALLOCATE(TransSystem(TransRefrigSysNum)%WalkInNumLT(NumWalkInsLT))
TransSystem(TransRefrigSysNum)%WalkInNumLT(1:NumWalkInsLT) = &
CaseAndWalkInList(CaseAndWalkInListNum)%WalkInItemNum(1:NumWalkInsLT)
END IF
ELSEIF (CaseNum /= 0) THEN !Name points to a case
NumCasesLT = 1
TransSystem(TransRefrigSysNum)%NumCasesLT = 1
IF(.NOT. ALLOCATED(TransSystem(TransRefrigSysNum)%CaseNumLT)) &
ALLOCATE(TransSystem(TransRefrigSysNum)%CaseNumLT(NumCasesLT))
TransSystem(TransRefrigSysNum)%CaseNumLT(NumCases)=CaseNum
ELSEIF (WalkInNum /= 0) THEN !Name points to a walkin
NumWalkInsLT = 1
TransSystem(TransRefrigSysNum)%NumWalkInsLT = 1
IF(.NOT. ALLOCATED(TransSystem(TransRefrigSysNum)%WalkInNumLT)) &
ALLOCATE(TransSystem(TransRefrigSysNum)%WalkInNumLT(NumWalkInsLT))
TransSystem(TransRefrigSysNum)%WalkInNumLT(NumWalkIns)=WalkInNum
END IF !NumNameMatches /= 1
END IF !blank input for cases, walkins, or caseandwalkinlist
IF(NumCasesLT > 0) THEN
! Find lowest design evap T
! Sum rated capacity of all LT cases on system
DO CaseIndex = 1, NumCasesLT
!mark all cases on system as used by this system - checking for unused or non-unique cases
CaseNum=TransSystem(TransRefrigSysNum)%CaseNumLT(CaseIndex)
RefrigCase(CaseNum)%NumSysAttach = RefrigCase(CaseNum)%NumSysAttach + 1
NominalTotalCaseCapLT = NominalTotalCaseCapLT + RefrigCase(CaseNum)%DesignRatedCap
TransSystem(TransRefrigSysNum)%RefInventory=TransSystem(TransRefrigSysNum)%RefInventory + &
RefrigCase(Casenum)%DesignRefrigInventory
IF(CaseIndex == 1) THEN !look for lowest case design evap T for system
TransSystem(TransRefrigSysNum)%TEvapDesignLT=RefrigCase(CaseNum)%EvapTempDesign
ELSE
TransSystem(TransRefrigSysNum)%TEvapDesignLT = &
MIN(RefrigCase(CaseNum)%EvapTempDesign,TransSystem(TransRefrigSysNum)%TEvapDesignLT)
END IF
END DO !CaseIndex=1,NumCases
END IF !NumcasesLT > 0
IF (NumWalkInsLT > 0) THEN
DO WalkInIndex = 1, NumWalkInsLT
WalkInID=TransSystem(TransRefrigSysNum)%WalkInNumLT(WalkInIndex)
!mark all WalkIns on rack as used by this system (checking for unused or non-unique WalkIns)
WalkIn(WalkInID)%NumSysAttach = WalkIn(WalkInID)%NumSysAttach + 1
NominalTotalWalkInCapLT = NominalTotalWalkInCapLT + WalkIn(WalkInID)%DesignRatedCap
TransSystem(TransRefrigSysNum)%RefInventory=TransSystem(TransRefrigSysNum)%RefInventory + &
WalkIn(WalkInID)%DesignRefrigInventory
!Defrost capacity is treated differently by compressor racks and detailed systems,
! so this value may be adjusted (or warnings issued) after the walkin is assigned
! to either the rack or system.
!for walkins served by detailed system, need capacity for both fluid and electric types.
IF (WalkIn(WalkInID)%DefrostCapacity <= -98.d0) THEN
! - 99 used as a flag for blank input error message for detailed systems
CALL ShowSevereError(RoutineName//'Refrigeration:WalkIn="'//TRIM(WalkIn(WalkInID)%Name)//&
'", Defrost capacity must be greater than or equal to 0 W' //&
' for electric and hotfluid defrost types')
ErrorsFound = .TRUE.
END IF
! Find design evaporating temperature for system by getting min design evap for ALL loads
IF ((WalkInIndex == 1) .AND. (TransSystem(TransRefrigSysNum)%NumCasesLT ==0)) THEN
!note use walk in index, not walkinid here to get
!first walkin on this suction group/system
TransSystem(TransRefrigSysNum)%TEvapDesignLT=WalkIn(WalkInID)%TEvapDesign
ELSE
TransSystem(TransRefrigSysNum)%TEvapDesignLT= &
MIN(WalkIn(WalkInID)%TEvapDesign,TransSystem(TransRefrigSysNum)%TEvapDesignLT)
END IF
END DO !WalkInIndex=1,NumWalkIns
END IF !NumWalkInsMT > 0
NominalTotalCoolingCap = NominalTotalCaseCapMT + NominalTotalCaseCapLT + NominalTotalWalkInCapMT + &
NominalTotalWalkInCapLT
! Read Gas Cooler
! currently assumes one gas cooler per refrigeration system and but multiple systems allowed per gas cooler
AlphaNum = 5
NumGasCoolers = 1
IF(.NOT. ALLOCATED(TransSystem(TransRefrigSysNum)%GasCoolerNum)) &
ALLOCATE(TransSystem(TransRefrigSysNum)%GasCoolerNum(NumGasCoolers))
TransSystem(TransRefrigSysNum)%NumGasCoolers = 1
!Find gascooler number
GCNum = FindItemInList(Alphas(AlphaNum),GasCooler%Name,NumSimulationGasCooler)
IF(GCNum == 0) THEN ! Invalid Gas Cooler attached to Transcritical Refrigeration System
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(TransSystem(TransRefrigSysNum)%Name)//&
'", has an invalid '// &
TRIM(cAlphaFieldNames(AlphaNum))//' defined as "'//TRIM(Alphas(AlphaNum))//'".')
ErrorsFound = .TRUE.
ELSE IF (GCNum /= 0) THEN ! Gas Cooler attached to Transcritical Refrigeration System
TransSystem(TransRefrigSysNum)%GasCoolerNum(NumGasCoolers) = GCNum
TransSystem(TransRefrigSysNum)%NumGasCoolers = 1
!Now take care of case where multiple systems share a gas cooler
GasCooler(GCNum)%NumSysAttach = GasCooler(GCNum)%NumSysAttach + 1
GasCooler(GCNum)%SysNum(GasCooler(GCNum)%NumSysAttach) = TransRefrigSysNum
TransSystem(TransRefrigSysNum)%RefInventory=TransSystem(TransRefrigSysNum)%RefInventory + &
GasCooler(GCNum)%RefReceiverInventory + &
GasCooler(GCNum)%RefPipingInventory + GasCooler(GCNum)%RefOpCharge
IF(GasCooler(GCNum)%GasCoolerRejectHeatToZone)TransSystem(TransRefrigSysNum)%SystemRejectHeatToZone = .TRUE.
END IF
! Read High Pressure Compressor
AlphaNum=6
NumCompressorsSys = 0
IF(lAlphaBlanks(AlphaNum)) THEN
!blank input where must have compressor or compressor list input.
CALL ShowSevereError(Trim(RoutineName)//TRIM(CurrentModuleObject)//' '//TRIM(cAlphaFieldNames(AlphaNum))//'" : '//&
'must be input.')
ErrorsFound = .TRUE.
ELSE ! Entry for Alphas(AlphaNum) can be either a compressor name or a compressorlist name
ListNum=FindItemInList(Alphas(AlphaNum),CompressorLists%Name,NumCompressorLists)
CompNum=FindItemInList(Alphas(AlphaNum),Compressor%Name,NumSimulationCompressors)
IF((ListNum == 0) .AND. (CompNum == 0)) THEN ! name doesn't match either a compressor or a compressor list
CALL ShowSevereError(Trim(RoutineName)//TRIM(CurrentModuleObject)//', "'//&
TRIM(cAlphaFieldNames(AlphaNum))//'", has an invalid '//&
'or undefined value="'//TRIM(Alphas(AlphaNum))//'".')
ErrorsFound = .TRUE.
ELSEIF((ListNum /= 0) .AND. (CompNum /= 0)) THEN !have compressor list and compressor with same name
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//' '//&
TRIM(cAlphaFieldNames(AlphaNum))//', has a non-unique name '//&
' used for both Compressor and CompressorList name: "'//TRIM(Alphas(AlphaNum))//'".')
ErrorsFound = .TRUE.
ELSE IF(ListNum /= 0) THEN
NumCompressorsSys = CompressorLists(ListNum)%NumCompressors
TransSystem(TransRefrigSysNum)%NumCompressorsHP = NumCompressorsSys
IF(.NOT. ALLOCATED(TransSystem(TransRefrigSysNum)%CompressorNumHP))&
ALLOCATE(TransSystem(TransRefrigSysNum)%CompressorNumHP(NumCompressorsSys))
TransSystem(TransRefrigSysNum)%CompressorNumHP(1:NumCompressorsSys) = &
CompressorLists(ListNum)%CompItemNum(1:NumCompressorsSys)
ELSEIF (CompNum /= 0) THEN
NumCompressorsSys = 1
TransSystem(TransRefrigSysNum)%NumCompressorsHP = 1
IF(.NOT. ALLOCATED(TransSystem(TransRefrigSysNum)%CompressorNumHP))&
ALLOCATE(TransSystem(TransRefrigSysNum)%CompressorNumHP(NumCompressorsSys))
TransSystem(TransRefrigSysNum)%CompressorNumHP(NumCompressorsSys)=CompNum
END IF
! Sum rated capacity of all HP compressors on system
NominalTotalCompCapHP = 0.0d0
DO CompIndex=1,NumCompressorsSys
CompNum = TransSystem(TransRefrigSysNum)%CompressorNumHP(CompIndex)
IF (Compressor(CompNum)%TransFlag) THEN ! Calculate nominal capacity of transcritical Compressor
GCOutletH = GetSupHeatEnthalpyRefrig(TransSystem(TransRefrigSysNum)%RefrigerantName, &
GasCooler(TransSystem(TransRefrigSysNum)%GasCoolerNum(1))%RatedOutletT, &
GasCooler(TransSystem(TransRefrigSysNum)%GasCoolerNum(1))%RatedOutletP, &
RefrigIndex,'GetRefrigerationInput')
Compressor(CompNum)%NomCap = CurveValue(Compressor(CompNum)%TransCapacityCurvePtr,&
TransSystem(TransRefrigSysNum)%TEvapDesignMT,GCOutletH)
NominalTotalCompCapHP = NominalTotalCompCapHP + Compressor(CompNum)%NomCap
Compressor(CompNum)%NumSysAttach = Compressor(CompNum)%NumSysAttach + 1
ELSE ! Subcritical compressor attached to transcritical system - show error
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//', '// &
'No transcritical CO2 compressors are attached to the transcritical refrigeration system, "'// &
TRIM(TransSystem(TransRefrigSysNum)%Name)//'".')
ErrorsFound = .TRUE.
END IF
END DO
ENDIF
! Read Low Pressure Compressor
AlphaNum=7
NumCompressorsSys = 0
IF((lAlphaBlanks(AlphaNum)) .AND. (TransSystem(TransRefrigSysNum)%TransSysType == 2)) THEN
! TwoStage system type is specified but low pressure compressor input is blank
CALL ShowSevereError(Trim(RoutineName)//TRIM(CurrentModuleObject)//', '// &
'The transcritical refrigeration system, "'//TRIM(TransSystem(TransRefrigSysNum)%Name)//'", is specified to be '// &
'"TwoStage", however, the "'//TRIM(cAlphaFieldNames(AlphaNum))//'" '//'is not given.')
ErrorsFound = .TRUE.
ELSE IF((.NOT.(lAlphaBlanks(AlphaNum))) .AND. (TransSystem(TransRefrigSysNum)%TransSysType == 1)) THEN
! SingleStage system type with low pressure compressors specified. Ignore low pressure compressors
CALL ShowWarningError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//', '// &
'The transcritical refrigeration system, "'//TRIM(TransSystem(TransRefrigSysNum)%Name)//'", is specified to be '// &
'"SingleStage", however, a"'//TRIM(cAlphaFieldNames(AlphaNum))//'" '// &
'was found. The low pressure compressors will be '// &
'ignored and will not simulated.')
ELSE IF((.NOT.(lAlphaBlanks(AlphaNum))) .AND. (TransSystem(TransRefrigSysNum)%TransSysType == 2)) THEN
! TwoStage system with low pressure compressors specified
ListNum=FindItemInList(Alphas(AlphaNum),CompressorLists%Name,NumCompressorLists)
CompNum=FindItemInList(Alphas(AlphaNum),Compressor%Name,NumSimulationCompressors)
IF((ListNum == 0) .AND. (CompNum == 0)) THEN ! name doesn't match either a compressor or a compressor list
CALL ShowSevereError(Trim(RoutineName)//TRIM(CurrentModuleObject)//', "'//&
TRIM(cAlphaFieldNames(AlphaNum))//'", has an invalid '//&
'or undefined value="'//TRIM(Alphas(AlphaNum))//'".')
ErrorsFound = .TRUE.
ELSEIF((ListNum /= 0) .AND. (CompNum /= 0)) THEN !have compressor list and compressor with same name
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//' '//&
TRIM(cAlphaFieldNames(AlphaNum))//', has a non-unique name '//&
' used for both Compressor and CompressorList name: "'//TRIM(Alphas(AlphaNum))//'".')
ErrorsFound = .TRUE.
ELSE IF(ListNum /= 0) THEN
NumCompressorsSys = CompressorLists(ListNum)%NumCompressors
TransSystem(TransRefrigSysNum)%NumCompressorsLP = NumCompressorsSys
IF(.NOT. ALLOCATED(TransSystem(TransRefrigSysNum)%CompressorNumLP))&
ALLOCATE(TransSystem(TransRefrigSysNum)%CompressorNumLP(NumCompressorsSys))
TransSystem(TransRefrigSysNum)%CompressorNumLP(1:NumCompressorsSys) = &
CompressorLists(ListNum)%CompItemNum(1:NumCompressorsSys)
ELSEIF (CompNum /= 0) THEN
NumCompressorsSys = 1
TransSystem(TransRefrigSysNum)%NumCompressorsLP = 1
IF(.NOT. ALLOCATED(TransSystem(TransRefrigSysNum)%CompressorNumLP))&
ALLOCATE(TransSystem(TransRefrigSysNum)%CompressorNumLP(NumCompressorsSys))
TransSystem(TransRefrigSysNum)%CompressorNumLP(NumCompressorsSys)=CompNum
END IF
! Sum rated capacity of all LP compressors on system
NominalTotalCompCapLP = 0.0d0
DO CompIndex=1,NumCompressorsSys
CompNum = TransSystem(TransRefrigSysNum)%CompressorNumLP(CompIndex)
IF (TransSystem(TransRefrigSysNum)%TransSysType == 2) THEN ! Calculate capacity of LP compressors
Compressor(CompNum)%NomCap = CurveValue(Compressor(CompNum)%CapacityCurvePtr,&
TransSystem(TransRefrigSysNum)%TEvapDesignLT,TransSystem(TransRefrigSysNum)%TEvapDesignMT)
NominalTotalCompCapLP = NominalTotalCompCapLP + Compressor(CompNum)%NomCap
Compressor(CompNum)%NumSysAttach = Compressor(CompNum)%NumSysAttach + 1
END IF
END DO
ENDIF
! Read Receiver Pressure
IF (.NOT. lNumericBlanks(1)) THEN
TransSystem(TransRefrigSysNum)%PReceiver = Numbers(1)
ELSE ! Default value receiver pressure = 4000000 Pa
TransSystem(TransRefrigSysNum)%PReceiver = 4.0d6
END IF
! Check receiver temperature against minimum condensing temperature (from gas cooler input) and design evaporator temperatures
TransSystem(TransRefrigSysNum)%TReceiver = GetSatTemperatureRefrig(TransSystem(TransRefrigSysNum)%RefrigerantName, &
TransSystem(TransRefrigSysNum)%PReceiver,RefrigIndex,'GetRefrigerationInput')
IF (TransSystem(TransRefrigSysNum)%TReceiver > &
GasCooler(TransSystem(TransRefrigSysNum)%GasCoolerNum(NumGasCoolers))%MinCondTemp) THEN
CALL ShowWarningError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(TransSystem(TransRefrigSysNum)%Name)//&
': The receiver temperature ('//TRIM(RoundSigDigits(TransSystem(TransRefrigSysNum)%TReceiver,2))//&
'C) is greater than the minimum condensing temperature specified for subcritical operation ('//&
TRIM(RoundSigDigits(GasCooler(TransSystem(TransRefrigSysNum)%GasCoolerNum(NumGasCoolers))%MinCondTemp,2))//'C).')
CALL ShowContinueError(' The minimum condensing temperature will be set at 5C greater than the receiver temperature.')
GasCooler(TransSystem(TransRefrigSysNum)%GasCoolerNum(NumGasCoolers))%MinCondTemp = &
TransSystem(TransRefrigSysNum)%TReceiver + 5.0d0
END IF
IF (NominalTotalCompCapLP > 0.0d0) THEN
IF (TransSystem(TransRefrigSysNum)%TReceiver <= TransSystem(TransRefrigSysNum)%TEvapDesignLT) THEN
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(TransSystem(TransRefrigSysNum)%Name)//&
': The receiver temperature ('//TRIM(RoundSigDigits(TransSystem(TransRefrigSysNum)%TReceiver,2))//&
'C) is less than the design evaporator temperature for the low temperature loads ('//&
TRIM(RoundSigDigits(TransSystem(TransRefrigSysNum)%TEvapDesignLT,2))//'C).')
CALL ShowContinueError(' Ensure that the receiver temperature is sufficiently greater than the design evaporator '//&
'temperature for the low temperature loads.')
CALL ShowContinueError(' A receiver pressure between 3.0 MPa to 4.0 MPa will '// &
'typically result in an adequate receiver temperature.')
ErrorsFound=.TRUE.
END IF
END IF
IF (NominalTotalCompCapHP > 0.0d0) THEN
IF (TransSystem(TransRefrigSysNum)%TReceiver <= TransSystem(TransRefrigSysNum)%TEvapDesignMT) THEN
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(TransSystem(TransRefrigSysNum)%Name)//&
': The receiver temperature ('//TRIM(RoundSigDigits(TransSystem(TransRefrigSysNum)%TReceiver,2))//&
'C) is less than the design evaporator temperature for the medium temperature loads ('//&
TRIM(RoundSigDigits(TransSystem(TransRefrigSysNum)%TEvapDesignMT,2))//'C).')
CALL ShowContinueError(' Ensure that the receiver temperature is sufficiently greater than the design evaporator '//&
'temperature for the medium temperature loads.')
CALL ShowContinueError(' A receiver pressure between 3.0 MPa to 4.0 MPa will '// &
'typically result in an adequate receiver temperature.')
ErrorsFound=.TRUE.
END IF
END IF
! Read subcooler effectiveness
IF (.NOT. lNumericBlanks(2)) THEN
TransSystem(TransRefrigSysNum)%SCEffectiveness = Numbers(2)
ELSE ! Default value effectiveness = 0.4
TransSystem(TransRefrigSysNum)%PReceiver = 0.4d0
END IF
! Check subcooler effectiveness value, must be value between 0 and 1
IF ((TransSystem(TransRefrigSysNum)%SCEffectiveness < 0).OR. &
(TransSystem(TransRefrigSysNum)%SCEffectiveness > 1)) THEN
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(TransSystem(TransRefrigSysNum)%Name)//&
': The value for subcooler effectivness is invalid. The subcooler effectivenss must be a value'//&
' greater than or equal to zero and less than or equal to one.')
ErrorsFound=.TRUE.
END IF
!Suction piping heat gain - optional
! Input UA and identify the Zone containing the bulk of the suction piping
! This Zone ID will be used to determine the temperature used for suction piping heat gain.
! The pipe heat gains are also counted as cooling credit for the zone.
! Zone Id is only required if Sum UA Suction Piping >0.0
! Get the Zone and zone node numbers from the zone name entered by the user
AlphaNum=9 ! Medium temperature suction piping
TransSystem(TransRefrigSysNum)%SumUASuctionPipingMT=0.d0
IF(.NOT. lNumericBlanks(3) .AND. .NOT. lAlphaBlanks(AlphaNum)) THEN
TransSystem(TransRefrigSysNum)%SumUASuctionPipingMT= Numbers(3)
TransSystem(TransRefrigSysNum)%SuctionPipeActualZoneNumMT = FindItemInList(Alphas(AlphaNum),Zone%Name,NumOfZones)
TransSystem(TransRefrigSysNum)%SuctionPipeZoneNodeNumMT = GetSystemNodeNumberForZone(Alphas(AlphaNum))
IF (TransSystem(TransRefrigSysNum)%SuctionPipeZoneNodeNumMT == 0) THEN
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(TransSystem(TransRefrigSysNum)%Name)//&
'", System Node Number not found for '//TRIM(cAlphaFieldNames(AlphaNum))// &
' = "'//TRIM(Alphas(AlphaNum))//'" even though '//TRIM(cNumericFieldNames(3))//&
' is greater than zero.')
CALL ShowContinueError(' The medium temperature suction piping heat gain cannot be calculated unless a Zone is defined '//&
'to deterimine the environmental temperature surrounding the piping.')
ErrorsFound=.TRUE.
ELSE
RefrigPresentInZone(TransSystem(TransRefrigSysNum)%SuctionPipeActualZoneNumMT) = .TRUE.
ENDIF
ELSEIF(.NOT. lNumericBlanks(3) .AND. lAlphaBlanks(AlphaNum)) THEN
CALL ShowWarningError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(TransSystem(TransRefrigSysNum)%Name)//&
'" '//TRIM(cAlphaFieldNames(AlphaNum))//' not found even though '//TRIM(cNumericFieldNames(3))//&
' is greater than zero.')
CALL ShowContinueError(' The medium temperature suction piping heat gain will not be calculated unless a Zone is defined '//&
'to determine the environmental temperature surrounding the piping.')
ELSEIF(lNumericBlanks(3) .AND. .NOT. lAlphaBlanks(AlphaNum)) THEN
CALL ShowWarningError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(TransSystem(TransRefrigSysNum)%Name)//&
'" '//TRIM(cAlphaFieldNames(AlphaNum))//' will not be used and suction piping heat gain will'//&
' not be calculated because '//TRIM(cNumericFieldNames(3))//&
' was blank.')
END IF ! Medium temperature suction piping heat gains
AlphaNum=10 ! Low temperature suction piping
TransSystem(TransRefrigSysNum)%SumUASuctionPipingLT=0.d0
IF(.NOT. lNumericBlanks(4) .AND. .NOT. lAlphaBlanks(AlphaNum)) THEN
TransSystem(TransRefrigSysNum)%SumUASuctionPipingLT= Numbers(4)
TransSystem(TransRefrigSysNum)%SuctionPipeActualZoneNumLT = FindItemInList(Alphas(AlphaNum),Zone%Name,NumOfZones)
TransSystem(TransRefrigSysNum)%SuctionPipeZoneNodeNumLT = GetSystemNodeNumberForZone(Alphas(AlphaNum))
IF (TransSystem(TransRefrigSysNum)%SuctionPipeZoneNodeNumLT == 0) THEN
CALL ShowSevereError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(TransSystem(TransRefrigSysNum)%Name)//&
'", System Node Number not found for '//TRIM(cAlphaFieldNames(AlphaNum))// &
' = "'//TRIM(Alphas(AlphaNum))//'" even though '//TRIM(cNumericFieldNames(4))//&
' is greater than zero.')
CALL ShowContinueError(' The low temperature suction piping heat gain cannot be calculated unless a Zone is defined '//&
'to deterimine the environmental temperature surrounding the piping.')
ErrorsFound=.TRUE.
ELSE
RefrigPresentInZone(TransSystem(TransRefrigSysNum)%SuctionPipeActualZoneNumLT) = .TRUE.
ENDIF
ELSEIF(.NOT. lNumericBlanks(4) .AND. lAlphaBlanks(AlphaNum)) THEN
CALL ShowWarningError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(TransSystem(TransRefrigSysNum)%Name)//&
'" '//TRIM(cAlphaFieldNames(AlphaNum))//' not found even though '//TRIM(cNumericFieldNames(4))//&
' is greater than zero.')
CALL ShowContinueError(' The low temperature suction piping heat gain will not be calculated unless a Zone is defined '//&
'to determine the environmental temperature surrounding the piping.')
ELSEIF(lNumericBlanks(4) .AND. .NOT. lAlphaBlanks(AlphaNum)) THEN
CALL ShowWarningError(TRIM(RoutineName)//TRIM(CurrentModuleObject)//'="'//TRIM(TransSystem(TransRefrigSysNum)%Name)//&
'" '//TRIM(cAlphaFieldNames(AlphaNum))//' will not be used and suction piping heat gain will'//&
' not be calculated because '//TRIM(cNumericFieldNames(4))//&
' was blank.')
END IF ! Low temperature suction piping heat gains
AlphaNum=11
IF (.NOT. lAlphaBlanks(AlphaNum)) TransSystem(TransRefrigSysNum)%EndUseSubcategory = Alphas(AlphaNum)
!Compare the rated capacity of compressor, condenser, and cases.
! Note, rated capacities can be far off from operating capacities, but rough check.
NominalCondCap=GasCooler(TransSystem(TransRefrigSysNum)%GasCoolerNum(1))%RatedCapacity
NominalTotalCompCap=NominalTotalCompCapHP + NominalTotalCompCapLP
IF((NominalTotalCompCap < (0.7d0*NominalTotalCoolingCap)) .OR. &
(NominalCondCap < (1.3d0*NominalTotalCoolingCap))) THEN
CALL ShowWarningError(TRIM(CurrentModuleObject)//'="'//TRIM(TransSystem(TransRefrigSysNum)%Name)//&
'", You may wish to check the system sizing.')
CALL ShowContinueError('Total nominal cooling capacity is '//&
TRIM(RoundSigDigits(NominalTotalCoolingCap,0))//'W. Condenser capacity is '//&
TRIM(RoundSigDigits(NominalCondCap,0))//'W. Nominal compressor capacity is '//&
TRIM(RoundSigDigits(NominalTotalCompCap,0))//'W.')
END IF
END DO ! Transcritical refrigeration systems
END IF !(NumTransRefrigSystems > 0)
DEALLOCATE(DayValues)
DEALLOCATE(Alphas)
DEALLOCATE(Numbers)
DEALLOCATE(cAlphaFieldNames)
DEALLOCATE(cNumericFieldNames)
DEALLOCATE(lAlphaBlanks)
DEALLOCATE(lNumericBlanks)
IF(NumSimulationCases > 0) THEN
! Find unused and non-unique display case objects to report in eio and err file and sum
! all HVAC RA fractions and write error message if greater than 1 for any zone
DO ZoneIndex = 1,NumOfZones !numofzones from dataglobals
TempRAFraction = CaseRAFraction(ZoneIndex)%TotalCaseRAFraction
DO CaseNum = 1,NumSimulationCases
! TempRaFraction already includes contributions from ALL cases in zone
! Want to delete portion from unused cases (numsysattach = 0)that will never be simulated
IF(RefrigCase(CaseNum)%ActualZoneNum /= ZoneIndex .OR. &
RefrigCase(CaseNum)%NumSysAttach > 0) CYCLE
TempRAFraction = TempRAFraction - RefrigCase(CaseNum)%RAFrac
END DO !NumSimulationCases
IF (TempRAFraction > 1.0d0) THEN
CALL ShowSevereError(TRIM(RoutineName)//': Refrigeration:Case'// &
', Refrigerated case return air fraction for all cases in zone="' &
//TRIM(CaseRAFraction(ZoneIndex)%ZoneName)//'" is greater than 1.0.')
!check in comment, can't use "currentModuleObject" because not in get input subroutine where that is known
ErrorsFound = .TRUE.
END IF
END DO !ZoneIndex=1,NumofZones
DEALLOCATE(CaseRAFraction) !only used for input check just completed
!check for cases not connected to systems and cases connected
!more than once (twice in a system or to more than one system)
NumunusedRefrigCases = 0
DO CaseNum = 1,NumSimulationCases
IF(RefrigCase(CaseNum)%NumSysAttach == 1) CYCLE
IF(RefrigCase(CaseNum)%NumSysAttach < 1) THEN
NumunusedRefrigCases = NumunusedRefrigCases + 1
IF (DisplayExtraWarnings) THEN
! individual case names listed if DisplayExtraWarnings option selected
CALL ShowWarningError(TRIM(RoutineName)//': Refrigeration:Case="'// &
TRIM(RefrigCase(CaseNum)%Name)//'" unused. ')
END IF !display extra warnings - give a list of unused cases
END IF !unused case
IF(RefrigCase(CaseNum)%NumSysAttach > 1)THEN
ErrorsFound = .TRUE.
CALL ShowSevereError(TRIM(RoutineName)//': Refrigeration:Case="'//&
TRIM(RefrigCase(CaseNum)%Name)//'", Same refrigerated case name referenced ')
CALL ShowContinueError(' by more than one refrigeration system and/or compressor rack.')
END IF ! if looking for same case attached to multiple systems/racks
END DO !NumSimulationCases
IF((NumunusedRefrigCases > 0) .AND. (.NOT. DisplayExtraWarnings)) THEN
! write to error file,
! summary number of unused cases given if DisplayExtraWarnings option not selected
CALL ShowWarningError('Refrigeration:Case -> '//TRIM(RoundSigDigits(NumunusedRefrigCases))//&
' unused refrigerated case(s) found during input processing.')
CALL ShowContinueError(' These refrigerated cases are in the input file but are not connected to a ')
CALL ShowContinueError(' Refrigeration:CompressorRack, Refrigeration:System, or Refrigeration:SecondarySystem object.')
CALL ShowContinueError(' These unused refrigeration cases will not be simulated.')
CALL ShowContinueError(' Use Output:Diagnostics,DisplayUnusedObjects; to see them. ')
END IF !NumunusedRefrigCases
END IF !numsimulation cases > 0
IF(NumSimulationCompressors > 0) THEN
!check for compressors not connected to systems and compressors connected more than once
! (twice in a system or to more than one system)
NumunusedCompressors = 0
DO CompNum=1,NumSimulationCompressors
IF(Compressor(CompNum)%NumSysAttach == 1) CYCLE
IF(Compressor(CompNum)%NumSysAttach < 1)THEN
NumunusedCompressors = NumunusedCompressors + 1
IF (DisplayExtraWarnings) THEN
! individual compressor names listed if DisplayExtraWarnings option selected
CALL ShowWarningError(TRIM(RoutineName)//': Refrigeration:Compressor="'// &
TRIM(Compressor(CompNum)%Name)//'" unused. ')
END IF !display extra warnings - give a list of unused compressors
END IF !unused compressor
IF(Compressor(CompNum)%NumSysAttach > 1)THEN
ErrorsFound = .TRUE.
CALL ShowSevereError(TRIM(RoutineName)//': Refrigeration:Compressor="'// &
TRIM(Compressor(CompNum)%Name)//'", Same refrigeration compressor name referenced')
CALL ShowContinueError(' by more than one refrigeration system.')
END IF ! looking for same compressor attached to multiple systems/racks
END DO !NumSimulationCompressors
IF((NumunusedCompressors > 0) .AND. (.NOT. DisplayExtraWarnings)) THEN
! write to error file,
! summary number of unused compressors given if DisplayExtraWarnings option not selected
CALL ShowWarningError('Refrigeration:Compressor -> '//TRIM(RoundSigDigits(NumunusedCompressors))//&
' unused refrigeration compressor(s) found during input processing.')
CALL ShowContinueError(' Those refrigeration compressors are in the input file but are not connected to a '// &
'Refrigeration:System object.')
CALL ShowContinueError(' These unused refrigeration compressors will not be simulated.')
CALL ShowContinueError(' Use Output:Diagnostics,DisplayUnusedObjects; to see them. ')
END IF !NumunusedCompressors
END IF !NumSimulationCompressors > 0
IF(NumSimulationWalkIns > 0) THEN
!check for refrigeration WalkIns not connected to any systems and
! refrigeration WalkIns connected more than once
NumunusedWalkIns = 0
DO WalkInNum=1,NumSimulationWalkIns
IF(WalkIn(WalkInNum)%NumSysAttach == 1) CYCLE
IF(WalkIn(WalkInNum)%NumSysAttach < 1)THEN
NumunusedWalkIns = NumunusedWalkIns + 1
IF (DisplayExtraWarnings) THEN
! individual walkin names listed if DisplayExtraWarnings option selected
CALL ShowWarningError(TRIM(RoutineName)//': Refrigeration:WalkIn="'// &
TRIM(WalkIn(WalkInNum)%Name)//'" unused. ')
END IF !display extra warnings - give a list of unused WalkIns
END IF !unused walkin
IF(WalkIn(WalkInNum)%NumSysAttach > 1)THEN
ErrorsFound = .TRUE.
CALL ShowSevereError(TRIM(RoutineName)//': Refrigeration:WalkIn="'// &
TRIM(WalkIn(WalkInNum)%Name)//'", Same Refrigeration WalkIn name referenced')
CALL ShowContinueError(' by more than one refrigeration system and/or compressor rack.')
END IF ! if looking for same walk in attached to multiple systems/racks
END DO !NumSimulationWalkIns
IF((NumunusedWalkIns > 0) .AND. (.NOT. DisplayExtraWarnings)) THEN
! write to error file,
! summary number of unused walkins given if DisplayExtraWarnings option not selected
CALL ShowWarningError(TRIM(RoutineName)//'Refrigeration:WalkIn -> '//TRIM(RoundSigDigits(NumunusedWalkIns))//&
' unused refrigeration WalkIns found during input processing.')
CALL ShowContinueError(' Those refrigeration WalkIns are in the input file but are not connected to a ')
CALL ShowContinueError(' Refrigeration:CompressorRack, Refrigeration:System or Refrigeration:SecondarySystem object.')
CALL ShowContinueError(' These unused refrigeration WalkIns will not be simulated.')
CALL ShowContinueError(' Use Output:Diagnostics,DisplayUnusedObjects; to see them. ')
END IF !NumunusedWalkIns
END IF !NumSimulationWalkIns > 0
IF(NumSimulationRefrigAirChillers > 0) THEN
!check for air chillers not connected to any systems and
! air chillers connected more than once
NumunusedCoils = 0
DO CoilNum=1,NumSimulationRefrigAirChillers
IF(WarehouseCoil(CoilNum)%NumSysAttach == 1) CYCLE
IF(WarehouseCoil(CoilNum)%NumSysAttach < 1)THEN
NumunusedWalkIns = NumunusedWalkIns + 1
IF (DisplayExtraWarnings) THEN
! individual walkin names listed if DisplayExtraWarnings option selected
CALL ShowWarningError(TRIM(RoutineName)//': Refrigeration:AirChiller="'// &
TRIM(WarehouseCoil(CoilNum)%Name)//'" unused. ')
END IF !display extra warnings - give a list of unused chillers
END IF !unused chiller
IF(WarehouseCoil(CoilNum)%NumSysAttach > 1)THEN
ErrorsFound = .TRUE.
CALL ShowSevereError(TRIM(RoutineName)//': Refrigeration:AirChiller="'// &
TRIM(WarehouseCoil(CoilNum)%Name)//'", Same Refrigeration Air Chiller name referenced')
CALL ShowContinueError(' by more than one refrigeration system and/or compressor rack.')
END IF ! if looking for same walk in attached to multiple systems/racks
END DO !NumSimulationRefrigAirchillers
IF((NumunusedCoils > 0) .AND. (.NOT. DisplayExtraWarnings)) THEN
! write to error file,
! summary number of unused air chillers given if DisplayExtraWarnings option not selected
CALL ShowWarningError(RoutineName//'Refrigeration:AirChiller -> '//TRIM(RoundSigDigits(NumunusedCoils))//&
' unused refrigeration air chillers found during input processing.')
CALL ShowContinueError(' Those refrigeration air chillers are in the input file but are not connected to a ')
CALL ShowContinueError(' Refrigeration:CompressorRack, Refrigeration:System or Refrigeration:SecondarySystem object.')
CALL ShowContinueError(' These unused refrigeration air chillers will not be simulated.')
CALL ShowContinueError(' Use Output:Diagnostics,DisplayUnusedObjects; to see them. ')
END IF !NumunusedAirChllerss
END IF !NumSimulationAirChillers > 0
IF(NumSimulationSecondarySystems > 0) THEN
!check for refrigeration Secondarys not connected to detailed systems and
! refrigeration Secondarys connected more than once
NumunusedSecondarys = 0
DO SecondaryNum=1,NumSimulationSecondarySystems
IF(Secondary(SecondaryNum)%NumSysAttach == 1) CYCLE
IF(Secondary(SecondaryNum)%NumSysAttach < 1) THEN
NumunusedSecondarys = NumunusedSecondarys + 1
IF (DisplayExtraWarnings) THEN
! individual secondary names listed if DisplayExtraWarnings option selected
CALL ShowWarningError(TRIM(RoutineName)//': Refrigeration:Secondary="'// &
TRIM(Secondary(SecondaryNum)%Name)//'" unused. ')
END IF !display extra warnings - give a list of unused Secondaries
END IF !unused secondary
IF(Secondary(SecondaryNum)%NumSysAttach > 1)THEN
ErrorsFound = .TRUE.
CALL ShowSevereError(TRIM(RoutineName)//': Refrigeration:Secondary="'// &
TRIM(Secondary(SecondaryNum)%Name)//'", Same Refrigeration Secondary name referenced')
CALL ShowContinueError(' by more than one refrigeration system')
END IF ! looking for same secondary loop attached to multiple systems/racks
END DO !NumSimulationSecondarys
IF((NumunusedSecondarys > 0) .AND. (.NOT. DisplayExtraWarnings)) THEN
! write to error file,
! summary number of unused secondaries given if DisplayExtraWarnings option not selected
CALL ShowWarningError(RoutineName//'Refrigeration:Secondary -> '//TRIM(RoundSigDigits(NumunusedSecondarys))//&
' unused refrigeration Secondary Loops found during input processing.')
CALL ShowContinueError(' Those refrigeration Secondary Loops are in the input file but are not connected to a'//&
' refrigeration system.')
CALL ShowContinueError(' These unused refrigeration secondaries will not be simulated.')
CALL ShowContinueError(' Use Output:Diagnostics,DisplayUnusedObjects; to see them. ')
END IF !NumunusedSecondarys
END IF !NumSimulationSecondarySystems > 0
IF(NumRefrigCondensers > 0) THEN
!Check for presence of shared condensers and for unused condensers
! - determines number of loops through refrigeration simulation
! because of dependence of performance on total condenser load
NumSimulationSharedCondensers = 0
NumunusedCondensers = 0
DO CondNum = 1,NumRefrigCondensers
IF(Condenser(CondNum)%NumSysAttach == 1) CYCLE
IF(Condenser(CondNum)%NumSysAttach < 1) THEN
NumunusedCondensers = NumunusedCondensers + 1
IF (DisplayExtraWarnings) THEN
! individual condenser names listed if DisplayExtraWarnings option selected
CALL ShowWarningError(TRIM(RoutineName)//': Refrigeration:Condenser="'// &
TRIM(Condenser(CondNum)%Name)//'" unused. ')
END IF !display extra warnings - give a list of unused condensers
END IF !unused condenser
IF(Condenser(CondNum)%NumSysAttach > 1) THEN
NumSimulationSharedCondensers = NumSimulationSharedCondensers + 1
END IF ! looking for shared condensers
END DO !CondNum
IF((NumunusedCondensers > 0) .AND. (.NOT. DisplayExtraWarnings)) THEN
! write to error file,
! summary number of unused condensers given if DisplayExtraWarnings option not selected
CALL ShowWarningError(TRIM(RoutineName)//'Refrigeration condenser -> '//TRIM(RoundSigDigits(NumunusedCondensers))//&
' unused refrigeration condensers found during input processing.')
CALL ShowContinueError(' Those refrigeration condensers are in the input file but are not connected to a'//&
' refrigeration system.')
CALL ShowContinueError(' These unused refrigeration condensers will not be simulated.')
CALL ShowContinueError(' Use Output:Diagnostics,DisplayUnusedObjects; to see them. ')
END IF !NumunusedCondensers and displayextra warnings
END IF !NumRefrigCondensers > 0
IF(NumSimulationGasCooler > 0) THEN
!Check for presence of shared gas coolers and for unused gas coolers
NumSimulationSharedGasCoolers = 0
NumunusedGasCoolers = 0
DO GCNum = 1,NumSimulationGasCooler
IF(GasCooler(GCNum)%NumSysAttach == 1) CYCLE
IF(GasCooler(GCNum)%NumSysAttach < 1) THEN
NumunusedGasCoolers = NumunusedGasCoolers + 1
IF (DisplayExtraWarnings) THEN
! individual gas cooler names listed if DisplayExtraWarnings option selected
CALL ShowWarningError(TRIM(RoutineName)//': Refrigeration:GasCooler="'// &
TRIM(GasCooler(GCNum)%Name)//'" unused. ')
END IF !display extra warnings - give a list of unused gas coolers
END IF !unused gas cooler
IF(GasCooler(GCNum)%NumSysAttach > 1) THEN
NumSimulationSharedGasCoolers = NumSimulationSharedGasCoolers + 1
END IF ! looking for shared gas coolers
END DO !GCNum
IF((NumunusedGasCoolers > 0) .AND. (.NOT. DisplayExtraWarnings)) THEN
! write to error file,
! summary number of unused gas coolers given if DisplayExtraWarnings option not selected
CALL ShowWarningError(TRIM(RoutineName)//'Refrigeration gas cooler -> '// &
TRIM(RoundSigDigits(NumunusedGasCoolers))//&
' unused refrigeration gas cooler(s) found during input processing.')
CALL ShowContinueError(' These refrigeration gas coolers are in the input file but are not connected to a'//&
' refrigeration system.')
CALL ShowContinueError(' These unused refrigeration gas coolers will not be simulated.')
CALL ShowContinueError(' Use Output:Diagnostics,DisplayUnusedObjects; to see them. ')
END IF !NumunusedGasCoolers and displayextra warnings
END IF !NumSimulationGasCooler > 0
!echo input to eio file.
CALL ReportRefrigerationComponents()
IF (ErrorsFound) THEN
CALL ShowFatalError(TRIM(RoutineName)//' Previous errors cause program termination')
ENDIF
RETURN
END SUBROUTINE GetRefrigerationInput