Nodes of different colours represent the following:
Solid arrows point from a parent (sub)module to the submodule which is descended from it. Dashed arrows point from a module being used to the module or program unit using it. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
logical, | intent(inout) | :: | ErrorsFound |
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 GetZoneData(ErrorsFound)
! SUBROUTINE INFORMATION:
! AUTHOR Linda K. Lawrie
! DATE WRITTEN November 1997
! MODIFIED PGE: Added ZONE LIST and ZONE GROUP objects, Nov 2003
! RJH: Added init of DElight member of ZoneDaylight object, Jan 2004
! JG: Added Part of Total Floor Area field March 2006
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine gets the zone data for each zone in the input file.
! METHODOLOGY EMPLOYED:
! The GetObjectItem routines are employed to retrieve the data.
! REFERENCES:
! IDD Definition for Zone object
! USE STATEMENTS:
USE DataDaylighting, ONLY: ZoneDaylight
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
LOGICAL, INTENT(INOUT) :: ErrorsFound ! If errors found in input
! SUBROUTINE PARAMETER DEFINITIONS:
CHARACTER(len=*), PARAMETER :: BlankString=' '
CHARACTER(len=*), PARAMETER :: RoutineName='GetZoneData: '
! INTEGER, PARAMETER :: MaxZonesInList = 100 ! This is to allow DIMENSIONing below
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
! CHARACTER(len=MaxNameLength), DIMENSION(MaxZonesInList + 1) :: Alphas
! REAL(r64), DIMENSION(8) :: Numbers
INTEGER :: NumAlphas, NumNumbers
INTEGER :: IOStatus
INTEGER :: ZoneLoop
INTEGER :: TMP
INTEGER :: Loop
INTEGER :: ListNum
INTEGER :: ZoneNum
CHARACTER(len=MaxNameLength) :: ZoneName
INTEGER :: GroupNum
LOGICAL :: ErrorInName
LOGICAL :: IsBlank
cCurrentModuleObject='Zone'
NumOfZones=GetNumObjectsFound(cCurrentModuleObject)
ALLOCATE(Zone(NumOfZones))
ALLOCATE(ZoneDaylight(NumOfZones))
ZoneLoop=0
DO Loop=1,NumOfZones
rNumericArgs=0.0d0 ! Zero out just in case
CALL GetObjectItem(cCurrentModuleObject,Loop,cAlphaArgs,NumAlphas,rNumericArgs,NumNumbers,IOStatus, &
AlphaBlank=lAlphaFieldBlanks,NumBlank=lNumericFieldBlanks, &
AlphaFieldnames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
TMP=INDEX(cAlphaArgs(1),CHAR(1))
DO WHILE (TMP /= 0)
cAlphaArgs(1)(TMP:TMP)=','
TMP=INDEX(cAlphaArgs(1),CHAR(1))
END DO
TMP=INDEX(cAlphaArgs(1),CHAR(2))
DO WHILE (TMP /= 0)
cAlphaArgs(1)(TMP:TMP)='!'
TMP=INDEX(cAlphaArgs(1),CHAR(2))
END DO
! Make sure Zone Name is unique
ErrorInName=.false.
IsBlank=.false.
CALL VerifyName(cAlphaArgs(1),Zone%Name,ZoneLoop,ErrorInName,IsBlank,TRIM(cCurrentModuleObject)//' Name')
IF (ErrorInName) THEN
ErrorsFound=.true.
CYCLE
ENDIF
ZoneLoop=ZoneLoop+1
Zone(ZoneLoop)%Name=cAlphaArgs(1)
IF (NumNumbers >=1) &
Zone(ZoneLoop)%RelNorth=rNumericArgs(1)
IF (NumNumbers >=2) &
Zone(ZoneLoop)%OriginX=rNumericArgs(2)
IF (NumNumbers >=3) &
Zone(ZoneLoop)%OriginY=rNumericArgs(3)
IF (NumNumbers >=4) &
Zone(ZoneLoop)%OriginZ=rNumericArgs(4)
IF (NumNumbers >=5) &
Zone(ZoneLoop)%OfType=rNumericArgs(5)
Zone(ZoneLoop)%OfType=StandardZone
IF (NumNumbers >=6) &
Zone(ZoneLoop)%Multiplier=rNumericArgs(6)
IF (NumNumbers >=7) &
Zone(ZoneLoop)%CeilingHeight=rNumericArgs(7)
IF (NumNumbers >=8) &
Zone(ZoneLoop)%Volume=rNumericArgs(8)
IF (NumNumbers >=9) &
Zone(ZoneLoop)%UserEnteredFloorArea=rNumericArgs(9)
IF (NumAlphas > 1 .and. .not. lAlphaFieldBlanks(2)) THEN
SELECT CASE (cAlphaArgs(2))
CASE ('SIMPLE')
Zone(ZoneLoop)%InsideConvectionAlgo=ASHRAESimple
CASE ('TARP', 'DETAILED')
IF (cAlphaArgs(2) == 'DETAILED') THEN
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//trim(Zone(ZoneLoop)%Name)//'".')
CALL ShowContinueError('Deprecated value in '//TRIM(cAlphaFieldNames(2))//'="'// &
TRIM(cAlphaArgs(2))//'", defaulting to TARP.')
ENDIF
Zone(ZoneLoop)%InsideConvectionAlgo=ASHRAETARP
CASE ('CEILINGDIFFUSER')
Zone(ZoneLoop)%InsideConvectionAlgo=CeilingDiffuser
CASE ('TROMBEWALL')
Zone(ZoneLoop)%InsideConvectionAlgo=TrombeWall
CASE ('ADAPTIVECONVECTIONALGORITHM ')
Zone(ZoneLoop)%InsideConvectionAlgo=AdaptiveConvectionAlgorithm
CASE DEFAULT
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//trim(Zone(ZoneLoop)%Name)//'".')
CALL ShowContinueError('Invalid value for '//TRIM(cAlphaFieldNames(2))//'="'// &
TRIM(cAlphaArgs(2))//'".')
ErrorsFound=.true.
! Zone(ZoneLoop)%InsideConvectionAlgo=ASHRAETARP
END SELECT
ELSE
! No zone specific algorithm specified, use default Inside Convection Algorithm
Zone(ZoneLoop)%InsideConvectionAlgo=DefaultInsideConvectionAlgo
ENDIF
IF (NumAlphas > 2 .and. .not. lAlphaFieldBlanks(3)) THEN
SELECT CASE (cAlphaArgs(3))
CASE ('SIMPLECOMBINED', 'SIMPLE')
IF (cAlphaArgs(3) == 'SIMPLE') THEN
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//trim(Zone(ZoneLoop)%Name)//'".')
CALL ShowContinueError('Deprecated value in '//TRIM(cAlphaFieldNames(3))//'="'// &
TRIM(cAlphaArgs(3))//'", defaulting to SimpleCombined.')
ENDIF
Zone(ZoneLoop)%OutsideConvectionAlgo=ASHRAESimple
CASE ('TARP', 'DETAILED', 'BLAST')
IF (cAlphaArgs(3) == 'DETAILED') THEN
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//trim(Zone(ZoneLoop)%Name)//'".')
CALL ShowContinueError('Deprecated value in '//TRIM(cAlphaFieldNames(3))//'="'// &
TRIM(cAlphaArgs(3))//'", defaulting to TARP.')
ENDIF
IF (cAlphaArgs(3) == 'BLAST') THEN
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//trim(Zone(ZoneLoop)%Name)//'".')
CALL ShowContinueError('Deprecated value in '//TRIM(cAlphaFieldNames(3))//'="'// &
TRIM(cAlphaArgs(3))//'", defaulting to TARP.')
ENDIF
Zone(ZoneLoop)%OutsideConvectionAlgo=ASHRAETARP
CASE ('MOWITT')
Zone(ZoneLoop)%OutsideConvectionAlgo=MoWittHcOutside
CASE ('DOE2','DOE-2')
Zone(ZoneLoop)%OutsideConvectionAlgo=DOE2HcOutside
CASE ('ADAPTIVECONVECTIONALGORITHM')
Zone(ZoneLoop)%OutsideConvectionAlgo=AdaptiveConvectionAlgorithm
CASE DEFAULT
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//trim(Zone(ZoneLoop)%Name)//'".')
CALL ShowContinueError('Invalid value for '//TRIM(cAlphaFieldNames(3))//'="'// &
TRIM(cAlphaArgs(3))//'".')
ErrorsFound=.true.
!Zone(ZoneLoop)%OutsideConvectionAlgo=AdaptiveConvectionAlgorithm
END SELECT
ELSE
! No zone specific algorithm specified, use default Outside Convection Algorithm
Zone(ZoneLoop)%OutsideConvectionAlgo=DefaultOutsideConvectionAlgo
ENDIF
! Process the input field: Part of Total Floor Area
! The default value is YES and so only NO needs to be handled
IF (NumAlphas > 3) THEN
IF (SameString('No',cAlphaArgs(4))) THEN
Zone(ZoneLoop)%isPartOfTotalArea = .FALSE.
ELSEIF (SameString('Yes',cAlphaArgs(4)) .or. lAlphaFieldBlanks(4)) THEN
Zone(ZoneLoop)%isPartOfTotalArea = .TRUE.
ELSE
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//trim(Zone(ZoneLoop)%Name)//'".')
CALL ShowContinueError('Invalid value for '//TRIM(cAlphaFieldNames(4))//'="'// &
TRIM(cAlphaArgs(4))//'".')
ErrorsFound=.true.
END IF
END IF
! Zone outdoor environmental variables, used for zone infiltration/ventilation
CALL SetupOutputVariable('Zone Outdoor Air Drybulb Temperature [C]',Zone(ZoneLoop)%OutDryBulbTemp, &
'Zone','Average',Zone(ZoneLoop)%Name)
CALL SetupOutputVariable('Zone Outdoor Air Wetbulb Temperature [C]',Zone(ZoneLoop)%OutWetBulbTemp, &
'Zone','Average',Zone(ZoneLoop)%Name)
CALL SetupOutputVariable('Zone Outdoor Air Wind Speed [m/s]',Zone(ZoneLoop)%WindSpeed, &
'Zone','Average',Zone(ZoneLoop)%Name)
END DO ! Loop
DO Loop=1,NumOfZones
! Check to see if "nominally" controlled -- Zone Name appears in Zone Equip Configuration
! relies on zone name being the "name" of the Zone Controlled Equip Configuration
IF (GetObjectItemNum('ZoneHVAC:EquipmentConnections',Zone(Loop)%Name) > 0) THEN
Zone(Loop)%IsNominalControlled=.true.
ELSE
Zone(Loop)%IsNominalControlled=.false.
ENDIF
ENDDO
! Get ZONE LIST objects
cCurrentModuleObject='ZoneList'
NumOfZoneLists = GetNumObjectsFound(cCurrentModuleObject)
IF (NumOfZoneLists > 0) THEN
ALLOCATE(ZoneList(NumOfZoneLists))
DO ListNum = 1, NumOfZoneLists
CALL GetObjectItem(cCurrentModuleObject,ListNum,cAlphaArgs,NumAlphas,rNumericArgs,NumNumbers,IOStatus, &
AlphaBlank=lAlphaFieldBlanks,NumBlank=lNumericFieldBlanks, &
AlphaFieldnames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
! List name
ErrorInName = .FALSE.
IsBlank = .FALSE.
CALL VerifyName(cAlphaArgs(1),ZoneList%Name,ListNum-1,ErrorInName,IsBlank,TRIM(cCurrentModuleObject)//' Name')
IF (ErrorInName) THEN
ErrorsFound = .TRUE.
END IF
ZoneList(ListNum)%Name = cAlphaArgs(1)
IF (FindItemInList(ZoneList(ListNum)%Name,Zone%Name,NumOfZones) > 0) THEN
CALL ShowWarningError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))// &
'": is a duplicate of a zone name.')
CALL ShowContinueError('This could be a problem in places where either a Zone Name or a Zone List can be used.')
ENDIF
! List of zones
ZoneList(ListNum)%NumOfZones = NumAlphas - 1
IF (ZoneList(ListNum)%NumOfZones < 1) THEN
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//'": No zones specified.')
ErrorsFound = .TRUE.
ELSE
ALLOCATE(ZoneList(ListNum)%Zone(ZoneList(ListNum)%NumOfZones))
ZoneList(ListNum)%Zone = 0
DO ZoneNum = 1, ZoneList(ListNum)%NumOfZones
ZoneName = cAlphaArgs(ZoneNum + 1)
ZoneList(ListNum)%MaxZoneNameLength=MAX(ZoneList(ListNum)%MaxZoneNameLength,len_trim(ZoneName))
ZoneList(ListNum)%Zone(ZoneNum) = FindItemInList(ZoneName,Zone%Name,NumOfZones)
IF (ZoneList(ListNum)%Zone(ZoneNum) == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//'": '// &
TRIM(cAlphaFieldNames(ZoneNum+1))//' '//TRIM(ZoneName)//' not found.')
ErrorsFound = .TRUE.
END IF
! Check for duplicate zones
DO Loop = 1, ZoneNum - 1
IF (ZoneList(ListNum)%Zone(ZoneNum) == ZoneList(ListNum)%Zone(Loop)) THEN
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//'": '// &
TRIM(cAlphaFieldNames(ZoneNum+1))// &
' '//TRIM(ZoneName)//' appears more than once in list.')
ErrorsFound = .TRUE.
END IF
END DO ! Loop
END DO ! ZoneNum
END IF
END DO ! ListNum
END IF
! Get ZONE GROUP objects
cCurrentModuleObject='ZoneGroup'
NumOfZoneGroups = GetNumObjectsFound(cCurrentModuleObject)
IF (NumOfZoneGroups > 0) THEN
ALLOCATE(ZoneGroup(NumOfZoneGroups))
DO GroupNum = 1, NumOfZoneGroups
CALL GetObjectItem(cCurrentModuleObject,GroupNum,cAlphaArgs,NumAlphas,rNumericArgs,NumNumbers,IOStatus, &
AlphaBlank=lAlphaFieldBlanks,NumBlank=lNumericFieldBlanks, &
AlphaFieldnames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
! Group name
ErrorInName = .FALSE.
IsBlank = .FALSE.
CALL VerifyName(cAlphaArgs(1),ZoneGroup%Name,GroupNum-1,ErrorInName,IsBlank,TRIM(cCurrentModuleObject)//' Name')
IF (ErrorInName) THEN
ErrorsFound = .TRUE.
END IF
ZoneGroup(GroupNum)%Name = cAlphaArgs(1)
! Multiplier - checked already by IDD rules
ZoneGroup(GroupNum)%Multiplier = rNumericArgs(1)
! Zone list
ListNum = FindItemInList(cAlphaArgs(2),ZoneList%Name,NumOfZoneLists)
ZoneGroup(GroupNum)%ZoneList = ListNum
IF (ListNum == 0) THEN
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//'": '// &
TRIM(cAlphaFieldNames(2))//' named '//TRIM(cAlphaArgs(2))//' not found.')
ErrorsFound = .TRUE.
ELSE
! Check to make sure list is not in use by another ZONE GROUP
DO Loop = 1, GroupNum - 1
IF (ZoneGroup(GroupNum)%ZoneList == ZoneGroup(Loop)%ZoneList) THEN
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//'": '// &
TRIM(cAlphaFieldNames(2))//' already used by '//TRIM(cCurrentModuleObject)//' named '// &
TRIM(ZoneGroup(Loop)%Name)//'.')
ErrorsFound = .TRUE.
END IF
END DO ! Loop
! Set group multiplier for each zone in the list
DO Loop = 1, ZoneList(ListNum)%NumOfZones
ZoneNum = ZoneList(ListNum)%Zone(Loop)
IF (ZoneNum > 0 ) THEN
! Check to make sure group multiplier was not already set by another ZONE GROUP
IF (Zone(ZoneNum)%ListGroup == 0) THEN
Zone(ZoneNum)%ListMultiplier = ZoneGroup(GroupNum)%Multiplier
Zone(ZoneNum)%ListGroup = ListNum
ELSE
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//'": Zone '// &
TRIM(Zone(ZoneNum)%Name)// &
' in ZoneList already exists in ZoneList of another ZoneGroup.')
CALL ShowContinueError('Previous ZoneList='//TRIM(ZoneList(Zone(ZoneNum)%ListGroup)%Name))
ErrorsFound = .TRUE.
END IF
END IF
END DO ! Loop
END IF
END DO ! GroupNum
END IF
!allocate the array the holds the predefined report data
ALLOCATE(ZonePreDefRep(NumOfZones))
RETURN
END SUBROUTINE GetZoneData