Skip to content

Commit

Permalink
X.H.EwmhDesktops: Split workspaceListTransform into two (fix wmctrl -s)
Browse files Browse the repository at this point in the history
Turns out that renaming workspaces in the transform is a bad idea in the
`ewmhDesktopsEventHook'` as W.view is then unable to find the workspace.
This was somewhat usable before we introduced the unified `ewmh'` config
combinator as one would only rename in the transform passed to
`ewmhDesktopsLogHookCustom`, but with the unified config, we actually
need to separate renames from sorting/reordering, otherwise switching
workspaces by pagers or wmctrl doesn't work.

Related: #105
Related: #122
Related: f271d59 ("X.A.WorkspaceNames: Provide workspaceListTransform for EwmhDesktops")
  • Loading branch information
liskin committed Feb 7, 2021
1 parent 09de2ea commit d30806e
Show file tree
Hide file tree
Showing 3 changed files with 24 additions and 20 deletions.
4 changes: 2 additions & 2 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -329,8 +329,8 @@

* `XMonad.Actions.WorkspaceNames`

- Added `workspaceNamesListTransform` which makes workspace names visible
to external pagers.
- Added `workspaceNamesRenameWS` which makes workspace names visible
to external pagers and tools like `wmctrl` or `arbtt`.

* `XMonad.Util.PureX`

Expand Down
12 changes: 6 additions & 6 deletions XMonad/Actions/WorkspaceNames.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,7 @@ module XMonad.Actions.WorkspaceNames (
workspaceNamePrompt,

-- * EwmhDesktops integration
workspaceNamesListTransform
workspaceNamesRenameWS,
) where

import XMonad
Expand Down Expand Up @@ -190,12 +190,12 @@ workspaceNamePrompt conf job = do
contains completions input =
return $ filter (Data.List.isInfixOf input) completions

-- | 'XMonad.Hooks.EwmhDesktops.workspaceListTransform' that exposes workspace
-- | 'XMonad.Hooks.EwmhDesktops.workspaceRename' that exposes workspace
-- names to pagers and other EWMH-aware clients.
--
-- Usage:
-- > ewmh' def{ workspaceListTransform = workspaceNamesListTransform }
workspaceNamesListTransform :: X ([WindowSpace] -> [WindowSpace])
workspaceNamesListTransform = do
-- > ewmh' def{ workspaceRename = workspaceNamesRenameWS }
workspaceNamesRenameWS :: X (WindowSpace -> WindowSpace)
workspaceNamesRenameWS = do
names <- getWorkspaceNames
return $ map $ \ws -> ws{ W.tag = names $ W.tag ws }
return $ \ws -> ws{ W.tag = names $ W.tag ws }
28 changes: 16 additions & 12 deletions XMonad/Hooks/EwmhDesktops.hs
Original file line number Diff line number Diff line change
Expand Up @@ -75,14 +75,16 @@ import XMonad.Util.WindowProperties (getProp32)

-- | TODO
data EwmhConfig = EwmhConfig
{ workspaceListTransform :: X ([WindowSpace] -> [WindowSpace])
{ workspaceListSort :: X ([WindowSpace] -> [WindowSpace])
, workspaceRename :: X (WindowSpace -> WindowSpace)
, activateHook :: ManageHook
, fullscreen :: Bool
}

instance Default EwmhConfig where
def = EwmhConfig
{ workspaceListTransform = pure id
{ workspaceListSort = pure id
, workspaceRename = pure id
, activateHook = doFocus
, fullscreen = False
}
Expand Down Expand Up @@ -169,16 +171,18 @@ ewmhDesktopsLogHook = ewmhDesktopsLogHook' def
-- user-specified function to transform the workspace list (post-sorting)
{-# DEPRECATED ewmhDesktopsLogHookCustom "Use ewmhDesktopsLogHook' instead" #-}
ewmhDesktopsLogHookCustom :: ([WindowSpace] -> [WindowSpace]) -> X ()
ewmhDesktopsLogHookCustom f = ewmhDesktopsLogHook' def{ workspaceListTransform = pure f }
ewmhDesktopsLogHookCustom f = ewmhDesktopsLogHook' def{ workspaceListSort = pure f }

-- |
-- Notifies pagers and window lists, such as those in the gnome-panel
-- of the current state of workspaces and windows.
ewmhDesktopsLogHook' :: EwmhConfig -> X ()
ewmhDesktopsLogHook' EwmhConfig{workspaceListTransform} = withWindowSet $ \s -> do
ewmhDesktopsLogHook' EwmhConfig{workspaceListSort, workspaceRename} = withWindowSet $ \s -> do
sort' <- getSortByIndex
workspaceListTransform' <- workspaceListTransform
let ws = workspaceListTransform' $ sort' $ W.workspaces s
workspaceListSort' <- workspaceListSort
workspaceRename' <- workspaceRename
let wsTransform = map workspaceRename' . workspaceListSort'
let ws = wsTransform $ sort' $ W.workspaces s

-- Set number of workspaces and names thereof
let desktopNames = map W.tag ws
Expand All @@ -190,8 +194,8 @@ ewmhDesktopsLogHook' EwmhConfig{workspaceListTransform} = withWindowSet $ \s ->
let clientList = nub . concatMap (maybe [] (\(W.Stack x l r) -> reverse l ++ r ++ [x]) . W.stack) $ ws
whenChanged (ClientList clientList) $ setClientList clientList

-- Remap the current workspace to handle any renames that f might be doing.
let maybeCurrent' = W.tag <$> listToMaybe (workspaceListTransform' [W.workspace $ W.current s])
-- Remap the current workspace to handle any renames that wsTransform might be doing.
let maybeCurrent' = W.tag <$> listToMaybe (wsTransform [W.workspace $ W.current s])
current = join (flip elemIndex (map W.tag ws) <$> maybeCurrent')
whenChanged (CurrentDesktop $ fromMaybe 0 current) $
mapM_ setCurrentDesktop current
Expand All @@ -216,7 +220,7 @@ ewmhDesktopsEventHook = ewmhDesktopsEventHook' def
-- user-specified function to transform the workspace list (post-sorting)
{-# DEPRECATED ewmhDesktopsEventHookCustom "Use ewmhDesktopsEventHook' instead" #-}
ewmhDesktopsEventHookCustom :: ([WindowSpace] -> [WindowSpace]) -> Event -> X All
ewmhDesktopsEventHookCustom f = ewmhDesktopsEventHook' def{ workspaceListTransform = pure f }
ewmhDesktopsEventHookCustom f = ewmhDesktopsEventHook' def{ workspaceListSort = pure f }

-- |
-- Intercepts messages from pagers and similar applications and reacts on them.
Expand All @@ -234,12 +238,12 @@ ewmhDesktopsEventHookCustom f = ewmhDesktopsEventHook' def{ workspaceListTransfo
-- handled by other modules like "XMonad.Hooks.ManageHelpers",
-- "XMonad.Actions.Minimize", etc.)
ewmhDesktopsEventHook' :: EwmhConfig -> Event -> X All
ewmhDesktopsEventHook' EwmhConfig{ workspaceListTransform, activateHook, fullscreen }
ewmhDesktopsEventHook' EwmhConfig{ workspaceListSort, activateHook, fullscreen }
e@ClientMessageEvent{ev_window = w, ev_message_type = mt, ev_data = d}
= withWindowSet $ \s -> do
sort' <- getSortByIndex
workspaceListTransform' <- workspaceListTransform
let ws = workspaceListTransform' $ sort' $ W.workspaces s
workspaceListSort' <- workspaceListSort
let ws = workspaceListSort' $ sort' $ W.workspaces s

a_cd <- getAtom "_NET_CURRENT_DESKTOP"
a_d <- getAtom "_NET_WM_DESKTOP"
Expand Down

0 comments on commit d30806e

Please sign in to comment.