summaryrefslogtreecommitdiffhomepage
path: root/src/Xmobar/Plugins/Monitors/Common/Types.hs
diff options
context:
space:
mode:
authorSibi Prabakaran <sibi@psibi.in>2020-06-14 09:46:47 +0530
committerjao <jao@gnu.org>2020-06-23 16:38:20 +0100
commitb4f0f35ef118064bc7829b6224a896b448a37bc4 (patch)
treeccee394fdd32d6bb4d65bf21648cab3b00274883 /src/Xmobar/Plugins/Monitors/Common/Types.hs
parent2b13b5cf6595d81280c95eb9cf507a9817e3f641 (diff)
downloadxmobar-b4f0f35ef118064bc7829b6224a896b448a37bc4.tar.gz
xmobar-b4f0f35ef118064bc7829b6224a896b448a37bc4.tar.bz2
Optimize CPU monitor
Diffstat (limited to 'src/Xmobar/Plugins/Monitors/Common/Types.hs')
-rw-r--r--src/Xmobar/Plugins/Monitors/Common/Types.hs76
1 files changed, 76 insertions, 0 deletions
diff --git a/src/Xmobar/Plugins/Monitors/Common/Types.hs b/src/Xmobar/Plugins/Monitors/Common/Types.hs
index fc71da3..e8e9bfd 100644
--- a/src/Xmobar/Plugins/Monitors/Common/Types.hs
+++ b/src/Xmobar/Plugins/Monitors/Common/Types.hs
@@ -1,3 +1,5 @@
+{-#LANGUAGE RecordWildCards#-}
+
------------------------------------------------------------------------------
-- |
-- Module: Xmobar.Plugins.Monitors.Types
@@ -23,6 +25,12 @@ module Xmobar.Plugins.Monitors.Common.Types ( Monitor
, getConfigValue
, mkMConfig
, io
+ , PureConfig (..)
+ , getPConfigValue
+ , getConfigValue
+ , getPureConfig
+ , PSelector
+ , TemplateInput(..)
) where
import Control.Monad.Reader (ReaderT, ask, liftIO)
@@ -34,6 +42,12 @@ type Monitor a = ReaderT MConfig IO a
io :: IO a -> Monitor a
io = liftIO
+data TemplateInput = TemplateInput {
+ temMonitorValues :: [String],
+ temInputTemplate :: [(String, String, String)],
+ temAllTemplate :: [(String, [(String, String, String)])]
+ }
+
data MConfig =
MC { normalColor :: IORef (Maybe String)
, low :: IORef Int
@@ -58,14 +72,73 @@ data MConfig =
, maxTotalWidthEllipsis :: IORef String
}
+data PureConfig =
+ PureConfig
+ { pNormalColor :: (Maybe String)
+ , pLow :: Int
+ , pLowColor :: (Maybe String)
+ , pHigh :: Int
+ , pHighColor :: (Maybe String)
+ , pTemplate :: String
+ , pExport :: [String]
+ , pPpad :: Int
+ , pDecDigits :: Int
+ , pMinWidth :: Int
+ , pMaxWidth :: Int
+ , pMaxWidthEllipsis :: String
+ , pPadChars :: String
+ , pPadRight :: Bool
+ , pBarBack :: String
+ , pBarFore :: String
+ , pBarWidth :: Int
+ , pUseSuffix :: Bool
+ , pNaString :: String
+ , pMaxTotalWidth :: Int
+ , pMaxTotalWidthEllipsis :: String
+ }
+ deriving (Eq, Ord)
+
+getPureConfig :: MConfig -> IO PureConfig
+getPureConfig MC{..} = do
+ pNormalColor <- readIORef normalColor
+ pLow <- readIORef low
+ pLowColor <- readIORef lowColor
+ pHigh <- readIORef high
+ pHighColor <- readIORef highColor
+ pTemplate <- readIORef template
+ pExport <- readIORef export
+ pPpad <- readIORef ppad
+ pDecDigits <- readIORef decDigits
+ pMinWidth <- readIORef minWidth
+ pMaxWidth <- readIORef maxWidth
+ pMaxWidthEllipsis <- readIORef maxWidthEllipsis
+ pPadChars <- readIORef padChars
+ pPadRight <- readIORef padRight
+ pBarBack <- readIORef barBack
+ pBarFore <- readIORef barFore
+ pBarWidth <- readIORef barWidth
+ pUseSuffix <- readIORef useSuffix
+ pNaString <- readIORef naString
+ pMaxTotalWidth <- readIORef maxTotalWidth
+ pMaxTotalWidthEllipsis <- readIORef maxTotalWidthEllipsis
+ pure $ PureConfig {..}
+
-- | from 'http:\/\/www.haskell.org\/hawiki\/MonadState'
type Selector a = MConfig -> IORef a
+type PSelector a = PureConfig -> a
+
+psel :: PureConfig -> PSelector a -> a
+psel value accessor = accessor value
sel :: Selector a -> Monitor a
sel s =
do hs <- ask
liftIO $ readIORef (s hs)
+pmods :: PureConfig -> PSelector a -> (a -> a) -> a
+pmods config value f = let val = value config
+ in f val
+
mods :: Selector a -> (a -> a) -> Monitor ()
mods s m =
do v <- ask
@@ -78,6 +151,9 @@ setConfigValue v s =
getConfigValue :: Selector a -> Monitor a
getConfigValue = sel
+getPConfigValue :: PureConfig -> PSelector a -> a
+getPConfigValue = psel
+
mkMConfig :: String
-> [String]
-> IO MConfig