Merge pull request #406 from liskin/managedocks-cache-on-demand

X.H.ManageDocks: Init strut cache on demand if necessary
This commit is contained in:
Tomáš Janoušek
2021-01-24 16:43:56 +01:00
committed by GitHub
2 changed files with 44 additions and 17 deletions

View File

@@ -294,8 +294,12 @@
- Export `popHiddenWindow` function restoring a specific window. - Export `popHiddenWindow` function restoring a specific window.
* `XMonad.Hooks.ManageDocks` * `XMonad.Hooks.ManageDocks`
- Export `AvoidStruts` constructor - Export `AvoidStruts` constructor
- Restored compatibility with pre-0.13 configs by making the startup hook
unnecessary for correct functioning.
* `XMonad.Hooks.ManageHelpers` * `XMonad.Hooks.ManageHelpers`
- Export `doSink` - Export `doSink`
@@ -899,6 +903,12 @@
* `XMonad.Prompt` now stores its history file in the XMonad cache * `XMonad.Prompt` now stores its history file in the XMonad cache
directory in a file named `prompt-history`. directory in a file named `prompt-history`.
* `XMonad.Hooks.ManageDocks` now requires an additional startup hook to be
added to configuration in addition to the other 3 hooks, otherwise docks
started before xmonad are covered by windows. It's recommended to use the
newly introduced `docks` function to add all necessary hooks to xmonad
config.
### New Modules ### New Modules
* `XMonad.Layout.SortedLayout` * `XMonad.Layout.SortedLayout`
@@ -932,7 +942,7 @@
### Bug Fixes and Minor Changes ### Bug Fixes and Minor Changes
* `XMonad.Hooks.ManageDocks`, * `XMonad.Hooks.ManageDocks`
- Fix a very annoying bug where taskbars/docs would be - Fix a very annoying bug where taskbars/docs would be
covered by windows. covered by windows.

View File

@@ -1,4 +1,5 @@
{-# LANGUAGE DeriveDataTypeable, PatternGuards, FlexibleInstances, MultiParamTypeClasses, CPP #-} {-# LANGUAGE DeriveDataTypeable, PatternGuards, FlexibleInstances, MultiParamTypeClasses, CPP #-}
{-# LANGUAGE LambdaCase #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Hooks.ManageDocks -- Module : XMonad.Hooks.ManageDocks
@@ -44,7 +45,7 @@ import Data.Monoid (All(..))
import qualified Data.Set as S import qualified Data.Set as S
import qualified Data.Map as M import qualified Data.Map as M
import Control.Monad (when, forM_, filterM) import Control.Monad (when, filterM, void)
-- $usage -- $usage
-- To use this module, add the following import to @~\/.xmonad\/xmonad.hs@: -- To use this module, add the following import to @~\/.xmonad\/xmonad.hs@:
@@ -90,7 +91,10 @@ docks c = c { startupHook = docksStartupHook <+> startupHook c
, handleEventHook = docksEventHook <+> handleEventHook c , handleEventHook = docksEventHook <+> handleEventHook c
, manageHook = manageDocks <+> manageHook c } , manageHook = manageDocks <+> manageHook c }
newtype StrutCache = StrutCache { fromStrutCache :: M.Map Window [Strut] } type WindowStruts = M.Map Window [Strut]
-- Nothing means cache hasn't been initialized yet
newtype StrutCache = StrutCache { fromStrutCache :: Maybe WindowStruts }
deriving (Eq, Typeable) deriving (Eq, Typeable)
data UpdateDocks = UpdateDocks deriving Typeable data UpdateDocks = UpdateDocks deriving Typeable
@@ -100,15 +104,35 @@ refreshDocks :: X ()
refreshDocks = sendMessage UpdateDocks refreshDocks = sendMessage UpdateDocks
instance ExtensionClass StrutCache where instance ExtensionClass StrutCache where
initialValue = StrutCache M.empty initialValue = StrutCache Nothing
initStrutCache :: X WindowStruts
initStrutCache = withDisplay $ \dpy -> do
rootw <- asks theRoot
(_,_,wins) <- io $ queryTree dpy rootw
dockws <- filterM (runQuery checkDock) wins
M.fromList . zip dockws <$> mapM getStrut dockws
getStrutCache :: X (Bool, WindowStruts)
getStrutCache = XS.gets fromStrutCache >>= \case
Just cache ->
return (False, cache)
Nothing -> do
cache <- initStrutCache
XS.put $ StrutCache $ Just cache
return (True, cache)
updateStrutCache :: Window -> [Strut] -> X Bool updateStrutCache :: Window -> [Strut] -> X Bool
updateStrutCache w strut = updateStrutCache w strut = do
XS.modified $ StrutCache . M.insert w strut . fromStrutCache ch1 <- fst <$> getStrutCache
ch2 <- XS.modified $ StrutCache . fmap (M.insert w strut) . fromStrutCache
return $ ch1 || ch2
deleteFromStructCache :: Window -> X Bool deleteFromStructCache :: Window -> X Bool
deleteFromStructCache w = deleteFromStructCache w = do
XS.modified $ StrutCache . M.delete w . fromStrutCache ch1 <- fst <$> getStrutCache
ch2 <- XS.modified $ StrutCache . fmap (M.delete w) . fromStrutCache
return $ ch1 || ch2
-- | Detects if the given window is of type DOCK and if so, reveals -- | Detects if the given window is of type DOCK and if so, reveals
-- it, but does not manage it. -- it, but does not manage it.
@@ -151,14 +175,7 @@ docksEventHook (DestroyWindowEvent {ev_window = w}) = do
docksEventHook _ = return (All True) docksEventHook _ = return (All True)
docksStartupHook :: X () docksStartupHook :: X ()
docksStartupHook = withDisplay $ \dpy -> do docksStartupHook = void $ getStrutCache
rootw <- asks theRoot
(_,_,wins) <- io $ queryTree dpy rootw
docks <- filterM (runQuery checkDock) wins
forM_ docks $ \win -> do
strut <- getStrut win
updateStrutCache win strut
refreshDocks
-- | Gets the STRUT config, if present, in xmonad gap order -- | Gets the STRUT config, if present, in xmonad gap order
getStrut :: Window -> X [Strut] getStrut :: Window -> X [Strut]
@@ -181,7 +198,7 @@ getStrut w = do
calcGap :: S.Set Direction2D -> X (Rectangle -> Rectangle) calcGap :: S.Set Direction2D -> X (Rectangle -> Rectangle)
calcGap ss = withDisplay $ \dpy -> do calcGap ss = withDisplay $ \dpy -> do
rootw <- asks theRoot rootw <- asks theRoot
struts <- (filter careAbout . concat) <$> XS.gets (M.elems . fromStrutCache) struts <- filter careAbout . concat . M.elems . snd <$> getStrutCache
-- we grab the window attributes of the root window rather than checking -- we grab the window attributes of the root window rather than checking
-- the width of the screen because xlib caches this info and it tends to -- the width of the screen because xlib caches this info and it tends to