hans-3.0.1: Network Stack

Safe HaskellNone
LanguageHaskell2010

Hans

Contents

Synopsis

Network Stack

data Config Source #

General network stack configuration.

Constructors

Config 

Fields

newNetworkStack :: Config -> IO NetworkStack Source #

Create a network stack with no devices registered.

processPackets :: NetworkStack -> IO () Source #

Handle incoming packets.

Devices

data DeviceConfig Source #

Static configuration data for creating a device.

Constructors

DeviceConfig 

Fields

addDevice :: NetworkStack -> DeviceName -> DeviceConfig -> IO Device Source #

Initialize and register a device with the network stack. NOTE: this does not start the device.

listDevices :: IO [DeviceName] Source #

Not sure how this should work yet... Should it only ever show tap device names? Maybe this should return a singleton list of an ephemeral device?

closeDevice :: Device -> IO () Source #

Stop packets flowing, and cleanup any resources associated with this device.

startDevice :: Device -> IO () Source #

Start processing packets through this device.

Network Layer

data Addr Source #

Instances

Eq Addr Source # 

Methods

(==) :: Addr -> Addr -> Bool #

(/=) :: Addr -> Addr -> Bool #

Ord Addr Source # 

Methods

compare :: Addr -> Addr -> Ordering #

(<) :: Addr -> Addr -> Bool #

(<=) :: Addr -> Addr -> Bool #

(>) :: Addr -> Addr -> Bool #

(>=) :: Addr -> Addr -> Bool #

max :: Addr -> Addr -> Addr #

min :: Addr -> Addr -> Addr #

Show Addr Source # 

Methods

showsPrec :: Int -> Addr -> ShowS #

show :: Addr -> String #

showList :: [Addr] -> ShowS #

Generic Addr Source # 

Associated Types

type Rep Addr :: * -> * #

Methods

from :: Addr -> Rep Addr x #

to :: Rep Addr x -> Addr #

Hashable Addr Source # 

Methods

hashWithSalt :: Int -> Addr -> Int #

hash :: Addr -> Int #

NetworkAddr Addr Source # 
Network Addr Source # 
type Rep Addr Source # 
type Rep Addr = D1 (MetaData "Addr" "Hans.Addr.Types" "hans-3.0.1-KeOG55p4YoBGIRSfyF4N16" False) (C1 (MetaCons "Addr4" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 IP4)))

class (Hashable addr, Show addr, Typeable addr, Eq addr, Generic addr) => NetworkAddr addr where Source #

Methods

toAddr :: addr -> Addr Source #

Forget what kind of address this is.

fromAddr :: Addr -> Maybe addr Source #

Try to remember what this opaque address was.

isWildcardAddr :: addr -> Bool Source #

Check to see if this address is the wildcard address.

wildcardAddr :: addr -> addr Source #

The wildcard address

isBroadcastAddr :: addr -> Bool Source #

Check to see if this address is the broadcast address.

broadcastAddr :: addr -> addr Source #

The broadcast address.

class NetworkAddr addr => Network addr where Source #

Interaction with routing and message delivery for a network layer.

Minimal complete definition

pseudoHeader, lookupRoute, sendDatagram'

Methods

pseudoHeader :: addr -> addr -> NetworkProtocol -> Int -> PartialChecksum Source #

Calculate the pseudo-header for checksumming a packet at this layer of the network.

lookupRoute :: HasNetworkStack ns => ns -> addr -> IO (Maybe (RouteInfo addr)) Source #

Lookup a route to reach this destination address.

sendDatagram' :: HasNetworkStack ns => ns -> Device -> addr -> addr -> addr -> Bool -> NetworkProtocol -> ByteString -> IO () Source #

Send a single datagram to a destination.

data RouteInfo addr Source #

Information about how to reach a specific destination address (source and next-hop addresses, and device to use).

Constructors

RouteInfo 

Fields

  • riSource :: !addr

    The source address to use when sending

  • riNext :: !addr

    The next-hop in the route

  • riDev :: !Device

    The device used for delivery

Instances

Functor RouteInfo Source # 

Methods

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

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

Eq addr => Eq (RouteInfo addr) Source # 

Methods

(==) :: RouteInfo addr -> RouteInfo addr -> Bool #

(/=) :: RouteInfo addr -> RouteInfo addr -> Bool #

HasDeviceConfig (RouteInfo addr) Source # 

IP4

data IP4 Source #

Instances

Eq IP4 Source # 

Methods

(==) :: IP4 -> IP4 -> Bool #

(/=) :: IP4 -> IP4 -> Bool #

Ord IP4 Source # 

Methods

compare :: IP4 -> IP4 -> Ordering #

(<) :: IP4 -> IP4 -> Bool #

(<=) :: IP4 -> IP4 -> Bool #

(>) :: IP4 -> IP4 -> Bool #

(>=) :: IP4 -> IP4 -> Bool #

max :: IP4 -> IP4 -> IP4 #

min :: IP4 -> IP4 -> IP4 #

Read IP4 Source # 
Show IP4 Source # 

Methods

showsPrec :: Int -> IP4 -> ShowS #

show :: IP4 -> String #

showList :: [IP4] -> ShowS #

Generic IP4 Source # 

Associated Types

type Rep IP4 :: * -> * #

Methods

from :: IP4 -> Rep IP4 x #

to :: Rep IP4 x -> IP4 #

Serialize IP4 Source # 

Methods

put :: Putter IP4 #

get :: Get IP4 #

Hashable IP4 Source # 

Methods

hashWithSalt :: Int -> IP4 -> Int #

hash :: IP4 -> Int #

Checksum IP4 Source # 
CodecAtom IP4 Source # 
Option IP4 Source # 
NetworkAddr IP4 Source # 
Network IP4 Source # 
type Rep IP4 Source # 
type Rep IP4 = D1 (MetaData "IP4" "Hans.IP4.Packet" "hans-3.0.1-KeOG55p4YoBGIRSfyF4N16" True) (C1 (MetaCons "IP4" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)))

data Route Source #

Constructors

Route 

data RouteType Source #

Constructors

Direct 
Indirect !IP4 

addIP4Route :: NetworkStack -> Bool -> Route -> IO () Source #

Add a route to the IP4 layer.