-----------------------------------------------------------------------------
-- |
-- 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 temperature monitor that works with AMD CPUs for Xmobar
--
-----------------------------------------------------------------------------

module Xmobar.Plugins.Monitors.K10Temp where

import Xmobar.Plugins.Monitors.Common

-- |
-- K10 temperature default configuration. Default template contains only the
-- die temperature, user should specify custom template in order to get more
-- ccd or IO die temperatures.
k10TempConfig :: IO MConfig
k10TempConfig :: IO MConfig
k10TempConfig = String -> [String] -> IO MConfig
mkMConfig
       String
"Temp: <Tdie>C" -- template
       [String
"Tctl", String
"Tdie", String
"Tccd1", String
"Tccd2", String
"Tccd3"
       ,String
"Tccd4", String
"Tccd5", String
"Tccd6", String
"Tccd7", String
"Tccd8"
       ] -- available replacements

-- |
-- Function retrieves monitor string holding the temperature
-- (or temperatures)
runK10Temp :: [String] -> Monitor String
runK10Temp :: [String] -> Monitor String
runK10Temp [String]
args = 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 slot :: String
slot = [String] -> String
forall a. [a] -> a
head [String]
args
       path :: [String]
path = [String
"/sys/bus/pci/drivers/k10temp/" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
slot String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/hwmon/hwmon", String
"/temp", String
"_input"]
       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] Maybe (String, String -> Int)
forall a. Maybe a
Nothing (Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
divisor) Double -> String
show'