module Monky.Network.Dynamic
( getUHandles
, UHandles
, Handles
, getMultiReadWrite
)
where
import Data.Bits ((.|.))
import Control.Monad (when)
import Control.Concurrent (forkIO, threadWaitRead)
import Data.IntMap.Strict (IntMap)
import qualified Data.IntMap.Strict as IM
import qualified Data.Map as M
import Data.IORef
import qualified Data.ByteString.Char8 as BS
import System.Linux.Netlink
import System.Linux.Netlink.Constants
import System.Linux.Netlink.Route
import Monky.Network.Static
#if MIN_VERSION_base(4,8,0)
#else
import Control.Applicative ((<$>))
#endif
data NetHandle = NetHandle String NetworkHandle
type Handles = IntMap NetHandle
type UHandles = (IORef Handles, String -> Bool)
instance Show NetHandle where
show (NetHandle x _) = x
foldF :: NetworkHandle -> IO (Maybe (Int, Int)) -> IO (Maybe (Int, Int))
foldF h o = do
m <- getReadWrite h
case m of
(Just (r, w)) -> do
om <- o
case om of
Just (oldr, oldw) -> return $ Just (oldr + r, oldw + w)
Nothing -> return $ Just (r, w)
Nothing -> o
getMultiReadWrite :: Handles -> IO (Maybe (Int, Int))
getMultiReadWrite =
IM.foldr (\(NetHandle _ v) -> foldF v) (return Nothing)
gotNew :: Int -> String -> Handles -> IO Handles
gotNew index name m =
case IM.lookup index m of
Nothing -> do
h <- getNetworkHandle name
return $IM.insert index (NetHandle name h) m
Just (NetHandle x v) -> if x == name
then return m
else do
h <- getNetworkHandle name
closeNetworkHandle v
return $IM.adjust (const (NetHandle name h)) index m
lostOld :: Int -> Handles -> IO Handles
lostOld index m = case IM.lookup index m of
Nothing -> return m
(Just (NetHandle _ h)) ->
closeNetworkHandle h >>
return (IM.delete index m)
requestPacket :: RoutePacket
requestPacket =
let flags = fNLM_F_REQUEST .|. fNLM_F_MATCH .|. fNLM_F_ROOT
header = Header eRTM_GETLINK flags 42 0
msg = NLinkMsg 0 0 0 in
Packet header msg M.empty
readInterface :: RoutePacket -> (Int, String)
readInterface (Packet _ msg attrs) =
let (Just name) = M.lookup eIFLA_IFNAME attrs
names = init $ BS.unpack name
index = interfaceIndex msg in
(fromIntegral index, names)
readInterface x = error ("Something went wrong while getting interfaces: " ++ show x)
getCurrentDevs :: IO [(Int, String)]
getCurrentDevs = do
sock <- makeSocket
ifs <- query sock requestPacket
closeSocket sock
return $map readInterface ifs
getNetworkHandles :: (String -> Bool) -> IO Handles
getNetworkHandles f = do
interfaces <- filter (f . snd) <$> getCurrentDevs
foldr build (return IM.empty) interfaces
where build (index, dev) m =
gotNew index dev =<< m
doUpdate :: UHandles -> RoutePacket -> IO ()
doUpdate (mr, f) (Packet hdr msg attrs)
| messageType hdr == eRTM_NEWLINK = do
let (Just name) = M.lookup eIFLA_IFNAME attrs
let names = init $BS.unpack name
when (f names) $ do
let index = interfaceIndex msg
m <- readIORef mr
nm <- gotNew (fromIntegral index) names m
writeIORef mr nm
| messageType hdr == eRTM_DELLINK = do
let index = interfaceIndex msg
m <- readIORef mr
nm <- lostOld (fromIntegral index) m
writeIORef mr nm
| otherwise = return ()
doUpdate _ _ = return ()
updaterLoop :: NetlinkSocket -> UHandles -> IO ()
updaterLoop sock h = do
threadWaitRead (getNetlinkFd sock)
packet <- recvOne sock :: IO [RoutePacket]
mapM_ (doUpdate h) packet
updaterLoop sock h
updater :: UHandles -> IO ()
updater h = do
sock <- makeSocket
joinMulticastGroup sock 1
updaterLoop sock h
getUHandles
:: (String -> Bool)
-> IO UHandles
getUHandles f = do
handle <- getNetworkHandles f
ref <- newIORef handle
_ <- forkIO (updater (ref, f))
return (ref, f)