Hello community,

here is the log from the commit of package xmobar for openSUSE:Factory checked 
in at 2020-07-09 13:20:02
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/xmobar (Old)
 and      /work/SRC/openSUSE:Factory/.xmobar.new.3060 (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Package is "xmobar"

Thu Jul  9 13:20:02 2020 rev:15 rq:819601 version:0.35.1

Changes:
--------
--- /work/SRC/openSUSE:Factory/xmobar/xmobar.changes    2020-06-19 
17:22:21.803713337 +0200
+++ /work/SRC/openSUSE:Factory/.xmobar.new.3060/xmobar.changes  2020-07-09 
13:20:32.133491100 +0200
@@ -1,0 +2,9 @@
+Sat Jun 27 02:00:29 UTC 2020 - psim...@suse.com
+
+- Update xmobar to version 0.35.1.
+  Upstream has edited the change log file since the last release in
+  a non-trivial way, i.e. they did more than just add a new entry
+  at the top. You can review the file at:
+  http://hackage.haskell.org/package/xmobar-0.35.1/src/changelog.md
+
+-------------------------------------------------------------------

Old:
----
  xmobar-0.34.tar.gz

New:
----
  xmobar-0.35.1.tar.gz

++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Other differences:
------------------
++++++ xmobar.spec ++++++
--- /var/tmp/diff_new_pack.nrW8Dm/_old  2020-07-09 13:20:32.981493781 +0200
+++ /var/tmp/diff_new_pack.nrW8Dm/_new  2020-07-09 13:20:32.981493781 +0200
@@ -19,7 +19,7 @@
 %global pkg_name xmobar
 %bcond_with tests
 Name:           %{pkg_name}
-Version:        0.34
+Version:        0.35.1
 Release:        0
 Summary:        A Minimalistic Text Based Status Bar
 License:        BSD-3-Clause
@@ -94,7 +94,6 @@
 
 %prep
 %setup -q
-cabal-tweak-dep-ver timezone-olson '== 0.1.*' '< 1'
 
 %build
 %define cabal_configure_options -fall_extensions

++++++ xmobar-0.34.tar.gz -> xmobar-0.35.1.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/xmobar-0.34/bench/main.hs 
new/xmobar-0.35.1/bench/main.hs
--- old/xmobar-0.34/bench/main.hs       1970-01-01 01:00:00.000000000 +0100
+++ new/xmobar-0.35.1/bench/main.hs     2001-09-09 03:46:40.000000000 +0200
@@ -0,0 +1,32 @@
+{-#LANGUAGE RecordWildCards#-}
+
+import Gauge
+import Xmobar
+import Xmobar.Plugins.Monitors.Common.Types
+import Xmobar.Plugins.Monitors.Common.Run
+import Xmobar.Plugins.Monitors.Cpu
+import Control.Monad.Reader
+import Data.IORef (newIORef)
+
+main :: IO ()
+main = do
+  cpuParams <- mkCpuArgs
+  defaultMain $ normalBench cpuParams
+    where
+      normalBench args = [ bgroup "Cpu Benchmarks" $ normalCpuBench args]
+
+runMonitor :: MConfig -> Monitor a -> IO a
+runMonitor config r = runReaderT r config
+
+mkCpuArgs :: IO CpuArguments
+mkCpuArgs = getArguments 
["-L","3","-H","50","--normal","green","--high","red", "-t", "Cpu: <total>%"]
+  
+-- | The action which will be benchmarked
+cpuAction :: CpuArguments -> IO String
+cpuAction = runCpu
+
+cpuBenchmark :: CpuArguments -> Benchmarkable
+cpuBenchmark cpuParams = nfIO $ cpuAction cpuParams
+
+normalCpuBench :: CpuArguments -> [Benchmark]
+normalCpuBench args = [bench "CPU normal args" (cpuBenchmark args)]
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/xmobar-0.34/changelog.md 
new/xmobar-0.35.1/changelog.md
--- old/xmobar-0.34/changelog.md        2001-09-09 03:46:40.000000000 +0200
+++ new/xmobar-0.35.1/changelog.md      2001-09-09 03:46:40.000000000 +0200
@@ -1,3 +1,16 @@
+## Version 0.35.1 (June, 2020)
+
+- Dropped support for GHC < 8.4 (see issue #461)
+
+## Version 0.35 (June, 2020)
+
+_New features_
+
+  - `MultiCoreTemp` now works with Ryzen processors.  New option
+    `--hwmonitor-path` for better performance.
+  - CPU Monitor optimizations.
+  - Version bumps for some dependencies, including timezone-olson.
+
 ## Version 0.34 (June, 2020)
 
 _New features_
@@ -8,8 +21,9 @@
   - Optimize date plugin by avoiding calling getTimeZone for each of
     the time the date has to be updated. Instead, it's computed once
     at the start and re-used for each invocation.
-  - Optimize Weather and UVMeter plugin by using global Manager instead of
-    creating for each http request when useManager is explicitly configured as 
False.
+  - Optimize Weather and UVMeter plugin by using global Manager
+    instead of creating for each http request when useManager is
+    explicitly configured as False.
 
 ## Version 0.33 (February, 2020)
 
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/xmobar-0.34/readme.md new/xmobar-0.35.1/readme.md
--- old/xmobar-0.34/readme.md   2001-09-09 03:46:40.000000000 +0200
+++ new/xmobar-0.35.1/readme.md 2001-09-09 03:46:40.000000000 +0200
@@ -1135,6 +1135,15 @@
     limit for percentage calculation.
   - `--maxtemp`: temperature in degree Celsius, that sets the upper
     limit for percentage calculation.
+  - `--hwmonitor-path`: this monitor tries to find coretemp devices by
+    looking for them in directories following the pattern
+    `/sys/bus/platform/devices/coretemp.*/hwmon/hwmon*`, but some
+    processors (notably Ryzen) might expose those files in a different
+    tree (e.g., Ryzen) puts them somewhere in
+    "/sys/class/hwmon/hwmon*", and the lookup is most costly.  With
+    this option, it is possible to explicitly specify the full path to
+    the directory where the `tempN_label` and `tempN_input` files are
+    located.
 - Thresholds refer to temperature in degree Celsius
 - Variables that can be used with the `-t`/`--template` argument:
             `max`, `maxpc`, `maxbar`, `maxvbar`, `maxipat`,
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/xmobar-0.34/src/Xmobar/Plugins/Monitors/Common/Output.hs 
new/xmobar-0.35.1/src/Xmobar/Plugins/Monitors/Common/Output.hs
--- old/xmobar-0.34/src/Xmobar/Plugins/Monitors/Common/Output.hs        
2001-09-09 03:46:40.000000000 +0200
+++ new/xmobar-0.35.1/src/Xmobar/Plugins/Monitors/Common/Output.hs      
2001-09-09 03:46:40.000000000 +0200
@@ -1,3 +1,5 @@
+{-#LANGUAGE RecordWildCards#-}
+
 ------------------------------------------------------------------------------
 -- |
 -- Module: Xmobar.Plugins.Monitors.Strings
@@ -37,6 +39,11 @@
                                              , parseFloat
                                              , parseInt
                                              , stringParser
+                                             , pShowPercentsWithColors
+                                             , pShowPercentBar
+                                             , pShowVerticalBar
+                                             , pShowIconPattern
+                                             , pShowPercentWithColors
                                              ) where
 
 import Data.Char
@@ -44,11 +51,64 @@
 import qualified Data.ByteString.Lazy.Char8 as B
 import Numeric
 import Control.Monad (zipWithM)
-
+import Control.Monad.IO.Class (MonadIO(..))
 import Xmobar.Plugins.Monitors.Common.Types
 
 type IconPattern = Int -> 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
+          | t <= 9600 = ' '
+          | t > 9608 = chr 9608
+          | otherwise = chr t
+          where t = 9600 + (round val `div` 12)
+
+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) => MonitorConfig -> Float -> m String
+pShowPercentWithColors p f = fmap head $ pShowPercentsWithColors p [f]
+
+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) => 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) => MonitorConfig -> a -> String 
-> m String
+pColorizeString p x s = do
+    let col = pSetColor p s
+        [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 :: 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 :: MonitorConfig -> String -> String
+pShowWithPadding MonitorConfig {..} =
+  padString pMinWidth pMaxWidth pPadChars pPadRight pMaxWidthEllipsis
+
+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 =
     let spl = splitOnPercent path
@@ -171,6 +231,15 @@
   where convert val
           | t <= 0 = 0
           | t > 8 = 8
+          | otherwise = t
+          where t = round val `div` 12
+
+pShowIconPattern :: Maybe IconPattern -> Float -> IO String
+pShowIconPattern Nothing _ = return ""
+pShowIconPattern (Just str) x = return $ str $ convert $ 100 * x
+  where convert val
+          | t <= 0 = 0
+          | t > 8 = 8
           | otherwise = t
           where t = round val `div` 12
 
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/xmobar-0.34/src/Xmobar/Plugins/Monitors/Common/Parsers.hs 
new/xmobar-0.35.1/src/Xmobar/Plugins/Monitors/Common/Parsers.hs
--- old/xmobar-0.34/src/Xmobar/Plugins/Monitors/Common/Parsers.hs       
2001-09-09 03:46:40.000000000 +0200
+++ new/xmobar-0.35.1/src/Xmobar/Plugins/Monitors/Common/Parsers.hs     
2001-09-09 03:46:40.000000000 +0200
@@ -1,3 +1,6 @@
+{-#LANGUAGE RecordWildCards#-}
+{-#LANGUAGE ScopedTypeVariables#-}
+
 ------------------------------------------------------------------------------
 -- |
 -- Module: Xmobar.Plugins.Monitors.Parsers
@@ -25,6 +28,10 @@
                                               , parseTemplate
                                               , parseTemplate'
                                               , parseOptsWith
+                                              , templateParser
+                                              , runExportParser
+                                              , runTemplateParser
+                                              , pureParseTemplate
                                               ) where
 
 import Xmobar.Plugins.Monitors.Common.Types
@@ -34,6 +41,35 @@
 import System.Console.GetOpt (ArgOrder(Permute), OptDescr, getOpt)
 import Text.ParserCombinators.Parsec
 
+runTemplateParser :: MonitorConfig -> IO [(String, String, String)]
+runTemplateParser MonitorConfig{..} = runP templateParser pTemplate
+
+runExportParser :: [String] -> IO [(String, [(String, String,String)])]
+runExportParser [] = pure []
+runExportParser (x:xs) = do
+  s <- runP templateParser x
+  rest <- runExportParser xs
+  pure $ (x,s):rest
+
+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
+       let (n, s') = if pMaxTotalWidth > 0 && length s > pMaxTotalWidth
+                     then trimTo (pMaxTotalWidth - length 
pMaxTotalWidthEllipsis) "" s
+                     else (1, s)
+       return $ if n > 0 then s' else s' ++ pMaxTotalWidthEllipsis
+
+minCombine :: Map.Map String ([(String, String, String)], String) -> [(String, 
String, String)] -> IO String
+minCombine _ [] = return []
+minCombine m ((s,ts,ss):xs) =
+    do next <- minCombine m xs
+       str <- case Map.lookup ts m of
+         Nothing -> return $ "<" ++ ts ++ ">"
+         Just (s',r) -> let f "" = r; f n = n; in f <$> minCombine m s'
+       pure $ s ++ str ++ ss ++ next
+
 runP :: Parser [a] -> String -> IO [a]
 runP p i =
     case parse p "" i of
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/xmobar-0.34/src/Xmobar/Plugins/Monitors/Common/Run.hs 
new/xmobar-0.35.1/src/Xmobar/Plugins/Monitors/Common/Run.hs
--- old/xmobar-0.34/src/Xmobar/Plugins/Monitors/Common/Run.hs   2001-09-09 
03:46:40.000000000 +0200
+++ new/xmobar-0.35.1/src/Xmobar/Plugins/Monitors/Common/Run.hs 2001-09-09 
03:46:40.000000000 +0200
@@ -22,6 +22,9 @@
                                           , runML
                                           , runMLD
                                           , getArgvs
+                                          , doArgs
+                                          , computeMonitorConfig
+                                          , pluginOptions
                                           ) where
 
 import Control.Exception (SomeException,handle)
@@ -32,11 +35,11 @@
 import Xmobar.Plugins.Monitors.Common.Types
 import Xmobar.Run.Exec (doEveryTenthSeconds)
 
-options :: [OptDescr Opts]
-options =
+pluginOptions :: [OptDescr Opts]
+pluginOptions =
     [
-      Option "H" ["High"] (ReqArg High "number") "The high threshold"
-    , Option "L" ["Low"] (ReqArg Low "number") "The low threshold"
+      Option ['H'] ["High"] (ReqArg High "number") "The high threshold"
+    , Option ['L'] ["Low"] (ReqArg Low "number") "The low threshold"
     , Option "h" ["high"] (ReqArg HighColor "color number") "Color for the 
high threshold: ex \"#FF0000\""
     , Option "n" ["normal"] (ReqArg NormalColor "color number") "Color for the 
normal threshold: ex \"#00FF00\""
     , Option "l" ["low"] (ReqArg LowColor "color number") "Color for the low 
threshold: ex \"#0000FF\""
@@ -61,16 +64,18 @@
 -- | Get all argument values out of a list of arguments.
 getArgvs :: [String] -> [String]
 getArgvs args =
-    case getOpt Permute options args of
+    case getOpt Permute pluginOptions args of
         (_, n, []  ) -> n
         (_, _, errs) -> errs
 
+
+
 doArgs :: [String]
        -> ([String] -> Monitor String)
        -> ([String] -> Monitor Bool)
        -> Monitor String
 doArgs args action detect =
-    case getOpt Permute options args of
+    case getOpt Permute pluginOptions args of
       (o, n, [])   -> do doConfigOptions o
                          ready <- detect n
                          if ready
@@ -139,3 +144,18 @@
 
 showException :: SomeException -> String
 showException = ("error: "++) . show . flip asTypeOf undefined
+
+computeMonitorConfig :: [String] -> IO MConfig -> IO MonitorConfig
+computeMonitorConfig args mconfig = do
+  newConfig <- getMConfig args mconfig
+  getMonitorConfig newConfig
+
+getMConfig :: [String] -> IO MConfig -> IO MConfig
+getMConfig args mconfig = do
+  config <- mconfig
+  runReaderT (updateOptions args >> ask) config
+
+updateOptions :: [String] -> Monitor ()
+updateOptions args= case getOpt Permute pluginOptions args of
+                      (o, _, []) -> doConfigOptions o
+                      _ -> return ()
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/xmobar-0.34/src/Xmobar/Plugins/Monitors/Common/Types.hs 
new/xmobar-0.35.1/src/Xmobar/Plugins/Monitors/Common/Types.hs
--- old/xmobar-0.34/src/Xmobar/Plugins/Monitors/Common/Types.hs 2001-09-09 
03:46:40.000000000 +0200
+++ new/xmobar-0.35.1/src/Xmobar/Plugins/Monitors/Common/Types.hs       
2001-09-09 03:46:40.000000000 +0200
@@ -1,3 +1,5 @@
+{-#LANGUAGE RecordWildCards#-}
+
 ------------------------------------------------------------------------------
 -- |
 -- Module: Xmobar.Plugins.Monitors.Types
@@ -20,9 +22,14 @@
                                             , Opts (..)
                                             , Selector
                                             , setConfigValue
-                                            , getConfigValue
                                             , mkMConfig
                                             , io
+                                            , MonitorConfig (..)
+                                            , getPConfigValue
+                                            , getConfigValue
+                                            , getMonitorConfig
+                                            , PSelector
+                                            , TemplateInput(..)
                                             ) where
 
 import Control.Monad.Reader (ReaderT, ask, liftIO)
@@ -34,6 +41,12 @@
 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,8 +71,63 @@
        , maxTotalWidthEllipsis :: IORef String
        }
 
+data MonitorConfig =
+  MonitorConfig
+    { 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)
+
+getMonitorConfig :: MConfig -> IO MonitorConfig
+getMonitorConfig 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 $ MonitorConfig {..}
+
 -- | from 'http:\/\/www.haskell.org\/hawiki\/MonadState'
 type Selector a = MConfig -> IORef a
+type PSelector a = MonitorConfig -> a
+
+psel :: MonitorConfig -> PSelector a -> a
+psel value accessor = accessor value
 
 sel :: Selector a -> Monitor a
 sel s =
@@ -78,6 +146,9 @@
 getConfigValue :: Selector a -> Monitor a
 getConfigValue = sel
 
+getPConfigValue :: MonitorConfig -> PSelector a -> a
+getPConfigValue = psel
+
 mkMConfig :: String
           -> [String]
           -> IO MConfig
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/xmobar-0.34/src/Xmobar/Plugins/Monitors/Cpu.hs 
new/xmobar-0.35.1/src/Xmobar/Plugins/Monitors/Cpu.hs
--- old/xmobar-0.34/src/Xmobar/Plugins/Monitors/Cpu.hs  2001-09-09 
03:46:40.000000000 +0200
+++ new/xmobar-0.35.1/src/Xmobar/Plugins/Monitors/Cpu.hs        2001-09-09 
03:46:40.000000000 +0200
@@ -1,3 +1,5 @@
+{-#LANGUAGE RecordWildCards#-}
+
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  Plugins.Monitors.Cpu
@@ -13,12 +15,23 @@
 --
 -----------------------------------------------------------------------------
 
-module Xmobar.Plugins.Monitors.Cpu (startCpu) where
+module Xmobar.Plugins.Monitors.Cpu
+  ( startCpu
+  , runCpu
+  , cpuConfig
+  , CpuDataRef
+  , CpuOpts
+  , CpuArguments
+  , parseCpu
+  , getArguments
+  ) where
 
 import Xmobar.Plugins.Monitors.Common
 import qualified Data.ByteString.Lazy.Char8 as B
 import Data.IORef (IORef, newIORef, readIORef, writeIORef)
 import System.Console.GetOpt
+import Xmobar.App.Timer (doEveryTenthSeconds)
+import Control.Monad (void)
 
 newtype CpuOpts = CpuOpts
   { loadIconPattern :: Maybe IconPattern
@@ -35,48 +48,206 @@
      o { loadIconPattern = Just $ parseIconPattern x }) "") ""
   ]
 
+barField :: String
+barField = "bar"
+
+vbarField :: String
+vbarField = "vbar"
+
+ipatField :: String
+ipatField = "ipat"
+
+totalField :: String
+totalField = "total"
+
+userField :: String
+userField = "user"
+
+niceField :: String
+niceField = "nice"
+
+systemField :: String
+systemField = "system"
+
+idleField :: String
+idleField = "idle"
+
+iowaitField :: String
+iowaitField = "iowait"
+
 cpuConfig :: IO MConfig
-cpuConfig = mkMConfig
-       "Cpu: <total>%"
-       ["bar","vbar","ipat","total","user","nice","system","idle","iowait"]
+cpuConfig =
+  mkMConfig
+    "Cpu: <total>%"
+    [ barField
+    , vbarField
+    , ipatField
+    , totalField
+    , userField
+    , niceField
+    , systemField
+    , idleField
+    , iowaitField
+    ]
 
 type CpuDataRef = IORef [Int]
 
+-- Details about the fields here: 
https://www.kernel.org/doc/Documentation/filesystems/proc.txt
 cpuData :: IO [Int]
-cpuData = cpuParser `fmap` B.readFile "/proc/stat"
+cpuData = cpuParser <$> B.readFile "/proc/stat"
+
+readInt :: B.ByteString -> Int
+readInt bs = case B.readInt bs of
+               Nothing -> 0
+               Just (i, _) -> i
 
 cpuParser :: B.ByteString -> [Int]
-cpuParser = map (read . B.unpack) . tail . B.words . head . B.lines
+cpuParser = map readInt . tail . B.words . head . B.lines
+
+data CpuData = CpuData {
+      cpuUser :: !Float,
+      cpuNice :: !Float,
+      cpuSystem :: !Float,
+      cpuIdle :: !Float,
+      cpuIowait :: !Float,
+      cpuTotal :: !Float
+    }
+
+convertToCpuData :: [Float] -> CpuData
+convertToCpuData (u:n:s:ie:iw:_) =
+  CpuData
+    { cpuUser = u
+    , cpuNice = n
+    , cpuSystem = s
+    , cpuIdle = ie
+    , cpuIowait = iw
+    , cpuTotal = sum [u, n, s]
+    }
+convertToCpuData args = error $ "convertToCpuData: Unexpected list" <> show 
args
 
-parseCpu :: CpuDataRef -> IO [Float]
+parseCpu :: CpuDataRef -> IO CpuData
 parseCpu cref =
     do a <- readIORef cref
        b <- cpuData
        writeIORef cref b
        let dif = zipWith (-) b a
            tot = fromIntegral $ sum dif
-           percent = map ((/ tot) . fromIntegral) dif
-       return percent
-
-formatCpu :: CpuOpts -> [Float] -> Monitor [String]
-formatCpu _ [] = return $ replicate 8 ""
-formatCpu opts xs = do
-  let t = sum $ take 3 xs
-  b <- showPercentBar (100 * t) t
-  v <- showVerticalBar (100 * t) t
-  d <- showIconPattern (loadIconPattern opts) t
-  ps <- showPercentsWithColors (t:xs)
-  return (b:v:d:ps)
-
-runCpu :: CpuDataRef -> [String] -> Monitor String
-runCpu cref argv =
-    do c <- io (parseCpu cref)
-       opts <- io $ parseOptsWith options defaultOpts argv
-       l <- formatCpu opts c
-       parseTemplate l
+           safeDiv n = case tot of
+                         0 -> 0
+                         v -> fromIntegral n / v
+           percent = map safeDiv dif
+       return $ convertToCpuData percent
+
+data Field = Field {
+      fieldName :: !String,
+      fieldCompute :: !ShouldCompute
+    } deriving (Eq, Ord, Show)
+
+data ShouldCompute = Compute | Skip deriving (Eq, Ord, Show)
+
+formatField :: MonitorConfig -> CpuOpts -> CpuData -> Field -> IO String
+formatField cpuParams cpuOpts cpuInfo@CpuData {..} Field {..}
+  | fieldName == barField =
+    if fieldCompute == Compute
+      then pShowPercentBar cpuParams (100 * cpuTotal) cpuTotal
+      else pure []
+  | fieldName == vbarField =
+    if fieldCompute == Compute
+      then pShowVerticalBar cpuParams (100 * cpuTotal) cpuTotal
+      else pure []
+  | fieldName == ipatField =
+    if fieldCompute == Compute
+      then pShowIconPattern (loadIconPattern cpuOpts) cpuTotal
+      else pure []
+  | otherwise =
+    if fieldCompute == Compute
+      then pShowPercentWithColors cpuParams (getFieldValue fieldName cpuInfo)
+      else pure []
+
+getFieldValue :: String -> CpuData -> Float
+getFieldValue field CpuData{..}
+    | field == barField = cpuTotal
+    | field == vbarField = cpuTotal
+    | field == ipatField = cpuTotal
+    | field == totalField = cpuTotal
+    | field == userField = cpuUser
+    | field == niceField = cpuNice
+    | field == systemField = cpuSystem
+    | field == idleField = cpuIdle
+    | otherwise = cpuIowait
+
+computeFields :: [String] -> [String] -> [Field]
+computeFields [] _ = []
+computeFields (x:xs) inputFields =
+  if x `elem` inputFields
+    then (Field {fieldName = x, fieldCompute = Compute}) :
+         computeFields xs inputFields
+    else (Field {fieldName = x, fieldCompute = Skip}) :
+         computeFields xs inputFields
+
+formatCpu :: CpuArguments -> CpuData -> IO [String]
+formatCpu CpuArguments{..} cpuInfo = do
+  strs <- mapM (formatField cpuParams cpuOpts cpuInfo) cpuFields
+  pure $ filter (not . null) strs
+
+getInputFields :: CpuArguments -> [String]
+getInputFields CpuArguments{..} = map (\(_,f,_) -> f) cpuInputTemplate
+
+optimizeAllTemplate :: CpuArguments -> CpuArguments
+optimizeAllTemplate args@CpuArguments {..} =
+  let inputFields = getInputFields args
+      allTemplates =
+        filter (\(field, _) -> field `elem` inputFields) cpuAllTemplate
+   in args {cpuAllTemplate = allTemplates}
+
+data CpuArguments =
+  CpuArguments
+    { cpuDataRef :: !CpuDataRef
+    , cpuParams :: !MonitorConfig
+    , cpuArgs :: ![String]
+    , cpuOpts :: !CpuOpts
+    , cpuInputTemplate :: ![(String, String, String)] -- [("Cpu: ","total","% 
"),("","user","%")]
+    , cpuAllTemplate :: ![(String, [(String, String, String)])] -- 
[("bar",[]),("vbar",[]),("ipat",[]),("total",[]),...]
+    , cpuFields :: ![Field]
+    }
+
+
+getArguments :: [String] -> IO CpuArguments
+getArguments cpuArgs = do
+  initCpuData <- cpuData
+  cpuDataRef <- newIORef initCpuData
+  void $ parseCpu cpuDataRef
+  cpuParams <- computeMonitorConfig cpuArgs cpuConfig
+  cpuInputTemplate <- runTemplateParser cpuParams
+  cpuAllTemplate <- runExportParser (pExport cpuParams)
+  nonOptions <-
+    case getOpt Permute pluginOptions cpuArgs of
+      (_, n, []) -> pure n
+      (_, _, errs) -> error $ "getArguments: " <> show errs
+  cpuOpts <-
+    case getOpt Permute options nonOptions of
+      (o, _, []) -> pure $ foldr id defaultOpts o
+      (_, _, errs) -> error $ "getArguments options: " <> show errs
+  let cpuFields =
+        computeFields
+          (map fst cpuAllTemplate)
+          (map (\(_, f, _) -> f) cpuInputTemplate)
+  pure $ optimizeAllTemplate CpuArguments {..}
+
+
+runCpu :: CpuArguments -> IO String
+runCpu args@CpuArguments {..} = do
+  cpuValue <- parseCpu cpuDataRef
+  temMonitorValues <- formatCpu args cpuValue
+  let templateInput =
+        TemplateInput
+          { temInputTemplate = cpuInputTemplate
+          , temAllTemplate = cpuAllTemplate
+          , ..
+          }
+  pureParseTemplate cpuParams templateInput
 
 startCpu :: [String] -> Int -> (String -> IO ()) -> IO ()
-startCpu a r cb = do
-  cref <- newIORef []
-  _ <- parseCpu cref
-  runM a cpuConfig (runCpu cref) r cb
+startCpu args refreshRate cb = do
+  cpuArgs <- getArguments args
+  doEveryTenthSeconds refreshRate (runCpu cpuArgs >>= cb)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/xmobar-0.34/src/Xmobar/Plugins/Monitors/MultiCoreTemp.hs 
new/xmobar-0.35.1/src/Xmobar/Plugins/Monitors/MultiCoreTemp.hs
--- old/xmobar-0.34/src/Xmobar/Plugins/Monitors/MultiCoreTemp.hs        
2001-09-09 03:46:40.000000000 +0200
+++ new/xmobar-0.35.1/src/Xmobar/Plugins/Monitors/MultiCoreTemp.hs      
2001-09-09 03:46:40.000000000 +0200
@@ -1,7 +1,7 @@
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  Plugins.Monitors.MultiCoreTemp
--- Copyright   :  (c) 2019 Felix Springer
+-- Copyright   :  (c) 2019, 2020 Felix Springer
 -- License     :  BSD-style (see LICENSE)
 --
 -- Maintainer  :  Felix Springer <felixspringer...@gmail.com>
@@ -26,6 +26,7 @@
                      , avgIconPattern :: Maybe IconPattern
                      , mintemp :: Float
                      , maxtemp :: Float
+                     , hwMonitorPath :: Maybe String
                      }
 
 -- | Set default Options.
@@ -34,6 +35,7 @@
                      , avgIconPattern = Nothing
                      , mintemp = 0
                      , maxtemp = 100
+                     , hwMonitorPath = Nothing
                      }
 
 -- | Apply configured Options.
@@ -58,6 +60,11 @@
                 (\ arg opts -> opts { maxtemp = read arg })
                 "")
               ""
+          , Option [] ["hwmon-path"]
+              (ReqArg
+                (\ arg opts -> opts { hwMonitorPath = Just arg })
+                "")
+              ""
           ]
 
 -- | Generate Config with a default template and options.
@@ -68,41 +75,50 @@
                     , "avg" , "avgpc" , "avgbar" , "avgvbar" , "avgipat"
                     ] ++ map (("core" ++) . show) [0 :: Int ..]
 
+
 -- | Returns the first coretemp.N path found.
-coretempPath :: IO String
+coretempPath :: IO (Maybe String)
 coretempPath = do xs <- filterM doesDirectoryExist ps
-                  let x = head xs
-                  return x
-  where ps = [ "/sys/bus/platform/devices/coretemp." ++ show (x :: Int) ++ "/" 
| x <- [0..9] ]
-
--- | Returns the first hwmonN path found.
-hwmonPath :: IO String
-hwmonPath = do p <- coretempPath
-               xs <- filterM doesDirectoryExist [ p ++ "hwmon/hwmon" ++ show 
(x :: Int) ++ "/" | x <- [0..9] ]
-               let x = head xs
-               return x
+                  return (if null xs then Nothing else Just $ head xs)
+  where ps = [ "/sys/bus/platform/devices/coretemp." ++ show (x :: Int) ++ "/"
+             | x <- [0..9] ]
+
+-- | Returns the first hwmonN in coretemp path found or the ones in sys/class.
+hwmonPaths :: IO [String]
+hwmonPaths = do p <- coretempPath
+                let (sc, path) = case p of
+                                   Just s -> (False, s)
+                                   Nothing -> (True, "/sys/class/")
+                let cps  = [ path ++ "hwmon/hwmon" ++ show (x :: Int) ++ "/"
+                           | x <- [0..9] ]
+                ecps <- filterM doesDirectoryExist cps
+                return $ if sc || null ecps then ecps else [head ecps]
 
 -- | Checks Labels, if they refer to a core and returns Strings of core-
 -- temperatures.
-corePaths :: IO [String]
-corePaths = do p <- hwmonPath
-               ls <- filterM doesFileExist [ p ++ "temp" ++ show (x :: Int) ++ 
"_label" | x <- [0..9] ]
-               cls <- filterM isLabelFromCore ls
-               return $ map labelToCore cls
+corePaths :: Maybe String -> IO [String]
+corePaths s = do ps <- case s of
+                        Just pth -> return [pth]
+                        _ -> hwmonPaths
+                 let cps = [p ++ "temp" ++ show (x :: Int) ++ "_label"
+                           | x <- [0..9], p <- ps ]
+                 ls <- filterM doesFileExist cps
+                 cls <- filterM isLabelFromCore ls
+                 return $ map labelToCore cls
 
 -- | Checks if Label refers to a core.
 isLabelFromCore :: FilePath -> IO Bool
 isLabelFromCore p = do a <- readFile p
-                       return $ take 4 a == "Core"
+                       return $ take 4 a `elem` ["Core", "Tdie", "Tctl"]
 
 -- | Transform a path to Label to a path to core-temperature.
 labelToCore :: FilePath -> FilePath
 labelToCore = (++ "input") . reverse . drop 5 . reverse
 
 -- | Reads core-temperatures as data from the system.
-cTData :: IO [Float]
-cTData = do fps <- corePaths
-            traverse readSingleFile fps
+cTData :: Maybe String -> IO [Float]
+cTData p = do fps <- corePaths p
+              traverse readSingleFile fps
   where readSingleFile :: FilePath -> IO Float
         readSingleFile s = do a <- readFile s
                               return $ parseContent a
@@ -110,10 +126,10 @@
                 parseContent = read . head . lines
 
 -- | Transforms data of temperatures into temperatures of degree Celsius.
-parseCT :: IO [Float]
-parseCT = do rawCTs <- cTData
-             let normalizedCTs = map (/ 1000) rawCTs :: [Float]
-             return normalizedCTs
+parseCT :: CTOpts -> IO [Float]
+parseCT opts = do rawCTs <- cTData (hwMonitorPath opts)
+                  let normalizedCTs = map (/ 1000) rawCTs :: [Float]
+                  return normalizedCTs
 
 -- | Performs calculation for maximum and average.
 -- Sets up Bars and Values to be printed.
@@ -150,8 +166,8 @@
 
 
 runCT :: [String] -> Monitor String
-runCT argv = do cTs <- io parseCT
-                opts <- io $ parseOptsWith options defaultOpts argv
+runCT argv = do opts <- io $ parseOptsWith options defaultOpts argv
+                cTs <- io $ parseCT opts
                 l <- formatCT opts cTs
                 parseTemplate l
 
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/xmobar-0.34/test/Xmobar/Plugins/Monitors/CpuSpec.hs 
new/xmobar-0.35.1/test/Xmobar/Plugins/Monitors/CpuSpec.hs
--- old/xmobar-0.34/test/Xmobar/Plugins/Monitors/CpuSpec.hs     1970-01-01 
01:00:00.000000000 +0100
+++ new/xmobar-0.35.1/test/Xmobar/Plugins/Monitors/CpuSpec.hs   2001-09-09 
03:46:40.000000000 +0200
@@ -0,0 +1,41 @@
+module Xmobar.Plugins.Monitors.CpuSpec
+  ( 
+   spec, main
+  ) where
+
+import Test.Hspec
+import Xmobar.Plugins.Monitors.Common
+import Xmobar.Plugins.Monitors.Cpu
+import Data.List
+
+main :: IO ()
+main = hspec spec
+
+spec :: Spec
+spec =
+  describe "CPU Spec" $ do
+    it "works with total template" $
+      do let args = ["-L","3","-H","50","--normal","green","--high","red", 
"-t", "Cpu: <total>%"]
+         cpuArgs <- getArguments args
+         cpuValue <- runCpu cpuArgs
+         cpuValue `shouldSatisfy` (\item -> "Cpu:" `isPrefixOf` item)
+    it "works with bar template" $
+      do let args = ["-L","3","-H","50","--normal","green","--high","red", 
"-t", "Cpu: <total>% <bar>"]
+         cpuArgs <- getArguments args
+         cpuValue <- runCpu cpuArgs
+         cpuValue `shouldSatisfy` (\item -> "::" `isSuffixOf` item)
+    it "works with no icon pattern template" $
+      do let args = ["-L","3","-H","50","--normal","green","--high","red", 
"-t", "Cpu: <total>% <bar>", "--", "--load-icon-pattern", 
"<icon=bright_%%.xpm/>"]
+         cpuArgs <- getArguments args
+         cpuValue <- runCpu cpuArgs
+         cpuValue `shouldSatisfy` (\item -> not $ "<icon=bright_" `isInfixOf` 
cpuValue)
+    it "works with icon pattern template" $
+      do let args = ["-L","3","-H","50","--normal","green","--high","red", 
"-t", "Cpu: <total>% <bar> <ipat>", "--", "--load-icon-pattern", 
"<icon=bright_%%.xpm/>"]
+         cpuArgs <- getArguments args
+         cpuValue <- runCpu cpuArgs
+         cpuValue `shouldSatisfy` (\item -> "<icon=bright_" `isInfixOf` 
cpuValue)
+    it "works with other parameters in template" $
+      do let args = ["-L","3","-H","50","--normal","green","--high","red", 
"-t", "Cpu: <user> <nice> <iowait>"]
+         cpuArgs <- getArguments args
+         cpuValue <- runCpu cpuArgs
+         cpuValue `shouldSatisfy` (\item -> "Cpu:" `isPrefixOf` cpuValue)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/xmobar-0.34/xmobar.cabal 
new/xmobar-0.35.1/xmobar.cabal
--- old/xmobar-0.34/xmobar.cabal        2001-09-09 03:46:40.000000000 +0200
+++ new/xmobar-0.35.1/xmobar.cabal      2001-09-09 03:46:40.000000000 +0200
@@ -1,5 +1,5 @@
 name:               xmobar
-version:            0.34
+version:            0.35.1
 homepage:           http://xmobar.org
 synopsis:           A Minimalistic Text Based Status Bar
 description:       Xmobar is a minimalistic text based status bar.
@@ -95,7 +95,10 @@
     default-language: Haskell2010
     hs-source-dirs:  src
 
-    exposed-modules: Xmobar
+    exposed-modules: Xmobar,
+                     Xmobar.Plugins.Monitors.Common.Types,
+                     Xmobar.Plugins.Monitors.Common.Run,
+                     Xmobar.Plugins.Monitors.Cpu
 
     other-modules: Paths_xmobar,
                    Xmobar.Config.Types,
@@ -140,14 +143,11 @@
                    Xmobar.Plugins.Monitors,
                    Xmobar.Plugins.Monitors.Batt,
                    Xmobar.Plugins.Monitors.Common,
-                   Xmobar.Plugins.Monitors.Common.Types,
-                   Xmobar.Plugins.Monitors.Common.Run,
                    Xmobar.Plugins.Monitors.Common.Output,
                    Xmobar.Plugins.Monitors.Common.Parsers,
                    Xmobar.Plugins.Monitors.Common.Files,
                    Xmobar.Plugins.Monitors.CoreTemp,
                    Xmobar.Plugins.Monitors.CpuFreq,
-                   Xmobar.Plugins.Monitors.Cpu,
                    Xmobar.Plugins.Monitors.Disk,
                    Xmobar.Plugins.Monitors.Mem,
                    Xmobar.Plugins.Monitors.MultiCoreTemp,
@@ -166,7 +166,7 @@
     ghc-options: -funbox-strict-fields -Wall -fno-warn-unused-do-bind
 
     build-depends:
-      base >= 4.9.1.0 && < 4.15,
+      base >= 4.11.0 && < 4.15,
       containers,
       regex-compat,
       process,
@@ -242,7 +242,7 @@
        cpp-options: -DALSA
 
     if flag(with_datezone) || flag(all_extensions)
-       build-depends: timezone-olson == 0.1.*, timezone-series == 0.1.*
+       build-depends: timezone-olson >= 0.1 && < 0.3, timezone-series == 0.1.*
        other-modules: Xmobar.Plugins.DateZone
        cpp-options: -DDATEZONE
 
@@ -331,10 +331,11 @@
   other-modules: Xmobar.Plugins.Monitors.CommonSpec
                  Xmobar.Plugins.Monitors.Common
                  Xmobar.Plugins.Monitors.Common.Parsers
-                 Xmobar.Plugins.Monitors.Common.Run
                  Xmobar.Plugins.Monitors.Common.Types
                  Xmobar.Plugins.Monitors.Common.Output
                  Xmobar.Plugins.Monitors.Common.Files
+                 Xmobar.Plugins.Monitors.Cpu
+                 Xmobar.Plugins.Monitors.Common.Run
                  Xmobar.Run.Exec
                  Xmobar.App.Timer
                  Xmobar.System.Signal
@@ -346,5 +347,15 @@
       other-modules: Xmobar.Plugins.Monitors.Volume
                      Xmobar.Plugins.Monitors.Alsa
                      Xmobar.Plugins.Monitors.AlsaSpec
+                     Xmobar.Plugins.Monitors.CpuSpec
 
       cpp-options: -DALSA
+
+benchmark xmobarbench
+  type: exitcode-stdio-1.0
+  main-is: main.hs
+  hs-source-dirs:
+      bench
+  ghc-options: -O2
+  build-depends: base, gauge, xmobar, mtl
+  default-language: Haskell2010


Reply via email to