Nodes of different colours represent the following:
Solid arrows point from a parent (sub)module to the submodule which is descended from it. Dashed arrows point from a module being used to the module or program unit using it. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
Nodes of different colours represent the following:
Solid arrows point from a procedure to one which it calls. Dashed arrows point from an interface to procedures which implement that interface. This could include the module procedures in a generic interface or the implementation in a submodule of an interface in a parent module. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
Nodes of different colours represent the following:
Solid arrows point from a procedure to one which it calls. Dashed arrows point from an interface to procedures which implement that interface. This could include the module procedures in a generic interface or the implementation in a submodule of an interface in a parent module. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
SUBROUTINE GetFluidCoolerInput
! SUBROUTINE INFORMATION:
! AUTHOR: Chandan Sharma
! DATE WRITTEN: August 2008
! MODIFIED Chandan Sharma, FSEC, April 2010
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Obtains input data for fluid coolers and stores it in SimpleFluidCooler data structure.
! METHODOLOGY EMPLOYED:
! Uses "Get" routines to read in the data.
! REFERENCES:
! Based on GetTowerInput subroutine from Don Shirey, Jan 2001 and Sept/Oct 2002;
! USE STATEMENTS:
USE InputProcessor, ONLY: GetNumObjectsFound, GetObjectItem, VerifyName, SameString
USE DataIPShortCuts ! Data for field names, blank numerics
USE NodeInputManager, ONLY: GetOnlySingleNode
USE BranchNodeConnections, ONLY: TestCompSet
USE DataSizing, ONLY: AutoSize
USE CurveManager, ONLY: GetCurveIndex
USE ScheduleManager, ONLY: GetScheduleIndex
USE OutAirNodeManager, ONLY: CheckOutAirNodeNumber
USE General, ONLY: TrimSigDigits
USE FluidProperties, ONLY: CheckFluidPropertyName, FindGlycol
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
! na
! SUBROUTINE PARAMETER DEFINITIONS:
CHARACTER(len=*), PARAMETER :: Blank = ' '
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: FluidCoolerNum ! Fluid cooler number, reference counter for SimpleFluidCooler data array
INTEGER :: NumSingleSpeedFluidCoolers ! Total number of single-speed Fluid Coolers
INTEGER :: SingleSpeedFluidCoolerNumber ! Specific single-speed fluid cooler of interest
INTEGER :: NumTwoSpeedFluidCoolers ! Number of two-speed Fluid Coolers
INTEGER :: TwoSpeedFluidCoolerNumber ! Specific two-speed fluid cooler of interest
INTEGER :: NumAlphas ! Number of elements in the alpha array
INTEGER :: NumNums ! Number of elements in the numeric array
INTEGER :: IOStat ! IO Status when calling get input subroutine
LOGICAL :: IsNotOK ! Flag to verify name
LOGICAL :: IsBlank ! Flag for blank name
LOGICAL, SAVE :: ErrorsFound=.false. ! Logical flag set .true. if errors found while getting input data
REAL(r64), DIMENSION(16) :: NumArray ! Numeric input data array
CHARACTER(len=MaxNameLength),DIMENSION(5) :: AlphArray ! Character string input data array
!! LKL - still more renaming stuff to go.
! Get number of all Fluid Coolers specified in the input data file (idf)
NumSingleSpeedFluidCoolers = GetNumObjectsFound('FluidCooler:SingleSpeed')
NumTwoSpeedFluidCoolers = GetNumObjectsFound('FluidCooler:TwoSpeed')
NumSimpleFluidCoolers = NumSingleSpeedFluidCoolers + NumTwoSpeedFluidCoolers
IF (NumSimpleFluidCoolers <= 0 ) &
CALL ShowFatalError('No fluid cooler objects found in input, however, a branch object has specified a fluid cooler. '//&
'Search the input for fluid cooler to determine the cause for this error.')
! See if load distribution manager has already gotten the input
IF (ALLOCATED(SimpleFluidCooler))RETURN
! Allocate data structures to hold fluid cooler input data, report data and fluid cooler inlet conditions
ALLOCATE (SimpleFluidCooler(NumSimpleFluidCoolers))
ALLOCATE (SimpleFluidCoolerReport(NumSimpleFluidCoolers))
ALLOCATE (SimpleFluidCoolerInlet(NumSimpleFluidCoolers))
ALLOCATE(CheckEquipName(NumSimpleFluidCoolers))
CheckEquipName=.true.
! Load data structures with fluid cooler input data
cCurrentModuleObject = cFluidCooler_SingleSpeed
DO SingleSpeedFluidCoolerNumber = 1 , NumSingleSpeedFluidCoolers
FluidCoolerNum = SingleSpeedFluidCoolerNumber
CALL GetObjectItem(cCurrentModuleObject,SingleSpeedFluidCoolerNumber,AlphArray,NumAlphas,NumArray,NumNums,IOSTAT, &
AlphaBlank=lAlphaFieldBlanks,NumBlank=lNumericFieldBlanks, &
AlphaFieldnames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
IsNotOK=.false.
IsBlank=.false.
CALL VerifyName(AlphArray(1),SimpleFluidCooler%Name,FluidCoolerNum-1,IsNotOK,IsBlank,TRIM(cCurrentModuleObject)//' Name')
IF (IsNotOK) THEN
ErrorsFound=.true.
IF (IsBlank) AlphArray(1)='xxxxx'
ENDIF
SimpleFluidCooler(FluidCoolerNum)%Name = AlphArray(1)
SimpleFluidCooler(FluidCoolerNum)%FluidCoolerType = TRIM(cCurrentModuleObject)
SimpleFluidCooler(FluidCoolerNum)%FluidCoolerType_Num = FluidCooler_SingleSpeed
SimpleFluidCooler(FluidCoolerNum)%FluidCoolerMassFlowRateMultiplier = 2.5d0
SimpleFluidCooler(FluidCoolerNum)%WaterInletNodeNum = &
GetOnlySingleNode(AlphArray(2),ErrorsFound,TRIM(cCurrentModuleObject),AlphArray(1), &
NodeType_Water,NodeConnectionType_Inlet, 1, ObjectIsNotParent)
SimpleFluidCooler(FluidCoolerNum)%WaterOutletNodeNum = &
GetOnlySingleNode(AlphArray(3),ErrorsFound,TRIM(cCurrentModuleObject),AlphArray(1), &
NodeType_Water,NodeConnectionType_Outlet, 1, ObjectIsNotParent)
CALL TestCompSet(TRIM(cCurrentModuleObject),AlphArray(1),AlphArray(2),AlphArray(3),'Chilled Water Nodes')
SimpleFluidCooler(FluidCoolerNum)%HighSpeedFluidCoolerUA = NumArray(1)
SimpleFluidCooler(FluidCoolerNum)%FluidCoolerNominalCapacity = NumArray(2)
SimpleFluidCooler(FluidCoolerNum)%DesignEnteringWaterTemp = NumArray(3)
SimpleFluidCooler(FluidCoolerNum)%DesignEnteringAirTemp = NumArray(4)
SimpleFluidCooler(FluidCoolerNum)%DesignEnteringAirWetbulbTemp = NumArray(5)
SimpleFluidCooler(FluidCoolerNum)%DesignWaterFlowRate = NumArray(6)
SimpleFluidCooler(FluidCoolerNum)%HighSpeedAirFlowRate = NumArray(7)
SimpleFluidCooler(FluidCoolerNum)%HighSpeedFanPower = NumArray(8)
! outdoor air inlet node
IF (AlphArray(5) == Blank) THEN
SimpleFluidCooler(FluidCoolerNum)%OutdoorAirInletNodeNum = 0
ELSE
SimpleFluidCooler(FluidCoolerNum)%OutdoorAirInletNodeNum = &
GetOnlySingleNode(AlphArray(5),ErrorsFound,TRIM(cCurrentModuleObject),SimpleFluidCooler(FluidCoolerNum)%Name, &
NodeType_Air,NodeConnectionType_OutsideAirReference,1,ObjectIsNotParent)
IF(.not. CheckOutAirNodeNumber(SimpleFluidCooler(FluidCoolerNum)%OutdoorAirInletNodeNum))THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'= "'//TRIM(SimpleFluidCooler(FluidCoolerNum)%Name)// &
'" '//trim(cAlphaFieldNames(5))//'= "'//TRIM(AlphArray(5))//'" not valid.')
CALL ShowContinueError('...does not appear in an OutdoorAir:NodeList or as an OutdoorAir:Node.')
ErrorsFound=.true.
END IF
ENDIF
! Design entering water temperature, design entering air temperature and design entering air
! wetbulb temperature must be specified for the both the performance input methods
IF (SimpleFluidCooler(FluidCoolerNum)%DesignEnteringWaterTemp <= 0.0d0) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//' = "'//trim(AlphArray(1))//'", invalid data for "'// &
trim(cNumericFieldNames(3))//'", entered value <= 0.0, but must be > 0 ')
ErrorsFound=.true.
ENDIF
IF (SimpleFluidCooler(FluidCoolerNum)%DesignEnteringAirTemp <= 0.0d0) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//' = "'//trim(AlphArray(1))//'", invalid data for "'// &
trim(cNumericFieldNames(4))//'", entered value <= 0.0, but must be > 0 ')
ErrorsFound=.true.
ENDIF
IF (SimpleFluidCooler(FluidCoolerNum)%DesignEnteringAirWetbulbTemp <= 0.0d0) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//' = "'//trim(AlphArray(1))//'", invalid data for "'// &
trim(cNumericFieldNames(5))//'", entered value <= 0.0, but must be > 0 ')
ErrorsFound=.true.
ENDIF
IF (SimpleFluidCooler(FluidCoolerNum)%DesignEnteringWaterTemp <= &
SimpleFluidCooler(FluidCoolerNum)%DesignEnteringAirTemp) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//'= "'//trim(AlphArray(1))//'",'// &
trim(cNumericFieldNames(3))//' must be greater than '//trim(cNumericFieldNames(4))//'.')
ErrorsFound=.true.
ENDIF
IF (SimpleFluidCooler(FluidCoolerNum)%DesignEnteringAirTemp <= &
SimpleFluidCooler(FluidCoolerNum)%DesignEnteringAirWetbulbTemp) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//'= "'//trim(AlphArray(1))//'",'// &
trim(cNumericFieldNames(4))//' must be greater than '//trim(cNumericFieldNames(5))//'.')
ErrorsFound=.true.
ENDIF
IF (SimpleFluidCooler(FluidCoolerNum)%HighSpeedAirFlowRate <= 0.0d0 .AND. &
SimpleFluidCooler(FluidCoolerNum)%HighSpeedAirFlowRate .NE. AutoSize) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//' = "'//trim(AlphArray(1))//'", invalid data for "'// &
trim(cNumericFieldNames(7))//'", entered value <= 0.0, but must be > 0 for '// &
trim(cAlphaFieldNames(4))//' = "'//trim(AlphArray(4))//'".')
ErrorsFound=.true.
ENDIF
IF (SimpleFluidCooler(FluidCoolerNum)%DesignWaterFlowRate <= 0.0d0 .AND. &
SimpleFluidCooler(FluidCoolerNum)%DesignWaterFlowRate .NE. AutoSize) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//' = "'//trim(AlphArray(1))//'", invalid data for "'// &
trim(cNumericFieldNames(6))//'", entered value <= 0.0, but must be > 0 for '// &
trim(cAlphaFieldNames(4))//' = "'//trim(AlphArray(4))//'".')
ErrorsFound=.true.
ENDIF
IF (SimpleFluidCooler(FluidCoolerNum)%HighSpeedFanPower <= 0.0d0 .AND. &
SimpleFluidCooler(FluidCoolerNum)%HighSpeedFanPower .NE. AutoSize) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//' = "'//trim(AlphArray(1))//'", invalid data for "'// &
trim(cNumericFieldNames(8))//'", entered value <= 0.0, but must be > 0 for '// &
trim(cAlphaFieldNames(4))//' = "'//trim(AlphArray(4))//'".')
ErrorsFound=.true.
ENDIF
! Check various inputs for both the performance input methods
IF (SameString(AlphArray(4),'UFactorTimesAreaAndDesignWaterFlowRate')) THEN
SimpleFluidCooler(FluidCoolerNum)%PerformanceInputMethod_Num = PIM_UFactor
IF (SimpleFluidCooler(FluidCoolerNum)%HighSpeedFluidCoolerUA <= 0.0d0 .AND. &
SimpleFluidCooler(FluidCoolerNum)%HighSpeedFluidCoolerUA .NE. AutoSize) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//' = "'//trim(AlphArray(1))//'", invalid data for "'// &
trim(cNumericFieldNames(1))//'", entered value <= 0.0, but must be > 0 for '// &
trim(cAlphaFieldNames(4))//' = "'//trim(AlphArray(4))//'".')
ErrorsFound=.true.
ENDIF
ELSEIF(SameString(AlphArray(4),'NominalCapacity')) THEN
SimpleFluidCooler(FluidCoolerNum)%PerformanceInputMethod_Num = PIM_NominalCapacity
IF (SimpleFluidCooler(FluidCoolerNum)%FluidCoolerNominalCapacity <= 0.0d0) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//' = "'//trim(AlphArray(1))//'", invalid data for "'// &
trim(cNumericFieldNames(2))//'", entered value <= 0.0, but must be > 0 for '// &
trim(cAlphaFieldNames(4))//' = "'//trim(AlphArray(4))//'".')
ErrorsFound=.true.
ENDIF
IF (SimpleFluidCooler(FluidCoolerNum)%HighSpeedFluidCoolerUA .NE. 0.0d0) THEN
IF (SimpleFluidCooler(FluidCoolerNum)%HighSpeedFluidCoolerUA > 0.0d0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'= "'//TRIM(SimpleFluidCooler(FluidCoolerNum)%Name)//&
'". Nominal fluid cooler capacity and design fluid cooler UA have been specified.')
ELSE
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'= "'//TRIM(SimpleFluidCooler(FluidCoolerNum)%Name)//&
'". Nominal fluid cooler capacity has been specified and design fluid cooler UA is being autosized.')
ENDIF
CALL ShowContinueError('Design fluid cooler UA field must be left blank '// &
'when nominal fluid cooler capacity performance input method is used.')
ErrorsFound=.true.
ENDIF
ELSE ! Fluid cooler performance input method is not specified as a valid "choice"
CALL ShowSevereError(trim(cCurrentModuleObject)//'= "'//trim(AlphArray(1))//'", invalid '// &
trim(cAlphaFieldNames(4))//' = "'//trim(AlphArray(4))//'".')
CALL ShowContinueError('... must be "UFactorTimesAreaAndDesignWaterFlowRate" or "NominalCapacity".')
ErrorsFound=.true.
ENDIF
END DO ! End Single-Speed fluid cooler Loop
cCurrentModuleObject = cFluidCooler_TwoSpeed
DO TwoSpeedFluidCoolerNumber = 1 , NumTwoSpeedFluidCoolers
FluidCoolerNum = NumSingleSpeedFluidCoolers + TwoSpeedFluidCoolerNumber
CALL GetObjectItem(cCurrentModuleObject,TwoSpeedFluidCoolerNumber,AlphArray,NumAlphas,NumArray,NumNums,IOSTAT, &
AlphaBlank=lAlphaFieldBlanks,NumBlank=lNumericFieldBlanks, &
AlphaFieldnames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
IsNotOK=.false.
IsBlank=.false.
CALL VerifyName(AlphArray(1),SimpleFluidCooler%Name,FluidCoolerNum-1,IsNotOK,IsBlank,TRIM(cCurrentModuleObject)//' Name')
IF (IsNotOK) THEN
ErrorsFound=.true.
IF (IsBlank) AlphArray(1)='xxxxx'
ENDIF
SimpleFluidCooler(FluidCoolerNum)%Name = AlphArray(1)
SimpleFluidCooler(FluidCoolerNum)%FluidCoolerType = TRIM(cCurrentModuleObject)
SimpleFluidCooler(FluidCoolerNum)%FluidCoolerType_Num = FluidCooler_TwoSpeed
SimpleFluidCooler(FluidCoolerNum)%FluidCoolerMassFlowRateMultiplier = 2.5d0
SimpleFluidCooler(FluidCoolerNum)%WaterInletNodeNum = &
GetOnlySingleNode(AlphArray(2),ErrorsFound,TRIM(cCurrentModuleObject),AlphArray(1), &
NodeType_Water,NodeConnectionType_Inlet, 1, ObjectIsNotParent)
SimpleFluidCooler(FluidCoolerNum)%WaterOutletNodeNum = &
GetOnlySingleNode(AlphArray(3),ErrorsFound,TRIM(cCurrentModuleObject),AlphArray(1), &
NodeType_Water,NodeConnectionType_Outlet, 1, ObjectIsNotParent)
CALL TestCompSet(TRIM(cCurrentModuleObject),AlphArray(1),AlphArray(2),AlphArray(3),'Chilled Water Nodes')
SimpleFluidCooler(FluidCoolerNum)%HighSpeedFluidCoolerUA = NumArray(1)
SimpleFluidCooler(FluidCoolerNum)%LowSpeedFluidCoolerUA = NumArray(2)
SimpleFluidCooler(FluidCoolerNum)%LowSpeedFluidCoolerUASizingFactor = NumArray(3)
SimpleFluidCooler(FluidCoolerNum)%FluidCoolerNominalCapacity = NumArray(4)
SimpleFluidCooler(FluidCoolerNum)%FluidCoolerLowSpeedNomCap = NumArray(5)
SimpleFluidCooler(FluidCoolerNum)%FluidCoolerLowSpeedNomCapSizingFactor = NumArray(6)
SimpleFluidCooler(FluidCoolerNum)%DesignEnteringWaterTemp = NumArray(7)
SimpleFluidCooler(FluidCoolerNum)%DesignEnteringAirTemp = NumArray(8)
SimpleFluidCooler(FluidCoolerNum)%DesignEnteringAirWetbulbTemp = NumArray(9)
SimpleFluidCooler(FluidCoolerNum)%DesignWaterFlowRate = NumArray(10)
SimpleFluidCooler(FluidCoolerNum)%HighSpeedAirFlowRate = NumArray(11)
SimpleFluidCooler(FluidCoolerNum)%HighSpeedFanPower = NumArray(12)
SimpleFluidCooler(FluidCoolerNum)%LowSpeedAirFlowRate = NumArray(13)
SimpleFluidCooler(FluidCoolerNum)%LowSpeedAirFlowRateSizingFactor = NumArray(14)
SimpleFluidCooler(FluidCoolerNum)%LowSpeedFanPower = NumArray(15)
SimpleFluidCooler(FluidCoolerNum)%LowSpeedFanPowerSizingFactor = NumArray(16)
! outdoor air inlet node
IF (AlphArray(5) == Blank) THEN
SimpleFluidCooler(FluidCoolerNum)%OutdoorAirInletNodeNum = 0
ELSE
SimpleFluidCooler(FluidCoolerNum)%OutdoorAirInletNodeNum = &
GetOnlySingleNode(AlphArray(5),ErrorsFound,TRIM(cCurrentModuleObject),SimpleFluidCooler(FluidCoolerNum)%Name, &
NodeType_Air,NodeConnectionType_OutsideAirReference,1,ObjectIsNotParent)
IF(.not. CheckOutAirNodeNumber(SimpleFluidCooler(FluidCoolerNum)%OutdoorAirInletNodeNum))THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'= "'//TRIM(SimpleFluidCooler(FluidCoolerNum)%Name)// &
'" '//trim(cAlphaFieldNames(5))//'= "'//TRIM(AlphArray(5))//'" not valid.')
CALL ShowContinueError('...does not appear in an OutdoorAir:NodeList or as an OutdoorAir:Node.')
ErrorsFound=.true.
END IF
ENDIF
! Design entering water temperature, design entering air temperature and design entering air
! wetbulb temperature must be specified for the both the performance input methods
IF (SimpleFluidCooler(FluidCoolerNum)%DesignEnteringWaterTemp <= 0.0d0) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//' = "'//trim(AlphArray(1))//'", invalid data for "'// &
trim(cNumericFieldNames(7))//'", entered value <= 0.0, but must be > 0 ')
ErrorsFound=.true.
ENDIF
IF (SimpleFluidCooler(FluidCoolerNum)%DesignEnteringAirTemp <= 0.0d0) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//' = "'//trim(AlphArray(1))//'", invalid data for "'// &
trim(cNumericFieldNames(8))//'", entered value <= 0.0, but must be > 0 ')
ErrorsFound=.true.
ENDIF
IF (SimpleFluidCooler(FluidCoolerNum)%DesignEnteringAirWetbulbTemp <= 0.0d0) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//' = "'//trim(AlphArray(1))//'", invalid data for "'// &
trim(cNumericFieldNames(9))//'", entered value <= 0.0, but must be > 0 ')
ErrorsFound=.true.
ENDIF
IF (SimpleFluidCooler(FluidCoolerNum)%DesignEnteringWaterTemp <= &
SimpleFluidCooler(FluidCoolerNum)%DesignEnteringAirTemp) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//' = "'//trim(AlphArray(1))//'", '// &
trim(cNumericFieldNames(7))//' must be greater than '//trim(cNumericFieldNames(8))//'.')
ErrorsFound=.true.
ENDIF
IF (SimpleFluidCooler(FluidCoolerNum)%DesignEnteringAirTemp <= &
SimpleFluidCooler(FluidCoolerNum)%DesignEnteringAirWetbulbTemp) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//' = "'//trim(AlphArray(1))//'", '// &
trim(cNumericFieldNames(8))//' must be greater than '//trim(cNumericFieldNames(9))//'.')
ErrorsFound=.true.
ENDIF
! Check various inputs for both the performance input methods
IF (SimpleFluidCooler(FluidCoolerNum)%DesignWaterFlowRate <= 0.0d0 .AND. &
SimpleFluidCooler(FluidCoolerNum)%DesignWaterFlowRate .NE. AutoSize) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//'= "'//trim(AlphArray(1))//'", invalid data for "'// &
trim(cNumericFieldNames(10))//'", entered value <= 0.0, but must be > 0 for '// &
trim(cAlphaFieldNames(4))//'= "'//trim(AlphArray(4))//'".')
ErrorsFound=.true.
ENDIF
IF (SimpleFluidCooler(FluidCoolerNum)%HighSpeedAirFlowRate <= 0.0d0 .AND. &
SimpleFluidCooler(FluidCoolerNum)%HighSpeedAirFlowRate .NE. AutoSize) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//'= "'//trim(AlphArray(1))//'", invalid data for "'// &
trim(cNumericFieldNames(11))//'", entered value <= 0.0, but must be > 0 for '// &
trim(cAlphaFieldNames(4))//'= "'//trim(AlphArray(4))//'".')
ErrorsFound=.true.
ENDIF
IF (SimpleFluidCooler(FluidCoolerNum)%LowSpeedAirFlowRate <= 0.0d0 .AND. &
SimpleFluidCooler(FluidCoolerNum)%LowSpeedAirFlowRate .NE. AutoSize) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//'= "'//trim(AlphArray(1))//'", invalid data for "'// &
trim(cNumericFieldNames(13))//'", entered value <= 0.0, but must be > 0 for '// &
trim(cAlphaFieldNames(4))//'= "'//trim(AlphArray(4))//'".')
ErrorsFound=.true.
ENDIF
! High speed air flow rate must be greater than low speed air flow rate.
! Can't tell yet if autosized, check later in InitFluidCooler.
IF (SimpleFluidCooler(FluidCoolerNum)%HighSpeedAirFlowRate <= &
SimpleFluidCooler(FluidCoolerNum)%LowSpeedAirFlowRate .and. &
SimpleFluidCooler(FluidCoolerNum)%HighSpeedAirFlowRate .NE. AutoSize) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'= "'//TRIM(SimpleFluidCooler(FluidCoolerNum)%Name)//&
'". Fluid cooler air flow rate at low fan speed must be less than the air '// &
'flow rate at high fan speed.')
ErrorsFound=.true.
ENDIF
IF (SimpleFluidCooler(FluidCoolerNum)%HighSpeedFanPower <= 0.0d0 .AND. &
SimpleFluidCooler(FluidCoolerNum)%HighSpeedFanPower .NE. AutoSize) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//' = "'//trim(AlphArray(1))//'", invalid data for "'// &
trim(cNumericFieldNames(12))//'", entered value <= 0.0, but must be > 0 for '// &
trim(cAlphaFieldNames(4))//' = "'//trim(AlphArray(4))//'".')
ErrorsFound=.true.
ENDIF
IF (SimpleFluidCooler(FluidCoolerNum)%LowSpeedFanPower <= 0.0d0 .AND. &
SimpleFluidCooler(FluidCoolerNum)%LowSpeedFanPower .NE. AutoSize) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//' = "'//trim(AlphArray(1))//'", invalid data for "'// &
trim(cNumericFieldNames(15))//'", entered value <= 0.0, but must be > 0 for '// &
trim(cAlphaFieldNames(4))//' = "'//trim(AlphArray(4))//'".')
ErrorsFound=.true.
ENDIF
IF (SimpleFluidCooler(FluidCoolerNum)%HighSpeedFanPower <= &
SimpleFluidCooler(FluidCoolerNum)%LowSpeedFanPower .and. &
SimpleFluidCooler(FluidCoolerNum)%HighSpeedFanPower .NE. AutoSize) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'= "'//TRIM(SimpleFluidCooler(FluidCoolerNum)%Name)//&
'". Fluid cooler low speed fan power must be less than high speed fan power.')
ErrorsFound=.true.
ENDIF
IF (SameString(AlphArray(4),'UFactorTimesAreaAndDesignWaterFlowRate')) THEN
SimpleFluidCooler(FluidCoolerNum)%PerformanceInputMethod_Num = PIM_UFactor
IF (SimpleFluidCooler(FluidCoolerNum)%HighSpeedFluidCoolerUA <= 0.0d0 .AND. &
SimpleFluidCooler(FluidCoolerNum)%HighSpeedFluidCoolerUA .NE. AutoSize) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//' = "'//trim(AlphArray(1))//'", invalid data for "'// &
trim(cNumericFieldNames(1))//'", entered value <= 0.0, but must be > 0 for '// &
trim(cAlphaFieldNames(4))//' = "'//trim(AlphArray(4))//'".')
ErrorsFound=.true.
ENDIF
IF (SimpleFluidCooler(FluidCoolerNum)%LowSpeedFluidCoolerUA <= 0.0d0 .AND. &
SimpleFluidCooler(FluidCoolerNum)%LowSpeedFluidCoolerUA .NE. AutoSize) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//' = "'//trim(AlphArray(1))//'", invalid data for "'// &
trim(cNumericFieldNames(2))//'", entered value <= 0.0, but must be > 0 for '// &
trim(cAlphaFieldNames(4))//' = "'//trim(AlphArray(4))//'".')
ErrorsFound=.true.
ENDIF
IF (SimpleFluidCooler(FluidCoolerNum)%HighSpeedFluidCoolerUA <= &
SimpleFluidCooler(FluidCoolerNum)%LowSpeedFluidCoolerUA .and. &
SimpleFluidCooler(FluidCoolerNum)%HighSpeedFluidCoolerUA .NE. AutoSize) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'= "'//TRIM(SimpleFluidCooler(FluidCoolerNum)%Name)//&
'". Fluid cooler UA at low fan speed must be less than the fluid cooler UA at high fan speed.')
ErrorsFound=.true.
ENDIF
ELSEIF(SameString(AlphArray(4),'NominalCapacity')) THEN
SimpleFluidCooler(FluidCoolerNum)%PerformanceInputMethod_Num = PIM_NominalCapacity
IF (SimpleFluidCooler(FluidCoolerNum)%FluidCoolerNominalCapacity <= 0.0d0) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//' = "'//trim(AlphArray(1))//'", invalid data for "'// &
trim(cNumericFieldNames(4))//'", entered value <= 0.0, but must be > 0 for '// &
trim(cAlphaFieldNames(4))//'= "'//trim(AlphArray(4))//'".')
ErrorsFound=.true.
ENDIF
IF (SimpleFluidCooler(FluidCoolerNum)%FluidCoolerLowSpeedNomCap <= 0.0d0) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//' = "'//trim(AlphArray(1))//'", invalid data for "'// &
trim(cNumericFieldNames(5))//'", entered value <= 0.0, but must be > 0 for '// &
trim(cAlphaFieldNames(4))//'= "'//trim(AlphArray(4))//'".')
ErrorsFound=.true.
ENDIF
IF (SimpleFluidCooler(FluidCoolerNum)%HighSpeedFluidCoolerUA .NE. 0.0d0) THEN
IF (SimpleFluidCooler(FluidCoolerNum)%HighSpeedFluidCoolerUA > 0.0d0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'= "'//TRIM(SimpleFluidCooler(FluidCoolerNum)%Name)//&
'". Nominal capacity input method and fluid cooler UA at high fan speed have been specified.')
ELSE
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'= "'//TRIM(SimpleFluidCooler(FluidCoolerNum)%Name)//&
'". Nominal capacity input method has been specified and fluid cooler UA at high fan speed is being autosized.')
ENDIF
CALL ShowContinueError('Fluid cooler UA at high fan speed must be left blank '// &
'when nominal fluid cooler capacity performance input method'// &
' is used.')
ErrorsFound=.true.
ENDIF
IF (SimpleFluidCooler(FluidCoolerNum)%LowSpeedFluidCoolerUA .NE. 0.0d0) THEN
IF (SimpleFluidCooler(FluidCoolerNum)%LowSpeedFluidCoolerUA > 0.0d0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'= "'//TRIM(SimpleFluidCooler(FluidCoolerNum)%Name)//&
'". Nominal capacity input method and fluid cooler UA at low fan speed have been specified.')
ELSE
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'= "'//TRIM(SimpleFluidCooler(FluidCoolerNum)%Name)//&
'". Nominal capacity input method has been specified and fluid cooler UA at low fan speed is being autosized.')
ENDIF
CALL ShowContinueError('Fluid cooler UA at low fan speed must be left blank '// &
'when nominal fluid cooler capacity performance input method is used.')
ErrorsFound=.true.
ENDIF
IF (SimpleFluidCooler(FluidCoolerNum)%FluidCoolerLowSpeedNomCap >= &
SimpleFluidCooler(FluidCoolerNum)%FluidCoolerNominalCapacity) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//' = "'//TRIM(SimpleFluidCooler(FluidCoolerNum)%Name)//&
'". Low-speed nominal capacity must be less than the high-speed nominal capacity.')
ErrorsFound=.true.
END IF
ELSE ! Fluid cooler performance input method is not specified as a valid "choice"
CALL ShowSevereError(trim(cCurrentModuleObject)//'= "'//trim(AlphArray(1))//'", invalid '// &
trim(cAlphaFieldNames(4))//'= "'//trim(AlphArray(4))//'".')
CALL ShowContinueError('... must be "UFactorTimesAreaAndDesignWaterFlowRate" or "NominalCapacity".')
ErrorsFound=.true.
ENDIF
END DO ! End Two-Speed Fluid Cooler Loop
IF (ErrorsFound) THEN
CALL ShowFatalError('Errors found in getting fluid cooler input.')
ENDIF
! Set up output variables, CurrentModuleObject='FluidCooler:SingleSpeed'
DO FluidCoolerNum = 1, NumSingleSpeedFluidCoolers
CALL SetupOutputVariable('Cooling Tower Inlet Temperature [C]', &
SimpleFluidCoolerReport(FluidCoolerNum)%InletWaterTemp,'System','Average',SimpleFluidCooler(FluidCoolerNum)%Name)
CALL SetupOutputVariable('Cooling Tower Outlet Temperature [C]', &
SimpleFluidCoolerReport(FluidCoolerNum)%OutletWaterTemp,'System','Average',SimpleFluidCooler(FluidCoolerNum)%Name)
CALL SetupOutputVariable('Cooling Tower Mass Flow Rate [kg/s]', &
SimpleFluidCoolerReport(FluidCoolerNum)%WaterMassFlowRate,'System','Average',SimpleFluidCooler(FluidCoolerNum)%Name)
CALL SetupOutputVariable('Cooling Tower Heat Transfer Rate [W]', &
SimpleFluidCoolerReport(FluidCoolerNum)%Qactual,'System','Average',SimpleFluidCooler(FluidCoolerNum)%Name)
CALL SetupOutputVariable('Cooling Tower Fan Electric Power [W]', &
SimpleFluidCoolerReport(FluidCoolerNum)%FanPower,'System','Average',SimpleFluidCooler(FluidCoolerNum)%Name)
CALL SetupOutputVariable('Cooling Tower Fan Electric Energy [J]', &
SimpleFluidCoolerReport(FluidCoolerNum)%FanEnergy,'System','Sum',SimpleFluidCooler(FluidCoolerNum)%Name, &
ResourceTypeKey='Electric',EndUseKey='HeatRejection',GroupKey='Plant')
END DO
! CurrentModuleObject='FluidCooler:TwoSpeed'
DO FluidCoolerNum = NumSingleSpeedFluidCoolers+1, NumSingleSpeedFluidCoolers+NumTwoSpeedFluidCoolers
CALL SetupOutputVariable('Cooling Tower Inlet Temperature [C]', &
SimpleFluidCoolerReport(FluidCoolerNum)%InletWaterTemp,'System','Average',SimpleFluidCooler(FluidCoolerNum)%Name)
CALL SetupOutputVariable('Cooling Tower Outlet Temperature [C]', &
SimpleFluidCoolerReport(FluidCoolerNum)%OutletWaterTemp,'System','Average',SimpleFluidCooler(FluidCoolerNum)%Name)
CALL SetupOutputVariable('Cooling Tower Mass Flow Rate [kg/s]', &
SimpleFluidCoolerReport(FluidCoolerNum)%WaterMassFlowRate,'System','Average',SimpleFluidCooler(FluidCoolerNum)%Name)
CALL SetupOutputVariable('Cooling Tower Heat Transfer Rate [W]', &
SimpleFluidCoolerReport(FluidCoolerNum)%Qactual,'System','Average',SimpleFluidCooler(FluidCoolerNum)%Name)
CALL SetupOutputVariable('Cooling Tower Fan Electric Power [W]', &
SimpleFluidCoolerReport(FluidCoolerNum)%FanPower,'System','Average',SimpleFluidCooler(FluidCoolerNum)%Name)
CALL SetupOutputVariable('Cooling Tower Fan Electric Energy [J]', &
SimpleFluidCoolerReport(FluidCoolerNum)%FanEnergy,'System','Sum',SimpleFluidCooler(FluidCoolerNum)%Name, &
ResourceTypeKey='Electric',EndUseKey='HeatRejection',GroupKey='Plant')
END DO
RETURN
END SUBROUTINE GetFluidCoolerInput