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

From HaskellWiki
Jump to navigation Jump to search
Line 38: Line 38:
 
[[/StackSet.hs]]
 
[[/StackSet.hs]]
   
== Core.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.
 
 
=== <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> ===
 
 
This is a bit more advanced, and not really a central part of the system, so I'm skipping it for now, hopefully coming back to add more later.
 
 
=== <hask>LayoutClass</hask> ===
 
 
Next, let's take a look at the <hask>LayoutClass</hask>. This is one of the places that Haskell's type classes really shine. <hask>LayoutClass</hask> is a type class of which every layout must be an instance. It defines the basic functions which define what a layout is and how it behaves. The comments in the source code explain very clearly what each of these functions is supposed to do, but here are some highlights:
 
 
* Note that all the <hask>LayoutClass</hask> functions provide default implementations, so that <hask>LayoutClass</hask> instances do not have to provide implementations of those functions where the default behavior is desired. For example, by default, <hask>doLayout</hask> simply calls <hask>pureLayout</hask>, so a layout that does not require access to the X monad need only implement the <hask>pureLayout</hask> function. (For example, the Accordion, Square, and Grid layouts from the contrib library all use this approach.)
 
 
* Layouts can have their own private state, by storing this state in the <hask>LayoutClass</hask> instance and returning a modified structue (via <hask>doLayout</hask>) when the state changes.
 
 
* Both <hask>doLayout</hask> and <hask>handleMessage</hask> have corresponding "pure" versions, which do not give results in the X monad. These functions are never called directly by the xmonad core, which only calls <hask>doLayout</hask> and <hask>handleMessage</hask>, but a layout may choose to implement one (or both) of these "pure" functions, which will be called by the default implementation of the "impure" versions. Layouts which implement <hask>pureLayout</hask> or <hask>pureMessage</hask> are guaranteed to only make decisions about layout or messages (respectively) based on the internal layout state, and not on the state of the system or the window manager in general.
 
 
Now, every distinct layout will have a distinct type, although of course they all must be instances of <hask>LayoutClass</hask>. Given Haskell's strong typing, how can we store different layouts with different workspaces, or even change layouts on the fly? The solution is to wrap layouts using an <i>existential type</i> which hides the particular layout type and only exposes the fact that it is an instance of <hask>LayoutClass</hask>. Not only does this solve the problems caused by separate types for each layout, but it also guarantees that the xmonad core can only ever interact with a layout by calling functions from its <hask>LayoutClass</hask> instance. (Actually, this is a lie, since <hask>doLayout</hask> and <hask>handleMessage</hask> give results in the <hask>X</hask> monad, meaning they have access to the window manager state...)
 
 
<haskell>
 
-- | An existential type that can hold any object that is in Read and LayoutClass.
 
data Layout a = forall l. (LayoutClass l a, Read (l a)) => Layout (l a)
 
</haskell>
 
 
The <hask>forall l.</hask> abstracts over all layout types (types which are an instance of <hask>LayoutClass</hask>); this is what makes it an existential type. Note that <hask>l</hask> does not appear on the left-hand side of the type declaration. A variable <hask>lay</hask> may have the highly specific type of some particular layout (for example, the types of layouts formed by stacking various layout combinators and transformers can get rather long and hairy!), but no matter what the type of <hask>lay</hask>, <hask>Layout lay</hask> will simply have the type <hask>Layout a</hask> for some window type <hask>a</hask> (usually <hask>Window</hask>).
 
 
Note that <hask>(l a)</hask> is also required to be an instance of the <hask>Read</hask> type class -- this is so the state of all the layouts can be serialized and then read back in during dynamic restarts.
 
 
=== Messages ===
 
 
The xmonad core uses <i>messages</i> to communicate with layouts. The obvious, simple way to define messages would be by defining a new data type, something like
 
 
<haskell>
 
-- WARNING: not real xmonad code!
 
 
data Message = Hide | ReleaseResources | ShowMonkey
 
</haskell>
 
 
thus defining three messages types, which tell a layout to hide itself, release any resources, and display a monkey, respectively.
 
 
The problem with such an approach should be obvious: it is completely inflexible and inextensible; adding new message types later would be a pain, and it would be practically impossible for extension layouts to define their own message types without modifying the core. So, xmonad uses a more sophisticated system (at the cost of making things slightly harder to read and understand).
 
 
Instead of defining a <hask>Message</hask> data type, xmonad defines a <hask>Message</hask> <i>type class</i>:
 
 
<haskell>
 
class Typeable a => Message a
 
 
data SomeMessage = forall a. Message a => SomeMessage a
 
</haskell>
 
 
The <hask>Message</hask> class comes along with an existential wrapper <hask>SomeMessage</hask>, just like <hask>LayoutClass</hask> comes along with the <hask>Layout</hask> wrapper.
 
 
Note also that the <hask>Message</hask> type class doesn't declare any methods; it simply serves as a marker for types whose values we wish to use as messages. The <hask>Typeable</hask> constraint ensures that the types of values used as messages can be carried around as values at runtime, so dynamic type checks can be performed on messages extracted from a <hask>SomeMessage</hask> wrapper:
 
 
<haskell>
 
-- | And now, unwrap a given, unknown Message type, performing a (dynamic)
 
-- type check on the result.
 
--
 
fromMessage :: Message m => SomeMessage -> Maybe m
 
fromMessage (SomeMessage m) = cast m
 
</haskell>
 
 
Complicated? A bit, perhaps, but the good news is that you probably don't have to worry too much about it. =)
 
 
Finally, raw X events (like key presses, mouse movements, and so on) count as <hask>Message</hask>s, and two core message values are also defined as members of the <hask>LayoutMessages</hask> type.
 
 
<haskell>
 
-- | X Events are valid Messages
 
instance Message Event
 
 
-- | LayoutMessages are core messages that all layouts (especially stateful
 
-- layouts) should consider handling.
 
data LayoutMessages = Hide -- ^ sent when a layout becomes non-visible
 
| ReleaseResources -- ^ sent when xmonad is exiting or restarting
 
deriving (Typeable, Eq)
 
 
instance Message LayoutMessages
 
</haskell>
 
 
=== Utility functions ===
 
 
=== On-the-fly recompilation ===
 

Revision as of 20:14, 4 March 2008

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

/Core.hs