Script 'mail_helper' called by obssrc
Hello community,

here is the log from the commit of package xmobar for openSUSE:Factory checked 
in at 2025-06-11 16:26:59
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/xmobar (Old)
 and      /work/SRC/openSUSE:Factory/.xmobar.new.19631 (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Package is "xmobar"

Wed Jun 11 16:26:59 2025 rev:34 rq:1284558 version:0.50

Changes:
--------
--- /work/SRC/openSUSE:Factory/xmobar/xmobar.changes    2025-04-09 
21:50:56.507814751 +0200
+++ /work/SRC/openSUSE:Factory/.xmobar.new.19631/xmobar.changes 2025-06-11 
16:28:45.166046822 +0200
@@ -1,0 +2,16 @@
+Wed Jun  4 13:27:19 UTC 2025 - Peter Simons <psim...@suse.com>
+
+- Update xmobar to version 0.50.
+  ## Version 0.50 (June, 2025)
+
+  - New plugins: `PacmanUpdates` (thanks, Alexander)
+  - `ArchUpdates` deprecated in favor of `PacmanUpdates`
+    - a deprecation notice will be shown to users of that plugin in the bar in
+      the zero updates case
+  - `Accordion`: new constructor to allow short version to have plugins too
+  - `Swap`: update for FreeBSD 15
+  - `MPD` compiled again by default with `all_extensions`.
+
+- Drop obsolete "re-enable-support-for-libmpd.patch".
+
+-------------------------------------------------------------------

Old:
----
  re-enable-support-for-libmpd.patch
  xmobar-0.49.tar.gz

New:
----
  xmobar-0.50.tar.gz

BETA DEBUG BEGIN:
  Old:
- Drop obsolete "re-enable-support-for-libmpd.patch".
BETA DEBUG END:

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

Other differences:
------------------
++++++ xmobar.spec ++++++
--- /var/tmp/diff_new_pack.fnLy2o/_old  2025-06-11 16:28:45.934078860 +0200
+++ /var/tmp/diff_new_pack.fnLy2o/_new  2025-06-11 16:28:45.938079027 +0200
@@ -20,13 +20,12 @@
 %global pkgver %{pkg_name}-%{version}
 %bcond_with tests
 Name:           %{pkg_name}
-Version:        0.49
+Version:        0.50
 Release:        0
 Summary:        A Minimalistic Text Based Status Bar
 License:        BSD-3-Clause
 URL:            https://hackage.haskell.org/package/%{name}
 Source0:        
https://hackage.haskell.org/package/%{name}-%{version}/%{name}-%{version}.tar.gz
-Patch1:         re-enable-support-for-libmpd.patch
 BuildRequires:  chrpath
 BuildRequires:  ghc-Cabal-devel
 BuildRequires:  ghc-X11-devel
@@ -156,7 +155,7 @@
 This package provides the Haskell %{pkg_name} profiling library.
 
 %prep
-%autosetup -p1
+%autosetup
 
 %build
 %define cabal_configure_options -f+all_extensions

++++++ xmobar-0.49.tar.gz -> xmobar-0.50.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/xmobar-0.49/changelog.md new/xmobar-0.50/changelog.md
--- old/xmobar-0.49/changelog.md        2001-09-09 03:46:40.000000000 +0200
+++ new/xmobar-0.50/changelog.md        2001-09-09 03:46:40.000000000 +0200
@@ -1,3 +1,13 @@
+## Version 0.50 (June, 2025)
+
+- New plugins: `PacmanUpdates` (thanks, Alexander)
+- `ArchUpdates` deprecated in favor of `PacmanUpdates`
+  - a deprecation notice will be shown to users of that plugin in the bar in
+    the zero updates case
+- `Accordion`: new constructor to allow short version to have plugins too
+- `Swap`: update for FreeBSD 15
+- `MPD` compiled again by default with `all_extensions`.
+
 ## Version 0.49 (April, 2025)
 
 - New plugins: `ArchUpdates` and `Accordion` (thanks, Enrico Maria)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/xmobar-0.49/doc/plugins.org 
new/xmobar-0.50/doc/plugins.org
--- old/xmobar-0.49/doc/plugins.org     2001-09-09 03:46:40.000000000 +0200
+++ new/xmobar-0.50/doc/plugins.org     2001-09-09 03:46:40.000000000 +0200
@@ -1077,8 +1077,8 @@
 ** Music monitors
 *** =MPD Args RefreshRate=
 
-    - This monitor will only be compiled if you ask for it using the
-      =with_mpd= flag. It needs 
[[http://hackage.haskell.org/package/libmpd/][libmpd]] 5.0 or later (available 
on Hackage).
+    - This monitor will only be compiled if you ask for it using the =with_mpd=
+      flag. It needs [[http://hackage.haskell.org/package/libmpd/][libmpd]] 
0.10.1 or later (available on Hackage).
 
     - Aliases to =mpd=
 
@@ -1353,21 +1353,37 @@
       the display of those numeric fields.
     - Default template: =Up: <days>d <hours>h <minutes>m=
 
-*** =ArchUpdates (Zero, One, Many) Rate=
+*** =PacmanUpdates (Zero, One, Many, Error) Rate=
 
-  - Aliases to =arch=
+  - Aliases to =pacman=
   - =Zero=: a =String= to use when the system is up to date.
   - =One=: a =String= to use when only one update is available.
-  - =Many=: a =String= to use when several updates are available; it must 
contain
+  - =Many=: a =String= to use when several updates are available; it can 
contain
     a =?= character as a placeholder for the number of updates.
+  - =Error=: a =String= to use when pacman fails for unkown reasons (e.g.
+    network error)
   - Example:
     #+begin_src haskell
       ArchUpdates ("<fc=green>up to date</fc>",
                    "<fc=yellow>1 update</fc>,
-                   "<fc=red>? updates</fc>")
+                   "<fc=red>? updates</fc>",
+                   "<fc=red>!Pacman Error!</fc>")
                    600
     #+end_src
 
+*** =ArchUpdates (Zero, One, Many) Rate=
+
+  - *This plugin is deprecated. Use =PacmanUpdates= instead.*
+  - Aliases to =arch=
+  - Same As:
+    #+begin_src haskell
+      PacmanUpdates  (Zero,
+                      One,
+                      Many,
+                      "pacman: Unknown cause of failure.")
+                     Rate
+    #+end_src
+
 *** =makeAccordion Tuning [Runnable]=
 
   - Wraps other =Runnable= plugins and makes them all collapsible to a single 
string:
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/xmobar-0.49/readme.org new/xmobar-0.50/readme.org
--- old/xmobar-0.49/readme.org  2001-09-09 03:46:40.000000000 +0200
+++ new/xmobar-0.50/readme.org  2001-09-09 03:46:40.000000000 +0200
@@ -28,13 +28,6 @@
 
 * Breaking news
 
-  - Starting with version 0.47.1, we are excluding MPD from the extensions
-    included with ~all_extensions~ when GHC version is 9.4 or greater, because
-    that seems to break cabal compilation.  However, it's been reported that
-    in some installations compilation with ~libmpd~ works fine: just add
-    explicitly the ~with_mpd~ flag to include MPD and check for yourself.
-    Compilation with stack has also been reported to work.  Please see the
-    comments in issue #679 for details.
   - Starting with version 0.45, we use cairo/pango as our drawing engine
     (instead of plain X11/Xft).  From a user's point of view, that change
     should be mostly transparent, except for the facts that it's allowed
@@ -179,15 +172,15 @@
   Lennart Kolmodin, Krzysztof Kosciuszkiewicz, Dmitry Kurochkin, Todd Lunter,
   Vanessa McHale, Robert J. Macomber, Dmitry Malikov, David McLean, Ulrik de
   Muelenaere, Joan Milev, Marcin Mikołajczyk, Dino Morelli, Tony Morris, Eric
-  Mrak, Thiago Negri, Edward O'Callaghan, Svein Ove, Martin Perner, Jens
-  Petersen, Alexander Polakov, Sibi Prabakaran, Pavan Rikhi, Petr Rockai,
-  Andrew Emmanuel Rosa, Sackville-West, Amir Saeid, Markus Scherer, Daniel
-  Schüssler, Olivier Schneider, Alexander Shabalin, Valentin Shirokov, Peter
-  Simons, Alexander Solovyov, Will Song, John Soo, John Soros, Felix Springer,
-  Travis Staton, Artem Tarasov, Samuli Thomasson, Edward Tjörnhammar, Sergei
-  Trofimovich, Thomas Tuegel, John Tyree, Jan Vornberger, Anton Vorontsov,
-  Daniel Wagner, Zev Weiss, Phil Xiaojun Hu, Nikolay Yakimov, Edward Z. Yang,
-  Leo Zhang, Norbert Zeh, and Michał Zielonka.
+  Mrak, Thiago Negri, Edward O'Callaghan, Svein Ove, Martin Perner, Alexander
+  Pankoff, Jens Petersen, Alexander Polakov, Sibi Prabakaran, Pavan Rikhi,
+  Petr Rockai, Andrew Emmanuel Rosa, Sackville-West, Amir Saeid, Markus
+  Scherer, Daniel Schüssler, Olivier Schneider, Alexander Shabalin, Valentin
+  Shirokov, Peter Simons, Alexander Solovyov, Will Song, John Soo, John Soros,
+  Felix Springer, Travis Staton, Artem Tarasov, Samuli Thomasson, Edward
+  Tjörnhammar, Sergei Trofimovich, Thomas Tuegel, John Tyree, Jan Vornberger,
+  Anton Vorontsov, Daniel Wagner, Zev Weiss, Phil Xiaojun Hu, Nikolay Yakimov,
+  Edward Z. Yang, Leo Zhang, Norbert Zeh, and Michał Zielonka.
 
   Andrea wants to thank Robert Manea and Spencer Janssen for their help in
   understanding how X works. They gave him suggestions on how to solve many
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/xmobar-0.49/src/Xmobar/Plugins/Accordion.hs 
new/xmobar-0.50/src/Xmobar/Plugins/Accordion.hs
--- old/xmobar-0.49/src/Xmobar/Plugins/Accordion.hs     2001-09-09 
03:46:40.000000000 +0200
+++ new/xmobar-0.50/src/Xmobar/Plugins/Accordion.hs     2001-09-09 
03:46:40.000000000 +0200
@@ -15,7 +15,7 @@
 --
 -----------------------------------------------------------------------------
 
-module Xmobar.Plugins.Accordion (defaultTuning, makeAccordion, Tuning(..)) 
where
+module Xmobar.Plugins.Accordion (defaultTuning, makeAccordion, makeAccordion', 
Tuning(..)) where
 
 import Control.Concurrent.Async (withAsync)
 import Control.Exception (finally)
@@ -23,7 +23,7 @@
 import Control.Monad.IO.Class (liftIO)
 import Control.Monad.Reader (runReaderT, ask)
 import Control.Monad.State.Strict (evalStateT, get, modify')
-import Data.IORef (atomicModifyIORef', newIORef, readIORef)
+import Data.IORef (atomicModifyIORef', newIORef, readIORef, IORef)
 import Data.Maybe (isJust)
 import System.Directory (removeFile)
 import System.Exit (ExitCode(..))
@@ -38,10 +38,14 @@
 data Accordion a = Accordion {
     tuning :: Tuning
   , plugins :: [a]
+  , shortPlugins :: [a]
 } deriving (Show, Read)
 
 makeAccordion :: Exec a => Tuning -> [a] -> Accordion a
-makeAccordion t rs = Accordion { tuning = t, plugins = rs }
+makeAccordion t rs = Accordion { tuning = t, plugins = rs, shortPlugins = [] }
+
+makeAccordion' :: Exec a => Tuning -> [a] -> [a] -> Accordion a
+makeAccordion' t rs rs' = Accordion { tuning = t, plugins = rs, shortPlugins = 
rs' }
 
 data Tuning = Tuning {
     alias' :: String
@@ -59,11 +63,12 @@
 }
 
 instance (Exec a, Read a, Show a) => Exec (Accordion a) where
-  alias (Accordion Tuning { alias' = name } _) = name
+  alias (Accordion Tuning { alias' = name } _ _) = name
   start (Accordion Tuning { initial = initial'
-                          , expand = expand'
-                          , shrink = shrink' }
-                   runnables)
+                          , expand = expandIcon
+                          , shrink = shrinkIcon }
+                   runnables
+                   shortRunnables)
         cb = do
     clicked <- newIORef Nothing
     (_, n, _) <- readProcessWithExitCode "uuidgen" [] ""
@@ -74,24 +79,35 @@
                               ExitSuccess -> atomicModifyIORef' clicked (const 
(Just (), ()))
                               ExitFailure _ -> error "how is this possible?")
               (const $ do
-                  srefs <- mapM (newIORef . const "") runnables
-                  foldr (\(runnable, sref) acc -> withAsync (start runnable 
(writeToRef sref)) (const acc))
+                  strRefs <- mapM (newIORef . const "") runnables
+                  strRefs' <- mapM (newIORef . const "") shortRunnables
+                  foldr (\(runnable, strRef) acc -> withAsync (start runnable 
(writeToRef strRef)) (const acc))
                         (forever (do liftIO (tenthSeconds 1)
                                      clicked' <- liftIO $ readIORef clicked
                                      when (isJust clicked')
                                           (do liftIO $ clear clicked
                                               modify' not)
                                      b <- get
-                                     if b then loop pipe else liftIO $ cb 
(click pipe expand'))
-                                 `runReaderT` srefs `evalStateT` initial')
-                        (zip runnables srefs))
+                                     loop b pipe)
+                                 `runReaderT` (strRefs, strRefs')
+                                 `evalStateT` initial')
+                        (zip (runnables ++ shortRunnables)
+                             (strRefs ++ strRefs')))
       `finally` removeFile pipe
     where
-      click file icon = "<action=`echo 1 > " ++ file ++ "`>" ++ icon ++ 
"</action>"
-      clear = (`atomicModifyIORef'` const (Nothing, ()))
-      removeLinebreak = init
-      writeToRef strRef = atomicModifyIORef' strRef . const . (,())
-      loop p = do
-        srefs <- ask
-        text <- join <$> mapM (liftIO . readIORef) srefs
-        liftIO $ cb $ text ++ click p shrink'
+      loop b p = do
+        (strRefs, strRefs') <- ask
+        text <- join <$> mapM (liftIO . readIORef) (if b then strRefs else 
strRefs')
+        liftIO $ cb $ text ++ attachClick p (if b then shrinkIcon else 
expandIcon)
+
+writeToRef :: IORef a -> a -> IO ()
+writeToRef strRef = atomicModifyIORef' strRef . const . (,())
+
+clear :: IORef (Maybe a) -> IO ()
+clear = (`atomicModifyIORef'` const (Nothing, ()))
+
+removeLinebreak :: [a] -> [a]
+removeLinebreak = init
+
+attachClick :: String -> String -> String
+attachClick file icon = "<action=`echo 1 > " ++ file ++ "`>" ++ icon ++ 
"</action>"
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/xmobar-0.49/src/Xmobar/Plugins/ArchUpdates.hs 
new/xmobar-0.50/src/Xmobar/Plugins/ArchUpdates.hs
--- old/xmobar-0.49/src/Xmobar/Plugins/ArchUpdates.hs   2001-09-09 
03:46:40.000000000 +0200
+++ new/xmobar-0.50/src/Xmobar/Plugins/ArchUpdates.hs   2001-09-09 
03:46:40.000000000 +0200
@@ -1,41 +1,36 @@
 {-# LANGUAGE CPP #-}
 
 -----------------------------------------------------------------------------
--- |
--- Module      :  Plugins.Monitors.ArchUpdates
--- Copyright   :  (c) 2024 Enrico Maria De Angelis
--- License     :  BSD-style (see LICENSE)
---
--- Maintainer  :  Enrico Maria De Angelis <enricomaria.dean6e...@gmail.com>
--- Stability   :  unstable
--- Portability :  unportable
---
--- An ArchLinux updates availablility plugin for Xmobar
---
+
 -----------------------------------------------------------------------------
 
-module Xmobar.Plugins.ArchUpdates (ArchUpdates(..)) where
+{- |
+Module      :  Plugins.Monitors.ArchUpdates
+Copyright   :  (c) 2024 Enrico Maria De Angelis
+License     :  BSD-style (see LICENSE)
+
+Maintainer  :  Enrico Maria De Angelis <enricomaria.dean6e...@gmail.com>
+Stability   :  unstable
+Portability :  unportable
+
+An ArchLinux updates availablility plugin for Xmobar
+-}
+module Xmobar.Plugins.ArchUpdates (ArchUpdates (..)) where
 
-import System.Exit (ExitCode(..))
-import System.Process (readProcessWithExitCode)
-import Xmobar.Run.Exec
 import Xmobar.Plugins.Command (Rate)
+import Xmobar.Plugins.PacmanUpdates (PacmanUpdates (PacmanUpdates))
+import Xmobar.Run.Exec
 
 data ArchUpdates = ArchUpdates (String, String, String) Rate
   deriving (Read, Show)
 
+intoPacmanUpdates :: ArchUpdates -> PacmanUpdates
+intoPacmanUpdates (ArchUpdates (z, o, m) r) =
+  PacmanUpdates (z <> deprecation, o, m, "pacman: Unknown cause of failure.") r
+ where
+  deprecation = " <fc=#ff0000>(<action=`xdg-open 
https://codeberg.org/xmobar/xmobar/pulls/723`>deprecated plugin, click 
here</action>)</fc>"
+
 instance Exec ArchUpdates where
-    alias (ArchUpdates _ _) = "arch"
-    rate (ArchUpdates _ r) = r
-    run (ArchUpdates (z, o, m) _) = do
-      (exit, stdout, _) <- readProcessWithExitCode "checkupdates" [] ""
-      return $ case exit of
-        ExitFailure 2 -> z--ero updates
-        ExitFailure 1 -> "pacman: Unknown cause of failure."
-        ExitSuccess -> case length $ lines stdout of
-          0 -> impossible
-          1 -> o
-          n -> m >>= \c -> if c == '?' then show n else pure c
-        _ -> impossible
-        where
-          impossible = error "This is impossible based on pacman manpage"
+  alias = const "arch"
+  rate = rate . intoPacmanUpdates
+  run = run . intoPacmanUpdates
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/xmobar-0.49/src/Xmobar/Plugins/Monitors/MPD.hs 
new/xmobar-0.50/src/Xmobar/Plugins/Monitors/MPD.hs
--- old/xmobar-0.49/src/Xmobar/Plugins/Monitors/MPD.hs  2001-09-09 
03:46:40.000000000 +0200
+++ new/xmobar-0.50/src/Xmobar/Plugins/Monitors/MPD.hs  2001-09-09 
03:46:40.000000000 +0200
@@ -109,8 +109,9 @@
         si = stateGlyph s opts
         vol = int2str $ fromMaybe 0 (M.stVolume st)
         (p, t) = fromMaybe (0, 0) (M.stTime st)
-        [lap, len, remain] = map showTime
-                                 [floor p, floor t, max 0 (floor t - floor p)]
+        lap = showTime $ floor p
+        len = showTime $ floor t
+        remain = showTime $ max 0 (floor t - floor p)
         b = if t > 0 then realToFrac $ p / t else 0
         plen = int2str $ M.stPlaylistLength st
         ppos = maybe "" (int2str . (+1)) $ M.stSongPos st
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/xmobar-0.49/src/Xmobar/Plugins/Monitors/Swap/FreeBSD.hsc 
new/xmobar-0.50/src/Xmobar/Plugins/Monitors/Swap/FreeBSD.hsc
--- old/xmobar-0.49/src/Xmobar/Plugins/Monitors/Swap/FreeBSD.hsc        
2001-09-09 03:46:40.000000000 +0200
+++ new/xmobar-0.50/src/Xmobar/Plugins/Monitors/Swap/FreeBSD.hsc        
2001-09-09 03:46:40.000000000 +0200
@@ -71,11 +71,10 @@
 
   poke _ _    = pure ()
 
-
 isEnabled :: IO Bool
 isEnabled = do
-  enabled <- sysctlReadUInt "vm.swap_enabled"
-  return $ enabled == 1
+  nswapdev <- sysctlReadUInt "vm.nswapdev"
+  return $ nswapdev > 0
 
 parseMEM' :: Bool -> IO [Float]
 parseMEM' False = return []
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/xmobar-0.49/src/Xmobar/Plugins/PacmanUpdates.hs 
new/xmobar-0.50/src/Xmobar/Plugins/PacmanUpdates.hs
--- old/xmobar-0.49/src/Xmobar/Plugins/PacmanUpdates.hs 1970-01-01 
01:00:00.000000000 +0100
+++ new/xmobar-0.50/src/Xmobar/Plugins/PacmanUpdates.hs 2001-09-09 
03:46:40.000000000 +0200
@@ -0,0 +1,43 @@
+{-# LANGUAGE CPP #-}
+
+-----------------------------------------------------------------------------
+
+-----------------------------------------------------------------------------
+
+{- |
+Module      :  Plugins.Monitors.PacmanUpdates
+Copyright   :  (c) 2024 Enrico Maria De Angelis
+            ,  (c) 2025 Alexander Pankoff
+License     :  BSD-style (see LICENSE)
+
+Maintainer  :  Enrico Maria De Angelis <enricomaria.dean6e...@gmail.com>
+Stability   :  unstable
+Portability :  unportable
+
+A Pacman updates availablility plugin for Xmobar
+-}
+module Xmobar.Plugins.PacmanUpdates (PacmanUpdates (..)) where
+
+import System.Exit (ExitCode (..))
+import System.Process (readProcessWithExitCode)
+import Xmobar.Plugins.Command (Rate)
+import Xmobar.Run.Exec
+
+data PacmanUpdates = PacmanUpdates (String, String, String, String) Rate
+  deriving (Read, Show)
+
+instance Exec PacmanUpdates where
+  alias = const "pacman"
+  rate (PacmanUpdates _ r) = r
+  run (PacmanUpdates (z, o, m, e) _) = do
+    (exit, stdout, _) <- readProcessWithExitCode "checkupdates" [] ""
+    return $ case exit of
+      ExitFailure 2 -> z -- ero updates
+      ExitFailure 1 -> e
+      ExitSuccess -> case length $ lines stdout of
+        0 -> impossible
+        1 -> o
+        n -> m >>= \c -> if c == '?' then show n else pure c
+      _ -> impossible
+   where
+    impossible = error "This is impossible based on pacman manpage"
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/xmobar-0.49/src/Xmobar.hs 
new/xmobar-0.50/src/Xmobar.hs
--- old/xmobar-0.49/src/Xmobar.hs       2001-09-09 03:46:40.000000000 +0200
+++ new/xmobar-0.50/src/Xmobar.hs       2001-09-09 03:46:40.000000000 +0200
@@ -45,6 +45,7 @@
 #endif
               , module Xmobar.Plugins.NotmuchMail
               , module Xmobar.Plugins.Monitors
+              , module Xmobar.Plugins.PacmanUpdates
               , module Xmobar.Plugins.PipeReader
               , module Xmobar.Plugins.MarqueePipeReader
               , module Xmobar.Plugins.StdinReader
@@ -74,6 +75,7 @@
 import Xmobar.Plugins.MBox
 #endif
 import Xmobar.Plugins.Monitors
+import Xmobar.Plugins.PacmanUpdates
 import Xmobar.Plugins.PipeReader
 import Xmobar.Plugins.StdinReader
 import Xmobar.Plugins.MarqueePipeReader
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/xmobar-0.49/xmobar.cabal new/xmobar-0.50/xmobar.cabal
--- old/xmobar-0.49/xmobar.cabal        2001-09-09 03:46:40.000000000 +0200
+++ new/xmobar-0.50/xmobar.cabal        2001-09-09 03:46:40.000000000 +0200
@@ -1,5 +1,5 @@
 name:               xmobar
-version:            0.49
+version:            0.50
 homepage:           https://codeberg.org/xmobar/xmobar
 synopsis:           A Minimalistic Text Based Status Bar
 description:       Xmobar is a minimalistic text based status bar.
@@ -158,6 +158,7 @@
                    Xmobar.Plugins.EWMH,
                    Xmobar.Plugins.HandleReader,
                    Xmobar.Plugins.QueueReader,
+                   Xmobar.Plugins.PacmanUpdates,
                    Xmobar.Plugins.PipeReader,
                    Xmobar.Plugins.MarqueePipeReader,
                    Xmobar.Plugins.StdinReader,
@@ -265,8 +266,8 @@
                       cereal >= 0.5.8.1
        cpp-options: -DUSE_NL80211
 
-    if flag(with_mpd) || (flag(all_extensions) && impl(ghc < 9.4))
-       build-depends: libmpd >= 0.9.2.0
+    if flag(with_mpd) || flag(all_extensions)
+       build-depends: libmpd >= 0.10.0.1
        other-modules: Xmobar.Plugins.Monitors.MPD
        cpp-options: -DLIBMPD
 

Reply via email to