[Xmonad] moveLeft, moveRight

Robert Marlow bobstopper at bobturf.org
Tue May 22 00:03:26 EDT 2007


Hi

I've implemented an alternative to the current "swap" function in
StackSet.hs. The alternative uses two functions moveLeft and moveRight
(very similar to focusLeft and focusRight) to provide basic window
reordering functions. These functions can then be used to build more
complicated functions such as DWM-style promoting and the current method
of swapping.

moveLeft = 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) []

moveRight = 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)


Three further functions are also useful:

--
-- /O(1)/ Check if focused element is in the master position
masterIsFocus :: StackSet i a s -> Bool
masterIsFocus = with False (null . left)

--
-- /O(1)/ Check if current stack is empty
stackIsEmpty :: StackSet i a s -> Bool
stackIsEmpty = with True (const False)

--
-- /O(l), l is number of windows left of the focused window/.
--
-- Get index of focused window in the stack's current ordering
focusPosition :: StackSet i a s -> Maybe Int
focusPosition = with Nothing (Just . length . left) 


I find moveLeft and moveRight are useful functions in their own right
for binding to keys. But with the above three functions, swap and
DWM-style promote can both be built in Config.hs (after importing
StackSet qualified as W):

untilMaster :: (W.StackSet i a s -> W.StackSet i a s) -> W.StackSet i a
s -> W.StackSet i a s
untilMaster f s | W.stackIsEmpty s  = s
                | W.masterIsFocus s = s
                | otherwise         = untilMaster f (f s)

focusToMaster, masterToFocus :: W.StackSet i a s -> W.StackSet i a s
focusToMaster = untilMaster W.moveLeft
masterToFocus = untilMaster W.focusLeft

promote :: X ()
promote = windows focusToMaster

swap :: X ()
swap = windows $ \w -> case W.focusPosition w of
  Nothing -> w
  Just i  -> masterToFocus $ (doTimes (i-1) W.moveRight) $ W.focusRight
$ focusToMaster w
    where doTimes j f x = if j <= 0 then x else doTimes (j-1) f (f x)



The advantage is that moveLeft and moveRight are more basic functions
for building more complex functionality, especially when combined with
masterIsFocus, stackIsEmpty and focusPosition. moveLeft and moveRight
also display very similar properties to focusLeft and focusRight meaning
they can be checked as thoroughly. The disadvantage is that it's a fair
bit more code. The implementation of moveLeft and moveRight are very
similar to focusLeft and focusRight. Some clever way to get rid of code
duplication would be nice.

How does everyone feel about this idea? I can soon have a patch ready
with quickcheck properties if it's wanted.

-- 
Robert Marlow <bobstopper at bobturf.org>



More information about the Xmonad mailing list