diff options
| author | Sibi Prabakaran <sibi@psibi.in> | 2020-06-20 21:39:02 +0530 | 
|---|---|---|
| committer | jao <jao@gnu.org> | 2020-06-23 16:38:20 +0100 | 
| commit | 28ea8d95137131e81c836ed2d446f8925518e85c (patch) | |
| tree | 16f823a3d81a4bbb22861ce46d869391ab679574 /src/Xmobar | |
| parent | 148f1083c45bc66112ff18d44f4d2a43d891c5ca (diff) | |
| download | xmobar-28ea8d95137131e81c836ed2d446f8925518e85c.tar.gz xmobar-28ea8d95137131e81c836ed2d446f8925518e85c.tar.bz2 | |
Update based on feedback on the PR
Diffstat (limited to 'src/Xmobar')
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Common/Output.hs | 53 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Common/Parsers.hs | 8 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Common/Run.hs | 8 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Common/Types.hs | 20 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Cpu.hs | 6 | 
5 files changed, 41 insertions, 54 deletions
| diff --git a/src/Xmobar/Plugins/Monitors/Common/Output.hs b/src/Xmobar/Plugins/Monitors/Common/Output.hs index a1ece89..8bb52cf 100644 --- a/src/Xmobar/Plugins/Monitors/Common/Output.hs +++ b/src/Xmobar/Plugins/Monitors/Common/Output.hs @@ -56,7 +56,7 @@ import Xmobar.Plugins.Monitors.Common.Types  type IconPattern = Int -> String -pShowVerticalBar :: (MonadIO m) => PureConfig -> Float -> Float -> m String +pShowVerticalBar :: (MonadIO m) => MonitorConfig -> Float -> Float -> m String  pShowVerticalBar p v x = pColorizeString p v [convert $ 100 * x]    where convert :: Float -> Char          convert val @@ -65,62 +65,49 @@ pShowVerticalBar p v x = pColorizeString p v [convert $ 100 * x]            | otherwise = chr t            where t = 9600 + (round val `div` 12) -pShowPercentsWithColors :: (MonadIO m) => PureConfig -> [Float] -> m [String] +pShowPercentsWithColors :: (MonadIO m) => MonitorConfig -> [Float] -> m [String]  pShowPercentsWithColors p fs =    do let fstrs = map (pFloatToPercent p) fs           temp = map (*100) fs       zipWithM (pShowWithColors p . const) fstrs temp -pShowPercentWithColors :: (MonadIO m) => PureConfig -> Float -> m String +pShowPercentWithColors :: (MonadIO m) => MonitorConfig -> Float -> m String  pShowPercentWithColors p f = fmap head $ pShowPercentsWithColors p [f] -pShowPercentBar :: (MonadIO m) => PureConfig -> Float -> Float -> m String -pShowPercentBar p@PureConfig{..} v x = do -  let bb = pBarBack -      bf = pBarFore -      bw = pBarWidth -  let len = min bw $ round (fromIntegral bw * x) -  s <- pColorizeString p v (take len $ cycle bf) -  return $ s ++ take (bw - len) (cycle bb) +pShowPercentBar :: (MonadIO m) => MonitorConfig -> Float -> Float -> m String +pShowPercentBar p@MonitorConfig{..} v x = do +  let len = min pBarWidth $ round (fromIntegral pBarWidth * x) +  s <- pColorizeString p v (take len $ cycle pBarFore) +  return $ s ++ take (pBarWidth - len) (cycle pBarBack) -pShowWithColors :: (Num a, Ord a, MonadIO m) => PureConfig -> (a -> String) -> a -> m String +pShowWithColors :: (Num a, Ord a, MonadIO m) => MonitorConfig -> (a -> String) -> a -> m String  pShowWithColors p f x = do    let str = pShowWithPadding p (f x)    pColorizeString p x str -pColorizeString :: (Num a, Ord a, MonadIO m) => PureConfig -> a -> String -> m String +pColorizeString :: (Num a, Ord a, MonadIO m) => MonitorConfig -> a -> String -> m String  pColorizeString p x s = do -    let h = pHigh p -        l = pLow p      let col = pSetColor p s -        [ll,hh] = map fromIntegral $ sort [l, h] -- consider high < low +        [ll,hh] = map fromIntegral $ sort [pLow p, pHigh p] -- consider high < low      pure $ head $ [col pHighColor   | x > hh ] ++                    [col pNormalColor | x > ll ] ++                    [col pLowColor    | True] -pSetColor :: PureConfig -> String -> PSelector (Maybe String) -> String +pSetColor :: MonitorConfig -> String -> PSelector (Maybe String) -> String  pSetColor config str s =      do let a = getPConfigValue config s         case a of              Nothing -> str              Just c -> "<fc=" ++ c ++ ">" ++ str ++ "</fc>" -pShowWithPadding :: PureConfig -> String -> String -pShowWithPadding PureConfig{..} s = let mn = pMinWidth -                                        mx = pMaxWidth -                                        p = pPadChars -                                        pr = pPadRight -                                        ellipsis = pMaxWidthEllipsis -                                    in padString mn mx p pr ellipsis s - -pFloatToPercent :: PureConfig -> Float -> String -pFloatToPercent PureConfig{..} n = let pad = pPpad -                                       pc = pPadChars -                                       pr = pPadRight -                                       up = pUseSuffix -                                       p = showDigits 0 (n * 100) -                                       ps = if up then "%" else "" -                                   in padString pad pad pc pr "" p ++ ps +pShowWithPadding :: MonitorConfig -> String -> String +pShowWithPadding MonitorConfig {..} s = +  padString pMinWidth pMaxWidth pPadChars pPadRight pMaxWidthEllipsis s + +pFloatToPercent :: MonitorConfig -> Float -> String +pFloatToPercent MonitorConfig{..} n = let p = showDigits 0 (n * 100) +                                          ps = if pUseSuffix then "%" else "" +                                      in padString pPpad pPpad pPadChars pPadRight "" p ++ ps  parseIconPattern :: String -> IconPattern  parseIconPattern path = diff --git a/src/Xmobar/Plugins/Monitors/Common/Parsers.hs b/src/Xmobar/Plugins/Monitors/Common/Parsers.hs index 188b87d..db2a652 100644 --- a/src/Xmobar/Plugins/Monitors/Common/Parsers.hs +++ b/src/Xmobar/Plugins/Monitors/Common/Parsers.hs @@ -41,8 +41,8 @@ import qualified Data.Map as Map  import System.Console.GetOpt (ArgOrder(Permute), OptDescr, getOpt)  import Text.ParserCombinators.Parsec -runTemplateParser :: PureConfig -> IO [(String, String, String)] -runTemplateParser PureConfig{..} = runP templateParser pTemplate +runTemplateParser :: MonitorConfig -> IO [(String, String, String)] +runTemplateParser MonitorConfig{..} = runP templateParser pTemplate  runExportParser :: [String] -> IO [(String, [(String, String,String)])]  runExportParser [] = pure [] @@ -51,8 +51,8 @@ runExportParser (x:xs) = do    rest <- runExportParser xs    pure $ (x,s):rest -pureParseTemplate :: PureConfig -> TemplateInput -> IO String -pureParseTemplate PureConfig{..} TemplateInput{..} = +pureParseTemplate :: MonitorConfig -> TemplateInput -> IO String +pureParseTemplate MonitorConfig{..} TemplateInput{..} =      do let m = let expSnds :: [([(String, String, String)], String)]  = zip (map snd temAllTemplate) temMonitorValues                 in Map.fromList $ zip (map fst temAllTemplate) expSnds         s <- minCombine m temInputTemplate diff --git a/src/Xmobar/Plugins/Monitors/Common/Run.hs b/src/Xmobar/Plugins/Monitors/Common/Run.hs index 076ac07..188b02a 100644 --- a/src/Xmobar/Plugins/Monitors/Common/Run.hs +++ b/src/Xmobar/Plugins/Monitors/Common/Run.hs @@ -23,7 +23,7 @@ module Xmobar.Plugins.Monitors.Common.Run ( runM                                            , runMLD                                            , getArgvs                                            , doArgs -                                          , computePureConfig +                                          , computeMonitorConfig                                            , pluginOptions                                            ) where @@ -145,10 +145,10 @@ runMLD args conf action looper detect cb = handle (cb . showException) loop  showException :: SomeException -> String  showException = ("error: "++) . show . flip asTypeOf undefined -computePureConfig :: [String] -> IO MConfig -> IO PureConfig -computePureConfig args mconfig = do +computeMonitorConfig :: [String] -> IO MConfig -> IO MonitorConfig +computeMonitorConfig args mconfig = do    newConfig <- getMConfig args mconfig -  getPureConfig newConfig +  getMonitorConfig newConfig  getMConfig :: [String] -> IO MConfig -> IO MConfig  getMConfig args mconfig = do diff --git a/src/Xmobar/Plugins/Monitors/Common/Types.hs b/src/Xmobar/Plugins/Monitors/Common/Types.hs index a2d5eb4..d09da8e 100644 --- a/src/Xmobar/Plugins/Monitors/Common/Types.hs +++ b/src/Xmobar/Plugins/Monitors/Common/Types.hs @@ -24,10 +24,10 @@ module Xmobar.Plugins.Monitors.Common.Types ( Monitor                                              , setConfigValue                                              , mkMConfig                                              , io -                                            , PureConfig (..) +                                            , MonitorConfig (..)                                              , getPConfigValue                                              , getConfigValue -                                            , getPureConfig +                                            , getMonitorConfig                                              , PSelector                                              , TemplateInput(..)                                              ) where @@ -71,8 +71,8 @@ data MConfig =         , maxTotalWidthEllipsis :: IORef String         } -data PureConfig = -  PureConfig +data MonitorConfig = +  MonitorConfig      { pNormalColor :: Maybe String      , pLow :: Int      , pLowColor :: Maybe String @@ -97,8 +97,8 @@ data PureConfig =      }    deriving (Eq, Ord) -getPureConfig :: MConfig -> IO PureConfig -getPureConfig MC{..} = do +getMonitorConfig :: MConfig -> IO MonitorConfig +getMonitorConfig MC{..} = do    pNormalColor <- readIORef normalColor    pLow <- readIORef low    pLowColor <- readIORef lowColor @@ -120,13 +120,13 @@ getPureConfig MC{..} = do    pNaString <- readIORef naString    pMaxTotalWidth <- readIORef maxTotalWidth    pMaxTotalWidthEllipsis <- readIORef maxTotalWidthEllipsis -  pure $ PureConfig {..} +  pure $ MonitorConfig {..}  -- | from 'http:\/\/www.haskell.org\/hawiki\/MonadState'  type Selector a = MConfig -> IORef a -type PSelector a = PureConfig -> a +type PSelector a = MonitorConfig -> a -psel :: PureConfig -> PSelector a -> a +psel :: MonitorConfig -> PSelector a -> a  psel value accessor = accessor value  sel :: Selector a -> Monitor a @@ -146,7 +146,7 @@ setConfigValue v s =  getConfigValue :: Selector a -> Monitor a  getConfigValue = sel -getPConfigValue :: PureConfig -> PSelector a -> a +getPConfigValue :: MonitorConfig -> PSelector a -> a  getPConfigValue = psel  mkMConfig :: String diff --git a/src/Xmobar/Plugins/Monitors/Cpu.hs b/src/Xmobar/Plugins/Monitors/Cpu.hs index 7f05663..895eeb3 100644 --- a/src/Xmobar/Plugins/Monitors/Cpu.hs +++ b/src/Xmobar/Plugins/Monitors/Cpu.hs @@ -145,7 +145,7 @@ data Field = Field {  data ShouldCompute = Compute | Skip deriving (Eq, Ord, Show) -formatField :: PureConfig -> CpuOpts -> CpuData -> Field -> IO String +formatField :: MonitorConfig -> CpuOpts -> CpuData -> Field -> IO String  formatField cpuParams cpuOpts cpuInfo@CpuData {..} Field {..}    | fieldName == barField =      if fieldCompute == Compute @@ -203,7 +203,7 @@ optimizeAllTemplate args@CpuArguments {..} =  data CpuArguments =    CpuArguments      { cpuDataRef :: !CpuDataRef -    , cpuParams :: !PureConfig +    , cpuParams :: !MonitorConfig      , cpuArgs :: ![String]      , cpuOpts :: !CpuOpts      , cpuInputTemplate :: ![(String, String, String)] -- [("Cpu: ","total","% "),("","user","%")] @@ -217,7 +217,7 @@ getArguments cpuArgs = do    initCpuData <- cpuData    cpuDataRef <- newIORef initCpuData    void $ parseCpu cpuDataRef -  cpuParams <- computePureConfig cpuArgs cpuConfig +  cpuParams <- computeMonitorConfig cpuArgs cpuConfig    cpuInputTemplate <- runTemplateParser cpuParams    cpuAllTemplate <- runExportParser (pExport cpuParams)    nonOptions <- | 
