FIX disconnecting screensaver client

This commit is contained in:
Nathan Dwarshuis 2021-11-24 01:22:03 -05:00
parent 20b915631e
commit 0522766f38
1 changed files with 9 additions and 17 deletions

View File

@ -1,5 +1,3 @@
{-# LANGUAGE LambdaCase #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- | Screensaver plugin -- | Screensaver plugin
-- --
@ -11,14 +9,11 @@ module Xmobar.Plugins.Screensaver
, ssAlias , ssAlias
) where ) where
import Control.Concurrent
import Control.Monad
import Xmobar import Xmobar
import XMonad.Hooks.DynamicLog (xmobarColor) import XMonad.Internal.DBus.Common
import XMonad.Internal.DBus.Control
import XMonad.Internal.DBus.Screensaver import XMonad.Internal.DBus.Screensaver
import Xmobar.Plugins.Common
newtype Screensaver = Screensaver (String, String, String) deriving (Read, Show) newtype Screensaver = Screensaver (String, String, String) deriving (Read, Show)
@ -26,14 +21,11 @@ ssAlias :: String
ssAlias = "screensaver" ssAlias = "screensaver"
instance Exec Screensaver where instance Exec Screensaver where
alias (Screensaver _) = ssAlias alias (Screensaver _) = ssAlias
start (Screensaver (text, colorOn, colorOff)) cb = do start (Screensaver (text, colorOn, colorOff)) cb = do
withDBusClient_ False $ \c -> do withDBusClientConnection_ False $ \c -> do
matchSignal (cb . fmtState) c matchSignal (cb . fmtState) c
cb . fmtState =<< callQuery c cb . fmtState =<< callQuery c
forever (threadDelay 5000000) where
where fmtState = maybe "N/A" $ chooseColor text colorOn colorOff
fmtState = \case
Just s -> xmobarColor (if s then colorOn else colorOff) "" text
Nothing -> "N/A"