diff options
Diffstat (limited to 'Plugins/Monitors')
| -rw-r--r-- | Plugins/Monitors/CoreCommon.hs | 41 | ||||
| -rw-r--r-- | Plugins/Monitors/CoreTemp.hs | 33 | ||||
| -rw-r--r-- | Plugins/Monitors/CpuFreq.hs | 33 | ||||
| -rw-r--r-- | Plugins/Monitors/Thermal.hs | 37 | 
4 files changed, 144 insertions, 0 deletions
diff --git a/Plugins/Monitors/CoreCommon.hs b/Plugins/Monitors/CoreCommon.hs new file mode 100644 index 0000000..de737d4 --- /dev/null +++ b/Plugins/Monitors/CoreCommon.hs @@ -0,0 +1,41 @@ +----------------------------------------------------------------------------- +-- | +-- Module      :  Plugins.Monitors.CoreCommon +-- Copyright   :  (c) Juraj Hercek +-- License     :  BSD-style (see LICENSE) +-- +-- Maintainer  :  Juraj Hercek <juhe_haskell@hck.sk> +-- Stability   :  unstable +-- Portability :  unportable +-- +-- The common part for cpu core monitors (e.g. cpufreq, coretemp) +-- +----------------------------------------------------------------------------- + +module Plugins.Monitors.CoreCommon where + +import Plugins.Monitors.Common +import System.Posix.Files (fileExist) +import System.Directory + +checkedDataRetrieval :: String -> String -> String -> String -> Double -> Monitor String +checkedDataRetrieval failureMessage dir file pattern divisor = do +    exists <- io $ fileExist $ foldl (++) dir ["/", pattern, "0/", file] +    case exists of +         False  -> return failureMessage +         True   -> retrieveData dir file pattern divisor + +retrieveData :: String -> String -> String -> Double -> Monitor String +retrieveData dir file pattern divisor = do +    count <- io $ dirCount dir pattern +    contents <- io $ mapM readFile $ files count +    values <- mapM (showWithColors show) $ map conversion contents +    parseTemplate values +    where +        dirCount path str = getDirectoryContents path +                            >>= return . length +                                       . filter ((str ==) . take (length str)) +        files count = [ foldl (++) dir [ "/", pattern, show i, "/", file ] +                      | i <- [0 .. count - 1] ] +        conversion = flip (/) divisor . (read :: String -> Double) + diff --git a/Plugins/Monitors/CoreTemp.hs b/Plugins/Monitors/CoreTemp.hs new file mode 100644 index 0000000..e59f0d3 --- /dev/null +++ b/Plugins/Monitors/CoreTemp.hs @@ -0,0 +1,33 @@ +----------------------------------------------------------------------------- +-- | +-- Module      :  Plugins.Monitors.CoreTemp +-- Copyright   :  (c) Juraj Hercek +-- License     :  BSD-style (see LICENSE) +-- +-- Maintainer  :  Juraj Hercek <juhe_haskell@hck.sk> +-- Stability   :  unstable +-- Portability :  unportable +-- +-- A core temperature monitor for Xmobar +-- +----------------------------------------------------------------------------- + +module Plugins.Monitors.CoreTemp where + +import Plugins.Monitors.Common +import Plugins.Monitors.CoreCommon + +coreTempConfig :: IO MConfig +coreTempConfig = mkMConfig +       "Temp: <core0>C" -- template +       (zipWith (++) (repeat "core") (map show [0 :: Int ..])) -- available +                                                               -- replacements +runCoreTemp :: [String] -> Monitor String +runCoreTemp _ = do +    let dir = "/sys/bus/platform/devices" +        file = "temp1_input" +        pattern = "coretemp." +        divisor = 1e3 :: Double +        failureMessage = "CoreTemp: N/A" +    checkedDataRetrieval failureMessage dir file pattern divisor + diff --git a/Plugins/Monitors/CpuFreq.hs b/Plugins/Monitors/CpuFreq.hs new file mode 100644 index 0000000..0258037 --- /dev/null +++ b/Plugins/Monitors/CpuFreq.hs @@ -0,0 +1,33 @@ +----------------------------------------------------------------------------- +-- | +-- Module      :  Plugins.Monitors.CpuFreq +-- Copyright   :  (c) Juraj Hercek +-- License     :  BSD-style (see LICENSE) +-- +-- Maintainer  :  Juraj Hercek <juhe_haskell@hck.sk> +-- Stability   :  unstable +-- Portability :  unportable +-- +-- A cpu frequency monitor for Xmobar +-- +----------------------------------------------------------------------------- + +module Plugins.Monitors.CpuFreq where + +import Plugins.Monitors.Common +import Plugins.Monitors.CoreCommon + +cpuFreqConfig :: IO MConfig +cpuFreqConfig = mkMConfig +       "Freq: <core0>GHz" -- template +       (zipWith (++) (repeat "core") (map show [0 :: Int ..])) -- available +                                                               -- replacements +runCpuFreq :: [String] -> Monitor String +runCpuFreq _ = do +    let dir = "/sys/devices/system/cpu" +        file = "cpufreq/scaling_cur_freq" +        pattern = "cpu" +        divisor = 1e6 :: Double +        failureMessage = "CpuFreq: N/A" +    checkedDataRetrieval failureMessage dir file pattern divisor + diff --git a/Plugins/Monitors/Thermal.hs b/Plugins/Monitors/Thermal.hs new file mode 100644 index 0000000..2794a60 --- /dev/null +++ b/Plugins/Monitors/Thermal.hs @@ -0,0 +1,37 @@ +----------------------------------------------------------------------------- +-- | +-- Module      :  Plugins.Monitors.Thermal +-- Copyright   :  (c) Juraj Hercek +-- License     :  BSD-style (see LICENSE) +-- +-- Maintainer  :  Juraj Hercek <juhe_haskell@hck.sk> +-- Stability   :  unstable +-- Portability :  unportable +-- +-- A thermal monitor for Xmobar +-- +----------------------------------------------------------------------------- + +module Plugins.Monitors.Thermal where + +import qualified Data.ByteString.Lazy.Char8 as B +import Plugins.Monitors.Common +import System.Posix.Files (fileExist) + +thermalConfig :: IO MConfig +thermalConfig = mkMConfig +       "Thm: <temp>C" -- template +       ["temp"]       -- available replacements + +runThermal :: [String] -> Monitor String +runThermal _ = do +    let file = "/proc/acpi/thermal_zone/THM/temperature" +    exists <- io $ fileExist file +    case exists of +         False  -> return "Thermal: N/A" +         True   -> do number <- io $ B.readFile file +                                     >>= return . (read :: String -> Int) +                                                . stringParser (1, 0) +                      thermal <- showWithColors show number +                      parseTemplate [  thermal ] +  | 
