Difference between revisions of "Xmonad/Guided tour of the xmonad source"

From HaskellWiki
Jump to navigation Jump to search
(additional content: the X monad)
(8 intermediate revisions by 3 users not shown)
Line 1: Line 1:
  +
{{xmonad}}
  +
[[Category:XMonad]]
  +
 
== Introduction ==
 
== Introduction ==
   
Line 25: Line 28:
   
 
darcs get http://code.haskell.org/xmonad
 
darcs get http://code.haskell.org/xmonad
  +
  +
I intend for this guided tour to keep abreast of the latest darcs changes; if you see something which is out of sync, report it on the xmonad mailing list, or -- even better -- fix it!
   
 
You may also want to refer to the [http://www.haskell.org/haddock/ Haddock]-generated documentation (it's all in the source code, of course, but may be nicer to read this way). You can build the documentation by going into the root of the xmonad source directory, and issuing the command:
 
You may also want to refer to the [http://www.haskell.org/haddock/ Haddock]-generated documentation (it's all in the source code, of course, but may be nicer to read this way). You can build the documentation by going into the root of the xmonad source directory, and issuing the command:
Line 34: Line 39:
 
Without further ado, let's begin!
 
Without further ado, let's begin!
   
== StackSet.hs ==
 
   
StackSet.hs is the pure, functional heart of xmonad. Far removed from
 
corrupting pollutants such as the IO monad and the X server, it is
 
a beatiful, limpid pool of pure code which defines most of the basic
 
data structures used to store the state of xmonad. It is heavily
 
validated by [http://www.cs.chalmers.se/~rjmh/QuickCheck/ QuickCheck] tests; the combination of good use of types and QuickCheck validation means that we can be very confident of the correctness of the code in StackSet.hs.
 
   
===<hask>StackSet</hask>===
+
== StackSet.hs ==
   
  +
StackSet.hs is the pure, functional heart of xmonad. Far removed from corrupting pollutants such as the IO monad and the X server, it is a beautiful, limpid pool of pure code which defines most of the basic data structures used to store the state of xmonad. It is heavily validated by [http://www.cs.chalmers.se/~rjmh/QuickCheck/ QuickCheck] tests; the combination of good use of types and QuickCheck validation means that we can be very confident of the correctness of the code in StackSet.hs.
The <hask>StackSet</hask> data type is the mother-type which stores (almost) all
 
of xmonad's state. Let's take a look at the definition of the
 
<hask>StackSet</hask> data type itself:
 
   
  +
[[/StackSet.hs|Continue reading about StackSet.hs...]]
<haskell>
 
data StackSet i l a sid sd =
 
StackSet { current :: !(Screen i l a sid sd) -- ^ currently focused workspace
 
, visible :: [Screen i l a sid sd] -- ^ non-focused workspaces, visible in xinerama
 
, hidden :: [Workspace i l a] -- ^ workspaces not visible anywhere
 
, floating :: M.Map a RationalRect -- ^ floating windows
 
} deriving (Show, Read, Eq)
 
</haskell>
 
 
First of all, what's up with <hask>i l a sid sd</hask>? These are ''type parameters'' to <hask>StackSet</hask>---five types which must be provided to form a concrete instance of <hask>StackSet</hask>. It's not obvious just from this definition what they represent, so let's talk about them first, so we have a better idea of what's going on when they keep coming up later.
 
 
* The first type parameter, here represented by <hask>i</hask>, is the type of ''workspace tags''. Each workspace has a tag which uniquely identifies it (and which is shown in your status bar if you use the DynamicLog extension). At the moment, these tags are simply <hask>String</hask>s---but, as you can see, the definition of <hask>StackSet</hask> doesn't depend on knowing exactly what they are. If, in the future, the xmonad developers decided that <hask>Complex Double</hask>s would make better workspace tags, no changes would be required to any of the code in StackSet.hs!
 
 
* The second type parameter <hask>l</hask> is somewhat mysterious---there isn't much code in StackSet.hs that does much of anything with it. For now, it's enough to know that the type <hask>l</hask> has something to do with layouts; <hask>StackSet</hask> is completely independent of particular window layouts, so there's not much to see here.
 
 
* The third type parameter, <hask>a</hask>, is the type of a single window.
 
 
* <hask>sid</hask> is a screen id, which identifies a physical screen; as we'll see later, it is (essentially) <hask>Int</hask>.
 
 
* <hask>sd</hask>, the last type parameter to <hask>StackSet</hask>, represents details about a physical screen.
 
 
Although it's helpful to know what these types represent, it's
 
important to understand that as far as <hask>StackSet</hask> is concerned, the
 
particular types don't matter. A <hask>StackSet</hask> simply organizes data
 
with these types in particular ways, so it has no need to know the
 
actual types.
 
 
The <hask>StackSet</hask> data type has four members: <hask>current</hask> stores the
 
currently focused workspace; <hask>visible</hask> stores a list of those
 
workspaces which are not focused but are still visible on other
 
physical screens; <hask>hidden</hask> stores those workspaces which are, well,
 
hidden; and <hask>floating</hask> stores any windows which are in the floating
 
layer.
 
 
A few comments are in order:
 
 
* <hask>visible</hask> is only needed to support multiple physical screens with Xinerama; in a non-Xinerama setup, <hask>visible</hask> will always be the empty list.
 
 
* Notice that <hask>current</hask> and <hask>visible</hask> store <hask>Screen</hask>s, whereas <hask>hidden</hask> stores <hask>Workspace</hask>s. This might seem confusing until you realize that a <hask>Screen</hask> is really just a glorified <hask>Workspace</hask>, with a little extra information to keep track of which physical screen it is currently being displayed on:
 
 
<haskell>
 
data Screen i l a sid sd = Screen { workspace :: !(Workspace i l a)
 
, screen :: !sid
 
, screenDetail :: !sd }
 
deriving (Show, Read, Eq)
 
</haskell>
 
 
* A note about those exclamation points, as in <hask>workspace :: !(Workspace i l a)</hask>: they are ''strictness annotations'' which specify that the fields in question should never contain thunks (unevaluated expressions). This helps ensure that we don't get huge memory blowups with fields whose values aren't needed for a while and lazily accumulate large unevaluated expressions. Such fields could also potentially cause sudden slowdowns, freezing, etc. when their values are finally needed, so the strictness annotations also help ensure that xmonad runs smoothly by spreading out the work.
 
 
* The <hask>floating</hask> field stores a <hask>Map</hask> from windows (type <hask>a</hask>,remember?) to <hask>RationalRect</hask>s, which simply store x position, y position, width, and height. Note that floating windows are still stored in a <hask>Workspace</hask> in addition to being a key of <hask>floating</hask>, which means that floating/sinking a window is a simple matter of inserting/deleting it from <hask>floating</hask>, without having to mess with any <hask>Workspace</hask> data.
 
 
===<hask>StackSet</hask> functions===
 
 
StackSet.hs also provides a few functions for dealing directly with
 
<hask>StackSet</hask> values: <hask>new</hask>, <hask>view</hask>, and <hask>greedyView</hask>. For example,
 
here's <hask>new</hask>:
 
 
<haskell>
 
new :: (Integral s) => l -> [i] -> [sd] -> StackSet i l a s sd
 
new l wids m | not (null wids) && length m <= length wids = StackSet cur visi unseen M.empty
 
where (seen,unseen) = L.splitAt (length m) $ map (\i -> Workspace i l Nothing) wids
 
(cur:visi) = [ Screen i s sd | (i, s, sd) <- zip3 seen [0..] m ]
 
-- now zip up visibles with their screen id
 
new _ _ _ = abort "non-positive argument to StackSet.new"
 
</haskell>
 
 
If you're <hask>new</hask> (haha) to Haskell, this might seem dauntingly complex,
 
but it isn't actually all that bad. In general, if you just take
 
things slowly and break them down piece by piece, you'll probably be
 
surprised how much you understand after all.
 
 
<hask>new</hask> takes a layout thingy (<hask>l</hask>), a list of workspace tags (<hask>[i]</hask>),
 
and a list of screen descriptors (<hask>[sd]</hask>), and produces a new
 
<hask>StackSet</hask>. First, there's a guard, which requires <hask>wids</hask> to be
 
nonempty (there must be at least one workspace), and <hask>length m</hask> to be
 
at most <hask>length wids</hask> (there can't be more screens than workspaces).
 
If those conditions are met, it constructs a <hask>StackSet</hask> by creating a
 
list of empty <hask>Workspace</hask>s, splitting them into <hask>seen</hask> and <hask>unseen</hask>
 
workspaces (depending on the number of physical screens), combining
 
the <hask>seen</hask> workspaces with screen information, and finally picking the
 
first screen to be current. If the conditions on the guard are not
 
met, it aborts with an error. Since this function will only ever be
 
called internally, the call to <hask>abort</hask> isn't a problem: it's there
 
just so we can test to make sure it's never called! If this were a
 
function which might be called by users from their xmonad.hs configuration file,
 
aborting would be a huge no-no: by design, xmonad should never crash
 
for ''any'' reason (even user stupidity!).
 
 
Now take a look at <hask>view</hask> and <hask>greedyView</hask>. <hask>view</hask> takes a workspace
 
tag and a <hask>StackSet</hask>, and returns a new <hask>StackSet</hask> in which the given
 
workspace has been made current. <hask>greedyView</hask> only differs in the way
 
it treats Xinerama screens: <hask>greedyView</hask> will always swap the
 
requested workspace so it is now on the current screen even if it was
 
already visible, whereas calling <hask>view</hask> on a visible workspace will
 
just switch the focus to whatever screen it happens to be on. For
 
single-head setups, of course, there isn't any difference in behavior
 
between <hask>view</hask> and <hask>greedyView</hask>.
 
 
Note that <hask>view</hask>/<hask>greedyView</hask> do not ''modify'' a <hask>StackSet</hask>, but simply
 
return a new one computed from the old one. This is a common purely
 
functional paradigm: functions which would modify a data structure in
 
an imperative/non-pure paradigm are recast as functions which take an
 
old version of a data structure as input and produce a new version.
 
This might seem horribly inefficient to someone used to a non-pure
 
paradigm, but it actually isn't, for (at least) two reasons. First, a
 
lot of work has gone into memory allocation and garbage collection, so
 
that in a modern functional language such as Haskell, these processes
 
are quite efficient. Second, and more importantly, the fact that
 
Haskell is pure (modifying values is not allowed) means that when a
 
new structure is constructed out of an old one with only a small
 
change, usually the new structure can actually share most of the old
 
one, with new memory being allocated only for the part that changed.
 
In an impure language, this kind of sharing would be a big no-no,
 
since modifying the old value later would suddenly cause the new value
 
to change as well.
 
 
===<hask>Workspace</hask>===
 
 
The <hask>Workspace</hask> type is quite simple. It stores a tag, a layout, and possibly a <hask>Stack</hask>:
 
 
<haskell>
 
data Workspace i l a = Workspace { tag :: !i, layout :: l, stack :: Maybe (Stack a) }
 
deriving (Show, Read, Eq)
 
</haskell>
 
 
If there are no windows in a given workspace, <hask>stack</hask> will be <hask>Nothing</hask>; if there are windows, it will be <hask>Just s</hask>, where <hask>s</hask> is a non-empty <hask>Stack</hask> of windows.
 
 
There's not much else to say about it, which makes this a perfect chance to talk about record syntax. The basic way to define the <hask>Workspace</hask> type would be:
 
 
<haskell>
 
data Workspace i l a = Workspace i l (Maybe (Stack a))
 
</haskell>
 
 
This simply specifies a single constructor for the <hask>Workspace</hask> type (perhaps somewhat confusingly, also called <hask>Workspace</hask>, although these are two different things) which has three components, of types <hask>i</hask>, <hask>l</hask>, and <hask>Maybe (Stack a)</hask>, respectively. The record syntax in the actual code wraps the components in curly braces, and adds a name associated with each component. These names automatically turn into accessor functions which allow us to extract the corresponding component from a value of type <hask>Workspace i l a</hask>. For example, <hask>tag</hask> becomes a function of type
 
 
<haskell>
 
tag :: Workspace i l a -> i
 
</haskell>
 
 
Hence, we have two ways to get at the internals of any value whose type is defined using record syntax: pattern-matching, or accessor functions.
 
 
=== <hask>Stack</hask> ===
 
 
The <hask>Stack</hask> type stores a list of the actual windows on a given workspace, along with a notion of the "current" window. Now, the "obvious" way to do this in an imperative language would be to store an array of windows along with an index into the array. However, this approach has several disadvantages:
 
 
* Creating a new window or deleting the current one would be O(n) operations, as all the windows to the right of the current location would have to be shifted by one in the array.
 
* In Haskell, indexing into a list is O(n) anyway, and using an array library would be unwieldy here.
 
* Much work must go into maintaining guarantees such as always having the current index be a valid index into the array, maintaining the ordering of the windows when shifting them around in the array, and so on.
 
 
Instead, a <hask>Stack</hask> uses an ingenious structure known as a ''list zipper'':
 
 
<haskell>
 
data Stack a = Stack { focus :: !a -- focused thing in this set
 
, up :: [a] -- clowns to the left
 
, down :: [a] } -- jokers to the right
 
deriving (Show, Read, Eq)
 
</haskell>
 
 
Instead of using a single list with some sort of index, the list is broken into three pieces: a current window (<hask>focus</hask>), the windows before that, in reverse order (<hask>up</hask>), and the windows after it (<hask>down</hask>). This has several nice properties:
 
 
* A <hask>Stack a</hask> cannot be empty, since it must always contain a current element. Remember, the possibility of an empty workspace is handled by the type of <hask>Workspace</hask>'s <hask>stack</hask> field, <hask>Maybe (Stack a)</hask>.
 
* Shifting focus, adding a new window next to the current one, and reversing the window list are all simple O(1) operations.
 
* There is not even the possibility of any sort of index-out-of-bounds errors while keeping track of the current window.
 
 
For more information on zippers, the [http://haskell.org/haskellwiki/Zipper Zipper page on the Haskell wiki] and the [http://en.wikibooks.org/wiki/Haskell/Zippers chapter on zippers in the Haskell wikibook] are good starting places.
 
 
===Other functions===
 
 
At this point you should spend some time studying the rest of the functions in StackSet.hs, which provide various operations on <hask>Stack</hask>s and <hask>StackSet</hask>s. There are quite a few, but they are, for the most part, quite straightforward. Some general notes and commentary:
 
 
* The functions <hask>with</hask>, <hask>modify</hask>, and <hask>modify'</hask> are great examples of ''higher-order functions'', functions which take other functions as input. Haskell (and most functional languages) make such a thing easy and natural. For example, <hask>with</hask> applies a function to the current workspace's stack; <hask>modify</hask> essentially transforms a function on <hask>Stack</hask>s to a function on <hask>StackSet</hask>s, with some <hask>Maybe</hask> types thrown in to handle empty cases.
 
 
* The names of the functions <hask>integrate</hask> and <hask>differentiate</hask> may strike you as odd unless you know that there is an astonishing connection between derivatives (yes, from calculus) and zipper types. In short, finding the zipper of a given data type corresponds to finding a derivative. For more information, see the [http://en.wikibooks.org/wiki/Haskell/Zippers Haskell wikibook entry on zippers], or the paper by Conor McBride, [http://www.cs.nott.ac.uk/~ctm/diff.pdf The Derivative of a Regular Type is its Type of One-Hole Contexts].
 
 
* Note how the implementation of functions such as <hask>focusUp</hask>/<hask>Down</hask>, <hask>swapUp</hask>/<hask>Down</hask>, and <hask>reverseStack</hask> are quite simple, thanks to higher-order functions and the zipper structure of <hask>Stack</hask>s.
 
 
* I sort of lied when I said that moving focus is O(1) with the zipper structure: in the one case that focus wraps around the end of the list, it is O(n). But it is still takes O(1) amortized time.
 
 
=== QuickCheck properties ===
 
 
Now take a look at tests/Properties.hs, which contains a large collection of [http://www.cs.chalmers.se/~rjmh/QuickCheck/ QuickCheck] properties for testing StackSet.hs. Here's the way it works: a QuickCheck property is essentially a function of type <hask>a -> Bool</hask> which should always evaluate to <hask>True</hask> for any value of type <hask>a</hask>. (Actually, it's a little more complex than this: using a special return type <hask>Property</hask> instead of <hask>Bool</hask>, a property can also specify only a subset of values for which the property should hold.) The type <hask>a</hask> must be an instance of the type class <hask>Arbitrary</hask>, which defines a way to generate random values of that type. Running QuickCheck on a property generates a large amount of random test data of the appropriate type, and ensures that the property always evaluates to true; if not, it displays the input for which the property failed. Of course, this is not ''proof'' that the property is always true, but a set of well-defined properties is surprisingly good at catching bugs and forgotten corner cases.
 
 
These tests are run automatically with every recorded change to the xmonad source repository -- indeed, they must all pass in order for a change to be recorded.
 
   
 
== Core.hs ==
 
== Core.hs ==
Line 236: Line 51:
 
The next source file to examine is Core.hs. It defines several core data types and some of the core functionality of xmonad. If StackSet.hs is the heart of xmonad, Core.hs is its guts.
 
The next source file to examine is Core.hs. It defines several core data types and some of the core functionality of xmonad. If StackSet.hs is the heart of xmonad, Core.hs is its guts.
   
  +
[[/Core.hs|Continue reading about Core.hs...]]
=== <hask>XState</hask>, <hask>XConf</hask>, and <hask>XConfig</hask> ===
 
 
These three record types make up the core of xmonad's state and configuration:
 
 
* A value of type <hask>XState</hask> stores xmonad's mutable runtime state, consisting of the list of workspaces, a set of mapped windows, something to do with keeping track of pending UnmapEvents, and something to do with dragging.
 
<haskell>
 
data XState = XState
 
{ windowset :: !WindowSet -- ^ workspace list
 
, mapped :: !(S.Set Window) -- ^ the Set of mapped windows
 
, waitingUnmap :: !(M.Map Window Int) -- ^ the number of expected UnmapEvents
 
, dragging :: !(Maybe (Position -> Position -> X (), X ())) }
 
</haskell>
 
 
Note that the <hask>WindowSet</hask> type is just a <hask>StackSet</hask> with various concrete types substituted for its type parameters:
 
 
<haskell>
 
type WindowSet = StackSet WorkspaceId (Layout Window) Window ScreenId ScreenDetail
 
type WindowSpace = Workspace WorkspaceId (Layout Window) Window
 
 
-- | Virtual workspace indicies
 
type WorkspaceId = String
 
 
-- | Physical screen indicies
 
newtype ScreenId = S Int deriving (Eq,Ord,Show,Read,Enum,Num,Integral,Real)
 
 
-- | The 'Rectangle' with screen dimensions and the list of gaps
 
data ScreenDetail = SD { screenRect :: !Rectangle
 
, statusGap :: !(Int,Int,Int,Int) -- ^ width of status bar on the screen
 
} deriving (Eq,Show, Read)
 
</haskell>
 
 
The type of workspace tags, <hask>WorkspaceId</hask>, is just <hask>String</hask>; a <hask>ScreenDetail</hask> stores information about the screen dimension as well as any gaps which should be left at the edges of the screen for status bars and other such things. Now, you may wonder why we have
 
 
<haskell>
 
newtype ScreenId = S Int deriving (...)
 
</haskell>
 
 
rather than just <hask>type ScreenId = Int</hask>? The reason is that if <hask>type ScreenId = Int</hask>, it would be possible to accidentally do arithmetic with <hask>ScreenId</hask>s mixed with other <hask>Int</hask> values, which clearly doesn't make sense. Making <hask>ScreenId</hask> a separate type means that the type system will enforce non-mixing of <hask>ScreenId</hask>s with other types, while using <hask>newtype</hask> with automatic instance deriving means none of the convenience is lost -- we can write code ''just as if'' <hask>ScreenId</hask>s are normal <hask>Int</hask> values, but be sure that we can't accidentally get mixed up and do something silly like add a <hask>ScreenId</hask> to the width of a window. This is the power of a rich static type system like Haskell's -- we can encode certain invariants and constraints in the type system, and have them automatically checked at compile time.
 
 
* An <hask>XConf</hask> record stores xmonad's (immutable) configuration data, such as window border colors, the keymap, information about the X11 display and root window, and other user-specified configuration information. The reason this record is separated from <hask>XState</hask> is that, as we'll see later, xmonad's code provides a static guarantee that the data stored in this record is truly read-only, and cannot be changed while xmonad is running.
 
 
* <hask>XConfig</hask> provides a way for the user to customize xmonad's configuration, by defining an <hask>XConfig</hask> record in their <hask>xmonad.hs</hask> file. You're probably already familiar with this record type.
 
 
=== The <hask>X</hask> monad ===
 
 
And now, what you've all been waiting for: the X monad!
 
 
<haskell>
 
newtype X a = X (ReaderT XConf (StateT XState IO) a)
 
deriving (Functor, Monad, MonadIO, MonadState XState, MonadReader XConf)
 
</haskell>
 
 
The X monad represents a common pattern for building custom monad instances: using ''monad transformers'', one can simply 'layer' the capabilities and effects of several monads into one, and then use GHC's newtype deriving capabilities to automatically derive instances of the relevant type classes. In this case, the base monad out of which the X monad is built is IO; this is necessary since communicating with the X server involves IO operations. On top of that is <hask>StateT XState</hask>, which automatically threads a mutable <hask>XState</hask> record through computations in the X monad; finally there is a <hask>ReaderT XConf</hask> which also threads a read-only <hask>XConf</hask> record through. As noted in the comments in the source, the <hask>XState</hask> record can be accessed with any functions in the [http://haskell.org/ghc/docs/latest/html/libraries/mtl/Control-Monad-State-Class.html#t%3AMonadState <hask>MonadState</hask>] type class, such as <hask>get</hask>, <hask>put</hask>, <hask>gets</hask>, and <hask>modify</hask>; the <hask>XConf</hask> record can be accessed with [http://haskell.org/ghc/docs/latest/html/libraries/mtl/Control-Monad-Reader-Class.html#t%3AMonadReader <hask>MonadReader</hask>] functions, such as <hask>ask</hask>.
 
 
For more information on monad transformers in general, I recommend reading Martin Grabmüller's excellent tutorial paper, [http://uebb.cs.tu-berlin.de/~magr/pub/Transformers.en.html Monad Transformers Step-by-Step]; for more information on this particular style of composing monad transformers and using automatic newtype deriving, read Cale Gibbard's tutorial, [http://cale.yi.org/index.php/How_To_Use_Monad_Transformers How To Use Monad Transformers].
 
 
Along with the X monad, several utility functions are provided, such as <hask>runX</hask>, which turns an action in the X monad into an IO action, and <hask>catchX</hask>, which provides error handling for X actions. There are also several higher-order functions provided for convenience, including <hask>withDisplay</hask> (apply a function producing an X action to the current display) and <hask>withWindowSet</hask> (apply a function to the current window set).
 
 
=== <hask>ManageHook</hask> ===
 
 
=== Layout and Messages ===
 
   
  +
== Module structure of the core ==
=== Utility functions ===
 
   
  +
[[Image:Xmonad2.svg|The module structure of the xmonad core]]
=== On-the-fly recompilation ===
 

Revision as of 16:30, 16 September 2008

Xmonad-logo-small.png

XMonad

Introduction

Do you know a little Haskell and want to see how it can profitably be applied in a real-world situation? Would you like to quickly get up to speed on the xmonad source code so you can contribute modules and patches? Do you aspire to be as cool of a hacker as the xmonad authors? If so, this might be for you. Specifically, this document aims to:

  • Provide a readable overview of the xmonad source code for Haskell non-experts interested in contributing extensions or modifications to xmonad, or who are just curious.
  • Highlight some of the uniquenesses of xmonad and the things that make functional languages in general, and Haskell in particular, so ideally suited to this domain.

This is not a Haskell tutorial. I assume that you already know some basic Haskell: defining functions and data; the type system; standard functions, types, and type classes from the Standard Prelude; and at least a basic familiarity with monads. With that said, however, I do take frequent detours to highlight and explain more advanced topics and features of Haskell as they arise.

First things first

You'll want to have your own version of the xmonad source code to refer to as you read through the guided tour. In particular, you'll want the latest darcs version, which you can easily download by issuing the command:

darcs get http://code.haskell.org/xmonad

I intend for this guided tour to keep abreast of the latest darcs changes; if you see something which is out of sync, report it on the xmonad mailing list, or -- even better -- fix it!

You may also want to refer to the Haddock-generated documentation (it's all in the source code, of course, but may be nicer to read this way). You can build the documentation by going into the root of the xmonad source directory, and issuing the command:

runhaskell Setup haddock

which will generate HTML documentation in dist/doc/html/xmonad/.

Without further ado, let's begin!


StackSet.hs

StackSet.hs is the pure, functional heart of xmonad. Far removed from corrupting pollutants such as the IO monad and the X server, it is a beautiful, limpid pool of pure code which defines most of the basic data structures used to store the state of xmonad. It is heavily validated by QuickCheck tests; the combination of good use of types and QuickCheck validation means that we can be very confident of the correctness of the code in StackSet.hs.

Continue reading about StackSet.hs...

Core.hs

The next source file to examine is Core.hs. It defines several core data types and some of the core functionality of xmonad. If StackSet.hs is the heart of xmonad, Core.hs is its guts.

Continue reading about Core.hs...

Module structure of the core

The module structure of the xmonad core