[Xmonad] eliminating Workspace?

David Roundy droundy at darcs.net
Sat Jun 16 16:26:25 EDT 2007


Hi all,

I have an idea that I'd rather run by folks before
implementing--particularly as my tag-as-not-Num patches haven't been
accepted.  I'd like to add a tag field to Stack

data Stack i a = Stack { data   :: !i        -- name of this stack
                       , focus  :: !a        -- focused thing in this set
                       , up     :: [a]       -- clowns to the left
                       , down   :: [a] }     -- jokers to the right
    deriving (Show, Read, Eq)

and thus eliminate the Workspace data type.

The goal of this would be to also eliminate the Screen and StackSet types,
replacing them with something like:

type Workspace i a = Either i (Stack i a)

tag :: Workspace i a -> i
tag (Left i) = i
tag (Right s) = data s

type Screen i a sid = Stack sid (Workspace i a)

screen :: Screen i a sid -> sid
screen = data

workspace :: Screen i a sid -> Workspace i a
workspace = focus . stack'

type StackSet i a sid = Stack (M.Map a RationalRect)

floating :: StackSet i a sid -> M.Map a RationalRect
floating = data

current :: StackSet i a sid -> Screen i a sid
current = focus

visible :: StackSet i a sid -> [Screen i a sid]
visible s = reverse (up s) ++ down s

hidden :: StackSet i a sid -> [Workspace i a]
hidden s = map h (integrate s) where h scr = up scr ++ down scr

As you can see, the idea would be to use type to define synonyms for the
current data types, and functions to define accessors that grant the same
information as the current data structures (with almost the same API).  And
indeed, Workspace, Screen and StackSet would still each be distinct types,
so we aren't losing any typesafety.

I think that code will be simplified: the same function can shift focus
between Screens, Workspaces and Windows.  We'll need a new function (easily
written) to shift a Workspace to a given Screen, but on the whole things
look to me like they'll be nicer.

This data structure includes a bit more information than our current
StackSet, in that it associates each Workspace with a given Screen.  This
was recently requested as an option, so I think this is a good thing.  Note
that this doesn't require a change of behavior, is just make the existing
behavior slightly more complicated, and the behavior where Workspaces are
pinned associated with screens possible.  I only have one screen, but I can
certainly imagine that if I had one large and one small screen, I might
like to be able to designate certain Workspaces for either one or the
other.

As you can tell, this is part of my scheme to make xmonad code prettier.  I
greatly dislike having so many distinct data types, each implementing
basically the same sort of functionality in different ways:

* StackSet stores which Screen has focus... and which Workspaces aren't
  visible.

* Screen stores which Workspace has focus on that screen, but has no
  information about unfocussed Workspaces (those are in StackSet).

* Workspace stores which Window has focus, and also which other windows are
  on that Workspace.

This is almost but not quite symmetric, and that bothers me.  It also has
the result that the order of Workspaces is not stored anywhere except in
the workspace tags, which means we need to sort the workspaces in RotView.
So we store focus-order (which is also enforced to be stacking order now)
for Windows, but not for Workspaces or Screens.  Which among other things
means that there's no nice way for a user (or XMonadContrib module) to
alter the focus order for either Screens or Workspaces.

Anyhow, comments, suggestions and estimates as to whether such a drastic
change would be accepted will all be appreciated.
-- 
David Roundy
http://www.darcs.net


More information about the Xmonad mailing list