ControllerPropsType Derived Type

type, private :: ControllerPropsType

type~~controllerpropstype~~InheritsGraph type~controllerpropstype ControllerPropsType type~solutiontrackertype SolutionTrackerType type~solutiontrackertype->type~controllerpropstype SolutionTrackers
Help


Source Code


Components

TypeVisibility AttributesNameInitial
character(len=MaxNameLength), public :: ControllerName =' '
character(len=MaxNameLength), public :: ControllerType =' '
integer, public :: ControllerType_Num =ControllerSimple_Type
integer, public :: ControlVar =iNoControlVariable
integer, public :: ActuatorVar =0
integer, public :: Action =iNoAction
logical, public :: InitFirstPass =.TRUE.
integer, public :: NumCalcCalls =0
integer, public :: Mode =iModeNone
logical, public :: DoWarmRestartFlag =.FALSE.
logical, public :: ReuseIntermediateSolutionFlag =.FALSE.
logical, public :: ReusePreviousSolutionFlag =.FALSE.
type(SolutionTrackerType), public, DIMENSION(2):: SolutionTrackers
real(kind=r64), public :: MaxAvailActuated =0.0d0
real(kind=r64), public :: MaxAvailSensed =0.0d0
real(kind=r64), public :: MinAvailActuated =0.0d0
real(kind=r64), public :: MinAvailSensed =0.0d0
real(kind=r64), public :: MaxVolFlowActuated =0.0d0
real(kind=r64), public :: MinVolFlowActuated =0.0d0
real(kind=r64), public :: MaxActuated =0.0d0
real(kind=r64), public :: MinActuated =0.0d0
integer, public :: ActuatedNode =0
real(kind=r64), public :: ActuatedValue =0.0d0
real(kind=r64), public :: NextActuatedValue =0.0d0
integer, public :: ActuatedNodePlantLoopNum =0
integer, public :: ActuatedNodePlantLoopSide =0
integer, public :: ActuatedNodePlantLoopBranchNum =0
integer, public :: SensedNode =0
logical, public :: IsSetPointDefinedFlag =.FALSE.
real(kind=r64), public :: SetPointValue =0.0d0
real(kind=r64), public :: SensedValue =0.0d0
real(kind=r64), public :: DeltaSensed =0.0d0
real(kind=r64), public :: Offset =0.0d0
character(len=MaxNameLength), public :: LimitType =' '
real(kind=r64), public :: Range =0.0d0
real(kind=r64), public :: Limit =0.0d0
integer, public :: TraceFileUnit =0
logical, public :: FirstTraceFlag =.TRUE.
integer, public :: BadActionErrCount =0
integer, public :: BadActionErrIndex =0

Source Code

  TYPE ControllerPropsType
    CHARACTER(LEN=MaxNameLength) :: ControllerName = ' '  ! Name of the Controller
    CHARACTER(LEN=MaxNameLength) :: ControllerType = ' '  ! Type of Controller
    INTEGER      :: ControllerType_Num = ControllerSimple_Type
    INTEGER      :: ControlVar = iNoControlVariable       ! The type of control variable being sensed
    INTEGER      :: ActuatorVar = 0                       ! The variable that the controller will act on ie. flow
    INTEGER      :: Action = iNoAction                    ! Controller Action - Reverse or Normal

    ! Controller must be initialized to set MinActuated and MaxActuated
    LOGICAL      :: InitFirstPass = .TRUE.

    ! --------------------
    ! Internal data used for optimal restart across successive calls to SimAirLoop()
    ! --------------------
    INTEGER      :: NumCalcCalls = 0  ! Number of Calc() calls since last call to Reset()
    INTEGER      :: Mode = iModeNone  ! Operational model of controller at current iteration

    ! Flag indicating whether the current controller simulation was performed from a cold start
    ! or following a speculative warm restart. Set in the ResetController() routine.
    ! Used in the CheckController() routine.
    LOGICAL      :: DoWarmRestartFlag              = .FALSE.
    ! Flag used to decide whether or not it is allowed to reuse the intermediate solution from
    ! solving the previous controller on the air loop (COLD_START mode only) as the initial guess for
    ! the current controller.
    LOGICAL      :: ReuseIntermediateSolutionFlag  = .FALSE.
    ! Flag used to decide whether or not it is possible to reuse the solution from
    ! the last call to SimAirLoop() as a possible candidate.
    LOGICAL      :: ReusePreviousSolutionFlag      = .FALSE.
    ! Array of solution trackers. Saved at last call to SimAirLoop() in ManageControllers(iControllerOpEnd)
    ! The first tracker is used to track the solution when FirstHVACIteration is TRUE.
    ! The second tracker is used to track the solution at FirstHVACIteration is FALSE.
    TYPE(SolutionTrackerType), DIMENSION(2) :: SolutionTrackers

    ! --------------------
    ! Operational limits at min/max avail values for actuated variable and the corresponding sensed values
    ! --------------------
    REAL(r64)    :: MaxAvailActuated = 0.0d0 ! kg/s, The maximum actuated variable currently available.
                                           ! Reset by simulation at each HVAC iteration
    REAL(r64)    :: MaxAvailSensed   = 0.0d0 ! Sensed value at maximum available actuated variable
    REAL(r64)    :: MinAvailActuated = 0.0d0 ! kg/s, The minimum actuated variable currently available.
                                           ! Reset by simulation at each HVAC iteration
    REAL(r64)    :: MinAvailSensed   = 0.0d0 ! Sensed value at maximum available actuated variable

    ! --------------------
    ! User input min/max values for actuated variable
    ! --------------------
    REAL(r64)    :: MaxVolFlowActuated = 0.0d0 ! m3/s, From User input the Max amount for the actuated variable
    REAL(r64)    :: MinVolFlowActuated = 0.0d0 ! m3/s, From User input the Min amount for the actuated variable
    REAL(r64)    :: MaxActuated = 0.0d0  ! kg/s, From User input the Max amount for the actuated variable
    REAL(r64)    :: MinActuated = 0.0d0  ! kg/s, From User input the Min amount for the actuated variable

    ! --------------------
    ! Actuated variable
    ! --------------------
    INTEGER      :: ActuatedNode       = 0   ! The node that is acted upon by the controller
    REAL(r64)    :: ActuatedValue      = 0.0d0 ! Value of actuated variable before change by the controller
    REAL(r64)    :: NextActuatedValue  = 0.0d0 ! The new control actuated value
    INTEGER      :: ActuatedNodePlantLoopNum  = 0 ! the plant loop index for the actuated node DSU3
    INTEGER      :: ActuatedNodePlantLoopSide = 0 ! the plant loop side for the actuated node DSU3
    INTEGER      :: ActuatedNodePlantLoopBranchNum = 0 ! the plant loop branch num for actuated node DSU3

    ! --------------------
    ! Sensed variable
    ! --------------------
    INTEGER      :: SensedNode = 0    ! The sensed node number from the grid
    LOGICAL      :: IsSetPointDefinedFlag = .FALSE. ! If TRUE indicates that the setpoint has been defined and can
                                                    ! be used to compute DeltaSensed
    REAL(r64)    :: SetPointValue = 0.0d0 ! Desired setpoint; set in the SetPoint Manager or computed in Init() routine
    REAL(r64)    :: SensedValue = 0.0d0 ! The sensed control variable of any type
    REAL(r64)    :: DeltaSensed = 0.0d0 ! Difference of sensed to setpoint value for calculating proportional gain
    REAL(r64)    :: Offset = 0.0d0      ! This is the tolerance or droop from the error

    ! --------------------
    ! Other controller inputs, not yet used
    ! --------------------
    CHARACTER(LEN=MaxNameLength) :: LimitType = ' '  ! Limit type as in HIGH or LOW
    REAL(r64)    :: Range = 0.0d0  ! The range or hysteresis of the control limit
    REAL(r64)    :: Limit = 0.0d0  ! The Limit value for a Limit Controller

    ! --------------------
    ! Trace mechanism
    ! --------------------
    INTEGER      :: TraceFileUnit    = 0    ! File unit for individual controller trace file to use if > 0
    LOGICAL      :: FirstTraceFlag = .TRUE. ! To detect first individual write operation to individual controller trace file
    INTEGER      :: BadActionErrCount = 0   ! Counts number of incorrect action errors
    INTEGER      :: BadActionErrIndex = 0   ! index to recurring error structure for bad action error
  END TYPE ControllerPropsType

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