diff --git a/hsnrm/hsnrm-bin/Export.hs b/hsnrm/hsnrm-bin/Export.hs index 674f0223aae6a602fd483898f864bfd7d1b574fd..b6d1f7d05bb746e9e48df898bee0b409723ca212 100644 --- a/hsnrm/hsnrm-bin/Export.hs +++ b/hsnrm/hsnrm-bin/Export.hs @@ -48,7 +48,7 @@ foreign export ccall verbosityExport :: Ex foreign export ccall logfileExport :: Ex -foreign export ccall activeSensorFrequencyExport :: Ex +foreign export ccall passiveSensorFrequencyExport :: Ex foreign export ccall upstreamRpcAddressExport :: Ex @@ -88,7 +88,7 @@ verbosityExport = exportIO E.verbosity logfileExport = exportIO E.logfile -activeSensorFrequencyExport = exportIO E.activeSensorFrequency +passiveSensorFrequencyExport = exportIO E.passiveSensorFrequency upstreamRpcAddressExport = exportIO E.upstreamRpcAddress diff --git a/hsnrm/hsnrm/src/CPD/Integrated.hs b/hsnrm/hsnrm/src/CPD/Integrated.hs index 6183ffc8a6e8bc582e8b1646a71e48603480da1f..927a936956776a754609edcf6263388da79b6a30 100644 --- a/hsnrm/hsnrm/src/CPD/Integrated.hs +++ b/hsnrm/hsnrm/src/CPD/Integrated.hs @@ -9,12 +9,12 @@ -- Maintainer : fre@freux.fr module CPD.Integrated ( Integrator (..), + IntegratorMeta (..), IntegratorAction (..), MeasurementState (..), M (..), trapezoidArea, initIntegrator, - throughTuple, measureValue, squeeze, averageArea, @@ -25,6 +25,7 @@ import CPD.Core import Control.Lens import qualified Data.Aeson as A import Data.Data +import Data.Functor (($>)) import Data.Generics.Labels () import Data.JSON.Schema import qualified Data.Map as M @@ -36,9 +37,16 @@ import Protolude data Integrator = Integrator - { tLast :: Time, - minimumControlInterval :: Time, - measured :: Map SensorID (MeasurementState M) + { meta :: IntegratorMeta, + measured :: Map SensorID (MeasurementState M) -- measurement states + } + deriving (Generic) + +data IntegratorMeta + = IntegratorMeta + { tLast :: Time, -- time the last control loop was finished (init time) + minimumWaitInterval :: Time, -- wait period between measurement periods + minimumControlInterval :: Time -- delta min for measurement period } deriving (Generic) @@ -84,13 +92,20 @@ trapezoidArea (t1, v1) (t2, v2) = where deltaT = fromuS (t2 - t1) -measureValue :: Time -> (Time, Double) -> MeasurementState M -> MeasurementState M -measureValue delta (newTime, newValue) = \case - Never -> Discarded +measureValue :: + IntegratorMeta -> + (Time, Double) -> + MeasurementState M -> + MeasurementState M +measureValue meta (newTime, newValue) = \case + Never -> + if minimumWaitInterval meta + tLast meta <= newTime + then Discarded + else Never Discarded -> Running initial Done m -> Done $ measure m Running m -> - ( if newTime >= delta + firstTime m + ( if newTime >= minimumControlInterval meta + firstTime m then Done else Running ) @@ -114,26 +129,23 @@ averageArea M {firstTime, lastTime, lastValue, area} = where deltaT = fromuS (lastTime - firstTime) +-- | Tries to 'squeeze' the sensors for values. A squeeze is only successfull +-- if all sensors are in the Done state. squeeze :: Time -> Map SensorID (MeasurementState M) -> Maybe (Map SensorID Double, Map SensorID (MeasurementState M)) squeeze _t mstM = - case traverse throughTuple (M.toList mstM) of - Done (M.fromList -> m) -> Just (m <&> averageArea, m <&> const Never) + case traverse sequenceA (M.toList mstM) of + Done (M.fromList -> m) -> Just (m <&> averageArea, m $> Never) _ -> Nothing -throughTuple :: Functor f => (a, f b) -> f (a, b) -throughTuple (id, m) = (id,) <$> m - initIntegrator :: - Time -> - Time -> + IntegratorMeta -> [SensorID] -> Integrator -initIntegrator t tmin sensorIDs = +initIntegrator meta sensorIDs = Integrator - { tLast = t, - minimumControlInterval = tmin, + { meta = meta, measured = M.fromList (sensorIDs <&> (,Never)) } diff --git a/hsnrm/hsnrm/src/NRM/Behavior.hs b/hsnrm/hsnrm/src/NRM/Behavior.hs index c2b0395f4023788db2421280f11a6806376c5812..d6067c05e9038380ee6ef720fea016517b1b6111 100644 --- a/hsnrm/hsnrm/src/NRM/Behavior.hs +++ b/hsnrm/hsnrm/src/NRM/Behavior.hs @@ -212,7 +212,7 @@ nrm _callTime (ChildDied pid exitcode) = do put $ st & #slices - . at sliceID + . at sliceID ?~ (slice & #cmds . at cmdID ?~ cmd {processState = newPstate}) nrm callTime (DownstreamEvent clientid msg) = nrmDownstreamEvent callTime clientid msg @@ -253,7 +253,7 @@ doControl input = do zoom (#controller . _Just) $ do logInfo ("Control input:" <> show input) mccfg & \case - FixedCommand _ -> pass + NoControl -> pass ccfg@ControlCfg {} -> let cpd = NRMCPD.toCPD ccfg st mRefActions = @@ -262,10 +262,11 @@ doControl input = do ( M.toList (lenses st) :: [(ActuatorKey, ScopedLens NRMState A.Actuator)] ) - <&> \(k, ScopedLens l) -> CPD.Action - { actuatorID = toS k, - actuatorValue = CPD.DiscreteDouble $ st ^. l . #referenceAction - } + <&> \(k, ScopedLens l) -> + CPD.Action + { actuatorID = toS k, + actuatorValue = CPD.DiscreteDouble $ st ^. l . #referenceAction + } else Nothing in banditCartesianProductControl ccfg cpd input mRefActions >>= \case DoNothing -> pass @@ -388,8 +389,9 @@ nrmDownstreamEvent callTime clientid = \case Just c -> do put $ Just - ( c & #downstreamCmds - . at downstreamCmdID + ( c + & #downstreamCmds + . at downstreamCmdID .~ Nothing ) log "downstream cmd un-registered." @@ -407,8 +409,9 @@ nrmDownstreamEvent callTime clientid = \case Just c -> do put $ Just - ( c & #downstreamThreads - . at downstreamThreadID + ( c + & #downstreamThreads + . at downstreamThreadID .~ Nothing ) log "downstream thread un-registered." diff --git a/hsnrm/hsnrm/src/NRM/CPD.hs b/hsnrm/hsnrm/src/NRM/CPD.hs index 920b201cf07abcca764b6e57d9bd78fff5e557d4..0ddd7da76dcee5c930e620c328a21275851d4bb4 100644 --- a/hsnrm/hsnrm/src/NRM/CPD.hs +++ b/hsnrm/hsnrm/src/NRM/CPD.hs @@ -33,12 +33,15 @@ toCPD cfg st = Problem {..} where sensors = cpdSensors st actuators = cpdActuators st - (objectives, constraints) = fromMaybe ([], []) (throughputConstrained <$> mcfg cfg <*> Just st) + (objectives, constraints) = + fromMaybe + ([], []) + (throughputConstrained <$> mcfg cfg <*> Just st) mcfg jc@ControlCfg {} = Just jc mcfg _ = Nothing --- | This problem generator produces a global energy minimization problem under a --- throughput constraint. +-- | This problem generator produces a global energy minimization problem under +-- a throughput constraint. throughputConstrained :: -- | Control configuration ControlCfg -> @@ -54,7 +57,10 @@ throughputConstrained cfg st = let powerTerm = coerce (foldMap (OExprSum . sID) ids) \+ scalar (fromWatts $ staticPower cfg) - in [(Bandit.Types.one, maybe powerTerm (powerTerm \/) normalizedSumSlowdown)], + in [ ( Bandit.Types.one, + maybe powerTerm (powerTerm \/) normalizedSumSlowdown + ) + ], normalizedSumSlowdown & \case Nothing -> [] Just expr -> [(speedThreshold cfg, expr)] @@ -63,13 +69,21 @@ throughputConstrained cfg st = normalizedSumSlowdown :: Maybe OExpr normalizedSumSlowdown = nonEmpty (M.toList constrained) <&> \(fmap fst -> ids) -> - thresholded 0.5 1.5 (coerce (foldMap (OExprSum . sID) ids) \/ (coerce (foldMap (OExprSum . sRef) ids) \+ scalar 1)) + thresholded + 0.5 + 1.5 + ( coerce (foldMap (OExprSum . sRef) ids) + \/ (coerce (foldMap (OExprSum . sID) ids) \+ scalar 1) + ) idsToMinimize :: Maybe (NonEmpty SensorID) idsToMinimize = nonEmpty (fst <$> M.toList toMinimize) toMinimize :: Map SensorID SensorMeta toMinimize = M.filterWithKey (\_ m -> Power `elem` S.tags m) allSensorMeta constrained :: Map SensorID SensorMeta - constrained = M.filterWithKey (\_ m -> DownstreamCmdSignal `elem` S.tags m) allSensorMeta + constrained = + M.filterWithKey + (\_ m -> DownstreamCmdSignal `elem` S.tags m) + allSensorMeta allSensorMeta :: Map SensorID S.SensorMeta allSensorMeta = M.fromList @@ -81,7 +95,9 @@ throughputConstrained cfg st = -- | produces a sum objective normalized by #sensors addAll :: NonEmpty SensorID -> OExpr -addAll ss = coerce (foldMap (OExprSum . sID) ss) \/ (scalar . fromIntegral $ length ss) +addAll ss = + coerce (foldMap (OExprSum . sID) ss) + \/ (scalar . fromIntegral $ length ss) -- | Subtract two objectives, defaulting to either of them -- if one is absent. diff --git a/hsnrm/hsnrm/src/NRM/Control.hs b/hsnrm/hsnrm/src/NRM/Control.hs index 7de0b8612e4ed89a0fcd9be4bb8e62fc13516552..2c7de7c6581f7af21ee26b086b50815e877d844a 100644 --- a/hsnrm/hsnrm/src/NRM/Control.hs +++ b/hsnrm/hsnrm/src/NRM/Control.hs @@ -52,8 +52,8 @@ banditCartesianProductControl :: ControlM Decision banditCartesianProductControl ccfg cpd (Reconfigure t) _ = do pub (UPub.PubCPD t cpd) - minTime <- use $ #integrator . #minimumControlInterval - #integrator .= initIntegrator t minTime (M.keys $ sensors cpd) + meta <- use $ #integrator . #meta + #integrator .= initIntegrator meta (M.keys $ sensors cpd) case (CPD.Core.objectives cpd, M.toList (actuators cpd)) of ([], _) -> reset (_, l) -> @@ -129,13 +129,12 @@ banditCartesianProductControl ccfg cpd (NoEvent t) mRefActions = banditCartesianProductControl ccfg cpd (Event t ms) mRefActions = do forM_ ms $ \m@(Measurement sensorID sensorValue sensorTime) -> do log $ "Processing measurement " <> show m - #integrator %= \(Integrator tlast delta measuredM) -> - Integrator - tlast - delta - ( measuredM - & ix sensorID - %~ measureValue delta (sensorTime, sensorValue) + #integrator + %= execState + ( do + meta <- use #meta + #measured . ix sensorID + %= measureValue meta (sensorTime, sensorValue) ) tryControlStep ccfg cpd t mRefActions @@ -196,6 +195,7 @@ wrappedCStep cc stepObjectives stepConstraints sensorRanges t mRefActions = do Just (measurements, newMeasured) -> do -- squeeze was successfull: setting the new integrator state logInfo "control: integrator squeeze success" + #integrator . #meta . #tLast .= t #integrator . #measured .= newMeasured -- acquiring fields counter <- use #referenceMeasurementCounter diff --git a/hsnrm/hsnrm/src/NRM/Export.hs b/hsnrm/hsnrm/src/NRM/Export.hs index 59daddaa8edba81fba888182882edc34c36ba7bb..0cde4647eaa7ee0c41e250a574b93e8219c8c958 100644 --- a/hsnrm/hsnrm/src/NRM/Export.hs +++ b/hsnrm/hsnrm/src/NRM/Export.hs @@ -11,7 +11,7 @@ module NRM.Export verbosity, showConfiguration, C.logfile, - activeSensorFrequency, + passiveSensorFrequency, upstreamPubAddress, upstreamRpcAddress, downstreamEventAddress, @@ -46,8 +46,8 @@ import qualified NRM.Types.Configuration as C DaemonVerbosity (..), DownstreamCfg (..), UpstreamCfg (..), - activeSensorFrequency, logfile, + passiveSensorFrequency, verbose, ) import qualified NRM.Types.Messaging.UpstreamRep as URep @@ -64,8 +64,8 @@ parseDaemon :: [Text] -> IO C.Cfg parseDaemon = O.parseArgDaemonCli -- | Parses Daemon CLI arguments -activeSensorFrequency :: C.Cfg -> Double -activeSensorFrequency = fromHz . C.activeSensorFrequency +passiveSensorFrequency :: C.Cfg -> Double +passiveSensorFrequency = fromHz . C.passiveSensorFrequency -- | Queries configuration for 'verbose' verbosity verbosity :: C.Cfg -> Int diff --git a/hsnrm/hsnrm/src/NRM/ExportIO.hs b/hsnrm/hsnrm/src/NRM/ExportIO.hs index a8281544c1088881cd572de10f9bfa8c7c10c700..a9d85257fbe8787af27cda0e3f58af38e5bd0c3a 100644 --- a/hsnrm/hsnrm/src/NRM/ExportIO.hs +++ b/hsnrm/hsnrm/src/NRM/ExportIO.hs @@ -11,7 +11,7 @@ module NRM.ExportIO verbosity, showConfiguration, logfile, - activeSensorFrequency, + passiveSensorFrequency, upstreamPubAddress, upstreamRpcAddress, downstreamEventAddress, @@ -45,8 +45,8 @@ verbosity = return . E.verbosity logfile :: C.Cfg -> IO Text logfile = return . E.logfile -activeSensorFrequency :: C.Cfg -> IO Double -activeSensorFrequency = return . E.activeSensorFrequency +passiveSensorFrequency :: C.Cfg -> IO Double +passiveSensorFrequency = return . E.passiveSensorFrequency upstreamPubAddress :: C.Cfg -> IO Text upstreamPubAddress = return . E.upstreamPubAddress diff --git a/hsnrm/hsnrm/src/NRM/State.hs b/hsnrm/hsnrm/src/NRM/State.hs index ac8ed2cce549002d98d7c73fa111ba9e04e3baf8..f46d096173b08899a0e3153b59bf9bde295c26d2 100644 --- a/hsnrm/hsnrm/src/NRM/State.hs +++ b/hsnrm/hsnrm/src/NRM/State.hs @@ -19,6 +19,7 @@ module NRM.State ) where +import CPD.Integrated as I import Control.Lens import Data.Map as M import Data.Map.Merge.Lazy @@ -66,7 +67,7 @@ initialState c time = do updater _pkgid package (packageRaplConfig, packageRaplDir) = package { rapl = Just Rapl - { frequency = hz 3, + { frequency = passiveSensorFrequency c, raplCfg = packageRaplConfig, maxEnergyCounterValue = packageRaplDir ^. #maxEnergy, max = watts 150, @@ -86,8 +87,16 @@ initialState c time = do return newPkgs return NRMState { controller = controlCfg c & \case - FixedCommand _ -> Nothing - ccfg -> Just $ initialController time (minimumControlInterval ccfg) [], + NoControl -> Nothing + ccfg -> + Just $ + initialController + IntegratorMeta + { tLast = time, + I.minimumWaitInterval = Cfg.minimumWaitInterval ccfg, + I.minimumControlInterval = Cfg.minimumControlInterval ccfg + } + [], slices = M.fromList [], pus = M.fromList $ (,PU) <$> selectPUIDs hwl, cores = M.fromList $ (,Core) <$> selectCoreIDs hwl, @@ -108,7 +117,7 @@ initialState c time = do <&> NRMState.ExtraActuator, extraStaticPassiveSensors = Cfg.extraStaticPassiveSensors c - <&> concretizeExtraPassiveSensor (activeSensorFrequency c), + <&> concretizeExtraPassiveSensor (passiveSensorFrequency c), .. } @@ -116,12 +125,13 @@ concretizeExtraPassiveSensor :: Frequency -> Cfg.ExtraPassiveSensor -> NRMState.ExtraPassiveSensor -concretizeExtraPassiveSensor f x = NRMState.ExtraPassiveSensor - { NRMState.extraPassiveSensor = x, - NRMState.history = [], - NRMState.lastRead = Nothing, - NRMState.frequency = f - } +concretizeExtraPassiveSensor f x = + NRMState.ExtraPassiveSensor + { NRMState.extraPassiveSensor = x, + NRMState.history = [], + NRMState.lastRead = Nothing, + NRMState.frequency = f + } -- | Removes a slice from the state removeSlice :: SliceID -> NRMState -> (Maybe Slice, NRMState) diff --git a/hsnrm/hsnrm/src/NRM/Types/Configuration.hs b/hsnrm/hsnrm/src/NRM/Types/Configuration.hs index b76e1eddf6de87fcd2e7e3de842feeff3b138aa3..f09cd0d7c47537c97152249b2cd95c7d9d9c900a 100644 --- a/hsnrm/hsnrm/src/NRM/Types/Configuration.hs +++ b/hsnrm/hsnrm/src/NRM/Types/Configuration.hs @@ -67,7 +67,7 @@ data Cfg raplCfg :: Maybe RaplCfg, hwmonCfg :: HwmonCfg, controlCfg :: ControlCfg, - activeSensorFrequency :: Frequency, + passiveSensorFrequency :: Frequency, extraStaticPassiveSensors :: Map Text ExtraPassiveSensor, extraStaticActuators :: Map Text ExtraActuator } @@ -98,15 +98,14 @@ data ExtraPassiveSensor data ControlCfg = ControlCfg { minimumControlInterval :: Time, + minimumWaitInterval :: Time, staticPower :: Power, learnCfg :: LearnConfig, speedThreshold :: Double, referenceMeasurementRoundInterval :: Refined (GreaterThan 5) Int, hint :: Hint } - | FixedCommand - { fixedPower :: Power - } + | NoControl deriving (Eq, Show, Generic, MessagePack, Interpret, Inject) deriving (JSONSchema, ToJSON, FromJSON) via GenericJSON ControlCfg @@ -145,7 +144,8 @@ data UpstreamCfg instance Default ControlCfg where def = ControlCfg - { minimumControlInterval = 0.1 & seconds, + { minimumControlInterval = 1 & seconds, + minimumWaitInterval = 1 & seconds, staticPower = watts 200, speedThreshold = 1.1, learnCfg = Contextual (CtxCfg 4000), @@ -187,8 +187,8 @@ instance Default Cfg where raplCfg = Just def, hwmonCfg = def, verbose = NRM.Types.Configuration.Error, - controlCfg = FixedCommand (watts 250), - activeSensorFrequency = 1 & hz, + controlCfg = NoControl, + passiveSensorFrequency = 1 & hz, extraStaticPassiveSensors = [], extraStaticActuators = [] } diff --git a/hsnrm/hsnrm/src/NRM/Types/Controller.hs b/hsnrm/hsnrm/src/NRM/Types/Controller.hs index 520cffbaedeb0e0034a8450dc7d85bd033526d06..31f86ba05c3e6f71a9deb82db645d2b16f82b748 100644 --- a/hsnrm/hsnrm/src/NRM/Types/Controller.hs +++ b/hsnrm/hsnrm/src/NRM/Types/Controller.hs @@ -161,13 +161,12 @@ enqueueAll = (zipWithMatched $ \_ a abuffer -> enqueue a abuffer) initialController :: - Time -> - Time -> + IntegratorMeta -> [SensorID] -> Controller -initialController time minTime sensorIDs = +initialController integratorMeta sensorIDs = Controller - { integrator = initIntegrator time minTime sensorIDs, + { integrator = initIntegrator integratorMeta sensorIDs, lastA = Nothing, bandit = Nothing, armstats = M.empty, @@ -325,6 +324,12 @@ deriving via (GenericJSON Integrator) instance A.ToJSON Integrator deriving via (GenericJSON Integrator) instance A.FromJSON Integrator +deriving via (GenericJSON IntegratorMeta) instance JSONSchema IntegratorMeta + +deriving via (GenericJSON IntegratorMeta) instance A.ToJSON IntegratorMeta + +deriving via (GenericJSON IntegratorMeta) instance A.FromJSON IntegratorMeta + deriving instance Show Integrator deriving instance MessagePack Integrator @@ -333,6 +338,14 @@ deriving instance FromDhall Integrator deriving instance ToDhall Integrator +deriving instance Show IntegratorMeta + +deriving instance MessagePack IntegratorMeta + +deriving instance FromDhall IntegratorMeta + +deriving instance ToDhall IntegratorMeta + deriving via (GenericJSON (Arms [Action])) instance JSONSchema (Arms [Action]) deriving via (GenericJSON (Arms [Action])) instance A.ToJSON (Arms [Action]) diff --git a/hsnrm/hsnrm/src/NRM/Types/Units.hs b/hsnrm/hsnrm/src/NRM/Types/Units.hs index 91c25ad9400246e0f09969d0d5bf622485d68644..720e89f3c32f43657bfa991b81ba62a3458375fb 100644 --- a/hsnrm/hsnrm/src/NRM/Types/Units.hs +++ b/hsnrm/hsnrm/src/NRM/Types/Units.hs @@ -74,6 +74,9 @@ newtype Energy = Energy {fromuJ :: Double} deriving (Eq, Ord, Generic, Data, Inject, Interpret, MessagePack) deriving (Show, Num, JSONSchema, ToJSON, FromJSON) via Double +mil :: Double +mil = 1000000 + -- | Microjoule value constructor. progress :: Int -> Progress progress = Progress @@ -84,11 +87,11 @@ uJ = Energy -- | Joule value accessor. fromJoules :: Energy -> Double -fromJoules = (/ 1000000) . fromuJ +fromJoules = (/ mil) . fromuJ -- | Watt value constructor. joules :: Double -> Energy -joules = Energy . (* 1000000.0) +joules = Energy . (* mil) -- | Microwatt value constructor. uW :: Double -> Power @@ -96,11 +99,11 @@ uW = Power -- | Watt value accessor. fromWatts :: Power -> Double -fromWatts = (/ 1000000) . fromuW +fromWatts = (/ mil) . fromuW -- | Watt value constructor. watts :: Double -> Power -watts = Power . (* 1000000.0) +watts = Power . (* mil) -- | Microsecond value constructor. uS :: Double -> Time @@ -108,10 +111,10 @@ uS = Time -- | Second value constructor. seconds :: Double -> Time -seconds = Time . (* 1000000) +seconds = Time . (* mil) fromSeconds :: Time -> Double -fromSeconds (Time t) = t / 1000000 +fromSeconds (Time t) = t / mil -- | Hertz value constructor. hz :: Double -> Frequency diff --git a/hsnrm/resources/defaults/Cfg.dhall b/hsnrm/resources/defaults/Cfg.dhall index dcf1afc2e61bd89e5839875b1f01dcca164dbb7d..a251c2d6054925b4018eb98bf27b07e239951117 100644 --- a/hsnrm/resources/defaults/Cfg.dhall +++ b/hsnrm/resources/defaults/Cfg.dhall @@ -31,6 +31,7 @@ , controlCfg = < ControlCfg : { minimumControlInterval : { fromuS : Double } + , minimumWaitInterval : { fromuS : Double } , staticPower : { fromuW : Double } , learnCfg : < Lagrange : { lagrange : Double } @@ -52,10 +53,9 @@ } > } - | FixedCommand : { fixedPower : { fromuW : Double } } - >.FixedCommand - { fixedPower = { fromuW = 2.5e8 } } -, activeSensorFrequency = { fromHz = 1.0 } + | NoControl + >.NoControl +, passiveSensorFrequency = { fromHz = 1.0 } , extraStaticPassiveSensors = [] : List { mapKey : Text diff --git a/hsnrm/resources/defaults/Cfg.json b/hsnrm/resources/defaults/Cfg.json index 0998cfd72b8f466542734ab29466e483ecf8a9d4..33723df8a065aee8bb8b9e350e92f3796a8a4b71 100644 --- a/hsnrm/resources/defaults/Cfg.json +++ b/hsnrm/resources/defaults/Cfg.json @@ -5,20 +5,13 @@ "logfile": "/tmp/nrm.log", "singularity": false, "argo_nodeos_config": "argo_nodeos_config", - "controlCfg": { - "fixedPower": { - "fromuW": 250000000 - } - }, + "controlCfg": "NoControl", "upstreamCfg": { "upstreamBindAddress": "*", "rpcPort": 3456, "pubPort": 2345 }, "libnrmPath": null, - "activeSensorFrequency": { - "fromHz": 1 - }, "perf": "perf", "argo_perf_wrapper": "nrm-perfwrapper", "downstreamCfg": { @@ -46,5 +39,8 @@ "hwmonCfg": { "hwmonPath": "/sys/class/hwmon", "hwmonEnabled": true + }, + "passiveSensorFrequency": { + "fromHz": 1 } } \ No newline at end of file diff --git a/hsnrm/resources/defaults/Cfg.yaml b/hsnrm/resources/defaults/Cfg.yaml index 1880b5ff95883a089d9504432549b48578092ed5..c2028aa3a23513fee76e847d6fdfa93d84edc4f1 100644 --- a/hsnrm/resources/defaults/Cfg.yaml +++ b/hsnrm/resources/defaults/Cfg.yaml @@ -13,16 +13,12 @@ verbose: Error logfile: /tmp/nrm.log singularity: false argo_nodeos_config: argo_nodeos_config -controlCfg: - fixedPower: - fromuW: 2.5e8 +controlCfg: NoControl upstreamCfg: upstreamBindAddress: '*' rpcPort: 3456 pubPort: 2345 libnrmPath: null -activeSensorFrequency: - fromHz: 1 perf: perf argo_perf_wrapper: nrm-perfwrapper downstreamCfg: @@ -42,3 +38,5 @@ slice_runtime: Dummy hwmonCfg: hwmonPath: /sys/class/hwmon hwmonEnabled: true +passiveSensorFrequency: + fromHz: 1 diff --git a/hsnrm/resources/example-configurations/control.dhall b/hsnrm/resources/example-configurations/control.dhall index a685309546732feeb36a73f89452502cbbd34418..c3b7331c5bce309b7781f82014201853448b9768 100644 --- a/hsnrm/resources/example-configurations/control.dhall +++ b/hsnrm/resources/example-configurations/control.dhall @@ -31,6 +31,7 @@ , controlCfg = < ControlCfg : { minimumControlInterval : { fromuS : Double } + , minimumWaitInterval : { fromuS : Double } , staticPower : { fromuW : Double } , learnCfg : < Lagrange : { lagrange : Double } @@ -52,9 +53,10 @@ } > } - | FixedCommand : { fixedPower : { fromuW : Double } } + | NoControl >.ControlCfg - { minimumControlInterval = { fromuS = 100000.0 } + { minimumControlInterval = { fromuS = 1000000.0 } + , minimumWaitInterval = { fromuS = 1000000.0 } , staticPower = { fromuW = 2.0e8 } , learnCfg = < Lagrange : { lagrange : Double } @@ -75,7 +77,7 @@ } >.Full } -, activeSensorFrequency = { fromHz = 1.0 } +, passiveSensorFrequency = { fromHz = 1.0 } , extraStaticPassiveSensors = [] : List { mapKey : Text diff --git a/hsnrm/resources/example-configurations/control.json b/hsnrm/resources/example-configurations/control.json index 9f46ade11601c1b22bc3227dd4c8ecae38be933f..d1ace87f111d5ea631e9e342a816f9580d8c2e22 100644 --- a/hsnrm/resources/example-configurations/control.json +++ b/hsnrm/resources/example-configurations/control.json @@ -7,6 +7,9 @@ "argo_nodeos_config": "argo_nodeos_config", "controlCfg": { "referenceMeasurementRoundInterval": 6, + "minimumWaitInterval": { + "fromuS": 1000000 + }, "hint": "Full", "learnCfg": { "contextual": { @@ -18,7 +21,7 @@ }, "speedThreshold": 1.1, "minimumControlInterval": { - "fromuS": 100000 + "fromuS": 1000000 } }, "upstreamCfg": { @@ -27,9 +30,6 @@ "pubPort": 2345 }, "libnrmPath": null, - "activeSensorFrequency": { - "fromHz": 1 - }, "perf": "perf", "argo_perf_wrapper": "nrm-perfwrapper", "downstreamCfg": { @@ -57,5 +57,8 @@ "hwmonCfg": { "hwmonPath": "/sys/class/hwmon", "hwmonEnabled": true + }, + "passiveSensorFrequency": { + "fromHz": 1 } } \ No newline at end of file diff --git a/hsnrm/resources/example-configurations/control.yaml b/hsnrm/resources/example-configurations/control.yaml index 5a736628f4e862bfa3db118f509ea71a51fdcbdb..1e2fb56f7123cbe66446fa416be65bdd7e416e80 100644 --- a/hsnrm/resources/example-configurations/control.yaml +++ b/hsnrm/resources/example-configurations/control.yaml @@ -15,6 +15,8 @@ singularity: false argo_nodeos_config: argo_nodeos_config controlCfg: referenceMeasurementRoundInterval: 6 + minimumWaitInterval: + fromuS: 1000000.0 hint: Full learnCfg: contextual: @@ -23,14 +25,12 @@ controlCfg: fromuW: 2.0e8 speedThreshold: 1.1 minimumControlInterval: - fromuS: 100000.0 + fromuS: 1000000.0 upstreamCfg: upstreamBindAddress: '*' rpcPort: 3456 pubPort: 2345 libnrmPath: null -activeSensorFrequency: - fromHz: 1 perf: perf argo_perf_wrapper: nrm-perfwrapper downstreamCfg: @@ -50,3 +50,5 @@ slice_runtime: Dummy hwmonCfg: hwmonPath: /sys/class/hwmon hwmonEnabled: true +passiveSensorFrequency: + fromHz: 1 diff --git a/hsnrm/resources/example-configurations/extra-static-actuator.dhall b/hsnrm/resources/example-configurations/extra-static-actuator.dhall index 988af5e1c4372ea1d37734de9d6f48dbbd779702..18fce5d2ae353ecb09ce5df7531c75b067f57dba 100644 --- a/hsnrm/resources/example-configurations/extra-static-actuator.dhall +++ b/hsnrm/resources/example-configurations/extra-static-actuator.dhall @@ -31,6 +31,7 @@ , controlCfg = < ControlCfg : { minimumControlInterval : { fromuS : Double } + , minimumWaitInterval : { fromuS : Double } , staticPower : { fromuW : Double } , learnCfg : < Lagrange : { lagrange : Double } @@ -52,10 +53,9 @@ } > } - | FixedCommand : { fixedPower : { fromuW : Double } } - >.FixedCommand - { fixedPower = { fromuW = 2.5e8 } } -, activeSensorFrequency = { fromHz = 1.0 } + | NoControl + >.NoControl +, passiveSensorFrequency = { fromHz = 1.0 } , extraStaticPassiveSensors = [] : List { mapKey : Text diff --git a/hsnrm/resources/example-configurations/extra-static-actuator.json b/hsnrm/resources/example-configurations/extra-static-actuator.json index a6bda06c10d0039e8967a46dbe551f6c2bf1649b..b9fc6eb46a47ed4650107806fa2e484f88911eb1 100644 --- a/hsnrm/resources/example-configurations/extra-static-actuator.json +++ b/hsnrm/resources/example-configurations/extra-static-actuator.json @@ -5,20 +5,13 @@ "logfile": "/tmp/nrm.log", "singularity": false, "argo_nodeos_config": "argo_nodeos_config", - "controlCfg": { - "fixedPower": { - "fromuW": 250000000 - } - }, + "controlCfg": "NoControl", "upstreamCfg": { "upstreamBindAddress": "*", "rpcPort": 3456, "pubPort": 2345 }, "libnrmPath": null, - "activeSensorFrequency": { - "fromHz": 1 - }, "perf": "perf", "argo_perf_wrapper": "nrm-perfwrapper", "downstreamCfg": { @@ -63,5 +56,8 @@ "hwmonCfg": { "hwmonPath": "/sys/class/hwmon", "hwmonEnabled": true + }, + "passiveSensorFrequency": { + "fromHz": 1 } } \ No newline at end of file diff --git a/hsnrm/resources/example-configurations/extra-static-actuator.yaml b/hsnrm/resources/example-configurations/extra-static-actuator.yaml index 4eaf450c859af9a218abf8d0b33526fa73af9fbd..36bdd21452db2bcb4c5eee9ba5627040be431a8f 100644 --- a/hsnrm/resources/example-configurations/extra-static-actuator.yaml +++ b/hsnrm/resources/example-configurations/extra-static-actuator.yaml @@ -13,16 +13,12 @@ verbose: Error logfile: /tmp/nrm.log singularity: false argo_nodeos_config: argo_nodeos_config -controlCfg: - fixedPower: - fromuW: 2.5e8 +controlCfg: NoControl upstreamCfg: upstreamBindAddress: '*' rpcPort: 3456 pubPort: 2345 libnrmPath: null -activeSensorFrequency: - fromHz: 1 perf: perf argo_perf_wrapper: nrm-perfwrapper downstreamCfg: @@ -53,3 +49,5 @@ slice_runtime: Dummy hwmonCfg: hwmonPath: /sys/class/hwmon hwmonEnabled: true +passiveSensorFrequency: + fromHz: 1 diff --git a/hsnrm/resources/example-configurations/extra-static-sensor.dhall b/hsnrm/resources/example-configurations/extra-static-sensor.dhall index f1cb0e89c4bb17fd0252d61c721803633f59f1be..76dd4d950dd3326c387fd9ab77d2c0b50c99fb9c 100644 --- a/hsnrm/resources/example-configurations/extra-static-sensor.dhall +++ b/hsnrm/resources/example-configurations/extra-static-sensor.dhall @@ -31,6 +31,7 @@ , controlCfg = < ControlCfg : { minimumControlInterval : { fromuS : Double } + , minimumWaitInterval : { fromuS : Double } , staticPower : { fromuW : Double } , learnCfg : < Lagrange : { lagrange : Double } @@ -52,10 +53,9 @@ } > } - | FixedCommand : { fixedPower : { fromuW : Double } } - >.FixedCommand - { fixedPower = { fromuW = 2.5e8 } } -, activeSensorFrequency = { fromHz = 1.0 } + | NoControl + >.NoControl +, passiveSensorFrequency = { fromHz = 1.0 } , extraStaticPassiveSensors = [ { mapKey = "example extra static passive power sensor" , mapValue = diff --git a/hsnrm/resources/example-configurations/extra-static-sensor.json b/hsnrm/resources/example-configurations/extra-static-sensor.json index 78321e5578a9af4e582cfaa0535808bf9ea7df1d..0e2ef16571503145c55e60934d1e6927786971ec 100644 --- a/hsnrm/resources/example-configurations/extra-static-sensor.json +++ b/hsnrm/resources/example-configurations/extra-static-sensor.json @@ -23,20 +23,13 @@ "logfile": "/tmp/nrm.log", "singularity": false, "argo_nodeos_config": "argo_nodeos_config", - "controlCfg": { - "fixedPower": { - "fromuW": 250000000 - } - }, + "controlCfg": "NoControl", "upstreamCfg": { "upstreamBindAddress": "*", "rpcPort": 3456, "pubPort": 2345 }, "libnrmPath": null, - "activeSensorFrequency": { - "fromHz": 1 - }, "perf": "perf", "argo_perf_wrapper": "nrm-perfwrapper", "downstreamCfg": { @@ -64,5 +57,8 @@ "hwmonCfg": { "hwmonPath": "/sys/class/hwmon", "hwmonEnabled": true + }, + "passiveSensorFrequency": { + "fromHz": 1 } } \ No newline at end of file diff --git a/hsnrm/resources/example-configurations/extra-static-sensor.yaml b/hsnrm/resources/example-configurations/extra-static-sensor.yaml index 603a78034554d6cecacca672561c7cd1c2d8e402..e30757bfafad729eced63ce6d4c7339ad6a0c41e 100644 --- a/hsnrm/resources/example-configurations/extra-static-sensor.yaml +++ b/hsnrm/resources/example-configurations/extra-static-sensor.yaml @@ -24,16 +24,12 @@ verbose: Error logfile: /tmp/nrm.log singularity: false argo_nodeos_config: argo_nodeos_config -controlCfg: - fixedPower: - fromuW: 2.5e8 +controlCfg: NoControl upstreamCfg: upstreamBindAddress: '*' rpcPort: 3456 pubPort: 2345 libnrmPath: null -activeSensorFrequency: - fromHz: 1 perf: perf argo_perf_wrapper: nrm-perfwrapper downstreamCfg: @@ -53,3 +49,5 @@ slice_runtime: Dummy hwmonCfg: hwmonPath: /sys/class/hwmon hwmonEnabled: true +passiveSensorFrequency: + fromHz: 1 diff --git a/hsnrm/resources/example-configurations/variorum-two-package-power-limit-sensor.dhall b/hsnrm/resources/example-configurations/variorum-two-package-power-limit-sensor.dhall index a4bf54fb6196dec42d8724cdbc7e7b30ccfef8ce..159bda8f1cbbff41c8e43d9b53c2af7fedbd54a6 100644 --- a/hsnrm/resources/example-configurations/variorum-two-package-power-limit-sensor.dhall +++ b/hsnrm/resources/example-configurations/variorum-two-package-power-limit-sensor.dhall @@ -31,6 +31,7 @@ , controlCfg = < ControlCfg : { minimumControlInterval : { fromuS : Double } + , minimumWaitInterval : { fromuS : Double } , staticPower : { fromuW : Double } , learnCfg : < Lagrange : { lagrange : Double } @@ -52,10 +53,9 @@ } > } - | FixedCommand : { fixedPower : { fromuW : Double } } - >.FixedCommand - { fixedPower = { fromuW = 2.5e8 } } -, activeSensorFrequency = { fromHz = 1.0 } + | NoControl + >.NoControl +, passiveSensorFrequency = { fromHz = 1.0 } , extraStaticPassiveSensors = [ { mapKey = "Sensor that gets package power limits for package 0 through variorum" diff --git a/hsnrm/resources/example-configurations/variorum-two-package-power-limit-sensor.json b/hsnrm/resources/example-configurations/variorum-two-package-power-limit-sensor.json index b6eb577c8b12bfb681b34c0d490dab9d6b4467bb..6a1109c9f0357105bca535f7ee1f8dc0b20f241c 100644 --- a/hsnrm/resources/example-configurations/variorum-two-package-power-limit-sensor.json +++ b/hsnrm/resources/example-configurations/variorum-two-package-power-limit-sensor.json @@ -38,20 +38,13 @@ "logfile": "/tmp/nrm.log", "singularity": false, "argo_nodeos_config": "argo_nodeos_config", - "controlCfg": { - "fixedPower": { - "fromuW": 250000000 - } - }, + "controlCfg": "NoControl", "upstreamCfg": { "upstreamBindAddress": "*", "rpcPort": 3456, "pubPort": 2345 }, "libnrmPath": null, - "activeSensorFrequency": { - "fromHz": 1 - }, "perf": "perf", "argo_perf_wrapper": "nrm-perfwrapper", "downstreamCfg": { @@ -79,5 +72,8 @@ "hwmonCfg": { "hwmonPath": "/sys/class/hwmon", "hwmonEnabled": true + }, + "passiveSensorFrequency": { + "fromHz": 1 } } \ No newline at end of file diff --git a/hsnrm/resources/example-configurations/variorum-two-package-power-limit-sensor.yaml b/hsnrm/resources/example-configurations/variorum-two-package-power-limit-sensor.yaml index 8137f41321cd37cfea26c7cfa9b2c911bbafe004..b90492ddc0cb19b07ab56e2bde873ed266dfc3d8 100644 --- a/hsnrm/resources/example-configurations/variorum-two-package-power-limit-sensor.yaml +++ b/hsnrm/resources/example-configurations/variorum-two-package-power-limit-sensor.yaml @@ -37,16 +37,12 @@ verbose: Error logfile: /tmp/nrm.log singularity: false argo_nodeos_config: argo_nodeos_config -controlCfg: - fixedPower: - fromuW: 2.5e8 +controlCfg: NoControl upstreamCfg: upstreamBindAddress: '*' rpcPort: 3456 pubPort: 2345 libnrmPath: null -activeSensorFrequency: - fromHz: 1 perf: perf argo_perf_wrapper: nrm-perfwrapper downstreamCfg: @@ -66,3 +62,5 @@ slice_runtime: Dummy hwmonCfg: hwmonPath: /sys/class/hwmon hwmonEnabled: true +passiveSensorFrequency: + fromHz: 1 diff --git a/hsnrm/resources/example-configurations/variorum-two-package-power-limits-actuator.dhall b/hsnrm/resources/example-configurations/variorum-two-package-power-limits-actuator.dhall index 37ad73634d49c551cd37bca72ddf38cf8e405f6b..e55e62f520a5a418886b290a8124e9e374072e0b 100644 --- a/hsnrm/resources/example-configurations/variorum-two-package-power-limits-actuator.dhall +++ b/hsnrm/resources/example-configurations/variorum-two-package-power-limits-actuator.dhall @@ -31,6 +31,7 @@ , controlCfg = < ControlCfg : { minimumControlInterval : { fromuS : Double } + , minimumWaitInterval : { fromuS : Double } , staticPower : { fromuW : Double } , learnCfg : < Lagrange : { lagrange : Double } @@ -52,10 +53,9 @@ } > } - | FixedCommand : { fixedPower : { fromuW : Double } } - >.FixedCommand - { fixedPower = { fromuW = 2.5e8 } } -, activeSensorFrequency = { fromHz = 1.0 } + | NoControl + >.NoControl +, passiveSensorFrequency = { fromHz = 1.0 } , extraStaticPassiveSensors = [] : List { mapKey : Text diff --git a/hsnrm/resources/example-configurations/variorum-two-package-power-limits-actuator.json b/hsnrm/resources/example-configurations/variorum-two-package-power-limits-actuator.json index ee6fdd863287dac8239084b2d14995dd23fad03e..ec3ff3d2d1c083efffb1b0db5da372ee72db7827 100644 --- a/hsnrm/resources/example-configurations/variorum-two-package-power-limits-actuator.json +++ b/hsnrm/resources/example-configurations/variorum-two-package-power-limits-actuator.json @@ -5,20 +5,13 @@ "logfile": "/tmp/nrm.log", "singularity": false, "argo_nodeos_config": "argo_nodeos_config", - "controlCfg": { - "fixedPower": { - "fromuW": 250000000 - } - }, + "controlCfg": "NoControl", "upstreamCfg": { "upstreamBindAddress": "*", "rpcPort": 3456, "pubPort": 2345 }, "libnrmPath": null, - "activeSensorFrequency": { - "fromHz": 1 - }, "perf": "perf", "argo_perf_wrapper": "nrm-perfwrapper", "downstreamCfg": { @@ -59,5 +52,8 @@ "hwmonCfg": { "hwmonPath": "/sys/class/hwmon", "hwmonEnabled": true + }, + "passiveSensorFrequency": { + "fromHz": 1 } } \ No newline at end of file diff --git a/hsnrm/resources/example-configurations/variorum-two-package-power-limits-actuator.yaml b/hsnrm/resources/example-configurations/variorum-two-package-power-limits-actuator.yaml index 0018f732283f8a72a0623052f4e561a8f239d3d4..0b73dc44e563ab2c41e38985a135bf814e8b620f 100644 --- a/hsnrm/resources/example-configurations/variorum-two-package-power-limits-actuator.yaml +++ b/hsnrm/resources/example-configurations/variorum-two-package-power-limits-actuator.yaml @@ -13,16 +13,12 @@ verbose: Error logfile: /tmp/nrm.log singularity: false argo_nodeos_config: argo_nodeos_config -controlCfg: - fixedPower: - fromuW: 2.5e8 +controlCfg: NoControl upstreamCfg: upstreamBindAddress: '*' rpcPort: 3456 pubPort: 2345 libnrmPath: null -activeSensorFrequency: - fromHz: 1 perf: perf argo_perf_wrapper: nrm-perfwrapper downstreamCfg: @@ -50,3 +46,5 @@ slice_runtime: Dummy hwmonCfg: hwmonPath: /sys/class/hwmon hwmonEnabled: true +passiveSensorFrequency: + fromHz: 1 diff --git a/hsnrm/resources/example-configurations/variorum-two-package-power-value-sensor.dhall b/hsnrm/resources/example-configurations/variorum-two-package-power-value-sensor.dhall index c0d936eeab718fae2d1ba20bd1990714aaa158b2..476ee83cd1a04ff464b45162c19b038f5d6fab4d 100644 --- a/hsnrm/resources/example-configurations/variorum-two-package-power-value-sensor.dhall +++ b/hsnrm/resources/example-configurations/variorum-two-package-power-value-sensor.dhall @@ -31,6 +31,7 @@ , controlCfg = < ControlCfg : { minimumControlInterval : { fromuS : Double } + , minimumWaitInterval : { fromuS : Double } , staticPower : { fromuW : Double } , learnCfg : < Lagrange : { lagrange : Double } @@ -52,10 +53,9 @@ } > } - | FixedCommand : { fixedPower : { fromuW : Double } } - >.FixedCommand - { fixedPower = { fromuW = 2.5e8 } } -, activeSensorFrequency = { fromHz = 1.0 } + | NoControl + >.NoControl +, passiveSensorFrequency = { fromHz = 1.0 } , extraStaticPassiveSensors = [ { mapKey = "Sensor that gets package power limits for package 0 through variorum" diff --git a/hsnrm/resources/example-configurations/variorum-two-package-power-value-sensor.json b/hsnrm/resources/example-configurations/variorum-two-package-power-value-sensor.json index 10289e46db1ae159b5f6ed9c618f1cfa78bced82..b31271692f6099ee0eacee34c9bfc4f9f1006bad 100644 --- a/hsnrm/resources/example-configurations/variorum-two-package-power-value-sensor.json +++ b/hsnrm/resources/example-configurations/variorum-two-package-power-value-sensor.json @@ -42,20 +42,13 @@ "logfile": "/tmp/nrm.log", "singularity": false, "argo_nodeos_config": "argo_nodeos_config", - "controlCfg": { - "fixedPower": { - "fromuW": 250000000 - } - }, + "controlCfg": "NoControl", "upstreamCfg": { "upstreamBindAddress": "*", "rpcPort": 3456, "pubPort": 2345 }, "libnrmPath": null, - "activeSensorFrequency": { - "fromHz": 1 - }, "perf": "perf", "argo_perf_wrapper": "nrm-perfwrapper", "downstreamCfg": { @@ -83,5 +76,8 @@ "hwmonCfg": { "hwmonPath": "/sys/class/hwmon", "hwmonEnabled": true + }, + "passiveSensorFrequency": { + "fromHz": 1 } } \ No newline at end of file diff --git a/hsnrm/resources/example-configurations/variorum-two-package-power-value-sensor.yaml b/hsnrm/resources/example-configurations/variorum-two-package-power-value-sensor.yaml index 2e814dce4430ec1f3fb15903b94d330aa699c63a..efc57057a24be9d0f91cfc69f720e9c163f59c41 100644 --- a/hsnrm/resources/example-configurations/variorum-two-package-power-value-sensor.yaml +++ b/hsnrm/resources/example-configurations/variorum-two-package-power-value-sensor.yaml @@ -39,16 +39,12 @@ verbose: Error logfile: /tmp/nrm.log singularity: false argo_nodeos_config: argo_nodeos_config -controlCfg: - fixedPower: - fromuW: 2.5e8 +controlCfg: NoControl upstreamCfg: upstreamBindAddress: '*' rpcPort: 3456 pubPort: 2345 libnrmPath: null -activeSensorFrequency: - fromHz: 1 perf: perf argo_perf_wrapper: nrm-perfwrapper downstreamCfg: @@ -68,3 +64,5 @@ slice_runtime: Dummy hwmonCfg: hwmonPath: /sys/class/hwmon hwmonEnabled: true +passiveSensorFrequency: + fromHz: 1 diff --git a/hsnrm/resources/types/Cfg.dhall b/hsnrm/resources/types/Cfg.dhall index 4fd078e82aaf47d0ccfc5b1a3c91e1c81ad812b7..3907d22d7f536ffbdc2f417db3aa6b84b4a9e180 100644 --- a/hsnrm/resources/types/Cfg.dhall +++ b/hsnrm/resources/types/Cfg.dhall @@ -33,6 +33,7 @@ , controlCfg : < ControlCfg : { minimumControlInterval : { fromuS : Double } + , minimumWaitInterval : { fromuS : Double } , staticPower : { fromuW : Double } , learnCfg : < Lagrange : { lagrange : Double } @@ -54,9 +55,9 @@ } > } - | FixedCommand : { fixedPower : { fromuW : Double } } + | NoControl > -, activeSensorFrequency : { fromHz : Double } +, passiveSensorFrequency : { fromHz : Double } , extraStaticPassiveSensors : List { mapKey : Text diff --git a/hsnrm/resources/upstreamPub.json b/hsnrm/resources/upstreamPub.json index 73cd1dfae685020ef842a036ce4fe2de0a4a56c6..238d2403196ed9e74a19ddf770ddbfd6a0c15dae 100644 --- a/hsnrm/resources/upstreamPub.json +++ b/hsnrm/resources/upstreamPub.json @@ -911,8 +911,7 @@ }, "integrator": { "required": [ - "tLast", - "minimumControlInterval", + "meta", "measured" ], "type": "object", @@ -1010,11 +1009,24 @@ }, "type": "object" }, - "minimumControlInterval": { - "type": "number" - }, - "tLast": { - "type": "number" + "meta": { + "required": [ + "tLast", + "minimumWaitInterval", + "minimumControlInterval" + ], + "type": "object", + "properties": { + "minimumWaitInterval": { + "type": "number" + }, + "minimumControlInterval": { + "type": "number" + }, + "tLast": { + "type": "number" + } + } } } }, diff --git a/hsnrm/resources/upstreamRep.json b/hsnrm/resources/upstreamRep.json index 94fa913b664bb0f5ade2dcf06a38a52e0be50842..4c28116b0e9f7fdb93e2202fa438c8f68070288b 100644 --- a/hsnrm/resources/upstreamRep.json +++ b/hsnrm/resources/upstreamRep.json @@ -1080,7 +1080,7 @@ "upstreamCfg", "hwmonCfg", "controlCfg", - "activeSensorFrequency", + "passiveSensorFrequency", "extraStaticPassiveSensors", "extraStaticActuators" ], @@ -1247,6 +1247,7 @@ "controlCfg": { "required": [ "minimumControlInterval", + "minimumWaitInterval", "staticPower", "learnCfg", "speedThreshold", @@ -1258,6 +1259,9 @@ "referenceMeasurementRoundInterval": { "type": "number" }, + "minimumWaitInterval": { + "type": "number" + }, "hint": { "oneOf": [ { @@ -1421,20 +1425,13 @@ }, { "required": [ - "fixedCommand" + "noControl" ], "type": "object", "properties": { - "fixedCommand": { - "required": [ - "fixedPower" - ], + "noControl": { "type": "object", - "properties": { - "fixedPower": { - "type": "number" - } - } + "properties": {} } } } @@ -1462,9 +1459,6 @@ "libnrmPath": { "type": "string" }, - "activeSensorFrequency": { - "type": "number" - }, "perf": { "type": "string" }, @@ -1575,6 +1569,9 @@ "type": "boolean" } } + }, + "passiveSensorFrequency": { + "type": "number" } } } diff --git a/pynrm/nrm/daemon.py b/pynrm/nrm/daemon.py index c3e621fdfc59bbc149f00670eccaa03d01fc06f0..c4494cd9dc323d89cdb20b2ddcaab5bfa974eb85 100644 --- a/pynrm/nrm/daemon.py +++ b/pynrm/nrm/daemon.py @@ -63,7 +63,7 @@ class Daemon(object): # setup periodic sensor updates self.sensor_cb = ioloop.PeriodicCallback( - self.wrap("doSensor"), 1000 / self.lib.activeSensorFrequency(self.cfg) + self.wrap("doSensor"), 1000 / self.lib.passiveSensorFrequency(self.cfg) ) self.sensor_cb.start()