X.Operations: Fix mouse in Tabbed decorations (revert broadcastMessage refactor)

Turns out there was another aspect of `broadcastMessage` behaviour that
I missed in my review of the refactor: X.L.Tabbed updates the windowset
during handleMessage (via `X.O.focus`) and expects that change to
persist (by returning `Nothing` and hoping no other layout or layout
modifier returns `Just`). That's quite a hack, but the LayoutClass
interface doesn't allow a cleaner way to do this (well, some extensible
state plus a custom event hook might work, but then the layout isn't
self-contained any more).

And since rereading workspace layouts during `modifyLayouts` would force
this back into O(n²), we might as well revert the whole refactor. :-/

Fixes: https://github.com/xmonad/xmonad/issues/329
This commit is contained in:
Tomas Janousek
2021-09-14 11:25:18 +01:00
parent 3bb653bf9c
commit 33a86c0cdb
3 changed files with 13 additions and 20 deletions

View File

@@ -65,11 +65,6 @@
it easier for us to clean up the codebase. These can still be suppressed
manually using an `OPTIONS_GHC` pragma with `-Wno-deprecations`.
* `runOnWorkspaces` changed to first run the action on the current
workspace, then the visible workspaces and then hidden, to match the order
of processing messages in `broadcastMessage`. Previously,
`runOnWorkspaces` processed the hidden workspaces first.
* Added `withUnfocused` function to `XMonad.Operations`, allowing for
`X` operations to be applied to unfocused windows.

View File

@@ -470,9 +470,9 @@ xmessage msg = void . xfork $ do
runOnWorkspaces :: (WindowSpace -> X WindowSpace) -> X ()
runOnWorkspaces job = do
ws <- gets windowset
h <- mapM job $ hidden ws
c:v <- mapM (\s -> (\w -> s { workspace = w}) <$> job (workspace s))
$ current ws : visible ws
h <- mapM job $ hidden ws
modify $ \s -> s { windowset = ws { current = c, visible = v, hidden = h } }
-- | All the directories that xmonad will use. They will be used for

View File

@@ -440,24 +440,22 @@ sendMessage a = windowBracket_ $ do
-- | Send a message to all layouts, without refreshing.
broadcastMessage :: Message a => a -> X ()
broadcastMessage = filterMessageWithNoRefresh (const True)
broadcastMessage a = withWindowSet $ \ws -> do
-- this is O(n²), but we can't really fix this as there's code in
-- xmonad-contrib that touches the windowset during handleMessage
-- (returning Nothing for changes to not get overwritten), so we
-- unfortunately need to do this one by one and persist layout states
-- of each workspace separately)
let c = W.workspace . W.current $ ws
v = map W.workspace . W.visible $ ws
h = W.hidden ws
mapM_ (sendMessageWithNoRefresh a) (c : v ++ h)
-- | Send a message to a layout, without refreshing.
sendMessageWithNoRefresh :: Message a => a -> WindowSpace -> X ()
sendMessageWithNoRefresh a w =
filterMessageWithNoRefresh (((==) `on` W.tag) w) a
-- | Send a message to the layouts of some workspaces, without refreshing.
filterMessageWithNoRefresh :: Message a => (WindowSpace -> Bool) -> a -> X ()
filterMessageWithNoRefresh p a = modifyLayouts $ \wrk ->
if p wrk
then userCodeDef Nothing $ W.layout wrk `handleMessage` SomeMessage a
else pure Nothing
-- | Modify the layouts of some workspaces.
modifyLayouts :: (WindowSpace -> X (Maybe (Layout Window))) -> X ()
modifyLayouts f = runOnWorkspaces $ \ wrk ->
maybe wrk (\l -> wrk{ W.layout = l }) <$> f wrk
handleMessage (W.layout w) (SomeMessage a) `catchX` return Nothing >>=
updateLayout (W.tag w)
-- | Update the layout field of a workspace.
updateLayout :: WorkspaceId -> Maybe (Layout Window) -> X ()