{-# LANGUAGE TupleSections #-}
-----------------------------------------------------------------------------
-- |
-- Module      : System.Taffybar.Information.CPU2
-- Copyright   : (c) José A. Romero L.
-- License     : BSD3-style (see LICENSE)
--
-- Maintainer  : José A. Romero L. <escherdragon@gmail.com>
-- Stability   : unstable
-- Portability : unportable
--
-- Provides information about used CPU times, obtained from parsing the
-- @\/proc\/stat@ file using some of the facilities included in the
-- "System.Taffybar.Information.StreamInfo" module.
-- And also provides information about the temperature of cores.
-- (Now supports only physical cpu).
--
-----------------------------------------------------------------------------

module System.Taffybar.Information.CPU2 where

import Control.Monad
import Data.List
import Data.Maybe
import Safe
import System.Directory
import System.FilePath
import System.Taffybar.Information.StreamInfo

-- | Returns a list of 5 to 7 elements containing all the values available for
-- the given core (or all of them aggregated, if "cpu" is passed).
getCPUInfo :: String -> IO [Int]
getCPUInfo :: FilePath -> IO [Int]
getCPUInfo = FilePath
-> (FilePath -> [(FilePath, [Int])]) -> FilePath -> IO [Int]
forall a.
FilePath -> (FilePath -> [(FilePath, [a])]) -> FilePath -> IO [a]
getParsedInfo FilePath
"/proc/stat" FilePath -> [(FilePath, [Int])]
parse

parse :: String -> [(String, [Int])]
parse :: FilePath -> [(FilePath, [Int])]
parse = (FilePath -> Maybe (FilePath, [Int]))
-> [FilePath] -> [(FilePath, [Int])]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe ([FilePath] -> Maybe (FilePath, [Int])
tuplize ([FilePath] -> Maybe (FilePath, [Int]))
-> (FilePath -> [FilePath]) -> FilePath -> Maybe (FilePath, [Int])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> [FilePath]
words) ([FilePath] -> [(FilePath, [Int])])
-> (FilePath -> [FilePath]) -> FilePath -> [(FilePath, [Int])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
filter (\FilePath
x -> Int -> FilePath -> FilePath
forall a. Int -> [a] -> [a]
take Int
3 FilePath
x FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"cpu") ([FilePath] -> [FilePath])
-> (FilePath -> [FilePath]) -> FilePath -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> [FilePath]
lines

tuplize :: [String] -> Maybe (String, [Int])
tuplize :: [FilePath] -> Maybe (FilePath, [Int])
tuplize [FilePath]
s = do
  FilePath
cpu <- [FilePath]
s [FilePath] -> Int -> Maybe FilePath
forall a. [a] -> Int -> Maybe a
`atMay` Int
0
  (FilePath, [Int]) -> Maybe (FilePath, [Int])
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath
cpu, (FilePath -> Int) -> [FilePath] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> FilePath -> Int
forall a. Read a => a -> FilePath -> a
readDef (-Int
1)) ([FilePath] -> [FilePath]
forall a. [a] -> [a]
tailSafe [FilePath]
s))

-- | Returns a two-element list containing relative system and user times
-- calculated using two almost simultaneous samples of the @\/proc\/stat@ file
-- for the given core (or all of them aggregated, if \"cpu\" is passed).
getCPULoad :: String -> IO [Double]
getCPULoad :: FilePath -> IO [Double]
getCPULoad FilePath
cpu = do
  [Double]
load <- Double -> IO [Int] -> IO [Double]
forall a b. (Integral a, RealFloat b) => b -> IO [a] -> IO [b]
getLoad Double
0.05 (IO [Int] -> IO [Double]) -> IO [Int] -> IO [Double]
forall a b. (a -> b) -> a -> b
$ FilePath -> IO [Int]
getCPUInfo FilePath
cpu
  case [Double]
load of
    Double
l0:Double
l1:Double
l2:[Double]
_ -> [Double] -> IO [Double]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [ Double
l0 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
l1, Double
l2 ]
    [Double]
_ -> [Double] -> IO [Double]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []

-- | Get the directory in which core temperature files are kept.
getCPUTemperatureDirectory :: IO FilePath
getCPUTemperatureDirectory :: IO FilePath
getCPUTemperatureDirectory =
  (FilePath
baseDir FilePath -> FilePath -> FilePath
</>) (FilePath -> FilePath)
-> ([FilePath] -> FilePath) -> [FilePath] -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Maybe FilePath -> FilePath
forall a. a -> Maybe a -> a
fromMaybe FilePath
"hwmon0" (Maybe FilePath -> FilePath)
-> ([FilePath] -> Maybe FilePath) -> [FilePath] -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
  (FilePath -> Bool) -> [FilePath] -> Maybe FilePath
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
isPrefixOf FilePath
"hwmon")
  ([FilePath] -> FilePath) -> IO [FilePath] -> IO FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> IO [FilePath]
listDirectory FilePath
baseDir
  where baseDir :: FilePath
baseDir =
          FilePath
"/"  FilePath -> FilePath -> FilePath
</> FilePath
"sys" FilePath -> FilePath -> FilePath
</> FilePath
"bus" FilePath -> FilePath -> FilePath
</> FilePath
"platform" FilePath -> FilePath -> FilePath
</>
          FilePath
"devices" FilePath -> FilePath -> FilePath
</> FilePath
"coretemp.0" FilePath -> FilePath -> FilePath
</> FilePath
"hwmon"

readCPUTempFile :: FilePath -> IO Double
readCPUTempFile :: FilePath -> IO Double
readCPUTempFile FilePath
cpuTempFilePath = (Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
1000) (Double -> Double) -> (FilePath -> Double) -> FilePath -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Double
forall a. Read a => FilePath -> a
read (FilePath -> Double) -> IO FilePath -> IO Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> IO FilePath
readFile FilePath
cpuTempFilePath

getAllTemperatureFiles :: FilePath -> IO [FilePath]
getAllTemperatureFiles :: FilePath -> IO [FilePath]
getAllTemperatureFiles FilePath
temperaturesDirectory =
  (FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Bool -> Bool -> Bool)
-> (FilePath -> Bool) -> (FilePath -> Bool) -> FilePath -> Bool
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 Bool -> Bool -> Bool
(&&) (FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
isPrefixOf FilePath
"temp") (FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
isSuffixOf FilePath
"input")) ([FilePath] -> [FilePath]) -> IO [FilePath] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
         FilePath -> IO [FilePath]
listDirectory FilePath
temperaturesDirectory

getCPUTemperatures :: IO [(String, Double)]
getCPUTemperatures :: IO [(FilePath, Double)]
getCPUTemperatures = do
  FilePath
dir <- IO FilePath
getCPUTemperatureDirectory
  let mkPair :: FilePath -> IO (FilePath, Double)
mkPair FilePath
filename = (FilePath
filename,) (Double -> (FilePath, Double))
-> IO Double -> IO (FilePath, Double)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> IO Double
readCPUTempFile (FilePath
dir FilePath -> FilePath -> FilePath
</> FilePath
filename)
  FilePath -> IO [FilePath]
getAllTemperatureFiles FilePath
dir IO [FilePath]
-> ([FilePath] -> IO [(FilePath, Double)])
-> IO [(FilePath, Double)]
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (FilePath -> IO (FilePath, Double))
-> [FilePath] -> IO [(FilePath, Double)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FilePath -> IO (FilePath, Double)
mkPair