[xmonad] Strange workspace switching bug in my config

Leo Alekseyev dnquark at gmail.com
Mon May 14 01:23:28 CEST 2012


On Sun, May 13, 2012 at 8:45 AM, Norbert Zeh <nzeh at cs.dal.ca> wrote:
> Leo Alekseyev [2012.05.13 0127 -0400]:
>> Hi all,
>> A couple of years back I made the following addition to my xmonad.hs:
>> instead of 10 workspaces, it admits 20 workspaces, logically arranged
>> in two rows of 10.  I think of it as having a "scratch" workspace for
>> every main workspace, and I use up/down arrows to switch between the
>> main and the scratch workspace.  For instance, if you are on workspace
>> 4, Mod4-<down> will move to workspace 4SCR and Mod4-<up> will move
>> back to workspace 4.
>>
>> Recently this config started misbehaving (without any changes to
>> xmonad.hs, but with possible changes in xmonad/GHC version to 0.10 and
>> 7.4.1 as my system was upgraded).  In particular, in the example
>> above, now Mod4-<down> moves from workspace 4 to workspace 3SCR and
>> Mod4-<up> then moves from 3SCR to 2.  To fix it, I have to log in and
>> out of X, but the problem always reoccurs, possibly after sleep/resume
>> cycle(?).
>>
>> The embarrassing thing here is that I haven't touched Haskell in a
>> while, and barely grok my config anymore, so I don't know where to
>> start troubleshooting.  The code I described seems straightforward
>> enough, so it's my hope that maybe someone here can tell me what is
>> going on without too much effort...
>>
>> The relevant parts of my config are below, and the full file in its
>> horrifying glory is at http://hpaste.org/68453.  If someone seems
>> something obviously amiss, please shout...
>>
>> --leo
>>
>> myWorkspaces = ["1:terminals", "2:emacs", "3:web", "4", "5", "6",
>> "7","8","9","0"] ++ map (\x -> show x ++ "SCR") ([1..9]++[0])
>> .....
>>
>> zeroSub 0 = 10
>> zeroSub x = x
>>
>> jumpToMain = gets windowset >>= \W.StackSet { W.current = W.Screen {
>> W.workspace = w } } -> withNthWorkspace W.greedyView (-1+(zeroSub $
>> read [head(W.tag w)]))
>> jumpToScratch = gets windowset >>= \W.StackSet { W.current = W.Screen
>> { W.workspace = w } } -> withNthWorkspace W.greedyView (9+(zeroSub $
>> read [head(W.tag w)]))
>
> The math here looks all wrong, and I'm surprised that it worked at all before.
> What you want, I think, is the following:
>
> jumpToMain = gets (W.tag . W.workspace . W.current . windowset)
>         >>= W.greedyView . toMain
>  where
>    toMain ws = [head ws]
>
> jumpToScratch = gets (W.tag . W.workspace . W.current . windowset)
>            >>= W.greedyView . toScratch
>  where
>    toScratch ws | length ws == 1 = ws ++ "SCR"
>                 | otherwise      = ws
>
> The idea here is that you simply want to add or take away the "SCR" suffix in
> the workspace tag or, in the latter case, do nothing if it's already present.


Hi Norbert,
Yes, my original math was kind of dodgy...  Your solution seems
better, but it doesn't compile for me...  any ideas?

xmonad.hs:452:14:
    No instance for (MonadState
                       XState ((->) (W.StackSet [Char] l3 a3 s3 sd3)))
      arising from a use of `gets'
    Possible fix:
      add an instance declaration for
      (MonadState XState ((->) (W.StackSet [Char] l3 a3 s3 sd3)))
    In the first argument of `(>>=)', namely
      `gets (tag . W.workspace . W.current . windowset)'
    In the expression:
      gets (tag . W.workspace . W.current . windowset)
      >>= W.greedyView . toMain
    In an equation for `jumpToMain':
        jumpToMain
          = gets (tag . W.workspace . W.current . windowset)
            >>= W.greedyView . toMain
          where
              toMain ws = [head ws]


xmonad.hs:456:17:
    No instance for (MonadState
                       XState ((->) (W.StackSet [Char] l1 a1 s1 sd1)))
      arising from a use of `gets'
    Possible fix:
      add an instance declaration for
      (MonadState XState ((->) (W.StackSet [Char] l1 a1 s1 sd1)))
    In the first argument of `(>>=)', namely
      `gets (tag . W.workspace . W.current . windowset)'
    In the expression:
      gets (tag . W.workspace . W.current . windowset)
      >>= W.greedyView . toScratch
    In an equation for `jumpToScratch':
        jumpToScratch
          = gets (tag . W.workspace . W.current . windowset)
            >>= W.greedyView . toScratch
          where
              toScratch ws
                | length ws == 1 = ws ++ "SCR"
                | otherwise = ws



More information about the xmonad mailing list