Skip to content

Commit

Permalink
X.H.EwmhDesktops: Deprecate standalone hooks
Browse files Browse the repository at this point in the history
We should get rid of this error-prone interface ASAP, so mark it as
deprecated to give people some time to adapt their configs.
  • Loading branch information
liskin committed Oct 20, 2021
1 parent 860f80a commit f666cf4
Show file tree
Hide file tree
Showing 2 changed files with 9 additions and 6 deletions.
8 changes: 3 additions & 5 deletions XMonad/Config/Bluetile.hs
Original file line number Diff line number Diff line change
Expand Up @@ -197,15 +197,13 @@ bluetileLayoutHook = avoidStruts $ minimize $ boringWindows $
floatingDeco l = buttonDeco shrinkText defaultThemeWithButtons l

bluetileConfig =
docks $
docks . ewmhFullscreen . ewmh $
def
{ modMask = mod4Mask, -- logo key
manageHook = bluetileManageHook,
layoutHook = bluetileLayoutHook,
logHook = currentWorkspaceOnTop >> ewmhDesktopsLogHook,
handleEventHook = ewmhDesktopsEventHook
`mappend` fullscreenEventHook
`mappend` minimizeEventHook
logHook = currentWorkspaceOnTop,
handleEventHook = minimizeEventHook
`mappend` serverModeEventHook' bluetileCommands
`mappend` positionStoreEventHook,
workspaces = bluetileWorkspaces,
Expand Down
7 changes: 6 additions & 1 deletion XMonad/Hooks/EwmhDesktops.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,7 @@ module XMonad.Hooks.EwmhDesktops (
-- $customActivate
setEwmhActivateHook,

-- * Standalone hooks (to be deprecated)
-- * Standalone hooks (deprecated)
ewmhDesktopsStartup,
ewmhDesktopsLogHook,
ewmhDesktopsLogHookCustom,
Expand Down Expand Up @@ -230,11 +230,13 @@ setEwmhActivateHook h = XC.modifyDef $ \c -> c{ activateHook = h }


-- | Initializes EwmhDesktops and advertises EWMH support to the X server.
{-# DEPRECATED ewmhDesktopsStartup "Use ewmh instead." #-}
ewmhDesktopsStartup :: X ()
ewmhDesktopsStartup = setSupported

-- | Notifies pagers and window lists, such as those in the gnome-panel of the
-- current state of workspaces and windows.
{-# DEPRECATED ewmhDesktopsLogHook "Use ewmh instead." #-}
ewmhDesktopsLogHook :: X ()
ewmhDesktopsLogHook = XC.withDef ewmhDesktopsLogHook'

Expand All @@ -256,6 +258,7 @@ ewmhDesktopsLogHookCustom f =
-- * _NET_ACTIVE_WINDOW (activate another window, changing workspace if needed)
--
-- * _NET_CLOSE_WINDOW (close window)
{-# DEPRECATED ewmhDesktopsEventHook "Use ewmh instead." #-}
ewmhDesktopsEventHook :: Event -> X All
ewmhDesktopsEventHook = XC.withDef . ewmhDesktopsEventHook'

Expand Down Expand Up @@ -377,6 +380,7 @@ ewmhFullscreen c = c { startupHook = startupHook c <+> fullscreenStartup
, handleEventHook = handleEventHook c <+> fullscreenEventHook }

-- | Advertises EWMH fullscreen support to the X server.
{-# DEPRECATED fullscreenStartup "Use ewmhFullscreen instead." #-}
fullscreenStartup :: X ()
fullscreenStartup = setFullscreenSupported

Expand All @@ -385,6 +389,7 @@ fullscreenStartup = setFullscreenSupported
-- function, such as Totem, Evince and OpenOffice.org.
--
-- Note this is not included in 'ewmh'.
{-# DEPRECATED fullscreenEventHook "Use ewmhFullscreen instead." #-}
fullscreenEventHook :: Event -> X All
fullscreenEventHook (ClientMessageEvent _ _ _ dpy win typ (action:dats)) = do
managed <- isClient win
Expand Down

0 comments on commit f666cf4

Please sign in to comment.