agentx-0.1.0.4: AgentX protocol for write SNMP subagents

Safe HaskellNone
LanguageHaskell2010

Network.Protocol.Snmp.AgentX

Contents

Synopsis

About

Library for write extensible SNMP agents.

data MIB Source

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

Instances

data PVal Source

Wrapper for value

Instances

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

PVal constructor for read write value

rsValue :: Value -> PVal Source

PVal constructor for read only value

rdValue :: IO Value -> PVal Source

PVal constructor for read only IO Value

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

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

data CommitError Source

result for commitSetAIO (rfc 2741, section 7.2.4.2)

data UndoError Source

result for undoSetAIO (rfc 2741, section 7.2.4.3)

Constructors

NoUndoError 
UndoFailed 

data Context Source

rfc 2571 section 3.3.1, rfc 2741 section 6.1.1 Context

agent Source

Arguments

:: FilePath

path to socket

-> OID

base oid

-> Maybe Client

client

-> [MIB]

MIBs

-> IO () 

start agent

runAgent :: OID -> [MIB] -> Maybe Client -> Socket -> IO () Source

start agent with socket exit when catch sigQUIT, sigTERM, keyboardSignal show MIB tree when catch sigUSR1

data Client Source

if you need client

Instances

Default Client

by default just ping every 5s.

Usage

Imports



module Main where

import Network.Protocol.Snmp.AgentX 
import qualified Data.ByteString as BS
import Data.ByteString (ByteString)
import Data.Fixed (div')
import Data.Time.Clock.POSIX (getPOSIXTime)
import Control.Applicative ((<$>))
import Control.Monad.State
import Data.IORef

Desribe values for monitoring

str :: ByteString -> PVal
str x = rsValue (String x)

now :: PVal
now = rdValue $  TimeTicks . flip div' 1 <$> liftIO getPOSIXTime

rws :: IORef Value -> PVal
rws io = rwValue readV commit test undo
  where
    test (String x) 
      | BS.length x < 10 = return NoTestError
      | otherwise = return TooBig
    test _ = return WrongType
    commit v = do
        writeIORef io v
        return NoCommitError
    undo _ = return NoUndoError
    readV = readIORef io

rwi :: IORef Value -> PVal
rwi io = rwValue readV commit test undo
  where
    test (Integer x) 
      | x < 5 = return NoTestError
      | otherwise = return TooBig
    test _ = return WrongType
    commit v = do
        writeIORef io v
        return NoCommitError
    undo _ = return NoUndoError
    readV = readIORef io

Build dynamic tree

dynTree :: IORef Value -> Update
dynTree i = Update $ do
    Integer count <- liftIO $ readIORef i
    return $ concatMap fun [0 .. count]
    where
    fun x = [ mkObject (fromIntegral x) "trees" ("tree" ++ show x) Nothing
            , mkObjectType 0 ("tree" ++ show x) "abr" Nothing (str "abr")
            , mkObjectType 1 ("tree" ++ show x) "abrvalg" Nothing (str "abrvalg")
            ]

Describe context

ver :: Maybe Context
ver = Just "version"

Construct full tree

simpleTree :: IORef Value -> IORef Value -> [MIB]
simpleTree m i = 
      [ mkObject 0 "Fixmon" "about" Nothing
      , mkObjectType 0 "about" "name" Nothing $ rsValue (String "Fixmon agent")
      , mkObjectType 1 "about" "version" Nothing $ rsValue (String "0.0.1")
      , mkObjectType 1 "about" "version" ver $ rsValue (String "Alpha")
      , mkObjectType 2 "about" "comment" Nothing (rws m) 
      , mkObject 1 "Fixmon" "dyn" Nothing
      , mkObjectType 0 "dyn" "counter" Nothing (rwi i)
      , mkObject 1 "dyn" "trees" (Just $ dynTree i)
      ]

tree :: IO [MIB]
tree = do
    m <- newIORef (String "init")
    i <- newIORef (Integer 0)
    return $ simpleTree m i

Start subagent

main :: IO ()
main = agent "/var/agentx/master" [1,3,6,1,4,1,44729] Nothing =<< tree

Examples

SNMP server config
> cat /etc/snmp/snmpd.conf
> rwuser sha
> createUser sha SHA "password" DESi
> master agentx
> agentXPerms 777 775

SNMP client config
> cat /etc/snmp/snmp.conf
> defVersion 3
> defSecurityName sha
> defSecurityLevel authPriv
> defPassphrase password
> defAuthType SHA
> defPrivType DES
> defContext ""

Build example
> cabal install -f example
Start SNMP server
> sudo snmpd
Start SNMP agent
> .cabal-sandbox/bin/agentx_example

Get MIB tree
 > snmpwalk -r 1 -On localhost 1.3.6.1.4.1.44729
 > .1.3.6.1.4.1.44729.0.0 = STRING: "Fixmon agent"
 > .1.3.6.1.4.1.44729.0.1 = STRING: "0.0.1"
 > .1.3.6.1.4.1.44729.0.2 = STRING: "init"
 > .1.3.6.1.4.1.44729.1.0 = INTEGER: 0
 > .1.3.6.1.4.1.44729.1.1.0.0 = STRING: "abr"
 > .1.3.6.1.4.1.44729.1.1.0.1 = STRING: "abrvalg"
 
Change MIB tree 
 >  snmpset -r 1  -On localhost .1.3.6.1.4.1.44729.1.0 i 2
 > .1.3.6.1.4.1.44729.1.0 = INTEGER: 2
 >  snmpwalk -r 1 -On localhost 1.3.6.1.4.1.44729
 > .1.3.6.1.4.1.44729.0.0 = STRING: "Fixmon agent"
 > .1.3.6.1.4.1.44729.0.1 = STRING: "0.0.1"
 > .1.3.6.1.4.1.44729.0.2 = STRING: "init"
 > .1.3.6.1.4.1.44729.1.0 = INTEGER: 2
 > .1.3.6.1.4.1.44729.1.1.0.0 = STRING: "abr"
 > .1.3.6.1.4.1.44729.1.1.0.1 = STRING: "abrvalg"
 > .1.3.6.1.4.1.44729.1.1.1.0 = STRING: "abr"
 > .1.3.6.1.4.1.44729.1.1.1.1 = STRING: "abrvalg"
 > .1.3.6.1.4.1.44729.1.1.2.0 = STRING: "abr"
 > .1.3.6.1.4.1.44729.1.1.2.1 = STRING: "abrvalg"