ZoneDaylightCalc Derived Type

type, public :: ZoneDaylightCalc

type~~zonedaylightcalc~~InheritsGraph type~zonedaylightcalc ZoneDaylightCalc type~intwinadjzoneextwinstruct IntWinAdjZoneExtWinStruct type~intwinadjzoneextwinstruct->type~zonedaylightcalc IntWinAdjZoneExtWin
Help


Source Code


Components

TypeVisibility AttributesNameInitial
integer, public :: DaylightType =0
integer, public :: AvailSchedNum =0
integer, public :: TotalDaylRefPoints =0
integer, public :: TotalDElightRefPts =0
real(kind=r64), public, ALLOCATABLE, DIMENSION(:,:):: DaylRefPtAbsCoord
logical(kind=1), public, ALLOCATABLE, DIMENSION(:):: DaylRefPtInBounds
real(kind=r64), public, ALLOCATABLE, DIMENSION(:):: FracZoneDaylit
real(kind=r64), public, ALLOCATABLE, DIMENSION(:):: IllumSetPoint
integer, public :: LightControlType =1
real(kind=r64), public :: ViewAzimuthForGlare =0.0d0
integer, public :: MaxGlareallowed =0
real(kind=r64), public :: MinPowerFraction =0.0d0
real(kind=r64), public :: MinLightFraction =0.0d0
integer, public :: LightControlSteps =0
real(kind=r64), public :: LightControlProbability =0.0d0
integer, public :: TotalExtWindows =0
real(kind=r64), public :: AveVisDiffReflect =0.0d0
real(kind=r64), public, ALLOCATABLE, Dimension (:):: RefPtPowerReductionFactor
real(kind=r64), public :: ZonePowerReductionFactor =1.0D0
real(kind=r64), public, ALLOCATABLE, DIMENSION(:):: DaylIllumAtRefPt
real(kind=r64), public, ALLOCATABLE, DIMENSION(:):: GlareIndexAtRefPt
integer, public, ALLOCATABLE, DIMENSION(:):: AdjIntWinZoneNums
integer, public :: NumOfIntWinAdjZones =0
integer, public :: NumOfIntWinAdjZoneExtWins =0
type(IntWinAdjZoneExtWinStruct), public, ALLOCATABLE, DIMENSION(:):: IntWinAdjZoneExtWin
integer, public :: NumOfDayltgExtWins =0
integer, public, ALLOCATABLE, DIMENSION(:):: DayltgExtWinSurfNums
integer, public, ALLOCATABLE, DIMENSION(:):: DayltgFacPtrsForExtWins
real(kind=r64), public :: MinIntWinSolidAng =0.0d0
real(kind=r64), public :: TotInsSurfArea =0.0d0
real(kind=r64), public :: FloorVisRefl =0.0d0
real(kind=r64), public :: InterReflIllFrIntWins =0.0d0
real(kind=r64), public, ALLOCATABLE, DIMENSION(:):: BacLum
real(kind=r64), public, ALLOCATABLE, DIMENSION(:,:):: SolidAngAtRefPt
real(kind=r64), public, ALLOCATABLE, DIMENSION(:,:):: SolidAngAtRefPtWtd
real(kind=r64), public, ALLOCATABLE, DIMENSION(:,:,:):: IllumFromWinAtRefPt
real(kind=r64), public, ALLOCATABLE, DIMENSION(:,:,:):: BackLumFromWinAtRefPt
real(kind=r64), public, ALLOCATABLE, DIMENSION(:,:,:):: SourceLumFromWinAtRefPt
real(kind=r64), public, ALLOCATABLE, DIMENSION(:,:,:,:,:):: DaylIllFacSky
real(kind=r64), public, ALLOCATABLE, DIMENSION(:,:,:,:,:):: DaylSourceFacSky
real(kind=r64), public, ALLOCATABLE, DIMENSION(:,:,:,:,:):: DaylBackFacSky
real(kind=r64), public, ALLOCATABLE, DIMENSION(:,:,:,:):: DaylIllFacSun
real(kind=r64), public, ALLOCATABLE, DIMENSION(:,:,:,:):: DaylIllFacSunDisk
real(kind=r64), public, ALLOCATABLE, DIMENSION(:,:,:,:):: DaylSourceFacSun
real(kind=r64), public, ALLOCATABLE, DIMENSION(:,:,:,:):: DaylSourceFacSunDisk
real(kind=r64), public, ALLOCATABLE, DIMENSION(:,:,:,:):: DaylBackFacSun
real(kind=r64), public, ALLOCATABLE, DIMENSION(:,:,:,:):: DaylBackFacSunDisk
real(kind=r64), public, ALLOCATABLE, DIMENSION(:):: TimeExceedingGlareIndexSPAtRefPt
real(kind=r64), public, ALLOCATABLE, DIMENSION(:):: TimeExceedingDaylightIlluminanceSPAtRefPt
logical, public :: AdjZoneHasDayltgCtrl =.false.
integer, public :: MapCount =0
integer, public, ALLOCATABLE, DIMENSION(:):: ZoneToMap

Source Code

TYPE ZoneDaylightCalc
  INTEGER  :: DaylightType               = 0   ! Type of Daylighting (1=Detailed, 2=DElight)
  INTEGER  :: AvailSchedNum             = 0    ! pointer to availability schedule if present
  INTEGER  :: TotalDaylRefPoints        = 0   ! Number of detailed daylighting reference points in a zone (0,1 or 2)
  INTEGER  :: TotalDElightRefPts        = 0   ! Number of DElight daylighting reference points in a zone (0,1 or 2) - RJH
  REAL(r64), ALLOCATABLE, DIMENSION(:,:) :: DaylRefPtAbsCoord ! =0.0 ! X,Y,Z coordinates of all daylighting reference points
                                                        ! in absolute coordinate system (m)
                                                        ! Points 1 and 2 are the control reference points
  LOGICAL(kind=1), ALLOCATABLE, DIMENSION(:) :: DaylRefPtInBounds  ! True when coordinates are in bounds of zone coordinates
  REAL(r64), ALLOCATABLE, DIMENSION(:) :: FracZoneDaylit ! =0.0  ! Fraction of zone controlled by each reference point
  REAL(r64), ALLOCATABLE, DIMENSION(:) :: IllumSetPoint  ! =0.0  ! Illuminance setpoint at each reference point (lux)
  INTEGER  :: LightControlType          = 1   ! Lighting control type (same for all reference points)
                                              ! (1=continuous, 2=stepped, 3=continuous/off)
  REAL(r64):: ViewAzimuthForGlare       =0.0d0  ! View direction relative to window for glare calculation (deg)
  INTEGER  :: MaxGlareallowed           = 0   ! Maximum allowable discomfort glare index
  REAL(r64):: MinPowerFraction          = 0.0d0 ! Minimum fraction of power input that continuous dimming system can dim down to
  REAL(r64):: MinLightFraction          =0.0d0  ! Minimum fraction of light output that continuous dimming system can dim down to
  INTEGER  :: LightControlSteps         = 0   ! Number of levels (excluding zero) of stepped control system
  REAL(r64):: LightControlProbability   = 0.0d0 ! For manual control of stepped systems, probability that lighting will
  INTEGER  :: TotalExtWindows           = 0   ! Total number of exterior windows in the zone
  REAL(r64):: AveVisDiffReflect         =0.0d0  ! Area-weighted average inside surface visible reflectance of zone
  REAL(r64),ALLOCATABLE, Dimension (:) :: RefPtPowerReductionFactor !=1.0  ! Electric power reduction factor at reference points
                                                                  ! due to daylighting
  REAL(r64):: ZonePowerReductionFactor      =1.0D0  ! Electric power reduction factor for entire zone due to daylighting
  REAL(r64), ALLOCATABLE, DIMENSION(:) :: DaylIllumAtRefPt  !=0.0 ! Daylight illuminance at reference points (lux)
  REAL(r64), ALLOCATABLE, DIMENSION(:) :: GlareIndexAtRefPt !=0.0 ! Glare index at reference points
  INTEGER, ALLOCATABLE, DIMENSION(:) :: AdjIntWinZoneNums ! List of zone numbers of adjacent zones that have exterior windows and
                                     ! share one or more interior windows with target zone
  INTEGER  :: NumOfIntWinAdjZones        = 0   ! Number of adjacent zones that have exterior windows and share one or
                                              ! more interior windows with target zone
  INTEGER  :: NumOfIntWinAdjZoneExtWins  = 0   ! number of exterior windows associated with zone via interior windows
  TYPE(IntWinAdjZoneExtWinStruct), ALLOCATABLE, DIMENSION(:) &  ! nested structure
                                     :: IntWinAdjZoneExtWin ! info about exterior window associated with zone via interior window
  INTEGER  :: NumOfDayltgExtWins         = 0   ! Number of associated exterior windows providing daylight to this zone
  INTEGER, ALLOCATABLE, DIMENSION(:) ::  DayltgExtWinSurfNums  ! List of surface numbers of zone's exterior windows or
                                                ! exterior windows in adjacent zones sharing interior windows with the zone
  INTEGER, ALLOCATABLE, DIMENSION(:) ::  DayltgFacPtrsForExtWins ! Zone's daylighting factor pointers.
                                                                 ! Entries in this list have a one-to-one
                                                                 ! correspondence with the DayltgExtWinSurfNums list
  REAL(r64):: MinIntWinSolidAng             =0.0d0 ! Minimum solid angle subtended by an interior window in a zone
  REAL(r64):: TotInsSurfArea                =0.0d0 ! Total inside surface area of a daylit zone (m2)
  REAL(r64):: FloorVisRefl                  =0.0d0 ! Area-weighted visible reflectance of floor of a daylit zone
  REAL(r64):: InterReflIllFrIntWins         =0.0d0 ! Inter-reflected illuminance due to beam and diffuse solar passing
                                             !  through a zone's interior windows (lux)
  REAL(r64),ALLOCATABLE, DIMENSION(:) :: BacLum          ! =0.0 ! Background luminance at each reference point (cd/m2)
  REAL(r64), ALLOCATABLE, DIMENSION(:,:)     :: SolidAngAtRefPt !(MaxRefPoints,50)
  REAL(r64), ALLOCATABLE, DIMENSION(:,:)     :: SolidAngAtRefPtWtd !(MaxRefPoints,50)
  REAL(r64), ALLOCATABLE, DIMENSION(:,:,:)   :: IllumFromWinAtRefPt !(MaxRefPoints,2,50)
  REAL(r64), ALLOCATABLE, DIMENSION(:,:,:)   :: BackLumFromWinAtRefPt  !(MaxRefPoints,2,50)
  REAL(r64), ALLOCATABLE, DIMENSION(:,:,:)   :: SourceLumFromWinAtRefPt  !(MaxRefPoints,2,50)
  ! Allocatable daylight factor arrays
  ! Arguments for Dayl---Sky are:
  !  1: Daylit window number (1 to NumOfDayltgExtWins)
  !  2: Reference point number (1 to MaxRefPoints)
  !  3: Sky type (1 to 4; 1 = clear, 2 = clear turbid, 3 = intermediate, 4 = overcast
  !  4: Shading index (1 to MaxSlatAngs+1; 1 = bare window; 2 = with shade, or, if blinds
  !      2 = first slat position, 3 = second position, ..., MaxSlatAngs+1 = last position)
  !  5: Sun position index (1 to 24)
  REAL(r64), ALLOCATABLE, DIMENSION(:,:,:,:,:) :: DaylIllFacSky
  REAL(r64), ALLOCATABLE, DIMENSION(:,:,:,:,:) :: DaylSourceFacSky
  REAL(r64), ALLOCATABLE, DIMENSION(:,:,:,:,:) :: DaylBackFacSky

  ! Arguments for Dayl---Sun are:
  !  1: Daylit window number (1 to NumOfDayltgExtWins)
  !  2: Reference point number (1 to MaxRefPoints)
  !  3: Shading index (1 to MaxShadeIndex; 1 = no shade; 2 = with shade, or, if blinds
  !      2 = first slat position, 3 = second position, ..., MaxSlatAngs+1 = last position)
  !  4: Sun position index (1 to 24)
  REAL(r64), ALLOCATABLE, DIMENSION(:,:,:,:) :: DaylIllFacSun
  REAL(r64), ALLOCATABLE, DIMENSION(:,:,:,:) :: DaylIllFacSunDisk
  REAL(r64), ALLOCATABLE, DIMENSION(:,:,:,:) :: DaylSourceFacSun
  REAL(r64), ALLOCATABLE, DIMENSION(:,:,:,:) :: DaylSourceFacSunDisk
  REAL(r64), ALLOCATABLE, DIMENSION(:,:,:,:) :: DaylBackFacSun
  REAL(r64), ALLOCATABLE, DIMENSION(:,:,:,:) :: DaylBackFacSunDisk

  ! Time exceeding maximum allowable discomfort glare index at reference points (hours)
  REAL(r64), ALLOCATABLE, DIMENSION(:) :: TimeExceedingGlareIndexSPAtRefPt

  ! Time exceeding daylight illuminance setpoint at reference points (hours)
  REAL(r64), ALLOCATABLE, DIMENSION(:) :: TimeExceedingDaylightIlluminanceSPAtRefPt

  ! True if at least one adjacent zone, sharing one or more interior windows, has daylighting control
  LOGICAL :: AdjZoneHasDayltgCtrl = .false.
  INTEGER :: MapCount             = 0  ! Number of maps assigned to Zone
  INTEGER, ALLOCATABLE, DIMENSION(:) :: ZoneToMap  ! Pointers to maps allocated to Zone
END TYPE ZoneDaylightCalc

ActuatorUsedType AiflowNetworkReportProp AirChillerSetData AirConnectionStruct AirflowNetworkCompProp AirflowNetworkExchangeProp AirflowNetworkLinkageProp AirflowNetworkLinkReportData AirflowNetworkLinkSimuData AirflowNetworkNodeProp AirflowNetworkNodeReportData AirflowNetworkNodeSimuData AirflowNetworkReportVars AirflowNetworkSimuProp AirIn AirLoopBranchData AirLoopCompData AirLoopControlData AirLoopFlowData AirLoopMixerData AirLoopOutsideAirConnectData AirLoopSplitterData AirLoopStatsType AirLooptoZoneData AirLoopZoneEquipConnectData AirModelData AirNodeData AirPatternInfobyZoneStruct AirReportVars AirTerminalMixerData AngleFactorData BalancedDesDehumPerfData BaseboardParams BaseboardParams BaseCell BaseChillerSpecs BasementZoneInfo BaseReportVars BaseThermalPropertySet BasisElemDescr BasisStruct BatteryDichargeDataStruct BBHeatData BinObjVarIDType BinResultsType BinStatisticsType BLASTAbsorberSpecs BoilerSpecs BoilerSpecs BoundingBoxVertStruct BranchData BranchData BranchListData BSDFBkSurfDescr BSDFDaylghtGeomDescr BSDFDaylghtPosition BSDFGeomDescr BSDFLayerAbsorpStruct BSDFRefPoints BSDFRefPointsGeomDescr BSDFStateDescr BSDFWindowDescript BSDFWindowGeomDescr BSDFWindowInputStruct cached_psat_t cached_twb_t CartesianCell CartesianPipeCellInformation CaseAndWalkInListDef CaseRAFractionData CaseWIZoneReportData CashFlowType CBVAVData CECInverterLookUpTableData CFSFILLGAS CFSGAP CFSLAYER CFSLWP CFSSWP CFSTY CGSHPNodeData ChargeBlockType ChargeSimpleType ChillerheaterSpecs CHReportVars CoefficientProps CoilCreditData CoilType CollectorData ColumnTagType CommonPipeData CompData CompDesWaterFlowData ComponentData ComponentData ComponentListData ComponentNameData ComponentProps ComponentSetPtData CompressorListDef CompSizeTableEntryType ComputationType ConnectAirSysComp ConnectAirSysSubComp ConnectAirSysSubSubComp ConnectedLoopData ConnectionPoint ConnectorData ConnectZoneComp ConnectZoneSubComp ConnectZoneSubSubComp ConstantFlowRadiantSystemData ConstCOPChillerSpecs ConstCOPReportVars ConstGradPattern ConstructionData ConstructionDataFD ContaminantData ControllerListProps ControllerPropsType ControllerStatsType ControlList ControlsType ConvectionCoefficient CoolBeamData CoolTowerParams CostAdjustmentStruct CostLineItemStruct CTGeneratorSpecs CurSimConditionsInfo CVData CVDVParameters CVFlow DamperDesignParams DamperFlowConditions DataPeriodData DataSetPointManager DaylightSavingPeriodData DayScheduleData DayWeatherVariables DCtoACInverterStruct DefineASHRAEAdaptiveOptimumStartCoeffs DefineColdestSetPointManager DefineCondEntSetPointManager DefineDiffTSysAvailManager DefineFollowOATempSetPointManager DefineFollowSysNodeTempSetPointManager DefineGroundTempSetPointManager DefineHiLoSysAvailManager DefineHybridVentSysAvailManager DefineIdealCondEntSetPointManager DefineLinearModelNode DefineMixedAirSetPointManager DefineNightCycSysAvailManager DefineNightVentSysAvailManager DefineOAPretreatSetPointManager DefineOptStartSysAvailManager DefineOutsideAirSetPointManager DefinePriAirSysAvailMgrs DefinePrimaryAirSystem DefineSchedDualSetPointManager DefineSchedOffSysAvailManager DefineSchedOnSysAvailManager DefineSchedSysAvailManager DefineScheduledSetPointManager DefineSurfaceSettings DefineSZCoolingSetPointManager DefineSZHeatingSetPointManager DefineSZMaxHumSetPointManager DefineSZMinHumSetPointManager DefineSZOneStageCoolinggSetPointManager DefineSZOneStageHeatingSetPointManager DefineSZReheatSetPointManager DefineWarmestSetPointManager DefineZoneCompAvailMgrs DefineZoneData DefMultiZoneAverageCoolingSetPointManager DefMultiZoneAverageHeatingSetPointManager DefMultiZoneAverageMaxHumSetPointManager DefMultiZoneAverageMinHumSetPointManager DefMultiZoneMaxHumSetPointManager DefMultiZoneMinHumSetPointManager DefRABFlowSetPointManager DefWarmestSetPtManagerTempFlow DemandManagerData DemandManagerListData DesDayWeathData DesiccantDehumidifierData DesignDayData DesignSpecMSHPData DetailedIceStorageData DirectAirProps DirectionNeighbor_Dictionary DirectionReal_Dictionary DisSysCompCoilProp DisSysCompCPDProp DisSysCompCVFProp DisSysCompDamperProp DisSysCompDetFanProp DisSysCompDuctProp DisSysCompELRProp DisSysCompHXProp DisSysCompLeakProp DisSysCompTermUnitProp DisSysLinkageProp DisSysNodeProp DistributionStructure DomainRectangle dTriangle DuctData DVData DXCoilData DXCoolingConditions DXHeatPumpSystemStruct EarthTubeData EarthTubeZoneReportVars EconVarType ElecBaseboardParams ElecStorageDataStruct ElectricChillerSpecs ElectricEIRChillerSpecs ElectricPowerLoadCenter ElectricRadiantSystemData ElectricReportVars ElectricTransformer EMSActuatorAvailableType EMSProgramCallManagementType EndUseCategoryType Energy EngineDrivenChillerSpecs EngineDrivenReportVars EnvironmentData EqNodeConnectionDef EquipConfiguration EquipList EquipListCompData EquipListPtrData EquipmentData EquipMeterData EquipOpList ErlExpressionType ErlStackType ErlValueType ErlVariableType EvapConditions EvapFluidCoolerInletConds EvapFluidCoolerspecs ExhaustAbsorberSpecs ExtendedFluidProperties ExteriorEquipmentUsage ExteriorLightUsage ExtVentedCavityStruct Face FanCoilData FanEquipConditions FarfieldInfo FaultProperties FCAirSupplyDataStruct FCAuxilHeatDataStruct FCDataStruct FCElecStorageDataStruct FCExhaustHXDataStruct FCInverterDataStruct FCPowerModuleStruct FCReportDataStruct FCStackCoolerDataStruct FCWaterSupplyDataStruct FenestrationSolarAbsorbed FileSectionsDefinition FluidCellInformation FluidCoolerInletConds FluidCoolerspecs FluidPropsGlycolData FluidPropsGlycolErrors FluidPropsGlycolRawData FluidPropsRefrigerantData FluidPropsRefrigErrors FrameDividerProperties FuelTypeProps FullDomainStructureInfo FurnaceEquipConditions GapDeflectionState GapSupportPillar GasAbsorberSpecs GasPropertyDataStruct GasTurbineReportVars GenData GeneratorDynamicsManagerStruct GeneratorFuelSupplyDataStruct GenericComponentZoneIntGainStruct GlheSpecs GlobalInternalGainMiscObject GridRegion GroundwaterWellDataStruct GshpSpecs GshpSpecs GshpSpecs GTChillerSpecs HalfLoopData HcInsideFaceUserCurveStruct HcOutsideFaceUserCurveStruct HeatExchangerStruct HeatExchCond HeatingCoilEquipConditions HeatPumpWaterHeaterData HeatReclaimDXCoilData HeatReclaimRefrigCondenserData HeatReclaimRefrigeratedRackData HighTempRadiantSystemData HumidifierData HVACAirLoopIterationConvergenceStruct HVACNodeConvergLogStruct HVACZoneInletConvergenceStruct HWBaseboardParams HXAssistedCoilParameters HydronicRadiantSystemData ICEngineGeneratorSpecs IceStorageMapping IceStorageSpecs IllumMapData IndirectAbsorberSpecs IndUnitData InfiltrationData InsideFaceAdaptiveConvAlgoStruct InstructionType IntegerVariables IntegerVariableType InternalVarsAvailableType InternalVarsUsedType IntWinAdjZoneExtWinStruct IrrigationDataStruct LightsData LineDefinition LocalPipeData Location LoopPipeData LoopSidePumpInformation LoopSideReportVars m_FlowControlValidator MapCalcData MarkedNodeData MaterialDataFD MaterialProperties MatrixDataStruct MeshExtents MeshPartition MeshPartitions MeshProperties MeterArrayType MeterData MeterType MicroCHPDataStruct MicroCHPParamsNonNormalized MicroCHPReportDataStruct MissingData MissingDataCounts MixerConditions MixerData MixerData MixingData MoistureInfo monetaryUnitType MonthlyColumnsType MonthlyFieldSetInputType MonthlyInputType MonthlyTablesType MoreNodeData MSHeatPumpData MSHeatPumpReportData MTGeneratorSpecs MultizoneCompDetOpeningProp MultizoneCompExhaustFanProp MultizoneCompHorOpeningProp MultizoneCompSimpleOpeningProp MultizoneCPArrayProp MultizoneCPValueProp MultizoneExternalNodeProp MultizoneSurfaceCrackProp MultizoneSurfaceCrackStdCndns MultizoneSurfaceELAProp MultizoneSurfaceProp MultizoneZoneProp NamedMonthlyType NeighborInformation NightVentPerfData NodeConnectionDef NodeData NodeListDef NonrecurringCostType OAControllerData OAControllerProps OAEquipList OAMixerProps OARequirementsData OAUnitData ObjectsDefinition OperationData OperatorType OpSchemePtrData OptStartDataType OSCData OSCMData OutputReportingVariables OutputTableBinnedType OutputVarSensorType OutsideAirSysProps OutsideEnergySourceSpecs OutsideFaceAdpativeConvAlgoStruct PackagedTESCoolingCoilStruct ParametersData ParentListData PeopleData PerfCurveTableDataStruct PerfomanceCurveData PipeCircuitInfo PipeData PipeHeatTransferReport PipeHTData PipeSegmentInfo PlaneEq PlantAvailMgrData PlantCallingOrderInfoStruct PlantConnection PlantConnectionStruct PlantConnectionStruct PlantConvergencePoint PlantIterationConvergenceStruct PlantLocation PlantLocatorStruct PlantLoopData PlantPressureCurveData PlantProfileData PlantSizingData Point Point3DInteger Point3DReal PointF PointType PollutionProps Polyhedron PondGroundHeatExchangerData PondGroundHeatExchangerReport PowIndUnitData PTUnitData PumpSpecs PumpVFDControlData PVArrayStruct PVReportVariables PVTCollectorStruct PVTReportStruct QualifyType RadialCellInformation RadialSizing RadSysTypeData RainfallCollectorDataStruct RangeCheckDef RangeDataCounts RatchetType RealVariables RealVariableType RectangleF RecurringCostsType RecurringErrorData ReformulatedEIRChillerSpecs RefrigCaseCreditData RefrigCaseData RefrigCompressorData RefrigCondenserData RefrigGasCoolerData RefrigRackData RefrigSystemData ReportBranchData ReportCompData ReportEIRVars ReportingInformation ReportLoopData reportNameType ReportVars ReportVars ReportVars ReportVars ReportVars ReportVars ReportVars ReportVars ReportVars ReportVars ReportVars ReportVars ReportVars ReportVars ReportVars ReportVars ReportVars ReportVars ReportVars ReportVars ReportVars ReqReportVariables ReturnAir RoofGeoCharactisticsStruct RootFinderDataType RunPeriodData RuntimeReportVarType ScheduleData ScheduleTypeData ScreenTransData SecondaryLoopData SecretObjects SectionsDefinition ShadingVertexData ShadowingCombinations ShadowRelateType ShelfData SimplePVParamsStruct SimplePVTModelStruct SimpleWatertoAirHPConditions SimulationControl SimulationOrder SiteRainFallDataStruct SlabListData SNLModuleParamsStuct SNLPVCalcStruct SNLPVInputStruct SolReflRecSurfData SolutionTrackerType SpecialDayData SpectralDataProperties SplitterConditions SplitterData SplitterData StackType StandAloneERVData SteamBaseboardParams SteamCoilEquipConditions StorageTankDataStruct StormWindowData StratifiedNodeData subcell SubcomponentData SubcoolerData SubEquipmentData SubSubcomponentData SubSubEquipmentData SubTableType SummarizeLoads SupplyAir SurfaceAssocNestedStruct SurfaceData SurfaceDataFD SurfaceErrorTracking SurfaceGroundHeatExchangerData SurfaceGroundHeatExchangerQTF SurfaceGroundHeatExchngrReport SurfaceListData SurfaceScreenProperties SurfaceSolarIncident SurfaceWindowCalc SurfMapPattern SysAvailManagerList SysDesignParams SysFlowConditions SystemSizingData SystemSizingInputData TableDataStruct TableEntryType TableLookupData TariffType TCGlazingsType TDDPipeData TemperaturePatternStruct TemperValveData TempGridRegionData TempLoopData TempVsHeightPattern TerminalUnitListData TermUnitSizingData ThermalChimneyData ThermalComfortDataType ThermalComfortInASH55Type ThermalComfortSetpointType ThermChimReportVars ThermChimZnReportVars TimeSteps timings TOCEntriesType TokenType TowerInletConds Towerspecs TransferLoadListDef TransRefrigSystemData TrendVariableType TriQuadraticCurveDataStruct TRNSYSPVCalcStruct TRNSYSPVModuleParamsStruct TStatObject TwoVertGradInterpolPattern TypicalExtremeData UFEData UFIData UnitarySystemData UnitConvType UnitHeaterData UnitVentilatorData UseAdjustmentType UsePriceEscalationType UserAirTerminalComponentStruct UserCoilComponentStruct UserPlantComponentStruct UserZoneHVACForcedAirComponentStruct UTSCDataStruct VariableSpeedCoilData VariableTypeForDDOutput vector Vector_2d VentilatedSlabData VentilationData VentilationMechanicalProps VRFCondenserEquipment VRFTerminalUnitEquipment VSTowerData WalkInData WarehouseCoilData WarmupConvergence WaterCoilEquipConditions WaterConnectionsType WaterEquipmentType WaterHeaterDesuperheaterData WaterHeaterSizingData WaterSourceSpecs WaterThermalTankData WatertoAirHPEquipConditions WaterUseTankConnectionStruct WeatherProperties WeekScheduleData WholeBuildingElectricPowerSummary WindACData WindowBlindProperties WindowComplexShade WindowIndex WindowShadingControlData WindowStateIndex WindowThermalModelParams WindTurbineParams WrapperComponentSpecs WrapperReportVars WrapperSpecs ZoneAirBalanceData ZoneAirDistributionData ZoneAirEquip ZoneCatEUseData ZoneComfortControls ZoneComfortControlsFangerData ZoneComfortFangerControlType ZoneCompTypeData ZoneContamGenericDataBLDiff ZoneContamGenericDataConstant ZoneContamGenericDataCutoff ZoneContamGenericDataDecay ZoneContamGenericDataDRS ZoneContamGenericDataDVS ZoneContamGenericDataPDriven ZoneContControls ZoneData ZoneDaylightCalc ZoneDehumidifierData ZoneEqSizingData ZoneEquipData ZoneEvapCoolerUnitStruct ZoneGroupData ZoneHumidityControls ZoneInternalGainsStruct ZoneListData ZoneListData ZonePreDefRepType ZonePurchasedAir ZoneReportVars ZoneReturnPlenumConditions ZoneSatgedControls ZoneSimData ZoneSizingData ZoneSizingInputData ZoneSupplyPlenumConditions ZoneSystemContaminantDemandData ZoneSystemDemandData ZoneSystemMoistureDemand ZoneTempControls ZoneTempControlType ZoneViewFactorInformation