Skip to content

Commit

Permalink
X.H.EwmhDesktops: Add disableEwmhManageDesktopViewport
Browse files Browse the repository at this point in the history
This combinator forces XMonad to *not* set _NET_DESKTOP_VIEWPORT.

This information is picked up by polybar's xworkspaces module and used
to re-group the workspaces by monitor. I (and others) find this super
confusing, but polybar doesn't not seem open to addressing it.

polybar/polybar#2603

Opting in to the old behavior of not managing this property is one way
to work around it instead.
  • Loading branch information
pbrisbin authored and slotThe committed Jan 5, 2023
1 parent e2ffa53 commit cf13f8f
Show file tree
Hide file tree
Showing 2 changed files with 39 additions and 4 deletions.
7 changes: 7 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -144,6 +144,13 @@
- Fixed an issue where the bottom right window would not respond to
`MirrorShrink` and `MirrorExpand` messages.

* `XMonad.Hooks.EwmhDesktops`

- Added `disableEwmhManageDesktopViewport` to avoid setting the
`_NET_DESKTOP_VIEWPORT` property, as it can lead to issues with
some status bars (see this
[polybar issue](https://github.com/polybar/polybar/issues/2603)).

### Other changes

## 0.17.1 (September 3, 2022)
Expand Down
36 changes: 32 additions & 4 deletions XMonad/Hooks/EwmhDesktops.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,10 @@ module XMonad.Hooks.EwmhDesktops (
-- $customActivate
setEwmhActivateHook,

-- ** @_NET_DESKTOP_VIEWPORT@
-- $customManageDesktopViewport
disableEwmhManageDesktopViewport,

-- * Standalone hooks (deprecated)
ewmhDesktopsStartup,
ewmhDesktopsLogHook,
Expand Down Expand Up @@ -102,13 +106,16 @@ data EwmhDesktopsConfig =
-- ^ configurable workspace rename (see 'XMonad.Hooks.StatusBar.PP.ppRename')
, activateHook :: ManageHook
-- ^ configurable handling of window activation requests
, manageDesktopViewport :: Bool
-- ^ manage @_NET_DESKTOP_VIEWPORT@?
}

instance Default EwmhDesktopsConfig where
def = EwmhDesktopsConfig
{ workspaceSort = getSortByIndex
, workspaceRename = pure pure
, activateHook = doFocus
, manageDesktopViewport = True
}


Expand Down Expand Up @@ -228,6 +235,26 @@ setEwmhWorkspaceRename f = XC.modifyDef $ \c -> c{ workspaceRename = f }
setEwmhActivateHook :: ManageHook -> XConfig l -> XConfig l
setEwmhActivateHook h = XC.modifyDef $ \c -> c{ activateHook = h }

-- $customManageDesktopViewport
-- Setting @_NET_DESKTOP_VIEWPORT@ is typically desired but can lead to a
-- confusing workspace list in polybar, where this information is used to
-- re-group the workspaces by monitor. See
-- <https://github.com/polybar/polybar/issues/2603 polybar#2603>.
--
-- To avoid this, you can use:
--
-- > main = xmonad $ … . disableEwmhManageDesktopViewport . ewmh . … $ def{…}
--
-- Note that if you apply this configuration in an already running environment,
-- the property may remain at its previous value. It can be removed by running:
--
-- > xprop -root -remove _NET_DESKTOP_VIEWPORT
--
-- Which should immediately fix your bar.
--
disableEwmhManageDesktopViewport :: XConfig l -> XConfig l
disableEwmhManageDesktopViewport = XC.modifyDef $ \c -> c{ manageDesktopViewport = False }


-- | Initializes EwmhDesktops and advertises EWMH support to the X server.
{-# DEPRECATED ewmhDesktopsStartup "Use ewmh instead." #-}
Expand Down Expand Up @@ -303,7 +330,7 @@ whenChanged :: (Eq a, ExtensionClass a) => a -> X () -> X ()
whenChanged = whenX . XS.modified . const

ewmhDesktopsLogHook' :: EwmhDesktopsConfig -> X ()
ewmhDesktopsLogHook' EwmhDesktopsConfig{workspaceSort, workspaceRename} = withWindowSet $ \s -> do
ewmhDesktopsLogHook' EwmhDesktopsConfig{workspaceSort, workspaceRename, manageDesktopViewport} = withWindowSet $ \s -> do
sort' <- workspaceSort
let ws = sort' $ W.workspaces s

Expand Down Expand Up @@ -365,9 +392,10 @@ ewmhDesktopsLogHook' EwmhDesktopsConfig{workspaceSort, workspaceRename} = withWi
whenChanged (ActiveWindow activeWindow') $ setActiveWindow activeWindow'

-- Set desktop Viewport
let visibleScreens = W.current s : W.visible s
currentTags = map (W.tag . W.workspace) visibleScreens
whenChanged (MonitorTags currentTags) $ mkViewPorts s (map W.tag ws)
when manageDesktopViewport $ do
let visibleScreens = W.current s : W.visible s
currentTags = map (W.tag . W.workspace) visibleScreens
whenChanged (MonitorTags currentTags) $ mkViewPorts s (map W.tag ws)

-- | Create the viewports from the current 'WindowSet' and a list of
-- already sorted workspace IDs.
Expand Down

0 comments on commit cf13f8f

Please sign in to comment.