Use extensible state instead of IORef

This commit is contained in:
Ben Gamari 2018-06-19 11:14:04 -04:00
parent 203e63b055
commit f6f925c823

View File

@ -26,7 +26,6 @@ module XMonad.Hooks.EwmhDesktops (
import Codec.Binary.UTF8.String (encode) import Codec.Binary.UTF8.String (encode)
import Control.Applicative((<$>)) import Control.Applicative((<$>))
import Data.IORef
import Data.List import Data.List
import Data.Maybe import Data.Maybe
import Data.Monoid import Data.Monoid
@ -38,6 +37,7 @@ import Control.Monad
import qualified XMonad.StackSet as W import qualified XMonad.StackSet as W
import XMonad.Hooks.SetWMName import XMonad.Hooks.SetWMName
import qualified XMonad.Util.ExtensibleState as E
import XMonad.Util.XUtils (fi) import XMonad.Util.XUtils (fi)
import XMonad.Util.WorkspaceCompare import XMonad.Util.WorkspaceCompare
import XMonad.Util.WindowProperties (getProp32) import XMonad.Util.WindowProperties (getProp32)
@ -74,32 +74,44 @@ ewmhDesktopsStartup = setSupported
ewmhDesktopsLogHook :: X () ewmhDesktopsLogHook :: X ()
ewmhDesktopsLogHook = ewmhDesktopsLogHookCustom id ewmhDesktopsLogHook = ewmhDesktopsLogHookCustom id
-- |
-- The values of @_NET_NUMBER_OF_DESKTOPS@, @_NET_CLIENT_LIST@,
-- @_NET_CLIENT_LIST_STACKING@, and @_NET_CURRENT_DESKTOP@, cached to avoid
-- unnecessary property updates. Another design would be to cache each of these
-- independently to allow us to avoid even more updates.
data DesktopState
= DesktopState { desktopNames :: [String]
, clientList :: [Window]
, currentDesktop :: Maybe Int
, windowDesktops :: M.Map Window Int
}
deriving (Eq)
data EwmhState = EwmhState { desktopNames :: [String] instance ExtensionClass DesktopState where
, clientList :: [Window] initialValue = DesktopState [] [] Nothing M.empty
, currentDesktop :: Maybe Int
, windowDesktops :: M.Map Window Int
}
deriving (Eq, Show)
toEwmhState :: ([WindowSpace] -> [WindowSpace]) -> WindowSet -> EwmhState toDesktopState :: ([WindowSpace] -> [WindowSpace]) -> WindowSet -> DesktopState
toEwmhState f s = toDesktopState f s =
EwmhState { desktopNames = map W.tag ws DesktopState
, clientList = nub . concatMap (maybe [] (\(W.Stack x l r) -> reverse l ++ r ++ [x]) . W.stack) $ ws { desktopNames = map W.tag ws
, currentDesktop = , clientList = nub . concatMap (maybe [] (\(W.Stack x l r) -> reverse l ++ r ++ [x]) . W.stack) $ ws
let maybeCurrent' = W.tag <$> listToMaybe (f [W.workspace $ W.current s]) , currentDesktop =
in join (flip elemIndex (map W.tag ws) <$> maybeCurrent') let maybeCurrent' = W.tag <$> listToMaybe (f [W.workspace $ W.current s])
, windowDesktops = in join (flip elemIndex (map W.tag ws) <$> maybeCurrent')
let f wsId workspace = M.fromList [ (winId, wsId) | winId <- W.integrate' $ W.stack workspace ] , windowDesktops =
in M.unions $ zipWith f [0..] ws let f wsId workspace = M.fromList [ (winId, wsId) | winId <- W.integrate' $ W.stack workspace ]
} in M.unions $ zipWith f [0..] ws
}
where ws = f $ W.workspaces s where ws = f $ W.workspaces s
-- | -- | Compare the given value against the value in the extensible state. Run the
-- Cache last property state to avoid needless property changes. -- action if it has changed.
cachedState :: IORef (Maybe EwmhState) whenChanged :: (Eq a, ExtensionClass a) => a -> X () -> X ()
cachedState = unsafePerformIO $ newIORef Nothing whenChanged v action = do
{-# NOINLINE cachedState #-} v0 <- E.get
unless (v == v0) $ do
action
E.put v
-- | -- |
-- Generalized version of ewmhDesktopsLogHook that allows an arbitrary -- Generalized version of ewmhDesktopsLogHook that allows an arbitrary
@ -107,12 +119,8 @@ cachedState = unsafePerformIO $ newIORef Nothing
ewmhDesktopsLogHookCustom :: ([WindowSpace] -> [WindowSpace]) -> X () ewmhDesktopsLogHookCustom :: ([WindowSpace] -> [WindowSpace]) -> X ()
ewmhDesktopsLogHookCustom f = withWindowSet $ \s -> do ewmhDesktopsLogHookCustom f = withWindowSet $ \s -> do
sort' <- getSortByIndex sort' <- getSortByIndex
let s' = toEwmhState (f . sort') s let s' = toDesktopState (f . sort') s
whenChanged s' $ do
cached <- io $ readIORef cachedState
unless (cached == Just s') $ do
io $ writeIORef cachedState $ Just s'
-- Number of Workspaces -- Number of Workspaces
setNumberOfDesktops (length $ desktopNames s') setNumberOfDesktops (length $ desktopNames s')