module System.Taffybar.Widget.Text.MemoryMonitor (textMemoryMonitorNew, showMemoryInfo) where

import Control.Monad.IO.Class ( MonadIO )
import qualified Data.Text as T
import qualified Text.StringTemplate as ST
import System.Taffybar.Information.Memory
import System.Taffybar.Widget.Generic.PollingLabel ( pollingLabelNew )
import qualified GI.Gtk
import Text.Printf ( printf )

-- | Creates a simple textual memory monitor. It updates once every polling
-- period (in seconds).
textMemoryMonitorNew :: MonadIO m
                     => String -- ^ Format. You can use variables: "used", "total", "free", "buffer",
                               -- "cache", "rest", "available", "swapUsed", "swapTotal", "swapFree".
                     -> Double -- ^ Polling period in seconds.
                     -> m GI.Gtk.Widget
textMemoryMonitorNew :: forall (m :: * -> *). MonadIO m => String -> Double -> m Widget
textMemoryMonitorNew String
fmt Double
period = do
    Widget
label <- Double -> IO Text -> m Widget
forall (m :: * -> *). MonadIO m => Double -> IO Text -> m Widget
pollingLabelNew Double
period (String -> Int -> MemoryInfo -> Text
showMemoryInfo String
fmt Int
3 (MemoryInfo -> Text) -> IO MemoryInfo -> IO Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO MemoryInfo
parseMeminfo)
    Widget -> m Widget
forall (m :: * -> *) o. (MonadIO m, IsWidget o) => o -> m Widget
GI.Gtk.toWidget Widget
label

showMemoryInfo :: String -> Int -> MemoryInfo -> T.Text
showMemoryInfo :: String -> Int -> MemoryInfo -> Text
showMemoryInfo String
fmt Int
prec MemoryInfo
info =
  let template :: StringTemplate Text
template = String -> StringTemplate Text
forall a. Stringable a => String -> StringTemplate a
ST.newSTMP String
fmt
      labels :: [String]
labels = [ String
"used"
               , String
"total"
               , String
"free"
               , String
"buffer"
               , String
"cache"
               , String
"rest"
               , String
"available"
               , String
"swapUsed"
               , String
"swapTotal"
               , String
"swapFree"
               ]
      actions :: [MemoryInfo -> Double]
actions = [ MemoryInfo -> Double
memoryUsed
                , MemoryInfo -> Double
memoryTotal
                , MemoryInfo -> Double
memoryFree
                , MemoryInfo -> Double
memoryBuffer
                , MemoryInfo -> Double
memoryCache
                , MemoryInfo -> Double
memoryRest
                , MemoryInfo -> Double
memoryAvailable
                , MemoryInfo -> Double
memorySwapUsed
                , MemoryInfo -> Double
memorySwapTotal
                , MemoryInfo -> Double
memorySwapFree
                ]
      actions' :: [MemoryInfo -> String]
actions' = ((MemoryInfo -> Double) -> MemoryInfo -> String)
-> [MemoryInfo -> Double] -> [MemoryInfo -> String]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Double -> String
toAuto Int
prec (Double -> String)
-> (MemoryInfo -> Double) -> MemoryInfo -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) [MemoryInfo -> Double]
actions
      stats :: [String]
stats = [MemoryInfo -> String
f MemoryInfo
info | MemoryInfo -> String
f <- [MemoryInfo -> String]
actions']
      template' :: StringTemplate Text
template' = [(String, String)] -> StringTemplate Text -> StringTemplate Text
forall a b.
(ToSElem a, Stringable b) =>
[(String, a)] -> StringTemplate b -> StringTemplate b
ST.setManyAttrib ([String] -> [String] -> [(String, String)]
forall a b. [a] -> [b] -> [(a, b)]
zip [String]
labels [String]
stats) StringTemplate Text
template
  in StringTemplate Text -> Text
forall a. Stringable a => StringTemplate a -> a
ST.render StringTemplate Text
template'

toAuto :: Int -> Double -> String
toAuto :: Int -> Double -> String
toAuto Int
prec Double
value = String -> Int -> Double -> String -> String
forall r. PrintfType r => String -> r
printf String
"%.*f%s" Int
p Double
v String
unit
  where value' :: Double
value' = Double -> Double -> Double
forall a. Ord a => a -> a -> a
max Double
0 Double
value
        mag :: Int
        mag :: Int
mag = if Double
value' Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
0 then Int
0 else Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
2 (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Double -> Int
forall a b. (RealFrac a, Integral b) => a -> b
floor (Double -> Int) -> Double -> Int
forall a b. (a -> b) -> a -> b
$ Double -> Double -> Double
forall a. Floating a => a -> a -> a
logBase Double
1024 Double
value'
        v :: Double
v = Double
value' Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
1024 Double -> Double -> Double
forall a. Floating a => a -> a -> a
** Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
mag
        unit :: String
unit = case Int
mag of
          Int
0 -> String
"MiB"
          Int
1 -> String
"GiB"
          Int
2 -> String
"TiB"
          Int
_ -> String
"??B" -- unreachable
        p :: Int
        p :: Int
p = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Double -> Int
forall a b. (RealFrac a, Integral b) => a -> b
floor (Double -> Int) -> Double -> Int
forall a b. (a -> b) -> a -> b
$ Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
prec Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double -> Double -> Double
forall a. Floating a => a -> a -> a
logBase Double
10 Double
v