summaryrefslogtreecommitdiffhomepage
diff options
context:
space:
mode:
authorAndrea Rossato <andrea.rossato@ing.unitn.it>2007-07-05 15:19:49 +0200
committerAndrea Rossato <andrea.rossato@ing.unitn.it>2007-07-05 15:19:49 +0200
commit39f9a1fc168196d4def8b87d0c7a5107b2b48e11 (patch)
tree7ae33e5f8a085511e626b2fff2cc3052e1fe1e79
parenta293fb98a6627215181e6ddeaebb94e612bfd3c9 (diff)
downloadxmobar-39f9a1fc168196d4def8b87d0c7a5107b2b48e11.tar.gz
xmobar-39f9a1fc168196d4def8b87d0c7a5107b2b48e11.tar.bz2
updated to use the new Common.hs and split the swap part in a new monitor
darcs-hash:20070705131949-d6583-b9f1ebb8b27f2de5d0b694b596375050629cc24a.gz
-rw-r--r--Monitors/Mem.hs98
1 files changed, 32 insertions, 66 deletions
diff --git a/Monitors/Mem.hs b/Monitors/Mem.hs
index d8bd601..87f53b1 100644
--- a/Monitors/Mem.hs
+++ b/Monitors/Mem.hs
@@ -14,86 +14,52 @@
module Main where
-import Numeric
+import Monitors.Common
-data Config =
- Config { memNormal :: Integer
- , memNormalColor :: String
- , memCritical :: Integer
- , memCriticalColor :: String
- , swapNormal :: Integer
- , swapNormalColor :: String
- , swapCritical :: Integer
- , swapCriticalColor :: String
- }
+import Data.IORef
-defaultConfig :: Config
-defaultConfig =
- Config { memNormal = 80
- , memNormalColor = "#00FF00"
- , memCritical = 90
- , memCriticalColor = "#FF0000"
- , swapNormal = 15
- , swapNormalColor = "#00FF00"
- , swapCritical = 50
- , swapCriticalColor = "#FF0000"
- }
-config :: Config
-config = defaultConfig
-
--- Utilities
-
-takeDigits :: Int -> Float -> Float
-takeDigits d n =
- read $ showFFloat (Just d) n ""
-
-floatToPercent :: Float -> String
-floatToPercent n =
- showFFloat (Just 2) (n*100) "%"
+monitorConfig :: IO MConfig
+monitorConfig =
+ do lc <- newIORef "#BFBFBF"
+ l <- newIORef 300
+ nc <- newIORef "#00FF00"
+ h <- newIORef 500
+ hc <- newIORef "#FF0000"
+ t <- newIORef "Mem: <usedratio>% (<cache>M)"
+ p <- newIORef package
+ u <- newIORef ""
+ a <- newIORef []
+ e <- newIORef ["total", "free", "buffer", "cache", "rest", "used", "usedratio"]
+ return $ MC nc l lc h hc t p u a e
fileMEM :: IO String
fileMEM = readFile "/proc/meminfo"
parseMEM :: IO [Float]
-parseMEM =
+parseMEM =
do file <- fileMEM
- let content = map words $ take 13 $ lines file
- [total, free, buffer, cache,_,_,_,_,_,_,_,swapTotal,swapFree] = map (\line -> (read $ line !! 1 :: Float) / 1024) content
+ let content = map words $ take 4 $ lines file
+ [total, free, buffer, cache] = map (\line -> (read $ line !! 1 :: Float) / 1024) content
rest = free + buffer + cache
used = total - rest
usedratio = used * 100 / total
- swapRatio = 100 - (swapFree / swapTotal * 100)
- return [total, free, buffer, cache, rest, used, usedratio, swapFree, swapRatio]
+ return [total, free, buffer, cache, rest, used, usedratio]
+formatMem :: [Float] -> Monitor [String]
+formatMem x =
+ do let f n = show (takeDigits 2 n)
+ mapM (showWithColors f) x
-formatMem :: [Float] -> String
-formatMem [] = ""
-formatMem (total:_:buffer:cach:_:used:_:_:swapRatio:_) =
- "Ram: " ++ ram ++ " cached: " ++ cache ++ " Swap: " ++ swap
- where (memN,memC,swapN,swapC) = (fromIntegral $ memNormal config,fromIntegral $ memCritical config
- , fromIntegral $ swapNormal config, fromIntegral $ swapCritical config)
- m = floatToPercent ((used + buffer + cach) / total)
- sw = show (takeDigits 2 swapRatio) ++ "%"
- cache = show (takeDigits 2 cach) ++ "Mb"
- ram | (used / total * 100) >= memC = setColor m memCriticalColor
- | (used / total * 100) >= memN = setColor m memNormalColor
- | otherwise = floatToPercent (used / total)
- swap | swapRatio >= swapC = setColor sw swapCriticalColor
- | swapRatio >= swapN = setColor sw swapNormalColor
- | otherwise = sw
-formatMem _ = ""
+package :: String
+package = "xmb-mem"
-setColor :: String -> (Config -> String) -> String
-setColor str ty =
- "<fc=" ++ ty config ++ ">" ++
- str ++ "</fc>"
+runMem :: [String] -> Monitor String
+runMem _ =
+ do m <- io $ parseMEM
+ l <- formatMem m
+ parseTemplate l
-mem :: IO String
-mem =
- do m <- parseMEM
- return $ formatMem m
-
main :: IO ()
main =
- do m <- mem
- putStrLn m \ No newline at end of file
+ do let af = runMem []
+ runMonitor monitorConfig af runMem