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 GetZoneSizingInput
! SUBROUTINE INFORMATION:
! AUTHOR Fred Buhl
! DATE WRITTEN December 2000
! MODIFIED Mangesh Basarkar, 06/2011: Specifying zone outside air based on design specification object
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Obtains input data for zone sizing objects and stores it in
! appropriate data structures.
! METHODOLOGY EMPLOYED:
! Uses InputProcessor "Get" routines to obtain data.
! REFERENCES:
! na
! USE STATEMENTS:
USE InputProcessor, ONLY: GetNumObjectsFound, GetObjectItem, VerifyName, FindItemInList
USE DataIPShortCuts
USE General, ONLY: RoundSigDigits
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
! na
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
TYPE GlobalMiscObject
CHARACTER(len=MaxNameLength) :: Name =' '
INTEGER :: ZoneOrZoneListPtr =0
INTEGER :: NumOfZones =0
INTEGER :: StartPtr =0
LOGICAL :: ZoneListActive =.false.
END TYPE GlobalMiscObject
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: ZoneSizIndex ! loop index
INTEGER :: NumAlphas ! Number of Alphas for each GetObjectItem call
INTEGER :: NumNumbers ! Number of Numbers for each GetObjectItem call
INTEGER :: IOStatus ! Used in GetObjectItem
LOGICAL :: ErrorsFound=.false. ! Set to true if errors in input, fatal at end of routine
LOGICAL :: IsNotOK ! Flag to verify name
LOGICAL :: IsBlank ! Flag for blank name
INTEGER :: NumDesDays ! Number of design days in input
INTEGER :: NumSizingZoneStatements
INTEGER :: Item
INTEGER :: Item1
INTEGER :: ZLItem
LOGICAL :: ErrFlag
CHARACTER(len=MaxNameLength), ALLOCATABLE, DIMENSION(:) :: ZoneNames
INTEGER :: NumZones
TYPE(ZoneListData), ALLOCATABLE, DIMENSION(:) :: ZoneListNames
INTEGER :: NumZoneLists
TYPE (GlobalMiscObject), ALLOCATABLE, DIMENSION(:) :: SizingZoneObjects
INTEGER OAIndex ! Index of design specification object
INTEGER ObjIndex ! Index of zone air distribution effectiveness object name
cCurrentModuleObject='Sizing:Zone'
NumSizingZoneStatements=GetNumObjectsFound(cCurrentModuleObject)
ALLOCATE(SizingZoneObjects(NumSizingZoneStatements))
IF (NumSizingZoneStatements > 0) THEN
Errflag=.false.
CALL GetZoneAndZoneListNames(ErrFlag,NumZones,ZoneNames,NumZoneLists,ZoneListNames)
ENDIF
cCurrentModuleObject='Sizing:Zone'
NumZoneSizingInput=0
ErrFlag=.false.
DO Item=1,NumSizingZoneStatements
CALL GetObjectItem(cCurrentModuleObject,Item,cAlphaArgs,NumAlphas,rNumericArgs,NumNumbers,IOStatus, &
AlphaBlank=lAlphaFieldBlanks,NumBlank=lNumericFieldBlanks, &
AlphaFieldnames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
IsNotOK = .FALSE.
IsBlank = .FALSE.
CALL VerifyName(cAlphaArgs(1),SizingZoneObjects%Name,Item-1,IsNotOK,IsBlank,TRIM(cCurrentModuleObject)//' Name')
IF (IsNotOK) THEN
ErrorsFound = .TRUE.
ErrFlag=.true.
IF (IsBlank) cAlphaArgs(1) = 'xxxxx'
END IF
SizingZoneObjects(Item)%Name = cAlphaArgs(1)
Item1=FindItemInList(cAlphaArgs(1),ZoneNames,NumZones)
ZLItem=0
IF (Item1 == 0 .and. NumZoneLists > 0) &
ZLItem=FindItemInList(cAlphaArgs(1),ZoneListNames%Name,NumZoneLists)
IF (Item1 > 0) THEN
SizingZoneObjects(Item)%StartPtr=NumZoneSizingInput+1
NumZoneSizingInput=NumZoneSizingInput+1
SizingZoneObjects(Item)%NumOfZones=1
SizingZoneObjects(Item)%ZoneListActive=.false.
SizingZoneObjects(Item)%ZoneOrZoneListPtr=Item1
ELSEIF (ZLItem > 0) THEN
SizingZoneObjects(Item)%StartPtr=NumZoneSizingInput+1
NumZoneSizingInput=NumZoneSizingInput+ZoneListNames(ZLItem)%NumOfZones
SizingZoneObjects(Item)%NumOfZones=ZoneListNames(ZLItem)%NumOfZones
SizingZoneObjects(Item)%ZoneListActive=.true.
SizingZoneObjects(Item)%ZoneOrZoneListPtr=ZLItem
ELSE
CALL ShowSevereError(trim(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//'" invalid '// &
trim(cAlphaFieldNames(1))//' not found.')
ErrorsFound=.true.
ErrFlag=.true.
ENDIF
ENDDO
IF (ErrFlag) THEN
CALL ShowSevereError('GetZoneSizingInput: Errors with invalid names in '//trim(cCurrentModuleObject)// &
' objects.')
CALL ShowContinueError('...These will not be read in. Other errors may occur.')
NumZoneSizingInput=0
ENDIF
IF (NumZoneSizingInput > 0) THEN
NumDesDays = GetNumObjectsFound('SizingPeriod:DesignDay') + GetNumObjectsFound('SizingPeriod:WeatherFileDays') + &
GetNumObjectsFound('SizingPeriod:WeatherFileConditionType')
IF (NumDesDays == 0 .AND. (DoZoneSizing .OR. DoSystemSizing .OR. DoPlantSizing) ) THEN
CALL ShowSevereError('Zone Sizing calculations need SizingPeriod:* input. None found.')
ErrorsFound = .TRUE.
END IF
ALLOCATE(ZoneSizingInput(NumZoneSizingInput))
ZoneSizIndex=0
DO Item = 1, NumSizingZoneStatements
CALL GetObjectItem(cCurrentModuleObject,Item,cAlphaArgs,NumAlphas,rNumericArgs,NumNumbers,IOStatus, &
AlphaBlank=lAlphaFieldBlanks,NumBlank=lNumericFieldBlanks, &
AlphaFieldnames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
DO Item1=1,SizingZoneObjects(Item)%NumOfZones
ZoneSizIndex=ZoneSizIndex+1
IF (.not. SizingZoneObjects(Item)%ZoneListActive) THEN
IF (SizingZoneObjects(Item)%ZoneOrZoneListPtr > 0) THEN
ZoneSizingInput(ZoneSizIndex)%ZoneName = ZoneNames(SizingZoneObjects(Item)%ZoneOrZoneListPtr)
ELSE
! Invalid zone, will be caught later
ZoneSizingInput(ZoneSizIndex)%ZoneName = 'Invalid Zone Name'
ENDIF
ELSE ! Zone list active
IF (SizingZoneObjects(Item)%ZoneOrZoneListPtr > 0 .and. &
ZoneListNames(SizingZoneObjects(Item)%ZoneOrZoneListPtr)%Zones(Item1) > 0) THEN
ZoneSizingInput(ZoneSizIndex)%ZoneName = &
ZoneNames(ZoneListNames(SizingZoneObjects(Item)%ZoneOrZoneListPtr)%Zones(Item1))
ELSE
! Invalid zone, will be caught later
ZoneSizingInput(ZoneSizIndex)%ZoneName = 'Invalid Zone Name'
ENDIF
ENDIF
IsNotOK=.FALSE.
IsBlank=.FALSE.
CALL VerifyName(ZoneSizingInput(ZoneSizIndex)%ZoneName,ZoneSizingInput%ZoneName, &
ZoneSizIndex-1,IsNotOK,IsBlank,TRIM(cCurrentModuleObject)//' Name')
IF (IsNotOK) THEN
ErrorsFound=.true.
IF (IsBlank) cAlphaArgs(1)='xxxxx'
ENDIF
IF (IsNotOK .and. .not. SizingZoneObjects(Item)%ZoneListActive) THEN
CALL ShowContinueError('Zone may have been entered in a ZoneList assignment.')
ENDIF
! A2, \field Zone Cooling Design Supply Air Temperature Input Method
! \required-field
! \type choice
! \key SupplyAirTemperature
! \key TemperatureDifference
! \default SupplyAirTemperature
SELECT CASE(TRIM(cAlphaArgs(2)))
CASE('SUPPLYAIRTEMPERATURE')
ZoneSizingInput(ZoneSizIndex)%ZnCoolDgnSAMethod = SupplyAirTemperature
CASE('TEMPERATUREDIFFERENCE')
ZoneSizingInput(ZoneSizIndex)%ZnCoolDgnSAMethod = TemperatureDifference
CASE DEFAULT
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//'", invalid data.')
CALL ShowContinueError('... incorrect '//TRIM(cAlphaFieldNames(2))//'="'//TRIM(cAlphaArgs(2))//'"')
CALL ShowContinueError('... valid values are SupplyAirTemperature or TemperatureDifference.')
ErrorsFound=.true.
END SELECT
! N1, \field Zone Cooling Design Supply Air Temperature
! \type real
! \units C
! \note Zone Cooling Design Supply Air Temperature is only used when Zone Cooling Design
! \note Supply Air Temperature Input Method = SupplyAirTemperature
IF (lNumericFieldBlanks(1)) THEN
ZoneSizingInput(ZoneSizIndex)%CoolDesTemp = 0.0d0
ELSEIF (rNumericArgs(1) < 0.0d0 .and. ZoneSizingInput(ZoneSizIndex)%ZnCoolDgnSAMethod == SupplyAirTemperature) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//'", invalid data.')
CALL ShowContinueError('... incorrect '//TRIM(cNumericFieldNames(1))//'=['//TRIM(RoundSigDigits(rNumericArgs(1),2))// &
'], value should not be negative.')
ErrorsFound=.true.
ELSEIF (rNumericArgs(1) >= 0.0d0 .and. ZoneSizingInput(ZoneSizIndex)%ZnCoolDgnSAMethod == SupplyAirTemperature) THEN
ZoneSizingInput(ZoneSizIndex)%CoolDesTemp = rNumericArgs(1)
ELSE
ZoneSizingInput(ZoneSizIndex)%CoolDesTemp = 0.0d0
ENDIF
! N2, \field Zone Cooling Design Supply Air Temperature Difference
! \type real
! \units delta C
! \note Zone Cooling Design Supply Air Temperature is only used when Zone Cooling Design
! \note Supply Air Temperature Input Method = TemperatureDifference
! \note The absolute of this value is value will be subtracted from room temperature
! \note at peak load to calculate Zone Cooling Design Supply Air Temperature.
IF (lNumericFieldBlanks(2)) THEN
ZoneSizingInput(ZoneSizIndex)%CoolDesTempDiff = 0.0d0
ELSEIF (ZoneSizingInput(ZoneSizIndex)%ZnCoolDgnSAMethod == TemperatureDifference) THEN
ZoneSizingInput(ZoneSizIndex)%CoolDesTempDiff = rNumericArgs(2)
ELSE
ZoneSizingInput(ZoneSizIndex)%CoolDesTempDiff = 0.0d0
ENDIF
! A3, \field Zone Heating Design Supply Air Temperature Input Method
! \required-field
! \type choice
! \key SupplyAirTemperature
! \key TemperatureDifference
! \default SupplyAirTemperature
SELECT CASE(TRIM(cAlphaArgs(3)))
CASE('SUPPLYAIRTEMPERATURE')
ZoneSizingInput(ZoneSizIndex)%ZnHeatDgnSAMethod = SupplyAirTemperature
CASE('TEMPERATUREDIFFERENCE')
ZoneSizingInput(ZoneSizIndex)%ZnHeatDgnSAMethod = TemperatureDifference
CASE DEFAULT
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//'", invalid data.')
CALL ShowContinueError('... incorrect '//TRIM(cAlphaFieldNames(3))//'="'//TRIM(cAlphaArgs(3))//'"')
CALL ShowContinueError('... valid values are SupplyAirTemperature or TemperatureDifference.')
ErrorsFound=.true.
END SELECT
! N3, \field Zone Heating Design Supply Air Temperature
! \type real
! \units C
! \note Zone Heating Design Supply Air Temperature is only used when Zone Heating Design
! \note Supply Air Temperature Input Method = SupplyAirTemperature
IF (lNumericFieldBlanks(3)) THEN
ZoneSizingInput(ZoneSizIndex)%HeatDesTemp = 0.0d0
ELSEIF (rNumericArgs(3) < 0.0d0 .and. ZoneSizingInput(ZoneSizIndex)%ZnHeatDgnSAMethod == SupplyAirTemperature) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//'", invalid data.')
CALL ShowContinueError('... incorrect '//TRIM(cNumericFieldNames(3))//'=['//TRIM(RoundSigDigits(rNumericArgs(3),2))// &
'], value should not be negative.')
ErrorsFound=.true.
ELSEIF (rNumericArgs(3) >= 0.0d0 .and. ZoneSizingInput(ZoneSizIndex)%ZnHeatDgnSAMethod == SupplyAirTemperature) THEN
ZoneSizingInput(ZoneSizIndex)%HeatDesTemp = rNumericArgs(3)
ELSE
ZoneSizingInput(ZoneSizIndex)%HeatDesTemp = 0.0d0
ENDIF
! N4, \field Zone Heating Design Supply Air Temperature Difference
! \type real
! \units deltaC
! \note Zone Heating Design Supply Air Temperature is only used when Zone Heating Design
! \note Supply Air Temperature Input Method = TemperatureDifference
! \note The absolute of this value is value will be added to room temperature
! \note at peak load to calculate Zone Heating Design Supply Air Temperature.
IF (lNumericFieldBlanks(4)) THEN
ZoneSizingInput(ZoneSizIndex)%HeatDesTempDiff = 0.0d0
ELSEIF (ZoneSizingInput(ZoneSizIndex)%ZnHeatDgnSAMethod == TemperatureDifference) THEN
ZoneSizingInput(ZoneSizIndex)%HeatDesTempDiff = rNumericArgs(4)
ELSE
ZoneSizingInput(ZoneSizIndex)%HeatDesTempDiff = 0.0d0
ENDIF
! N5, \field Zone Cooling Design Supply Air Humidity Ratio
! \required-field
! \minimum 0.0
! \type real
! \units kg-H2O/kg-air
IF (lNumericFieldBlanks(5)) THEN
ZoneSizingInput(ZoneSizIndex)%CoolDesHumRat = 0.0d0
ELSEIF (rNumericArgs(5) < 0.0d0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//': incorrect '//TRIM(cNumericFieldNames(5))//': '// &
TRIM(RoundSigDigits(rNumericArgs(5),2)))
CALL ShowContinueError('.. value should not be negative. Occurs in Sizing Object='//TRIM(cAlphaArgs(1)))
ErrorsFound=.true.
ELSE
ZoneSizingInput(ZoneSizIndex)%CoolDesHumRat = rNumericArgs(5)
ENDIF
! N6, \field Zone Heating Design Supply Air Humidity Ratio
! \required-field
! \minimum 0.0
! \type real
! \units kg-H2O/kg-air
IF (lNumericFieldBlanks(6)) THEN
ZoneSizingInput(ZoneSizIndex)%HeatDesHumRat = 0.0d0
ELSEIF (rNumericArgs(6) < 0.0d0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//': incorrect '//TRIM(cNumericFieldNames(6))//': '// &
TRIM(RoundSigDigits(rNumericArgs(6),2)))
CALL ShowContinueError('.. value should not be negative. Occurs in Sizing Object='//TRIM(cAlphaArgs(1)))
ErrorsFound=.true.
ELSE
ZoneSizingInput(ZoneSizIndex)%HeatDesHumRat = rNumericArgs(6)
ENDIF
! A4, \field Design Specification Outdoor Air Object Name
! \type object-list
! \object-list DesignSpecificationOutdoorAirNames
ZoneSizingInput(ZoneSizIndex)%DesignSpecOAObjName = cAlphaArgs(4)
! Getting zone OA parameters from Design Specification object
IF (.NOT. lAlphaFieldBlanks(4)) THEN
OAIndex=FindItemInList(ZoneSizingInput(ZoneSizIndex)%DesignSpecOAObjName, &
OARequirements%Name,numOARequirements)
IF (OAIndex > 0) THEN
ZoneSizingInput(ZoneSizIndex)%OADesMethod = OARequirements(OAIndex)%OAFlowMethod
ZoneSizingInput(ZoneSizIndex)%DesOAFlowPPer = OARequirements(OAIndex)%OAFlowPerPerson
ZoneSizingInput(ZoneSizIndex)%DesOAFlowPerArea = OARequirements(OAIndex)%OAFlowPerArea
ZoneSizingInput(ZoneSizIndex)%DesOAFlow = OARequirements(OAIndex)%OAFlowPerZone
ZoneSizingInput(ZoneSizIndex)%ZoneDesignSpecOAIndex = OAIndex
ELSE
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//'", invalid data.')
CALL ShowContinueError('... incorrect '//TRIM(cAlphaFieldNames(4))//'="'//TRIM(cAlphaArgs(4))//'".')
ErrorsFound=.true.
ENDIF
ELSE ! If no design spec object specified, i.e. no OA, then set OA method to None as default but flows to 0
ZoneSizingInput(ZoneSizIndex)%OADesMethod = 0
ZoneSizingInput(ZoneSizIndex)%DesOAFlowPPer = 0.0d0
ZoneSizingInput(ZoneSizIndex)%DesOAFlowPerArea = 0.0d0
ZoneSizingInput(ZoneSizIndex)%DesOAFlow = 0.0d0
ENDIF
! N7, \field Zone Heating Sizing Factor
! \note if blank, global heating sizing factor from Sizing:Parameters is used.
! \minimum> 0
IF (lNumericFieldBlanks(7) .or. rNumericArgs(7) == 0.0d0) THEN
ZoneSizingInput(ZoneSizIndex)%HeatSizingFactor = GlobalHeatSizingFactor
ELSEIF (rNumericArgs(7) < 0.0d0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//'", invalid data.')
CALL ShowContinueError('... incorrect '//TRIM(cNumericFieldNames(7))//'=['//TRIM(RoundSigDigits(rNumericArgs(7),2))// &
'], value should not be negative.')
ErrorsFound=.true.
ELSE
ZoneSizingInput(ZoneSizIndex)%HeatSizingFactor = rNumericArgs(7)
ENDIF
! N8, \field Zone Cooling Sizing Factor
! \note if blank, global cooling sizing factor from Sizing:Parameters is used.
! \minimum> 0
IF (lNumericFieldBlanks(8) .or. rNumericArgs(8) == 0.0d0) THEN
ZoneSizingInput(ZoneSizIndex)%CoolSizingFactor = GlobalCoolSizingFactor
ELSEIF (rNumericArgs(8) < 0.0d0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//'", invalid data.')
CALL ShowContinueError('... incorrect '//TRIM(cNumericFieldNames(8))//'=['//TRIM(RoundSigDigits(rNumericArgs(8),2))// &
'], value should not be negative.')
ErrorsFound=.true.
ELSE
ZoneSizingInput(ZoneSizIndex)%CoolSizingFactor = rNumericArgs(8)
ENDIF
! N9, \field Cooling Design Air Flow Rate
! \type real
! \units m3/s
! \minimum 0
! \default 0
! \note This input is used if Cooling Design Air Flow Method is Flow/Zone
! \note This value will be multiplied by the global or zone sizing factor and
! \note by zone multipliers.
IF (lNumericFieldBlanks(9)) THEN
ZoneSizingInput(ZoneSizIndex)%DesCoolAirFlow = 0.0d0
ELSEIF (rNumericArgs(9) < 0.0d0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//'", invalid data.')
CALL ShowContinueError('... incorrect '//TRIM(cNumericFieldNames(9))//'=['//TRIM(RoundSigDigits(rNumericArgs(9),2))// &
'], value should not be negative.')
ErrorsFound=.true.
ELSE
ZoneSizingInput(ZoneSizIndex)%DesCoolAirFlow = rNumericArgs(9)
ENDIF
! N10,\field Cooling Minimum Air Flow per Zone Floor Area
! \type real
! \units m3/s-m2
! \minimum 0
! \default .000762
! \note default is .15 cfm/ft2
! \note This input is used if Cooling Design Air Flow Method is design day with limit
IF (lNumericFieldBlanks(10)) THEN
IF (rNumericArgs(10) <= 0.0d0) THEN ! in case someone changes the default in the IDD
ZoneSizingInput(ZoneSizIndex)%DesCoolMinAirFlowPerArea = .000762d0
ELSE
ZoneSizingInput(ZoneSizIndex)%DesCoolMinAirFlowPerArea = rNumericArgs(10)
ENDIF
ELSEIF (rNumericArgs(10) < 0.0d0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//'", invalid data.')
CALL ShowContinueError('... incorrect '//TRIM(cNumericFieldNames(108))//'=['// &
TRIM(RoundSigDigits(rNumericArgs(10),2))// &
'], value should not be negative.')
ErrorsFound=.true.
ELSE
ZoneSizingInput(ZoneSizIndex)%DesCoolMinAirFlowPerArea = rNumericArgs(10)
ENDIF
! N11,\field Cooling Minimum Air Flow
! \type real
! \units m3/s
! \minimum 0
! \default 0
! \note This input is used if Cooling Design Air Flow Method is design day with limit
IF (lNumericFieldBlanks(11)) THEN
ZoneSizingInput(ZoneSizIndex)%DesCoolMinAirFlow = 0.0d0
ELSEIF (rNumericArgs(11) < 0.0d0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//'", invalid data.')
CALL ShowContinueError('... incorrect '//TRIM(cNumericFieldNames(11))//'=['//TRIM(RoundSigDigits(rNumericArgs(11),2))// &
'], value should not be negative.')
ErrorsFound=.true.
ELSE
ZoneSizingInput(ZoneSizIndex)%DesCoolMinAirFlow = rNumericArgs(11)
ENDIF
! N12,\field Cooling Minimum Air Flow Fraction
! \note fraction of the Cooling design Air Flow Rate
! \type real
! \minimum 0
! \default 0
! \note This input is currently used in sizing the Fan minimum Flow Rate.
! \note It does not currently affect other component autosizing.
IF (lNumericFieldBlanks(12)) THEN
ZoneSizingInput(ZoneSizIndex)%DesCoolMinAirFlowFrac = 0.0d0
ELSEIF (rNumericArgs(12) < 0.0d0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//'", invalid data.')
CALL ShowContinueError('... incorrect '//TRIM(cNumericFieldNames(12))//'=['//TRIM(RoundSigDigits(rNumericArgs(12),2))// &
'], value should not be negative.')
ErrorsFound=.true.
ELSE
ZoneSizingInput(ZoneSizIndex)%DesCoolMinAirFlowFrac = rNumericArgs(12)
ENDIF
! N13,\field Heating Design Air Flow Rate
! \type real
! \units m3/s
! \minimum 0
! \default 0
! \note This input is used if Heating Design Air Flow Method is Flow/Zone.
! \note This value will be multiplied by the global or zone sizing factor and
! \note by zone multipliers.
IF (lNumericFieldBlanks(13)) THEN
ZoneSizingInput(ZoneSizIndex)%DesHeatAirFlow = 0.0d0
ELSEIF (rNumericArgs(13) < 0.0d0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//'", invalid data.')
CALL ShowContinueError('... incorrect '//TRIM(cNumericFieldNames(13))//'=['//TRIM(RoundSigDigits(rNumericArgs(13),2))// &
'], value should not be negative.')
ErrorsFound=.true.
ELSE
ZoneSizingInput(ZoneSizIndex)%DesHeatAirFlow = rNumericArgs(13)
ENDIF
! N14,\field Heating Maximum Air Flow per Zone Floor Area
! \type real
! \units m3/s-m2
! \minimum 0
! \default .002032
! \note default is .40 cfm/ft2
! \note This input is not currently used for autosizing any of the components.
IF (lNumericFieldBlanks(14)) THEN
IF (rNumericArgs(14) <= 0.0d0) THEN ! in case someone changes the default in the IDD
ZoneSizingInput(ZoneSizIndex)%DesHeatMaxAirFlowPerArea = 0.002032d0
ELSE
ZoneSizingInput(ZoneSizIndex)%DesHeatMaxAirFlowPerArea = rNumericArgs(14)
ENDIF
ELSEIF (rNumericArgs(14) < 0.0d0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//'", invalid data.')
CALL ShowContinueError('... incorrect '//TRIM(cNumericFieldNames(14))//'=['//TRIM(RoundSigDigits(rNumericArgs(14),2))// &
'], value should not be negative.')
ErrorsFound=.true.
ELSE
ZoneSizingInput(ZoneSizIndex)%DesHeatMaxAirFlowPerArea = rNumericArgs(14)
ENDIF
! N15,\field Heating Maximum Air Flow
! \type real
! \units m3/s
! \minimum 0
! \default .1415762
! \note default is 300 cfm
! \note This input is not currently used for autosizing any of the components.
IF (lNumericFieldBlanks(15)) THEN
IF (rNumericArgs(15) <= 0.0d0) THEN ! in case someone changes the default in the IDD
ZoneSizingInput(ZoneSizIndex)%DesHeatMaxAirFlow = 0.1415762d0
ELSE
ZoneSizingInput(ZoneSizIndex)%DesHeatMaxAirFlow = rNumericArgs(15)
ENDIF
ELSEIF (rNumericArgs(15) < 0.0d0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//'", invalid data.')
CALL ShowContinueError('... incorrect '//TRIM(cNumericFieldNames(15))//'=['//TRIM(RoundSigDigits(rNumericArgs(15),2))// &
'], value should not be negative.')
ErrorsFound=.true.
ELSE
ZoneSizingInput(ZoneSizIndex)%DesHeatMaxAirFlow = rNumericArgs(15)
ENDIF
! N16;\field Heating Maximum Air Flow Fraction
! \note fraction of the Heating Design Air Flow Rate
! \note This input is not currently used for autosizing any of the components.
! \type real
! \minimum 0
! \default 0.3
IF (lNumericFieldBlanks(16)) THEN
IF (rNumericArgs(16) <= 0.0d0) THEN ! in case someone changes the default in the IDD
ZoneSizingInput(ZoneSizIndex)%DesHeatMaxAirFlowFrac = 0.3d0
ELSE
ZoneSizingInput(ZoneSizIndex)%DesHeatMaxAirFlowFrac = rNumericArgs(16)
ENDIF
ELSEIF (rNumericArgs(16) < 0.0d0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//'", invalid data.')
CALL ShowContinueError('... incorrect '//TRIM(cNumericFieldNames(16))//'=['//TRIM(RoundSigDigits(rNumericArgs(16),2))// &
'], value should not be negative.')
ErrorsFound=.true.
ELSE
ZoneSizingInput(ZoneSizIndex)%DesHeatMaxAirFlowFrac = rNumericArgs(16)
ENDIF
! A7, \field Zone Air Distribution Object Name
IF (.NOT. lAlphaFieldBlanks(7)) THEN
ZoneSizingInput(ZoneSizIndex)%ZoneAirDistEffObjName = cAlphaArgs(7)
ObjIndex=FindItemInList(ZoneSizingInput(ZoneSizIndex)%ZoneAirDistEffObjName, &
ZoneAirDistribution%Name,numZoneAirDistribution)
IF (ObjIndex > 0) THEN
ZoneSizingInput(ZoneSizIndex)%ZoneADEffCooling = ZoneAirDistribution(ObjIndex)%ZoneADEffCooling
ZoneSizingInput(ZoneSizIndex)%ZoneADEffHeating = ZoneAirDistribution(ObjIndex)%ZoneADEffHeating
ZoneSizingInput(ZoneSizIndex)%ZoneSecondaryRecirculation = ZoneAirDistribution(ObjIndex)%ZoneSecondaryRecirculation
ZoneSizingInput(ZoneSizIndex)%ZoneAirDistributionIndex = ObjIndex
ELSE
! generate a warning message
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//'", invalid data.')
CALL ShowContinueError('... not found '//TRIM(cAlphaFieldNames(7))//'="'//TRIM(cAlphaArgs(7))//'".')
ErrorsFound=.true.
ENDIF
ELSE
! assume defaults
ZoneSizingInput(ZoneSizIndex)%ZoneADEffCooling = 1.0d0
ZoneSizingInput(ZoneSizIndex)%ZoneADEffHeating = 1.0d0
ZoneSizingInput(ZoneSizIndex)%ZoneSecondaryRecirculation = 0.0d0
ENDIF
SELECT CASE(TRIM(cAlphaArgs(5)))
CASE('DESIGNDAY')
ZoneSizingInput(ZoneSizIndex)%CoolAirDesMethod = FromDDCalc
CASE('FLOW/ZONE')
ZoneSizingInput(ZoneSizIndex)%CoolAirDesMethod = InpDesAirFlow
CASE('DESIGNDAYWITHLIMIT')
ZoneSizingInput(ZoneSizIndex)%CoolAirDesMethod = DesAirFlowWithLim
CASE DEFAULT
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//'", invalid data.')
CALL ShowContinueError('... incorrect '//TRIM(cAlphaFieldNames(5))//'="'//TRIM(cAlphaArgs(5))//'".')
CALL ShowContinueError('... valid values are DesignDay, Flow/Zone or DesignDayWithLimit.')
ErrorsFound=.true.
END SELECT
SELECT CASE(TRIM(cAlphaArgs(6)))
CASE('DESIGNDAY')
ZoneSizingInput(ZoneSizIndex)%HeatAirDesMethod = FromDDCalc
CASE('FLOW/ZONE')
ZoneSizingInput(ZoneSizIndex)%HeatAirDesMethod = InpDesAirFlow
CASE('DESIGNDAYWITHLIMIT')
ZoneSizingInput(ZoneSizIndex)%HeatAirDesMethod = DesAirFlowWithLim
CASE DEFAULT
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//'", invalid data.')
CALL ShowContinueError('... incorrect '//TRIM(cAlphaFieldNames(6))//'="'//TRIM(cAlphaArgs(6))//'".')
CALL ShowContinueError('... valid values are DesignDay, Flow/Zone or DesignDayWithLimit.')
ErrorsFound=.true.
END SELECT
END DO
END DO
ENDIF
IF (ErrorsFound) THEN
CALL ShowFatalError(TRIM(cCurrentModuleObject)//': Errors found in getting input. Program terminates.')
END IF
RETURN
END SUBROUTINE GetZoneSizingInput