Maintainer | ongy |
---|---|
Stability | testing |
Portability | Linux |
Safe Haskell | None |
Language | Haskell2010 |
This is the base module for the netlink package. It contains functions and datatype used by every netlink module. All definitions are (supposed to be) generic enough to be used by implementations of more specific netlink interfaces.
- data Header = Header {
- messageType :: MessageType
- messageFlags :: Word16
- messageSeqNum :: Word32
- messagePID :: Word32
- type Attributes = Map Int ByteString
- data Packet a
- = Packet { }
- | ErrorMsg {
- packetHeader :: Header
- packetError :: CInt
- errorPacket :: Packet a
- | DoneMsg { }
- class Convertable a where
- data NoData = NoData
- data NetlinkSocket
- getPacket :: ByteString -> Get a -> Either String [a]
- getAttributes :: Get Attributes
- getHeader :: Get (Int, Header)
- putHeader :: Int -> Header -> Put
- putAttributes :: Attributes -> Put
- putPacket :: (Convertable a, Eq a, Show a) => Packet a -> [ByteString]
- getPackets :: (Convertable a, Eq a, Show a) => ByteString -> Either String [Packet a]
- makeSocket :: IO NetlinkSocket
- makeSocketGeneric :: Int -> IO NetlinkSocket
- getNetlinkFd :: NetlinkSocket -> Fd
- closeSocket :: NetlinkSocket -> IO ()
- joinMulticastGroup :: NetlinkSocket -> Word32 -> IO ()
- query :: (Convertable a, Eq a, Show a) => NetlinkSocket -> Packet a -> IO [Packet a]
- queryOne :: (Convertable a, Eq a, Show a) => NetlinkSocket -> Packet a -> IO (Packet a)
- recvOne :: (Convertable a, Eq a, Show a) => NetlinkSocket -> IO [Packet a]
- showNLAttrs :: Attributes -> String
- showAttrs :: (Int -> String) -> Attributes -> String
- showAttr :: (Int -> String) -> (Int, ByteString) -> String
- showPacket :: Show a => Packet a -> String
Documentation
Data type for the netlink header
Header | |
|
type Attributes = Map Int ByteString Source #
Type used for netlink attributes
The generic netlink message type
Packet | |
| |
ErrorMsg | |
| |
DoneMsg | |
|
class Convertable a where Source #
Typeclase used by the system. Basically Storable
for Get
and Put
getGet Returns a Get
function for the convertable.
The MessageType is passed so that the function can parse different data structures based on the message type.
Convertable NoData Source # | |
Convertable Message Source # | |
Convertable GenlHeader Source # | The |
Convertable a => Convertable (GenlData a) Source # | The |
Datatype to be used when there is no additional static header
data NetlinkSocket Source #
Typesafe wrapper around a CInt
(fd)
:: ByteString | The buffer to read from |
-> Get a | The function to read a single message |
-> Either String [a] | Either an error message or a list of messages read |
Read packets from the buffer
getAttributes :: Get Attributes Source #
Get
Attributes
putAttributes :: Attributes -> Put Source #
Put
a Map
of Attributes
putPacket :: (Convertable a, Eq a, Show a) => Packet a -> [ByteString] Source #
getPackets :: (Convertable a, Eq a, Show a) => ByteString -> Either String [Packet a] Source #
Read all Packet
s from a buffer
The packets may have additional static data defined by the protocol.
makeSocket :: IO NetlinkSocket Source #
Open and return a NetlinkSocket
, for legacy reasons this opens a route socket
:: Int | The netlink family to use |
-> IO NetlinkSocket |
Open a NetlinkSocket
. This is the generic function
getNetlinkFd :: NetlinkSocket -> Fd Source #
Get the raw Fd
used for netlink communcation (this can be plugged into eventing)
closeSocket :: NetlinkSocket -> IO () Source #
Close a NetlinkSocket
when it is no longer used
:: NetlinkSocket | The socket to join with |
-> Word32 | The id of the group to join |
-> IO () |
Join a netlink multicast group
query :: (Convertable a, Eq a, Show a) => NetlinkSocket -> Packet a -> IO [Packet a] Source #
Query data over netlink.
This sends a Packet
over netlink and returns the answer.
This blocks in a safe foregin function until the other side replies.
queryOne :: (Convertable a, Eq a, Show a) => NetlinkSocket -> Packet a -> IO (Packet a) Source #
The same as query
but requires the answer to be a single message
recvOne :: (Convertable a, Eq a, Show a) => NetlinkSocket -> IO [Packet a] Source #
Calls recvmsg once and returns all received messages
This should only be used outside of the package when reading multicast messages.
The prototype of this function is unintuitive, but this cannot be avoided without buffering in userspace with the netlink api.
showNLAttrs :: Attributes -> String Source #
Convert generic NLAttrs into a string (# and hexdump)
:: (Int -> String) | A function from element id to its name |
-> Attributes | The attributes |
-> String | A string with Element name and hexdump of element |
Helper function to convert attributes into a string