module Hans.Layer.Ethernet (
EthernetHandle
, runEthernetLayer
, Tx
, Rx
, sendEthernet
, queueEthernet
, addEthernetDevice
, removeEthernetDevice
, addEthernetHandler
, removeEthernetHandler
, startEthernetDevice
, stopEthernetDevice
) where
import Hans.Address.Mac
import Hans.Channel
import Hans.Layer
import Hans.Message.EthernetFrame
import Hans.Utils (void,just)
import Control.Concurrent (forkIO,ThreadId,killThread)
import Control.Monad (mplus)
import MonadLib (get,set)
import qualified Data.ByteString.Lazy as L
import qualified Data.Map as Map
import qualified Data.ByteString as S
type Handler = S.ByteString -> IO ()
type Tx = L.ByteString -> IO ()
type Rx = EthernetHandle -> IO ()
type EthernetHandle = Channel (Eth ())
runEthernetLayer :: EthernetHandle -> IO ()
runEthernetLayer h =
void (forkIO (loopLayer "ethernet" (emptyEthernetState h) (receive h) id))
sendEthernet :: EthernetHandle -> EthernetFrame -> L.ByteString -> IO ()
sendEthernet h !frame body = send h (handleOutgoing frame body)
queueEthernet :: EthernetHandle -> S.ByteString -> IO ()
queueEthernet h !pkt = send h (handleIncoming pkt)
startEthernetDevice :: EthernetHandle -> Mac -> IO ()
startEthernetDevice h !m = send h (startDevice m)
stopEthernetDevice :: EthernetHandle -> Mac -> IO ()
stopEthernetDevice h !m = send h (stopDevice m)
addEthernetDevice :: EthernetHandle -> Mac -> Tx -> Rx -> IO ()
addEthernetDevice h !mac tx rx = send h (addDevice mac tx rx)
removeEthernetDevice :: EthernetHandle -> Mac -> IO ()
removeEthernetDevice h !mac = send h (delDevice mac)
addEthernetHandler :: EthernetHandle -> EtherType -> Handler -> IO ()
addEthernetHandler h !et k = send h (addHandler et k)
removeEthernetHandler :: EthernetHandle -> EtherType -> IO ()
removeEthernetHandler h !et = send h (removeHandler et)
data EthernetDevice = EthernetDevice
{ devTx :: Tx
, devRx :: IO ()
, devUp :: Maybe ThreadId
}
emptyDevice :: Tx -> IO () -> EthernetDevice
emptyDevice tx rx = EthernetDevice
{ devTx = tx
, devRx = rx
, devUp = Nothing
}
type Eth = Layer EthernetState
data EthernetState = EthernetState
{ ethHandlers :: Handlers EtherType Handler
, ethDevices :: Map.Map Mac EthernetDevice
, ethHandle :: EthernetHandle
}
instance ProvidesHandlers EthernetState EtherType Handler where
getHandlers = ethHandlers
setHandlers hs i = i { ethHandlers = hs }
emptyEthernetState :: EthernetHandle -> EthernetState
emptyEthernetState h = EthernetState
{ ethHandlers = emptyHandlers
, ethDevices = Map.empty
, ethHandle = h
}
self :: Eth EthernetHandle
self = ethHandle `fmap` get
handleIncoming :: S.ByteString -> Eth ()
handleIncoming pkt = do
(hdr,body) <- liftRight (parseEthernetFrame pkt)
h <- getHandler (etherType hdr)
output (h body)
getDevice :: Mac -> Eth EthernetDevice
getDevice mac = do
state <- get
just (Map.lookup mac (ethDevices state))
setDevice :: Mac -> EthernetDevice -> Eth ()
setDevice mac dev = do
state <- get
let ds' = Map.insert mac dev (ethDevices state)
ds' `seq` set state { ethDevices = ds' }
handleOutgoing :: EthernetFrame -> L.ByteString -> Eth ()
handleOutgoing frame body = do
dev <- getDevice (etherSource frame)
output (devTx dev (renderEthernetFrame frame body))
addDevice :: Mac -> Tx -> Rx -> Eth ()
addDevice mac tx rx = do
stopDevice mac `mplus` return ()
h <- self
setDevice mac (emptyDevice tx (rx h))
delDevice :: Mac -> Eth ()
delDevice mac = do
stopDevice mac
state <- get
let ds' = Map.delete mac (ethDevices state)
ds' `seq` set state { ethDevices = ds' }
stopDevice :: Mac -> Eth ()
stopDevice mac = do
dev <- getDevice mac
case devUp dev of
Nothing -> return ()
Just tid -> do
output (killThread tid)
setDevice mac dev { devUp = Nothing }
startDevice :: Mac -> Eth ()
startDevice mac = do
dev <- getDevice mac
case devUp dev of
Just _ -> return ()
Nothing -> output (void (forkIO (devRx dev)))