Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Session = Session {
- sessionSockets :: !(Chan Socket)
- sessionSocketCount :: !Int
- sessionRequestId :: !(TVar RequestId)
- sessionAesSalt :: !(TVar AesSalt)
- sessionTimeoutMicroseconds :: !Int
- sessionMaxTries :: !Int
- data Config = Config {}
- data Destination = Destination {
- destinationHost :: !(Word8, Word8, Word8, Word8)
- destinationPort :: !Word16
- data Credentials
- newtype CredentialsV2 = CredentialsV2 {}
- data CredentialsV3 = CredentialsV3 {}
- data Context = Context {}
- data PerHostV3 = PerHostV3 {}
- openSession :: Config -> IO Session
- closeSession :: Session -> IO ()
- generalRequest :: (RequestId -> Pdus) -> (Pdu -> Either SnmpException a) -> Context -> IO (Either SnmpException a)
- nextSalt :: TVar AesSalt -> STM AesSalt
- throwSnmpException :: IO (Either SnmpException a) -> IO a
- get :: Context -> ObjectIdentifier -> IO ObjectSyntax
- getBulkStep :: Context -> Int -> ObjectIdentifier -> IO (Vector (ObjectIdentifier, ObjectSyntax))
- getBulkChildren :: Context -> Int -> ObjectIdentifier -> IO (Vector (ObjectIdentifier, ObjectSyntax))
- get' :: Context -> ObjectIdentifier -> IO (Either SnmpException ObjectSyntax)
- getBulkStep' :: Context -> Int -> ObjectIdentifier -> IO (Either SnmpException (Vector (ObjectIdentifier, ObjectSyntax)))
- getBulkChildren' :: Context -> Int -> ObjectIdentifier -> IO (Either SnmpException (Vector (ObjectIdentifier, ObjectSyntax)))
- oidIsPrefixOf :: ObjectIdentifier -> ObjectIdentifier -> Bool
- multipleBindings :: Vector VarBind -> Vector (ObjectIdentifier, ObjectSyntax)
- singleBindingValue :: ObjectIdentifier -> Vector VarBind -> Either SnmpException ObjectSyntax
- onlyBindings :: Pdu -> Either SnmpException (Vector VarBind)
- data SnmpException
- = SnmpExceptionNotAllBytesSent !Int !Int
- | SnmpExceptionTimeout
- | SnmpExceptionTimeoutV3 !MessageV3
- | SnmpExceptionPduError !ErrorStatus !ErrorIndex
- | SnmpExceptionMultipleBindings !Int
- | SnmpExceptionMismatchedBinding !ObjectIdentifier !ObjectIdentifier
- | SnmpExceptionUnspecified
- | SnmpExceptionNoSuchObject !ObjectIdentifier
- | SnmpExceptionNoSuchInstance !ObjectIdentifier
- | SnmpExceptionEndOfMibView
- | SnmpExceptionMissedResponse !RequestId !RequestId
- | SnmpExceptionNonPduResponseV2 !MessageV2
- | SnmpExceptionNonPduResponseV3 !MessageV3
- | SnmpExceptionDecoding !String
- | SnmpExceptionSocketClosed
- | SnmpExceptionAuthenticationFailure !ByteString !ByteString
- | SnmpExceptionBadEngineId !MessageV3 !MessageV3
- | SnmpExceptionDecryptionFailure
- readTMVarTimeout :: Int -> TMVar a -> IO (Maybe a)
- fini :: TVar Bool -> STM ()
- nextRequestId :: TVar RequestId -> IO RequestId
- mySockFd :: Socket -> Fd
- hexByteStringInternal :: ByteString -> String
- inDebugMode :: Bool
Documentation
Session | |
|
data Destination Source #
Destination | |
|
data Credentials Source #
newtype CredentialsV2 Source #
openSession :: Config -> IO Session Source #
Only one connection can be open at a time on a given port.
closeSession :: Session -> IO () Source #
generalRequest :: (RequestId -> Pdus) -> (Pdu -> Either SnmpException a) -> Context -> IO (Either SnmpException a) Source #
throwSnmpException :: IO (Either SnmpException a) -> IO a Source #
get :: Context -> ObjectIdentifier -> IO ObjectSyntax Source #
getBulkStep :: Context -> Int -> ObjectIdentifier -> IO (Vector (ObjectIdentifier, ObjectSyntax)) Source #
getBulkChildren :: Context -> Int -> ObjectIdentifier -> IO (Vector (ObjectIdentifier, ObjectSyntax)) Source #
get' :: Context -> ObjectIdentifier -> IO (Either SnmpException ObjectSyntax) Source #
getBulkStep' :: Context -> Int -> ObjectIdentifier -> IO (Either SnmpException (Vector (ObjectIdentifier, ObjectSyntax))) Source #
getBulkChildren' :: Context -> Int -> ObjectIdentifier -> IO (Either SnmpException (Vector (ObjectIdentifier, ObjectSyntax))) Source #
oidIsPrefixOf :: ObjectIdentifier -> ObjectIdentifier -> Bool Source #
singleBindingValue :: ObjectIdentifier -> Vector VarBind -> Either SnmpException ObjectSyntax Source #
onlyBindings :: Pdu -> Either SnmpException (Vector VarBind) Source #
data SnmpException Source #
inDebugMode :: Bool Source #