Skip to content

Commit

Permalink
X.H.EwmhDesktops: Turn workspaceListTransform into X action
Browse files Browse the repository at this point in the history
This makes it easier to use transforms that need some state, e.g.
XMonad.Actions.WorkspaceNames could provide this.

Related: #105
Related: #122
Related: f271d59 ("X.A.WorkspaceNames: Provide workspaceListTransform for EwmhDesktops")
  • Loading branch information
liskin committed Jan 30, 2021
1 parent b27ad07 commit 8f5b332
Show file tree
Hide file tree
Showing 2 changed files with 12 additions and 11 deletions.
7 changes: 3 additions & 4 deletions XMonad/Actions/WorkspaceNames.hs
Original file line number Diff line number Diff line change
Expand Up @@ -188,12 +188,11 @@ workspaceNamePrompt conf job = do
contains completions input =
return $ filter (Data.List.isInfixOf input) completions

-- | Workspace list transformation for
-- 'XMonad.Hooks.EwmhDesktops.ewmhDesktopsLogHookCustom' that exposes
-- workspace names to pagers and other EWMH-aware clients.
-- | 'XMonad.Hooks.EwmhDesktops.workspaceListTransform' that exposes workspace
-- names to pagers and other EWMH-aware clients.
--
-- Usage:
-- > logHook = (workspaceNamesListTransform >>= ewmhDesktopsLogHookCustom) <+> …
-- > ewmh' def{ workspaceListTransform = workspaceNamesListTransform }
workspaceNamesListTransform :: X ([WindowSpace] -> [WindowSpace])
workspaceNamesListTransform = do
names <- getWorkspaceNames
Expand Down
16 changes: 9 additions & 7 deletions XMonad/Hooks/EwmhDesktops.hs
Original file line number Diff line number Diff line change
Expand Up @@ -75,14 +75,14 @@ import XMonad.Util.WindowProperties (getProp32)

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

instance Default EwmhConfig where
def = EwmhConfig
{ workspaceListTransform = id
{ workspaceListTransform = pure id
, activateHook = doFocus
, fullscreen = False
}
Expand Down Expand Up @@ -169,15 +169,16 @@ 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 = f }
ewmhDesktopsLogHookCustom f = ewmhDesktopsLogHook' def{ workspaceListTransform = 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
sort' <- getSortByIndex
let ws = workspaceListTransform $ sort' $ W.workspaces s
workspaceListTransform' <- workspaceListTransform
let ws = workspaceListTransform' $ sort' $ W.workspaces s

-- Set number of workspaces and names thereof
let desktopNames = map W.tag ws
Expand All @@ -190,7 +191,7 @@ ewmhDesktopsLogHook' EwmhConfig{workspaceListTransform} = withWindowSet $ \s ->
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])
let maybeCurrent' = W.tag <$> listToMaybe (workspaceListTransform' [W.workspace $ W.current s])
current = join (flip elemIndex (map W.tag ws) <$> maybeCurrent')
whenChanged (CurrentDesktop $ fromMaybe 0 current) $
mapM_ setCurrentDesktop current
Expand All @@ -215,7 +216,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 = f }
ewmhDesktopsEventHookCustom f = ewmhDesktopsEventHook' def{ workspaceListTransform = pure f }

-- |
-- Intercepts messages from pagers and similar applications and reacts on them.
Expand All @@ -237,7 +238,8 @@ ewmhDesktopsEventHook' EwmhConfig{ workspaceListTransform, activateHook, fullscr
e@ClientMessageEvent{ev_window = w, ev_message_type = mt, ev_data = d}
= withWindowSet $ \s -> do
sort' <- getSortByIndex
let ws = workspaceListTransform $ sort' $ W.workspaces s
workspaceListTransform' <- workspaceListTransform
let ws = workspaceListTransform' $ sort' $ W.workspaces s

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

0 comments on commit 8f5b332

Please sign in to comment.