| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Network.Protocol.Snmp.AgentX.MIBTree
Contents
- type MIBTree = StateT Module
- data Module
- mkModule :: (Monad m, MonadIO m, Functor m) => OID -> [MIB] -> m Module
- initModule :: (Monad m, MonadIO m, Functor m) => MIBTree m ()
- registerFullTree :: (Monad m, MonadIO m, Functor m) => MIBTree m ()
- unregisterFullTree :: (Monad m, MonadIO m, Functor m) => MIBTree m ()
- askTree :: (Monad m, MonadIO m, Functor m) => MIBTree m (Tree IValue)
- regByDiff :: (Monad m, MonadIO m, Functor m) => Tree IValue -> Tree IValue -> MIBTree m ()
- moduleOID :: forall cat. ArrowApply cat => Lens cat Module OID
- register :: forall cat. ArrowApply cat => Lens cat Module (MVar ([(OID, Maybe Context)], [(OID, Maybe Context)]))
- zipper :: forall cat. ArrowApply cat => Lens cat Module (Zipper Tree IValue)
- ou :: forall cat. ArrowApply cat => Lens cat Module (Zipper Tree IUpdate)
- findOne :: (Monad m, MonadIO m, Functor m) => OID -> Maybe Context -> MIBTree m MIB
- findMany :: (Monad m, MonadIO m, Functor m) => [OID] -> Maybe Context -> MIBTree m [MIB]
- findNext :: (Monad m, MonadIO m, Functor m) => SearchRange -> Maybe Context -> MIBTree m MIB
- findManyNext :: (Monad m, MonadIO m, Functor m) => [SearchRange] -> Maybe Context -> MIBTree m [MIB]
- type Parent = String
- type Name = String
- data MIB
- oi :: MIB -> OID
- val :: MIB -> PVal
- context :: MIB -> Maybe Context
- mkObject :: Integer -> Parent -> Name -> Maybe Update -> MIB
- mkObjectType :: Integer -> Parent -> Name -> Maybe Context -> PVal -> MIB
- isObjectType :: MIB -> Bool
- newtype Update = Update {}
- data PVal
- = Read { }
- | ReadWrite {
- readAIO :: IO Value
- commitSetAIO :: Value -> IO CommitError
- testSetAIO :: Value -> IO TestError
- undoSetAIO :: Value -> IO UndoError
- isWritable :: PVal -> Bool
- rsValue :: Value -> PVal
- rdValue :: IO Value -> PVal
- rwValue :: IO Value -> (Value -> IO CommitError) -> (Value -> IO TestError) -> (Value -> IO UndoError) -> PVal
- regWrapper :: (Monad m, MonadIO m, Functor m) => MIBTree m x -> MIBTree m x
- mibToVarBind :: (Monad m, MonadIO m, Functor m) => MIB -> m VarBind
Documentation
Module
create and init Module
Arguments
| :: (Monad m, MonadIO m, Functor m) | |
| => OID | base module OID |
| -> [MIB] | all MIB for create module |
| -> m Module |
Constructor for Module
registerFullTree :: (Monad m, MonadIO m, Functor m) => MIBTree m () Source
register all MIBs in snmp server
lenses for Module
register :: forall cat. ArrowApply cat => Lens cat Module (MVar ([(OID, Maybe Context)], [(OID, Maybe Context)])) Source
zipper :: forall cat. ArrowApply cat => Lens cat Module (Zipper Tree IValue) Source
ou :: forall cat. ArrowApply cat => Lens cat Module (Zipper Tree IUpdate) Source
functions for work with MIBTree
Arguments
| :: (Monad m, MonadIO m, Functor m) | |
| => OID | path for find |
| -> Maybe Context | context, you can have many values with one path and different context |
| -> MIBTree m MIB |
find one MIB
findMany :: (Monad m, MonadIO m, Functor m) => [OID] -> Maybe Context -> MIBTree m [MIB] Source
like findOne, but for many paths
Arguments
| :: (Monad m, MonadIO m, Functor m) | |
| => SearchRange | SearchRange (getwalk or getnext requests) |
| -> Maybe Context | context |
| -> MIBTree m MIB | search result |
find next node in MIBTree
findManyNext :: (Monad m, MonadIO m, Functor m) => [SearchRange] -> Maybe Context -> MIBTree m [MIB] Source
like findNext
MIB
lenses
constructors
Arguments
| :: Integer | OID number for this object |
| -> Parent | parent name for this object |
| -> Name | name for this object |
| -> Maybe Update | Just Update if you need dynamic module |
| -> MIB | created MIB |
Constructor for MIB, create Object in mib tree
Arguments
| :: Integer | OID number for this object |
| -> Parent | parent |
| -> Name | name |
| -> Maybe Context | context |
| -> PVal | value |
| -> MIB | created MIB |
Constructor for MIB, create Object-Type in mib tree
isObjectType :: MIB -> Bool Source
check MIB subtype
raw values for build SNMP subagent
Update, for rebuild oid tree in runtime
Wrapper for value
Constructors
| Read | |
| ReadWrite | |
Fields
| |
isWritable :: PVal -> Bool Source
check for PVal
helpers for create PVal
rwValue :: IO Value -> (Value -> IO CommitError) -> (Value -> IO TestError) -> (Value -> IO UndoError) -> PVal Source
PVal constructor for read write value