[Xmonad] Patch: swapLeft and swapRight

Donald Bruce Stewart dons at cse.unsw.edu.au
Tue May 22 02:06:11 EDT 2007


Thanks, applied. This is a rather nice behaviour, in my opinion.

Basically, permuting window order using the existing 'swap' (or
dwm-style promote) is hard. Given an unsorted window order:

    [4,2,1,3,5]

sorting that to:

    [1,2,3,4,5]

should be doable (i.e. producing a given window ordering).

Using xmonad's swap, or dwm's promote only (which swaps more windows
than 'swap' does), is rather tricky.  (Try it!) However, with
swapLeft/swapRight, you can bubble sort you windows to your heart's
content, and we keep 'swap' , for getting a window to master position
efficiently.

-- Don

bobstopper:
> After discussion on IRC, the moveLeft/moveRight set of functions have
> been trimmed down to just swapLeft/swapRight
> 
> 
> -- 
> Robert Marlow <bobstopper at bobturf.org>

> 
> New patches:
> 
> [add swapLeft and swapRight
> bobstopper at bobturf.org**20070522050008] {
> hunk ./Config.hs 163
> +    , ((modMask,               xK_Left  ), swapLeft)
> +    , ((modMask,               xK_Right ), swapRight)
> +
> hunk ./Config.hs 178
> -    , ((modMask,               xK_Return), swap)
> +    , ((modMask,               xK_Return), swapMaster)
> hunk ./Operations.hs 53
> -focusLeft, focusRight :: X ()
> +focusLeft, focusRight, swapLeft, swapRight :: X ()
> hunk ./Operations.hs 56
> +swapLeft   = windows W.swapLeft
> +swapRight  = windows W.swapRight
> hunk ./Operations.hs 59
> --- | swap. Move the currently focused window into the master frame
> -swap :: X ()
> -swap = windows W.swap
> +-- | swapMaster. Move the currently focused window into the master frame
> +swapMaster :: X ()
> +swapMaster = windows W.swapMaster
> hunk ./StackSet.hs 80
> -        focusWindow, member, findIndex, insertLeft, delete, swap, shift,
> -        modify -- needed by users
> +        focusWindow, member, findIndex, insertLeft, delete, shift,
> +        swapMaster, swapLeft, swapRight, modify -- needed by users
> hunk ./StackSet.hs 95
> +--  swapLeft, swapRight
> hunk ./StackSet.hs 99
> ---  swap,                   -- was: promote
> +--  swapMaster,             -- was: promote/swap
> hunk ./StackSet.hs 243
> --- /O(1), O(w) on the wrapping case/. Move the window focus left or
> +-- /O(1), O(w) on the wrapping case/. 
> +--
> +-- focusLeft, focusRight. Move the window focus left or
> hunk ./StackSet.hs 250
> -focusLeft, focusRight :: StackSet i a s -> StackSet i a s
> +-- swapLeft, swapRight. Swap the focused window with its left or right
> +-- neighbour in the stack ordering, wrapping if we reach the end. Again 
> +-- the wrapping model should 'cycle' on the current stack.
> +-- 
> +focusLeft, focusRight, swapLeft, swapRight :: StackSet i a s -> StackSet i a s
> hunk ./StackSet.hs 265
> +swapLeft = modify Empty $ \c -> case c of
> +    Node _ []     [] -> c
> +    Node t (l:ls) rs -> Node t ls (l:rs)
> +    Node t []     rs -> Node t (reverse rs) []
> +
> +swapRight = modify Empty $ \c -> case c of
> +    Node _ []     [] -> c
> +    Node t ls (r:rs) -> Node t (r:ls) rs
> +    Node t ls     [] -> Node t [] (reverse ls)
> +
> hunk ./StackSet.hs 362
> -swap :: StackSet i a s -> StackSet i a s
> -swap = modify Empty $ \c -> case c of
> +swapMaster :: StackSet i a s -> StackSet i a s
> +swapMaster = modify Empty $ \c -> case c of
> hunk ./tests/Properties.hs 158
> -prop_swap_I (x :: T) = invariant $ swap x
> +prop_swap_master_I (x :: T) = invariant $ swapMaster x
> +
> +prop_swap_left_I  (n :: NonNegative Int) (x :: T) =
> +    invariant $ foldr (const swapLeft ) x [1..n]
> +prop_swap_right_I (n :: NonNegative Int) (x :: T) =
> +    invariant $ foldr (const swapRight) x [1..n]
> hunk ./tests/Properties.hs 357
> -        y = swap x -- sets the master window to the current focus.
> -                   -- otherwise, we don't have a rule for where master goes.
> +        y = swapMaster x -- sets the master window to the current focus.
> +                         -- otherwise, we don't have a rule for where master goes.
> hunk ./tests/Properties.hs 387
> -        y = swap x
> +        y = swapMaster x
> hunk ./tests/Properties.hs 396
> --- swap: setting the master window
> -
> --- prop_swap_reversible a b xs = swap a b (swap a b ys) == ys
> ---     where ys = nub xs :: [Int]
> -
> --- swap doesn't change focus
> -prop_swap_focus (x :: T)
> -    = case peek x of
> -        Nothing -> True
> -        Just f  -> focus (stack (workspace $ current (swap x))) == f
> -
> --- swap is local
> -prop_swap_local (x :: T) = hidden_spaces x == hidden_spaces (swap x)
> +-- swapLeft, swapRight, swapMaster: reordiring windows
> hunk ./tests/Properties.hs 398
> +-- swap is trivially reversible
> +prop_swap_left  (x :: T) = (swapLeft  (swapRight x)) == x
> +prop_swap_right (x :: T) = (swapRight (swapLeft  x)) ==  x
> hunk ./tests/Properties.hs 413
> -prop_swap_idempotent (x :: T) = swap (swap x) == swap x
> +-- swap doesn't change focus
> +prop_swap_master_focus (x :: T) = peek x == (peek $ swapMaster x)
> +--    = case peek x of
> +--        Nothing -> True
> +--        Just f  -> focus (stack (workspace $ current (swap x))) == f
> +prop_swap_left_focus   (x :: T) = peek x == (peek $ swapLeft   x)
> +prop_swap_right_focus  (x :: T) = peek x == (peek $ swapRight  x)
> +
> +-- swap is local
> +prop_swap_master_local (x :: T) = hidden_spaces x == hidden_spaces (swapMaster x)
> +prop_swap_left_local   (x :: T) = hidden_spaces x == hidden_spaces (swapLeft   x)
> +prop_swap_right_local  (x :: T) = hidden_spaces x == hidden_spaces (swapRight  x)
> +
> +-- rotation through the height of a stack gets us back to the start
> +prop_swap_all_l (x :: T) = (foldr (const swapLeft)  x [1..n]) == x
> +  where n = length (index x)
> +prop_swap_all_r (x :: T) = (foldr (const swapRight) x [1..n]) == x
> +  where n = length (index x)
> +
> +prop_swap_master_idempotent (x :: T) = swapMaster (swapMaster x) == swapMaster x
> hunk ./tests/Properties.hs 447
> -        y = swap x
> +        y = swapMaster x
> hunk ./tests/Properties.hs 541
> -        ,("swap: invariant  "   , mytest prop_swap_I)
> -        ,("swap id on focus"    , mytest prop_swap_focus)
> -        ,("swap is idempotent"  , mytest prop_swap_idempotent)
> -        ,("swap is local"       , mytest prop_swap_local)
> +        ,("swapMaster: invariant", mytest prop_swap_master_I)
> +        ,("swapLeft: invariant" , mytest prop_swap_left_I)
> +        ,("swapRight: invariant", mytest prop_swap_right_I)
> +        ,("swapMaster id on focus", mytest prop_swap_master_focus)
> +        ,("swapLeft id on focus", mytest prop_swap_left_focus)
> +        ,("swapRight id on focus", mytest prop_swap_right_focus)
> +        ,("swapMaster is idempotent", mytest prop_swap_master_idempotent)
> +        ,("swap all left  "     , mytest prop_swap_all_l)
> +        ,("swap all right "     , mytest prop_swap_all_r)
> +        ,("swapMaster is local" , mytest prop_swap_master_local)
> +        ,("swapLeft is local"   , mytest prop_swap_left_local)
> +        ,("swapRight is local"  , mytest prop_swap_right_local)
> }
> 
> Context:
> 
> [Remove the magic '2'
> Spencer Janssen <sjanssen at cse.unl.edu>**20070521234535] 
> [List --resume args first
> Spencer Janssen <sjanssen at cse.unl.edu>**20070521232427] 
> [Move special case 'view' code into 'windows'.
> Spencer Janssen <sjanssen at cse.unl.edu>**20070521215646
>  This is ugly right now -- I promise to clean it up later.
> ] 
> [Experimental support for a beefier restart.
> Spencer Janssen <sjanssen at cse.unl.edu>**20070521194653] 
> [Catch the exception rather than explicitly checking the PATH
> Spencer Janssen <sjanssen at cse.unl.edu>**20070521191900] 
> [Put restart in the X monad
> Spencer Janssen <sjanssen at cse.unl.edu>**20070521190749] 
> [Show instances for WorkspaceId and ScreenId
> Spencer Janssen <sjanssen at cse.unl.edu>**20070521190704] 
> [Read instance for StackSet
> Spencer Janssen <sjanssen at cse.unl.edu>**20070521184504] 
> [Remove redundant fromIntegrals
> Spencer Janssen <sjanssen at cse.unl.edu>**20070521165123] 
> [Use Position for dimensions
> Spencer Janssen <sjanssen at cse.unl.edu>**20070521162809] 
> [Make screen info dynamic: first step to supporting randr
> Spencer Janssen <sjanssen at cse.unl.edu>**20070521152759] 
> [modify
> Don Stewart <dons at cse.unsw.edu.au>**20070521115750] 
> [Move xinerama current/visible/hidden workspace logic into StackSet directly.
> Don Stewart <dons at cse.unsw.edu.au>**20070521055253] 
> [s/workspace/windowset/
> Jason Creighton <jcreigh at gmail.com>**20070521040330] 
> [focusWindow: always view the containing workspace first
> Jason Creighton <jcreigh at gmail.com>**20070521035551] 
> [only hide old workspace on view if the old workspace is not visible (Xinerama)
> Jason Creighton <jcreigh at gmail.com>**20070521031435] 
> [Fix mod-j/k bindings
> Spencer Janssen <sjanssen at cse.unl.edu>**20070521030253] 
> [explicit export list for StackSet
> Don Stewart <dons at cse.unsw.edu.au>**20070521025250] 
> [comment only
> Don Stewart <dons at cse.unsw.edu.au>**20070520090846] 
> [Be explicit about suspicious System.Mem import
> Spencer Janssen <sjanssen at cse.unl.edu>**20070520165741] 
> [HEADS UP: Rewrite StackSet as a Zipper
> Don Stewart <dons at cse.unsw.edu.au>**20070520070053
>  
>  In order to give a better account of how focus and master interact, and
>  how each operation affects focus, we reimplement the StackSet type as a
>  two level nested 'Zipper'. To quote Oleg:
>  
>      A Zipper is essentially an `updateable' and yet pure functional
>      cursor into a data structure. Zipper is also a delimited
>      continuation reified as a data structure.
>  
>  That is, we use the Zipper as a cursor which encodes the window which is
>  in focus. Thus our data structure tracks focus correctly by
>  construction! We then get simple, obvious semantics for e.g. insert, in
>  terms of how it affects focus/master. Our transient-messes-with-focus
>  bug evaporates. 'swap' becomes trivial.
>  
>  By moving focus directly into the stackset, we can toss some QC
>  properties about focus handling: it is simply impossible now for focus
>  to go wrong. As a benefit, we get a dozen new QC properties for free,
>  governing how master and focus operate.
>  
>  The encoding of focus in the data type also simplifies the focus
>  handling in Operations: several operations affecting focus are now
>  simply wrappers over StackSet.
>  
>  For the full story, please read the StackSet module, and the QC
>  properties.
>  
>  Finally, we save ~40 lines with the simplified logic in Operations.hs
>  
>  For more info, see the blog post on the implementation,
>  
>      http://cgi.cse.unsw.edu.au/~dons/blog/2007/05/17#xmonad_part1b_zipper
>  
>  
> ] 
> [Read is not needed for StackSet
> Spencer Janssen <sjanssen at cse.unl.edu>**20070516054233] 
> [variable number of windows in master area
> Jason Creighton <jcreigh at gmail.com>**20070516031437] 
> [Use camelCase, please.
> Spencer Janssen <sjanssen at cse.unl.edu>**20070516014454] 
> [beautify tile
> David Roundy <droundy at darcs.net>**20070515154011] 
> [put doLayout in the X monad.
> David Roundy <droundy at darcs.net>**20070512215301] 
> [setsid() before exec.  Intended to fix issue #7
> Spencer Janssen <sjanssen at cse.unl.edu>**20070514044547] 
> [keep focus stack.
> David Roundy <droundy at darcs.net>**20070510131637] 
> [bump LOC limit to 550
> Jason Creighton <jcreigh at gmail.com>**20070510032731] 
> [Remove broken prop_promoterotate, replace it with prop_promote_raise_id
> Spencer Janssen <sjanssen at cse.unl.edu>**20070508211907] 
> [Disable shift_reversible until focus issues are decided.
> Spencer Janssen <sjanssen at cse.unl.edu>**20070508210952] 
> [Disable delete.push until focus issues are decided
> Spencer Janssen <sjanssen at cse.unl.edu>**20070508204921] 
> [Remove unsafe fromJust
> Spencer Janssen <sjanssen at cse.unl.edu>**20070508163822] 
> [Add the initial Catch testing framework for StackSet
> Neil Mitchell <http://www.cs.york.ac.uk/~ndm/>**20070508154621] 
> [Work around the fact that Yhc gets defaulting a bit wrong
> Neil Mitchell <http://www.cs.york.ac.uk/~ndm/>**20070508124949] 
> [Make tests typecheck
> Spencer Janssen <sjanssen at cse.unl.edu>**20070508152449] 
> [Remove unsafe use of head
> Spencer Janssen <sjanssen at cse.unl.edu>**20070508152116] 
> [Make 'index' return Nothing, rather than error
> Spencer Janssen <sjanssen at cse.unl.edu>**20070508151200] 
> [Use 'drop 1' rather than tail, skip equality check.
> Spencer Janssen <sjanssen at cse.unl.edu>**20070508150943] 
> [Redundant parens
> Spencer Janssen <sjanssen at cse.unl.edu>**20070508150412] 
> [StackSet.view: ignore invalid indices
> Spencer Janssen <sjanssen at cse.unl.edu>**20070508143951] 
> [Change the swap function so its Haskell 98, by using list-comps instead of pattern-guards.
> Neil Mitchell <http://www.cs.york.ac.uk/~ndm/>**20070508123158] 
> [Arbitrary instance for StackSet must set random focus on each workspace
> Don Stewart <dons at cse.unsw.edu.au>**20070508051126
>  
>  When focus was separated from the stack order on each workspace, we
>  forgot to update the Arbitrary instance to set random focus. As spotted
>  by David R, this then invalidates 4 of our QC properties. In particular,
>  the property involving where focus goes after a random transient
>  (annoying behaviour) appeared to be correct, but wasn't, due to
>  inadequate coverage.
>  
>  This patch sets focus to a random window on each workspace. As a result,
>  we now catch the focus/raise/delete issue people have been complaining
>  about.
>  
>  Lesson: make sure your QuickCheck generators are doing what you think
>  they are.
>   
> ] 
> [make quickcheck tests friendlier to read.
> David Roundy <droundy at darcs.net>**20070505175415] 
> [make Properties.hs exit with failure on test failure
> Jason Creighton <jcreigh at gmail.com>**20070505174357] 
> [since we just ignore type errors, no need to derive Show
> Don Stewart <dons at cse.unsw.edu.au>**20070504094143] 
> [Constrain layout messages to be members of a Message class
> Don Stewart <dons at cse.unsw.edu.au>**20070504081649
>  
>  Using Typeables as the only constraint on layout messages is a bit
>  scary, as a user can send arbitrary values to layoutMsg, whether they
>  make sense or not: there's basically no type feedback on the values you
>  supply to layoutMsg.
>  
>  Folloing Simon Marlow's dynamically extensible exceptions paper, we use
>  an existential type, and a Message type class, to constrain valid
>  arguments to layoutMsg to be valid members of Message.
>  
>  That is, a user writes some data type for messages their layout
>  algorithm accepts:
>  
>    data MyLayoutEvent = Zoom
>                       | Explode
>                       | Flaming3DGlassEffect
>                       deriving (Typeable)
>  
>  and they then add this to the set of valid message types:
>  
>    instance Message MyLayoutEvent
>  
>  Done. We also reimplement the dynamic type check while we're here, to
>  just directly use 'cast', rather than expose a raw fromDynamic/toDyn.
>  
>  With this, I'm much happier about out dynamically extensible layout
>  event subsystem.
>  
>  
> ] 
> [Handle empty layout lists
> Spencer Janssen <sjanssen at cse.unl.edu>**20070504045644] 
> [refactoring, style, comments on new layout code
> Don Stewart <dons at cse.unsw.edu.au>**20070504023618] 
> [use anyKey constant instead of magic number
> Jason Creighton <jcreigh at gmail.com>**20070504015043] 
> [added mirrorLayout to mirror arbitrary layouts
> Jason Creighton <jcreigh at gmail.com>**20070504014653] 
> [Fix layout switching order
> Spencer Janssen <sjanssen at cse.unl.edu>**20070503235632] 
> [More Config.hs bugs
> Spencer Janssen <sjanssen at cse.unl.edu>**20070503234607] 
> [Revert accidental change to Config.hs
> Spencer Janssen <sjanssen at cse.unl.edu>**20070503233148] 
> [Add -fglasgow-exts for pattern guards.  Properties.hs doesn't complain anymore
> Spencer Janssen <sjanssen at cse.unl.edu>**20070503214221] 
> [Avoid the unsafe pattern match, in case Config.hs has no layouts
> Spencer Janssen <sjanssen at cse.unl.edu>**20070503214007] 
> [add support for extensible layouts.
> David Roundy <droundy at darcs.net>**20070503144750] 
> [comments. and stop tracing events to stderr
> Don Stewart <dons at cse.unsw.edu.au>**20070503075821] 
> [-Wall police
> Don Stewart <dons at cse.unsw.edu.au>**20070503074937] 
> [elaborate documentation in Config.hs
> Don Stewart <dons at cse.unsw.edu.au>**20070503074843] 
> [Use updated refreshKeyboardMapping.  Requires latest X11-extras
> Spencer Janssen <sjanssen at cse.unl.edu>**20070503032040] 
> [run QC tests in addition to LOC test
> Jason Creighton <jcreigh at gmail.com>**20070503003202] 
> [Add 'mod-n': refreshes current layout
> Spencer Janssen <sjanssen at cse.unl.edu>**20070503002252] 
> [Fix tests after StackSet changes
> Spencer Janssen <sjanssen at cse.unl.edu>**20070502201622] 
> [First steps to adding floating layer
> Spencer Janssen <sjanssen at cse.unl.edu>**20070502195917] 
> [update motivational text using xmonad.org
> Don Stewart <dons at cse.unsw.edu.au>**20070502061859] 
> [Sort dependencies in installation order
> Spencer Janssen <sjanssen at cse.unl.edu>**20070501204249] 
> [Recommend X11-extras 0.1
> Spencer Janssen <sjanssen at cse.unl.edu>**20070501204121] 
> [elaborate description in .cabal
> Don Stewart <dons at cse.unsw.edu.au>**20070501035414] 
> [use -fasm by default. Much faster
> Don Stewart <dons at cse.unsw.edu.au>**20070501031220] 
> [check we never generate invalid stack sets
> Don Stewart <dons at cse.unsw.edu.au>**20070430065946] 
> [Make border width configurable
> Spencer Janssen <sjanssen at cse.unl.edu>**20070430163515] 
> [Add Config.hs-boot, remove defaultLayoutDesc from XConf
> Spencer Janssen <sjanssen at cse.unl.edu>**20070430162647] 
> [Comment only
> Spencer Janssen <sjanssen at cse.unl.edu>**20070430161635] 
> [Comment only
> Spencer Janssen <sjanssen at cse.unl.edu>**20070430161511] 
> [view n . shift n . view i . shift i) x == x --> shift + view is invertible
> Don Stewart <dons at cse.unsw.edu.au>**20070430062901] 
> [add rotate all and view idempotency tests
> Don Stewart <dons at cse.unsw.edu.au>**20070430055751] 
> [Add XConf for values that don't change.
> Spencer Janssen <sjanssen at cse.unl.edu>**20070430054715] 
> [Control.Arrow is suspicious, add an explicit import
> Spencer Janssen <sjanssen at cse.unl.edu>**20070430053623] 
> [push is idempotent
> Don Stewart <dons at cse.unsw.edu.au>**20070430054345] 
> [add two properties relating to empty window managers
> Don Stewart <dons at cse.unsw.edu.au>**20070430051016] 
> [new QC property: opening a window only affects the current screen
> Don Stewart <dons at cse.unsw.edu.au>**20070430050133] 
> [configurable border colors
> Jason Creighton <jcreigh at gmail.com>**20070430043859
>  This also fixes a bug where xmonad was assuming a 24-bit display, and just
>  using, eg, 0xff0000 as an index into a colormap without querying the X server
>  to determine the proper pixel value for "red".
> ] 
> [a bit more precise about building non-empty stacksets for one test
> Don Stewart <dons at cse.unsw.edu.au>**20070430035729] 
> [remove redundant call to 'delete' in 'shift'
> Don Stewart <dons at cse.unsw.edu.au>**20070430031151] 
> [clean 'delete' a little
> Don Stewart <dons at cse.unsw.edu.au>**20070430025319] 
> [shrink 'swap'
> Don Stewart <dons at cse.unsw.edu.au>**20070430024813] 
> [shrink 'rotate' a little
> Don Stewart <dons at cse.unsw.edu.au>**20070430024525] 
> [move size into Properties.hs
> Don Stewart <dons at cse.unsw.edu.au>**20070430021758] 
> [don't need 'size' operation on StackSet
> Don Stewart <dons at cse.unsw.edu.au>**20070430015927] 
> [add homepage: field to .cabal file
> Don Stewart <dons at cse.unsw.edu.au>**20070429041011] 
> [add fromList to Properties.hs
> Don Stewart <dons at cse.unsw.edu.au>**20070429035823] 
> [move fromList into Properties.hs, -17 loc
> Don Stewart <dons at cse.unsw.edu.au>**20070429035804] 
> [avoid grabbing all keys when a keysym is undefined
> Jason Creighton <jcreigh at gmail.com>**20070428180046
>  XKeysymToKeycode() returns zero if the keysym is undefined. Zero also happens
>  to be the value of AnyKey.
> ] 
> [Further refactoring
> Spencer Janssen <sjanssen at cse.unl.edu>**20070426212257] 
> [Refactor in Config.hs (no real changes)
> Spencer Janssen <sjanssen at cse.unl.edu>**20070426211407] 
> [Add the manpage to extra-source-files
> Spencer Janssen <sjanssen at cse.unl.edu>**20070426014105] 
> [add xmonad manpage
> David Lazar <davidlazar at styso.com>**20070426010812] 
> [Remove toList
> Spencer Janssen <sjanssen at cse.unl.edu>**20070426005713] 
> [Ignore numlock and capslock in keybindings
> Jason Creighton <jcreigh at gmail.com>**20070424013357] 
> [Clear numlock bit
> Spencer Janssen <sjanssen at cse.unl.edu>**20070424010352] 
> [force window border to 1px
> Jason Creighton <jcreigh at gmail.com>**20070423050824] 
> [s/creigh//
> Don Stewart <dons at cse.unsw.edu.au>**20070423024026] 
> [some other things to do
> Don Stewart <dons at cse.unsw.edu.au>**20070423023151] 
> [Start TODOs for 0.2
> Spencer Janssen <sjanssen at cse.unl.edu>**20070423021526] 
> [update readme
> Don Stewart <dons at cse.unsw.edu.au>**20070422090507] 
> [TAG 0.1
> Spencer Janssen <sjanssen at cse.unl.edu>**20070422083033] 
> Patch bundle hash:
> 20a7032761f3cacce356c93dbc8e0ee6bf033ed8

> _______________________________________________
> Xmonad mailing list
> Xmonad at haskell.org
> http://www.haskell.org/mailman/listinfo/xmonad



More information about the Xmonad mailing list