rtnetlink-0.2.0.1: Manipulate network devices, addresses, and routes on Linux

Copyright(c) Formaltech Inc. 2017
LicenseBSD3
Maintainerprotob3n@gmail.com
Stabilityexperimental
PortabilityLinux
Safe HaskellNone
LanguageHaskell2010

System.Linux.RTNetlink.Packet

Contents

Description

 
Synopsis

Low-level headers

data NLMsgHdr Source #

ADT corresponding to struct nlmsghdr from linux/netlink.h.

Constructors

NLMsgHdr 

Fields

Instances
Eq NLMsgHdr Source # 
Instance details

Defined in System.Linux.RTNetlink.Packet

Show NLMsgHdr Source # 
Instance details

Defined in System.Linux.RTNetlink.Packet

Serialize NLMsgHdr Source # 
Instance details

Defined in System.Linux.RTNetlink.Packet

Sized NLMsgHdr Source # 
Instance details

Defined in System.Linux.RTNetlink.Packet

Methods

size :: Integral i => NLMsgHdr -> i Source #

sizeAligned :: Integral a => a -> NLMsgHdr -> a Source #

nlMsgHdrIsError :: ByteString -> Bool Source #

Return True iff the message is an error, assuming the provided ByteString is headed by an NLMsgHdr.

splitMessages :: ByteString -> [ByteString] Source #

Split a ByteString into multiple messages using their NLMsgHdrs.

Attributes

data Attribute Source #

ADT representing a possibly nested netlink attribute.

Constructors

Attribute AttributeType ByteString

Simple attribute.

AttributeNest AttributeType [Attribute]

Nested attribute.

AttributePart AttributeType ByteString ByteString

Composable attribute.

type AttributeType = Word16 Source #

Type identifier for an Attribute.

attributeData :: Attribute -> Maybe ByteString Source #

Get the data from a simple Attribute.

findAttribute :: [AttributeType] -> AttributeList -> Maybe Attribute Source #

Search for an Attribute in a possibly nested list using the AttributeType to look for at each level. Unfortunately, the kernel does not presently seem to set NLA_F_NESTED on nested attribute types. Until this is changed in the kernel, we need to traverse nested elements manually.

findAttributeData :: [AttributeType] -> AttributeList -> Maybe ByteString Source #

Search for an Attribute and return its data field.

findAttributeDecode :: Serialize a => [AttributeType] -> AttributeList -> Maybe a Source #

Search for an Attribute; decode and return its data field.

findAttributeGet :: Get a -> [AttributeType] -> AttributeList -> Maybe a Source #

Search for an Attribute, run a getter on it, and return the result.

findAttributeCString :: [AttributeType] -> AttributeList -> Maybe ByteString Source #

Search for an Attribute and return its data field, minus any null bytes.

cStringAttr :: AttributeType -> ByteString -> Attribute Source #

Construct an Attribute with a null-byte-terminated string as data.

word32Attr :: AttributeType -> Word32 -> Attribute Source #

Construct an Attribute with a 32-bit word in host byte-order as data.

word32AttrPart :: AttributeType -> Word32 -> Word32 -> Attribute Source #

Composable Attribute with a 32-bit word in host byte-order as data. The second Word32 argument is a mask of bits we care about so that this attribute can be combined with others of the same type.

word16Attr :: AttributeType -> Word16 -> Attribute Source #

Construct an Attribute with a 16-bit word in host byte-order as data.

word16AttrPart :: AttributeType -> Word16 -> Word16 -> Attribute Source #

Composable Attribute with a 16-bit word in host byte-order as data. The second Word16 argument is a mask of bits we care about so that this attribute can be combined with others of the same type.

Sized data

class Sized s where Source #

Typeclass for data with a defined size. This lets us get sizes to use for constructing headers.

Minimal complete definition

size

Methods

size :: Integral i => s -> i Source #

Size of data.

sizeAligned :: Integral a => a -> s -> a Source #

Size of data with alignment padding added.

Instances
Sized () Source # 
Instance details

Defined in System.Linux.RTNetlink.Packet

Methods

size :: Integral i => () -> i Source #

sizeAligned :: Integral a => a -> () -> a Source #

Sized ByteString Source # 
Instance details

Defined in System.Linux.RTNetlink.Packet

Methods

size :: Integral i => ByteString -> i Source #

sizeAligned :: Integral a => a -> ByteString -> a Source #

Sized AttributeList Source # 
Instance details

Defined in System.Linux.RTNetlink.Packet

Sized Attribute Source # 
Instance details

Defined in System.Linux.RTNetlink.Packet

Methods

size :: Integral i => Attribute -> i Source #

sizeAligned :: Integral a => a -> Attribute -> a Source #

Sized NLMsgHdr Source # 
Instance details

Defined in System.Linux.RTNetlink.Packet

Methods

size :: Integral i => NLMsgHdr -> i Source #

sizeAligned :: Integral a => a -> NLMsgHdr -> a Source #

Sized NLMsgErr Source # 
Instance details

Defined in System.Linux.RTNetlink.Message

Methods

size :: Integral i => NLMsgErr -> i Source #

sizeAligned :: Integral a => a -> NLMsgErr -> a Source #

Sized IfInfoMsg Source # 
Instance details

Defined in System.Linux.RTNetlink.Link

Methods

size :: Integral i => IfInfoMsg -> i Source #

sizeAligned :: Integral a => a -> IfInfoMsg -> a Source #

Sized IfAddrMsg Source # 
Instance details

Defined in System.Linux.RTNetlink.Address

Methods

size :: Integral i => IfAddrMsg -> i Source #

sizeAligned :: Integral a => a -> IfAddrMsg -> a Source #

Sized header => Sized (NLMessage header) Source # 
Instance details

Defined in System.Linux.RTNetlink.Message

Methods

size :: Integral i => NLMessage header -> i Source #

sizeAligned :: Integral a => a -> NLMessage header -> a Source #

putAligned :: Integral a => a -> Putter ByteString Source #

Pad a ByteString to a given alignment.

Monoidal bit flags

data ChangeFlags a Source #

A flags bitfield encoded as a set of changes to an initial value, which can can be combined using the Monoid instance. This Monoid instance is *not* commutative. Flags set or cleared on the right will override those on the left.

Constructors

ChangeFlags 

Fields

  • cfFlags :: a

    Flag bits

  • cfMask :: a

    Mask of flag bits to use. Other bits will be ignored.

Instances
Bits a => Eq (ChangeFlags a) Source # 
Instance details

Defined in System.Linux.RTNetlink.Packet

Show a => Show (ChangeFlags a) Source # 
Instance details

Defined in System.Linux.RTNetlink.Packet

(Bits a, FiniteBits a) => Semigroup (ChangeFlags a) Source # 
Instance details

Defined in System.Linux.RTNetlink.Packet

(Bits a, FiniteBits a) => Monoid (ChangeFlags a) Source # 
Instance details

Defined in System.Linux.RTNetlink.Packet

applyChangeFlags :: Bits a => ChangeFlags a -> a -> a Source #

Apply a change to an existing flags bitfield.

applyChangeFlags' :: Bits a => ChangeFlags a -> a Source #

Apply a change to the all-zeroes bit field.

setChangeFlags :: Bits a => a -> ChangeFlags a Source #

Set cfFlags and cfMask to the same value.