[xmonad] MultiToggle with WorkspaceCursors

ivan ivan.brennan at gmail.com
Sat Mar 25 12:15:43 UTC 2023


Amazing! Thank you so much for the clear explanation.

On Sat, Mar 25, 2023 at 4:26 AM Platon Pronko <platon7pronko at gmail.com>
wrote:

> Hi!
>
> WorkspaceCursors doesn't introduce any groups, it's just a glorified
> workspace switcher - underneath all the chrome it uses the standard flat
> workspaces list. In essense it just defines some helper functions that
> allow user to imagine that workspaces are arranged as a multidimensional
> cube and navigate along axes of said cube. But it still does it using the
> usual StackSet.greedyView function.
>
> MultiToggle is irrelevant in this case, the same effect can be seen with
> the boring Choose layout combinator (i.e. `Tall ||| Full`) - the layout
> state is "spilling" over to other workspaces.
>
> It seems that the problem arises because WorspaceCursors calls `windows $
> greedyView` inside LayoutClass.handleMessage function - current workspace
> is switched at the same time as layout is updated, and Xmonad assigns the
> updated layout to the new workspace.
>
> Here's a reproducer (should work on all configs that have a workspace with
> id "4"):
>
> ```
> -- necessary language pragmas
> {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
>
> -- imports
> import qualified XMonad.StackSet as W
> import XMonad.Layout.LayoutModifier(ModifiedLayout(..),
> LayoutModifier(handleMess))
> import XMonad(Message, X, windows, sendMessage, fromMessage)
>
> -- Example LayoutModifier that showcases the issue.
> -- It does nothing except calling `greedyView "4"` upon reciept of
> SwitchWorkspace message
> data BadLayoutModifier a = BadLayoutModifier deriving (Read, Show)
>
> data SwitchWorkspace = SwitchWorkspace
> instance Message SwitchWorkspace
>
> instance LayoutModifier BadLayoutModifier a where
>    handleMess BadLayoutModifier m = do
>      case fromMessage m of
>        Just SwitchWorkspace -> do
>          windows $ W.greedyView "4"
>          return $ Just BadLayoutModifier
>        Nothing -> return Nothing
>
> -- add to keys (tweak the keybinding to your taste)
>    , ((modm, xK_v), sendMessage SwitchWorkspace)
>
> -- prepend BadLayoutModifier to layoutHook
> layoutHook =
>    ModifiedLayout BadLayoutModifier $
>    (Tall 1 (3/100) (1/2) ||| Full)
> ```
>
> Steps to reproduce:
>
> 1. Recompile and restart Xmonad.
> 2. Toggle workspace "2" to "Tall" layout, toggle workspace "4" to "Full"
> layout.
> 3. Switch to workspace "2".
> 4. Press keybinding to send the SwitchWorkspace message (Super-v in my
> case).
> 5. Observe that Xmonad switches to workspace "4", and layout on that
> workspace is now "Tall" instead of "Full" as set up originally.
>
> In my opinion WorkspaceCursors doesn't need to be a LayoutModifier at all
> - current state can be derived from the list of cursors and currently
> focused workspace, no need to store it somewhere. This will sidestep the
> problem of calling `greedyView` during layout update.
>
> --
> Best regards,
> Platon Pronko
> PGP 2A62D77A7A2CB94E
>
> On 2023-03-24 23:27, Brandon Allbery wrote:
> > My guess is that MultiToggle doesn't and can't know about
> > WorkspaceCursors, and WorkspaceCursors doesn't and can't know that it
> > needs to duplicate the layout state for each group it introduces, so
> > any layout state change applies to all groups.
> >
> > On Fri, Mar 24, 2023 at 11:22 AM ivan <ivan.brennan at gmail.com> wrote:
> >>
> >> Hi, I'm trying to get MultiToggle and WorkspaceCursors to play nicely
> with each other.
> >>
> >> Ordinarily, MultiToggle lets you apply a layout transformation to the
> current workspace without affecting the layouts of other workspaces. E.g.
> if I toggle workspace 1 to Full layout, it won't impact the layouts being
> used on workspaces 2, 3, etc.
> >>
> >> I've started using WorkspaceCursors (XMonad.Actions.WorkspaceCursors)
> to manage independent groups of workspaces, and noticed that if I use it's
> functions (e.g. modifyLayer) to navigate between workspaces, layout toggle
> states seem to bleed across workspaces rather than remaining independent
> per workspace.
> >>
> >> For example, starting on workspace 1 with my regular Tall layout, I
> navigate to workspace 2 and toggle it to Full layout. Then I go back to
> workspace 1 and see that it, too, has been toggled to Full layout.
> >>
> >> I can't figure out exactly what's causing this, or how to fix it so
> that workspace layouts toggle independently. I'm hoping someone here sees
> what I'm missing.
> >>
> >> I put together a minimal config to reproduce the problem:
> >>
> https://github.com/ivanbrennan/xmonad-testing/commit/2e9541b0937eee31ae7f300e130dc55a9c5933af#diff-61bfccbc988708bd118b33f9299c64aa8b3e532e25cc8eaa3b716f53215fb196
> >>
> >> The config provides two groups (A and B) of nine workspaces.
> >>
> >>      group A: 1A 2A 3A 4A 5A 6A 7A 8A 9A
> >>      group B: 1B 2B 3B 4B 5B 6B 7B 8B 9B
> >>
> >> Its layoutHook consists of:
> >>
> >>      myLayoutHook =
> >>        workspaceCursors cursors
> >>          . avoidStruts
> >>          . mkToggle1 FULL
> >>          $ Tall 1 (3/100) (1/2)
> >>
> >> Keys super+1 .. super+9 use WorkspaceCursors functions to switch
> between workspaces within the currently active group.
> >>
> >> Keys super+ctrl+1 .. super+ctrl+2 use WorkspaceCursors functions to
> switch between groups A and B.
> >>
> >> Additionally, keys super+meta+1 .. super+meta+9 use traditional
> StackSet functions to switch between workspaces 1A .. 9A. I added these for
> comparison, showing that MultiToggle state is recognized per-workspace when
> using this form of navigation.
> >>
> >> I can't figure out the root cause. I suspect the most relevant pieces
> of code from WorkspaceCursors and MultiToggle are the following:
> >>
> >>
> https://github.com/xmonad/xmonad-contrib/blob/e60805bd45ca2feb9ef3335d023daae5d02dbf4f/XMonad/Actions/WorkspaceCursors.hs#L204-L215
> >>
> >>
> https://github.com/xmonad/xmonad-contrib/blob/e60805bd45ca2feb9ef3335d023daae5d02dbf4f/XMonad/Layout/MultiToggle.hs#L193-L218
> >>
> >> Does anyone know what I might be missing, or how I could debug further
> to get to the root of the problem?
> >>
> >> Thanks!
> >> Ivan
> >> _______________________________________________
> >> xmonad mailing list
> >> xmonad at haskell.org
> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/xmonad
> >
> >
> >
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/xmonad/attachments/20230325/128f09ff/attachment-0001.html>


More information about the xmonad mailing list