Skip to content

Commit

Permalink
X.H.{EwmhDesktops,ManageHelpers}: Add _NET_WM_DESKTOP-handling Manage…
Browse files Browse the repository at this point in the history
…Hook

Useful for restoring browser windows to where they were before restart
(which is something one should do several times a week as security
updates get released).
  • Loading branch information
liskin committed Dec 17, 2023
1 parent e75eb16 commit 3c329e0
Show file tree
Hide file tree
Showing 3 changed files with 41 additions and 0 deletions.
4 changes: 4 additions & 0 deletions CHANGES.md
Expand Up @@ -246,6 +246,10 @@
`XMonad.Actions.ToggleFullFloat` for a float-restoring implementation of
fullscreening.

- Added `ewmhDesktops(Maybe)ManageHook` that places windows in their
preferred workspaces. This is useful when restoring a browser session
after a restart.

* `XMonad.Hooks.StatusBar`

- Added `startAllStatusBars` to start the configured status bars.
Expand Down
27 changes: 27 additions & 0 deletions XMonad/Hooks/EwmhDesktops.hs
Expand Up @@ -24,6 +24,8 @@ module XMonad.Hooks.EwmhDesktops (
-- $usage
ewmh,
ewmhFullscreen,
ewmhDesktopsManageHook,
ewmhDesktopsMaybeManageHook,

-- * Customization
-- $customization
Expand Down Expand Up @@ -481,6 +483,31 @@ ewmhDesktopsEventHook'
mempty
ewmhDesktopsEventHook' _ _ = mempty

-- | A 'ManageHook' that shifts windows to the workspace they want to be in.
-- Useful for restoring browser windows to where they were before restart.
--
-- To only use this for browsers (which might be a good idea, as many apps try
-- to restore their window to their original position, but it's rarely
-- desirable outside of security updates of multi-window apps like a browser),
-- use this:
--
-- > stringProperty "WM_WINDOW_ROLE" =? "browser" --> ewmhDesktopsManageHook
ewmhDesktopsManageHook :: ManageHook
ewmhDesktopsManageHook = maybeToDefinite ewmhDesktopsMaybeManageHook

-- | 'ewmhDesktopsManageHook' as a 'MaybeManageHook' for use with
-- 'composeOne'. Returns 'Nothing' if the window didn't indicate any desktop
-- preference, otherwise 'Just' (even if the preferred desktop was out of
-- bounds).
ewmhDesktopsMaybeManageHook :: MaybeManageHook
ewmhDesktopsMaybeManageHook = desktop >>= traverse doShiftI
where
doShiftI :: Int -> ManageHook
doShiftI d = do
sort' <- liftX . XC.withDef $ \EwmhDesktopsConfig{workspaceSort} -> workspaceSort
ws <- liftX . gets $ map W.tag . sort' . W.workspaces . windowset
maybe idHook doShift $ ws !? d

-- | Add EWMH fullscreen functionality to the given config.
ewmhFullscreen :: XConfig a -> XConfig a
ewmhFullscreen c = c { startupHook = startupHook c <> fullscreenStartup
Expand Down
10 changes: 10 additions & 0 deletions XMonad/Hooks/ManageHelpers.hs
Expand Up @@ -52,6 +52,7 @@ module XMonad.Hooks.ManageHelpers (
isMinimized,
isDialog,
pid,
desktop,
transientTo,
maybeToDefinite,
MaybeManageHook,
Expand Down Expand Up @@ -202,6 +203,15 @@ pid = ask >>= \w -> liftX $ getProp32s "_NET_WM_PID" w <&> \case
Just [x] -> Just (fromIntegral x)
_ -> Nothing

-- | This function returns 'Just' the @_NET_WM_DESKTOP@ property for a
-- particular window if set, 'Nothing' otherwise.
--
-- See <https://specifications.freedesktop.org/wm-spec/wm-spec-1.5.html#idm46181547492704>.
desktop :: Query (Maybe Int)
desktop = ask >>= \w -> liftX $ getProp32s "_NET_WM_DESKTOP" w <&> \case
Just [x] -> Just (fromIntegral x)
_ -> Nothing

-- | A predicate to check whether a window is Transient.
-- It holds the result which might be the window it is transient to
-- or it might be 'Nothing'.
Expand Down

0 comments on commit 3c329e0

Please sign in to comment.