agentx-0.1.0.4: AgentX protocol for write SNMP subagents

Safe HaskellNone
LanguageHaskell2010

Network.Protocol.Snmp.AgentX.MIBTree

Contents

Synopsis

Documentation

type MIBTree = StateT Module Source

MIBTree, state transformer, with Module under ground

Module

data Module Source

internal state for build SNMP submodule

Instances

create and init Module

mkModule Source

Arguments

:: (Monad m, MonadIO m, Functor m) 
=> OID

base module OID

-> [MIB]

all MIB for create module

-> m Module 

Constructor for Module

initModule :: (Monad m, MonadIO m, Functor m) => MIBTree m () Source

build tree and init module

registerFullTree :: (Monad m, MonadIO m, Functor m) => MIBTree m () Source

register all MIBs in snmp server

askTree :: (Monad m, MonadIO m, Functor m) => MIBTree m (Tree IValue) Source

regByDiff :: (Monad m, MonadIO m, Functor m) => Tree IValue -> Tree IValue -> MIBTree m () Source

lenses for Module

moduleOID :: forall cat. ArrowApply cat => Lens cat Module OID Source

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

findOne Source

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

findNext Source

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

data MIB Source

MIB describe objects and object-types in internal tree with data.

Instances

lenses

oi :: MIB -> OID Source

accessor for OID

val :: MIB -> PVal Source

accessor for PVal

context :: MIB -> Maybe Context Source

accessor for Maybe Context

constructors

mkObject Source

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

mkObjectType Source

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

newtype Update Source

Update, for rebuild oid tree in runtime

Constructors

Update 

Fields

unUpdate :: forall m. (Monad m, MonadIO m, Functor m) => m [MIB]
 

Instances

data PVal Source

Wrapper for value

Instances

isWritable :: PVal -> Bool Source

check for PVal

helpers for create PVal

rsValue :: Value -> PVal Source

PVal constructor for read only value

rdValue :: IO Value -> PVal Source

PVal constructor for read only IO Value

rwValue :: IO Value -> (Value -> IO CommitError) -> (Value -> IO TestError) -> (Value -> IO UndoError) -> PVal Source

PVal constructor for read write value

regWrapper :: (Monad m, MonadIO m, Functor m) => MIBTree m x -> MIBTree m x Source

wrap MIBTree action, get MIB tree before and after, register added mibs, unregister removed mibs

mibToVarBind :: (Monad m, MonadIO m, Functor m) => MIB -> m VarBind Source

convert MIB to VarBind