| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Hans
- data NetworkStack
 - data Config = Config {
- cfgInputQueueSize :: !Int
 - cfgArpTableSize :: !Int
 - cfgArpTableLifetime :: !NominalDiffTime
 - cfgArpRetry :: !Int
 - cfgArpRetryDelay :: !Int
 - cfgIP4FragTimeout :: !NominalDiffTime
 - cfgIP4InitialTTL :: !Word8
 - cfgIP4MaxFragTableEntries :: !Int
 - cfgUdpSocketTableSize :: !Int
 - cfgDnsResolveTimeout :: !Int
 - cfgTcpListenTableSize :: !Int
 - cfgTcpActiveTableSize :: !Int
 - cfgTcpTimeoutTimeWait :: !NominalDiffTime
 - cfgTcpInitialMSS :: !Int
 - cfgTcpMaxSynBacklog :: !Int
 - cfgTcpInitialWindow :: !Int
 - cfgTcpMSL :: !Int
 - cfgTcpTSClockFrequency :: !NominalDiffTime
 - cfgTcpTimeWaitSocketLimit :: !Int
 - cfgNatMaxEntries :: !Int
 
 - defaultConfig :: Config
 - newNetworkStack :: Config -> IO NetworkStack
 - processPackets :: NetworkStack -> IO ()
 - type DeviceName = ByteString
 - data Device
 - data DeviceConfig = DeviceConfig {
- dcSendQueueLen :: !Int
 - dcTxOffload :: !ChecksumOffload
 - dcRxOffload :: !ChecksumOffload
 - dcMtu :: !Int
 
 - defaultDeviceConfig :: DeviceConfig
 - addDevice :: NetworkStack -> DeviceName -> DeviceConfig -> IO Device
 - listDevices :: IO [DeviceName]
 - closeDevice :: Device -> IO ()
 - startDevice :: Device -> IO ()
 - data Addr
 - sameFamily :: Addr -> Addr -> Bool
 - class (Hashable addr, Show addr, Typeable addr, Eq addr, Generic addr) => NetworkAddr addr where
 - class NetworkAddr addr => Network addr where
 - data RouteInfo addr = RouteInfo {}
 - data IP4
 - packIP4 :: Word8 -> Word8 -> Word8 -> Word8 -> IP4
 - unpackIP4 :: IP4 -> (Word8, Word8, Word8, Word8)
 - data IP4Mask = IP4Mask !IP4 !Int
 - data Route = Route {
- routeNetwork :: !IP4Mask
 - routeType :: !RouteType
 - routeDevice :: !Device
 
 - data RouteType
 - addIP4Route :: NetworkStack -> Bool -> Route -> IO ()
 
Network Stack
data NetworkStack Source #
Instances
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
type DeviceName = ByteString Source #
data DeviceConfig Source #
Static configuration data for creating a device.
Constructors
| DeviceConfig | |
Fields 
  | |
Instances
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
class (Hashable addr, Show addr, Typeable addr, Eq addr, Generic addr) => NetworkAddr addr where Source #
Minimal complete definition
toAddr, fromAddr, isWildcardAddr, wildcardAddr, isBroadcastAddr, broadcastAddr
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.
Instances
class NetworkAddr addr => Network addr where Source #
Interaction with routing and message delivery for a network layer.
Minimal complete definition
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.
Information about how to reach a specific destination address (source and next-hop addresses, and device to use).
Constructors
| RouteInfo | |
IP4
Constructors
| Route | |
Fields 
  | |
addIP4Route :: NetworkStack -> Bool -> Route -> IO () Source #
Add a route to the IP4 layer.