From a8653d8712c2d218adf3f70cef7e511060bed695 Mon Sep 17 00:00:00 2001 From: Andrea Rossato Date: Wed, 18 Jul 2007 17:12:11 +0200 Subject: Monitors are now a Plugin that can be removed from Config.hs darcs-hash:20070718151211-d6583-7e0e49c22d07feda72d03370fd592c196dfcc9c1.gz --- Plugins/Monitors/Net.hs | 99 +++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 99 insertions(+) create mode 100644 Plugins/Monitors/Net.hs (limited to 'Plugins/Monitors/Net.hs') diff --git a/Plugins/Monitors/Net.hs b/Plugins/Monitors/Net.hs new file mode 100644 index 0000000..8534a2a --- /dev/null +++ b/Plugins/Monitors/Net.hs @@ -0,0 +1,99 @@ +----------------------------------------------------------------------------- +-- | +-- Module : Plugins.Monitors.Net +-- Copyright : (c) Andrea Rossato +-- License : BSD-style (see LICENSE) +-- +-- Maintainer : Andrea Rossato +-- Stability : unstable +-- Portability : unportable +-- +-- A net device monitor for Xmobar +-- +----------------------------------------------------------------------------- + +module Plugins.Monitors.Net where + +import Plugins.Monitors.Common +import qualified Data.ByteString.Lazy.Char8 as B + +data NetDev = NA + | ND { netDev :: String + , netRx :: Float + , netTx :: Float + } deriving (Eq,Show,Read) + +interval :: Int +interval = 500000 + +netConfig :: IO MConfig +netConfig = mkMConfig + ": |" -- template + ["dev", "rx", "tx"] -- available replacements + + +-- takes two elements of a list given their indexes +getTwoElementsAt :: Int -> Int -> [a] -> [a] +getTwoElementsAt x y xs = + z : [zz] + where z = xs !! x + zz = xs !! y + +-- split a list of strings returning a list with: 1. the first part of +-- the split; 2. the second part of the split without the Char; 3. the +-- rest of the list. For instance: +-- +-- > splitAtChar ':' ["lo:31174097","31174097"] +-- +-- will become ["lo","31174097","31174097"] +splitAtChar :: Char -> [String] -> [String] +splitAtChar c xs = + first : (rest xs) + where rest = map $ \x -> if (c `elem` x) then (tail $ dropWhile (/= c) x) else x + first = head $ map (takeWhile (/= c)) . filter (\x -> (c `elem` x)) $ xs + +readNetDev :: [String] -> NetDev +readNetDev [] = NA +readNetDev xs = + ND (xs !! 0) (r (xs !! 1)) (r (xs !! 2)) + where r s | s == "" = 0 + | otherwise = (read s) / 1024 + +fileNET :: IO [NetDev] +fileNET = + do f <- B.readFile "/proc/net/dev" + return $ netParser f + +netParser :: B.ByteString -> [NetDev] +netParser = + map readNetDev . map (splitAtChar ':') . map (getTwoElementsAt 0 8) . map (words . B.unpack) . drop 2 . B.lines + +formatNet :: Float -> Monitor String +formatNet d = + showWithColors f d + where f s = show s ++ "Kb" + +printNet :: NetDev -> Monitor String +printNet nd = + do case nd of + ND d r t -> do rx <- formatNet r + tx <- formatNet t + parseTemplate [d,rx,tx] + NA -> return "N/A" + +parseNET :: String -> IO [NetDev] +parseNET nd = + do (a,b) <- doActionTwiceWithDelay interval fileNET + let netRate f da db = takeDigits 2 $ ((f db) - (f da)) * fromIntegral (1000000 `div` interval) + diffRate (da,db) = ND (netDev da) + (netRate netRx da db) + (netRate netTx da db) + return $ filter (\d -> netDev d == nd) $ map diffRate $ zip a b + +runNet :: [String] -> Monitor String +runNet nd = + do pn <- io $ parseNET $ head nd + n <- case pn of + [x] -> return x + _ -> return $ NA + printNet n -- cgit v1.2.3