-----------------------------------------------------------------------------
-- |
-- 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 Xmobar.Plugins.Monitors.CoreTemp where

import Xmobar.Plugins.Monitors.Common

import Data.Char (isDigit)

-- |
-- Core temperature default configuration. Default template contains only one
-- core temperature, user should specify custom template in order to get more
-- core frequencies.
coreTempConfig :: IO MConfig
coreTempConfig :: IO MConfig
coreTempConfig = String -> [String] -> IO MConfig
mkMConfig
       String
"Temp: <core0>C" -- template
       ((Int -> String) -> [Int] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String -> String -> String
forall a. [a] -> [a] -> [a]
(++) String
"core" (String -> String) -> (Int -> String) -> Int -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show) [Int
0 :: Int ..]) -- available replacements

-- |
-- Function retrieves monitor string holding the core temperature
-- (or temperatures)
runCoreTemp :: [String] -> Monitor String
runCoreTemp :: [String] -> Monitor String
runCoreTemp [String]
_ = do
   Int
dn <- Selector Int -> Monitor Int
forall a. Selector a -> Monitor a
getConfigValue Selector Int
decDigits
   String
failureMessage <- Selector String -> Monitor String
forall a. Selector a -> Monitor a
getConfigValue Selector String
naString
   let path :: [String]
path = [String
"/sys/bus/platform/devices/coretemp.", String
"/temp", String
"_input"]
       path' :: [String]
path' = [String
"/sys/bus/platform/devices/coretemp.", String
"/hwmon/hwmon", String
"/temp", String
"_input"]
       lbl :: Maybe (String, String -> Int)
lbl  = (String, String -> Int) -> Maybe (String, String -> Int)
forall a. a -> Maybe a
Just (String
"_label", String -> Int
forall a. Read a => String -> a
read (String -> Int) -> (String -> String) -> String -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isDigit))
       divisor :: Double
divisor = Double
1e3 :: Double
       show' :: Double -> String
show' = Int -> Double -> String
forall a. RealFloat a => Int -> a -> String
showDigits (Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 Int
dn)
   String
-> [[String]]
-> Maybe (String, String -> Int)
-> (Double -> Double)
-> (Double -> String)
-> Monitor String
forall a.
(Ord a, Num a) =>
String
-> [[String]]
-> Maybe (String, String -> Int)
-> (Double -> a)
-> (a -> String)
-> Monitor String
checkedDataRetrieval String
failureMessage [[String]
path, [String]
path'] Maybe (String, String -> Int)
lbl (Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
divisor) Double -> String
show'