rtnetlink-0.1.0.3: 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

Contents

Description

RTNetlink is an extensible, high-level, pure Haskell interface for manipulating network interfaces on Linux: creating and destroying interfaces, changing and dumping interface settings, adding and removing addresses.

The core interface of RTNetlink is the RTNL monad. RTNL handles the heavy lifting of opening and closing netlink sockets, incrementing sequence numbers, and getting the responses for the current sequence number behind the scenes. Messages not that are not responses to a sent message, such as those sent to group subscribers, are stored in the backlog and can be retrieved with getBacklog.

The basic way to use RTNL is to use the create, destroy, dump, and change convenience functions. If you want more control, you can use talk and talk_. Import modules like System.Linux.RTNetlink.Link to get access to prefab instances of Create and Destroy messages, etc. Or import System.Linux.RTNetlink.Message to get access to the core typeclasses and create your own messages. System.Linux.RTNetlink.Packet has a number of functions to make this easier.

Example:

  
  module Main where

  import System.Linux.RTNetlink
  import System.Linux.RTNetlink.Link
  import Control.Monad (when)
  
  main :: IO ()
  main = runRTNL $ do
      let mybridge = LinkName "mybridge"
      create (Bridge mybridge)
      change mybridge Up
      state <- dump mybridge
      when (head state == Up) $
          liftIO (putStrLn "I did it, mom!")
      destroy mybridge

Synopsis

The RTNL monad

data RTNL a Source #

RTNL monad to simplify netlink communication.

Instances

Monad RTNL Source # 

Methods

(>>=) :: RTNL a -> (a -> RTNL b) -> RTNL b #

(>>) :: RTNL a -> RTNL b -> RTNL b #

return :: a -> RTNL a #

fail :: String -> RTNL a #

Functor RTNL Source # 

Methods

fmap :: (a -> b) -> RTNL a -> RTNL b #

(<$) :: a -> RTNL b -> RTNL a #

Applicative RTNL Source # 

Methods

pure :: a -> RTNL a #

(<*>) :: RTNL (a -> b) -> RTNL a -> RTNL b #

(*>) :: RTNL a -> RTNL b -> RTNL b #

(<*) :: RTNL a -> RTNL b -> RTNL a #

MonadIO RTNL Source # 

Methods

liftIO :: IO a -> RTNL a #

tryRTNL :: RTNL a -> IO (Either String a) Source #

Run an RTNL function and catch all IOErrors. This means that functions in this module are guaranteed not to throw uncaught exceptions.

runRTNL :: RTNL a -> IO a Source #

Run an RTNL function. RTNL functions in this module throw exclusively IOErrors.

runRTNLGroups :: [RTNetlinkGroup] -> RTNL a -> IO a Source #

Run an RTNL function and specify some groups to subscribe to.

High-level communication

create :: Create c => c -> RTNL () Source #

Send a Create message and ignore non-error Replys.

destroy :: Destroy d => d -> RTNL () Source #

Send a Destroy message and ignore non-error Replys.

dump :: (Request q, Reply r) => q -> RTNL [r] Source #

Send a Request and receive the associated Replys.

change :: Change id c => id -> c -> RTNL () Source #

Send a Change message and ignore non-error Replys.

getBacklog :: Reply r => RTNL [r] Source #

Get all the Replys of a particular type in the backlog and queued on the socket.

clearBacklog :: RTNL () Source #

Clear the backlog.

Lower-level communication

talk :: (Header h, Reply r) => (SequenceNumber -> NLMessage h) -> RTNL [r] Source #

Send any NLMessage and receive a list of Replys.

If the ReplyTypeNumbers of the return type do not include NLM_ERROR, any non-zero error messages received will be thrown as IOErrors. Responses that don't parse as the return type will be ignored.

talk_ :: Header h => (SequenceNumber -> NLMessage h) -> RTNL () Source #

Like talk, but discards non-error Replys.

talkRaw :: ByteString -> RTNL [ByteString] Source #

Lowest-level RTNL function. Send a BytsString and receive all responses and queued messages as ByteStrings.

_Note:_ This function does nothing to manage sequence numbers or distinguish between responses and queued messages. Nothing will be added to the backlog.

Utility functions

liftIO :: MonadIO m => forall a. IO a -> m a #

Lift a computation from the IO monad.