summaryrefslogtreecommitdiffhomepage
path: root/Plugins/Monitors/Net.hs
blob: 6a7f01f499c0e30daa9ae2b753ef1f88f0011c0e (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
-----------------------------------------------------------------------------
-- |
-- Module      :  Plugins.Monitors.Net
-- Copyright   :  (c) Andrea Rossato
-- License     :  BSD-style (see LICENSE)
-- 
-- Maintainer  :  Andrea Rossato <andrea.rossato@unibz.it>
-- 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
    "<dev>: <rx>|<tx>"      -- 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 = showDigits 1 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