summaryrefslogtreecommitdiffhomepage
path: root/Monitors/Cpu.hs
blob: b67f77294e71f49542873b38c0bdeaca6199cf04 (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
100
101
102
103
104
105
106
107
108
109
-----------------------------------------------------------------------------
-- |
-- Module      :  Monitors.Cpu
-- Copyright   :  (c) Andrea Rossato
-- License     :  BSD-style (see LICENSE)
-- 
-- Maintainer  :  Andrea Rossato <andrea.rossato@unibz.it>
-- Stability   :  unstable
-- Portability :  unportable
--
-- A cpu monitor for XMobar
--
-----------------------------------------------------------------------------

module Main where

import Numeric
import Control.Concurrent
import Text.ParserCombinators.Parsec


data Config = 
    Config { intervall :: Int
           , cpuNormal :: Integer
           , cpuNormalColor :: String
           , cpuCritical :: Integer
           , cpuCriticalColor :: String
           }

defaultConfig :: Config
defaultConfig = 
    Config { intervall = 500000
           , cpuNormal = 2
           , cpuNormalColor = "#00FF00" 
           , cpuCritical = 60
           , cpuCriticalColor = "#FF0000"  
           }

config :: Config
config = defaultConfig

-- Utilities

interSec :: IO ()
interSec = threadDelay  (intervall config)

takeDigits :: Int -> Float -> Float
takeDigits d n = 
    read $ showFFloat (Just d) n ""

floatToPercent :: Float -> String
floatToPercent n = 
    showFFloat (Just 2) (n*100) "%" 


run :: Parser [a] -> IO String -> IO [a]
run p input
        = do a <- input
             case (parse p "" a) of
               Left _ -> return []
               Right x  -> return x

fileCPU :: IO String
fileCPU = readFile "/proc/stat"


getNumbers :: Parser Float
getNumbers = skipMany space >> many1 digit >>= \n -> return $ read n

parserCPU :: Parser [Float]
parserCPU = string "cpu" >> count 4 getNumbers

parseCPU :: IO [Float]
parseCPU = 
    do a <- run parserCPU fileCPU
       interSec
       b <- run parserCPU fileCPU
       let dif = zipWith (-) b a
           tot = foldr (+) 0 dif
           percent = map (/ tot) dif
       return percent

formatCpu :: [Float] -> String 
formatCpu [] = ""
formatCpu (us:ni:sy:_)
    | x >= c = setColor z cpuCriticalColor
    | x >= n  = setColor z cpuNormalColor
    | otherwise = floatToPercent y
    where x = (us * 100) + (sy * 100) + (ni * 100)
          y = us + sy + ni
          z = floatToPercent y
          c = fromInteger (cpuCritical config)
          n = fromInteger (cpuNormal config)
formatCpu _ = ""

setColor :: String -> (Config -> String) -> String
setColor str ty =
    "<fc=" ++ ty config ++ ">" ++
    str ++ "</fc>"
    
cpu :: IO String
cpu = 
    do l <- parseCPU
       return $ "Cpu: " ++ formatCpu l

main :: IO ()
main =
    do c <- cpu
       putStrLn c