[xmonad] darcs patch: More flexible userCode function

Daniel Schoepe asgaroth_ at gmx.de
Sat Jan 10 17:49:23 EST 2009


Hello,
These patches change the function userCode to type X a -> X (Maybe a) 
for more flexibility and provide a userCodeDef :: a -> X a -> X a, for 
more convenience when using it, and adjust all uses of the old userCode.

-------------- next part --------------
Sat Jan 10 23:13:10 CET 2009  Daniel Schoepe <asgaroth_ at gmx.de>
  * Adjustments to new userCode function

New patches:

[Adjustments to new userCode function
Daniel Schoepe <asgaroth_ at gmx.de>**20090110221310] {
hunk ./XMonad/Hooks/UrgencyHook.hs 335
                   callUrgencyHook wuh w
                 else
                   clearUrgency w
-              userCode =<< asks (logHook . config) -- call *after* IORef has been modified
+              userCodeDef () =<< asks (logHook . config) -- call *after* IORef has been modified
         DestroyWindowEvent {ev_window = w} ->
           clearUrgency w
         _ ->
hunk ./XMonad/Hooks/UrgencyHook.hs 345
 callUrgencyHook :: UrgencyHook h => WithUrgencyHook h -> Window -> X ()
 callUrgencyHook (WithUrgencyHook hook UrgencyConfig { suppressWhen = sw, remindWhen = rw }) w =
     whenX (not <$> shouldSuppress sw w) $ do
-        userCode $ urgencyHook hook w
+        userCodeDef () $ urgencyHook hook w
         case rw of
             Repeatedly times int -> addReminder w int $ Just times
             Every int            -> addReminder w int Nothing
}

Context:

[XMonad.Util.XSelection: update maintainer information
gwern0 at gmail.com**20090110213000
 Ignore-this: 1592ba07f2ed5d2258c215c2d175190a
] 
[X.U.XSelection: get rid of warning about missing newline, add Haddock link
Brent Yorgey <byorgey at cis.upenn.edu>**20090102194357] 
[adds haddock documentation for transformPromptSelection
loupgaroublond at gmail.com**20090102190954
 
 also renames the function per mailing list recommendation
] 
[adds a weird function to XSelection
loupgaroublond at gmail.com**20081222020730
 
 This enables you to pass a function of (String -> String) to a selection function to modify the string before executing it.  This way, you can input your own escape routines to make it shell command line safe, and/or do other fancier things.
] 
[ThreeColumnsMiddle
xmonad at c-otto.de**20090102091019] 
[fix-fromJust-errors
rupa at lrrr.us**20081224045509
 
 bogner wrote all this stuff and i just tested it.
 
 I had:
 
 myLogHook = ewmhDesktopLogHookCustom ScratchpadFilterOutWorkspace >> updatePointer Nearest
 
 Everytime I invoked or hid Scratchpad, it would leave a 'Maybe.fromJust: Nothing' line in .xsession-errors, and updatePointer would stop working.
 
] 
[ Prompt: Change Filemode to 600 for history-file (fixes bug 244)
Dominik Bruhn <dominik at dbruhn.de>**20081218001601] 
[X.L.Monitor: changes in message passing
Roman Cheplyaka <roma at ro-che.info>**20081226220851
 - transform mbName (Maybe String) to name (String)
 - slghtly change semantics of messages, document it
] 
[X.L.Monitor: change interface
Roman Cheplyaka <roma at ro-che.info>**20081226213118
 - remove add*Monitor
 - add manageMonitor, monitor template
] 
[X.U.WindowProperties: propertyToQuery+docs
Roman Cheplyaka <roma at ro-che.info>**20081225080702] 
[X.L.Monitor: docs
Roman Cheplyaka <roma at ro-che.info>**20081225073904] 
[hlintify XUtils, XSelection, Search, WindowGo
gwern0 at gmail.com**20081220153302
 Ignore-this: 7e877484e3cd8954b74232ea83180fa9
] 
[fix focus issue for XMonad.Actions.Warp.banishScreen
Norbert Zeh <nzeh at cs.dal.ca>**20081212203532
 
 This patch ensures that the focus (or in fact the whose windowset)
 does not change as a result of a banishScreen.  The way this is implemented
 will become problematic if xmonad ever goes multithreaded.
] 
[addition of XMonad.Actions.Warp.banishScreen
Norbert Zeh <nzeh at cs.dal.ca>**20081212192621
 
 This works on top of warpToScreen and, thus, suffers from the same issue:
 focus change.
] 
[fixed documentation for banish
Norbert Zeh <nzeh at cs.dal.ca>**20081212191819
 
 banish actually warps to the specified corner of the current window, not
 the screen.
] 
[addition of combined TallGrid layout
Norbert Zeh <nzeh at cs.dal.ca>**20081212184836
 
 Added a module XMonad.Layouts.GridVariants, which defines layouts
 Grid and TallGrid.  The former is a customizable version of Grid.  The latter
 is a combination of Grid and Tall (see doc of the module).
] 
[Add FixedColumn, a layout like Tall but based on the resize hints of windows
Justin Bogner <mail at justinbogner.com>**20081213073054] 
[XMonad.Actions.WindowGo: fix a floating-related focus bug
gwern0 at gmail.com**20081205150755
 Ignore-this: c8b6625aa2bd4136937acbd2ad64ffd3
 If a floating window was focused, a cross-workspace 'raise' would cause a loop of
 shifting windows. Apparently the problem was 'focus' and its mouse-handling. Spencer
 suggested that the calls to focus be replaced with 'focusWindow', which resolved it.
] 
[Prompt.hs: +greenXPConfig and amberXPConfig
gwern0 at gmail.com**20081119213122
 Ignore-this: 95ac7dbe9c8fe3618135966f251f4fc6
] 
[Prompt.hs: increase font size to 12 from niggardly 10
gwern0 at gmail.com**20081119212523
 Ignore-this: 74a6e1ac5e1774da4ffc7c6667c034c
] 
[Prompt.hs: replace magic numbers with understandable names
gwern0 at gmail.com**20081119212502
 Ignore-this: 8401c0213be9a32c925e1bd0ba5e01f1
] 
[X.L.Monitor: recommend doHideIgnore (docs)
Roman Cheplyaka <roma at ro-che.info>**20081215190710] 
[X.L.Monitor: docs
Roman Cheplyaka <roma at ro-che.info>**20081215184423] 
[X.L.Monitor: export Monitor datatype
Roman Cheplyaka <roma at ro-che.info>**20081215184318] 
[X.H.ManageHelpers: add doHideIgnore
Roman Cheplyaka <roma at ro-che.info>**20081215182758] 
[Add KDE 4 config, thanks to Shirakawasuna on IRC
Spencer Janssen <spencerjanssen at gmail.com>**20081211071141
 Ignore-this: 51698961ab5b6e569c294d174f2804a9
] 
[I use the deleteConsecutive history filter
Spencer Janssen <spencerjanssen at gmail.com>**20081025070438] 
[Remove XMonad.Config.PlainConfig, it has been turned into the separate xmonad-light project.
Braden Shepherdson <Braden.Shepherdson at gmail.com>**20081203161534] 
[XMonad.Prompt: swap up and down per bug #243
gwern0 at gmail.com**20081203013323
 Ignore-this: 8ab0481a0da7a983f501ac2fec4a68e8
] 
[Fix boolean operator precedence in GridSelect keybindings
Aleksandar Dimitrov <aleks.dimitrov at googlemail.com>**20081201120928
 The vim-like hjkl keys were ORed to the key event AND arrow keys.
] 
[GridSelect.hs: navigate grid with h,j,k,l as well as arrow keys
sean.escriva at gmail.com**20081122084725] 
[Export setOpacity from FadeInactive. Document how to make monitor transparent (X.L.Monitor)
Roman Cheplyaka <roma at ro-che.info>**20081117153027] 
[Monitor: use broadcastMessage instead of sendMessage; this solves several issues
Roman Cheplyaka <roma at ro-che.info>**20081117133957] 
[FadeInactive: fade all inactive windows (including focused windows on visible screens)
Roman Cheplyaka <roma at ro-che.info>**20081117130115] 
[Monitor: documented one more issue
Roman Cheplyaka <roma at ro-che.info>**20081117113807] 
[Monitor: improved the docs
Roman Cheplyaka <roma at ro-che.info>**20081117073709] 
[added XMonad.Layout.Monitor
Roman Cheplyaka <roma at ro-che.info>**20081115104735] 
[WindowProperties: added allWithProperty
Roman Cheplyaka <roma at ro-che.info>**20081115104525] 
[ManageHelpers: added doSideFloat (generalization of doCenterFloat)
Roman Cheplyaka <roma at ro-che.info>**20081114113015] 
[GridSelect: Export default_colorizer
Dominik Bruhn <dominik at dbruhn.de>**20081112140005] 
[Simplify code for restriction-calculation and remove compiletime warnings
Dominik Bruhn <dominik at dbruhn.de>**20081112134630] 
[Simplify handle/eventLoop, introduce findInWindowMap, partial updates for key movements (less flickering)
Clemens Fruhwirth <clemens at endorphin.org>**20081111100405
 
 * handle/eventLoop carried the display and the drawing window as
   parameters. The display is available from the embedded X monad, the
   drawing windows was added.
 
 * updateWindows now takes a list of windows to
   update. updateAllWindows updates all windows.
 
 * only the windows that are modified by key movements are redrawn
   now. This means less flickering.
 
] 
[GridSelect: force cursor stay in visible area
Roman Cheplyaka <roma at ro-che.info>**20081111063348] 
[GridSelect: fix infiniteness problem with diamondRestrict
Roman Cheplyaka <roma at ro-che.info>**20081111055350] 
[GridSelect: remove tabs
Roman Cheplyaka <roma at ro-che.info>**20081111053647] 
[Exported shrinkWhile from Decoration to use in GridSelect
Roman Cheplyaka <roma at ro-che.info>**20081110191534] 
[GridSelect: added link to a screenshot
Roman Cheplyaka <roma at ro-che.info>**20081110190617] 
[GridSelect: various improvements
Roman Cheplyaka <roma at ro-che.info>**20081110184644
 Added documentation
 Restricted export list for the sake of haddock
 Added functions:
   withSelectedWindow
   bringSelected (by Clemens Fruhwirth)
   goToSelected (by Dominik Bruhn)
] 
[Initial version of GridSelect.hs with a lot room for improvement/cleanups
Clemens Fruhwirth <clemens at endorphin.org>**20081107115114] 
[documentation: XMonad.Util.Search.hs, add EZConfig keybindings example
sean.escriva at gmail.com**20081106171707] 
[typo
Don Stewart <dons at galois.com>**20081104043044
 Ignore-this: bdac0ff3316c821bce321b51c62f6e89
] 
[place an upper bound on the version of base we support
Don Stewart <dons at galois.com>**20081104035857
 Ignore-this: 29139cc4f0ecb299b56ae99f7d20b854
] 
[explicit import list for things in the process library
Don Stewart <dons at galois.com>**20081104035319
 Ignore-this: 91b7f96421828788760e8bcff7dec317
] 
[Work around ghc 6.10 bug #2738
Don Stewart <dons at galois.com>**20081104034819
 Ignore-this: c75da9693fa642025eac0d074869423d
] 
[windowPromptBringCopy
deadguysfrom at gmail.com**20081023173019] 
[generic menu and window bringer
Travis B. Hartwell <nafai at travishartwell.net>**20081027005523] 
[Search.hs: +hackage search, courtesy of byorgey
gwern0 at gmail.com**20081031214937
 Ignore-this: 24db0ceed49f8bd37ce98ccf8f8ca2ab
] 
[Prompt.hs rename deleteConsecutiveDuplicates
gwern0 at gmail.com**20081008205131
 That name is really unwieldy and long.
] 
[Prompt.hs: have historyCompletion filter dupes
gwern0 at gmail.com**20081008204710
 Specifically, it calls deleteConsecutiveDuplicates on the end product. uniqSort reverses order in an unfortunate way, so we don't use that.
 The use-case is when a user has added the same input many times - as it stands, if the history records 30 'top's or whatever, the completion will show 30 'top' entries! This fixes that.
] 
[Prompt.hs: tweak haddocks
gwern0 at gmail.com**20081008204649] 
[Prompt.hs: mv uniqSort to next to its confreres, and mention the trade-off
gwern0 at gmail.com**20081008192645] 
[Do not consider XMONAD_TIMER unknown
Joachim Breitner <mail at joachim-breitner.de>**20081008195643] 
[Kill window without focusing it first
Joachim Breitner <mail at joachim-breitner.de>**20081005002533
 This patch requires the patch "add killWindow function" in xmonad.
 Before this patch, people would experience “workspace flicker” when closing
 a window via EWMH that is not on the current workspace, for example when
 quitting pidgin via the panel icon.
] 
[let MagnifyLess actually magnify less
daniel at wagner-home.com**20081015153911] 
[Actions.Search: add a few search engines
intrigeri at boum.org**20081008104033
 
 Add Debian {package, bug, tracking system} search engines, as well as Google
 Images and isohunt.
 
] 
[Implement HiddenNonEmptyWS with HiddenWS and NonEmptyWS
Joachim Breitner <mail at joachim-breitner.de>**20081006211027
 (Just to reduce code duplication)
] 
[Add straightforward HiddenWS to WSType
Joachim Breitner <mail at joachim-breitner.de>**20081006210548
 With NonEmptyWS and HiddenNonEmptyWS present, HiddenWS is obviously missing.
] 
[Merge emptyLayoutMod into redoLayout
Joachim Breitner <mail at joachim-breitner.de>**20081005190220
 This removes the emptyLayoutMod method from the LayoutModifier class, and
 change the Stack parameter to redoLayout to a Maybe Stack one. It also changes
 all affected code. This should should be a refactoring without any change in
 program behaviour.
] 
[SmartBorders even for empty layouts
Joachim Breitner <mail at joachim-breitner.de>**20081005184426
 Fixes: http://code.google.com/p/xmonad/issues/detail?id=223
] 
[Paste.hs: improve haddocks
gwern0 at gmail.com**20080927150158] 
[Paste.hs: fix haddock
gwern0 at gmail.com**20080927145238] 
[minor explanatory comment
daniel at wagner-home.com**20081003015919] 
[XMonad.Layout.HintedGrid: add GridRatio (--no-test because of haddock breakage)
Lukas Mai <l.mai at web.de>**20080930141715] 
[XMonad.Util.Font: UTF8 -> USE_UTF8
Lukas Mai <l.mai at web.de>**20080930140056] 
[Paste.hs: implement noModMask suggestion
gwern0 at gmail.com**20080926232056] 
[fix a divide by zero error in Grid
daniel at wagner-home.com**20080926204148] 
[-DUTF8 flag with -DUSE_UTF8
gwern0 at gmail.com**20080921154014] 
[XSelection.hs: use CPP to compile against utf8-string
gwern0 at gmail.com**20080920151615] 
[add XMonad.Config.Azerty
Devin Mullins <me at twifkak.com>**20080924044946] 
[flip GridRatio to match convention (x/y)
Devin Mullins <me at twifkak.com>**20080922033354] 
[let Grid have a configurable aspect ratio goal
daniel at wagner-home.com**20080922010950] 
[Paste.hs: +warning about ASCII limitations
gwern0 at gmail.com**20080921155038] 
[Paste.hs: shorten comment lines to under 80 columns per sjanssen
gwern0 at gmail.com**20080921154950] 
[Forgot to enable historyFilter :(
Spencer Janssen <spencerjanssen at gmail.com>**20080921094254] 
[Prompt: add configurable history filters
Spencer Janssen <spencerjanssen at gmail.com>**20080921093453] 
[Update my config to use 'statusBar'
Spencer Janssen <spencerjanssen at gmail.com>**20080921063513] 
[Rename pasteKey functions to sendKey
Spencer Janssen <spencerjanssen at gmail.com>**20080921062016] 
[DynamicLog: doc fixes
Spencer Janssen <spencerjanssen at gmail.com>**20080921061314] 
[Move XMonad.Util.XPaste to XMonad.Util.Paste
Spencer Janssen <spencerjanssen at gmail.com>**20080921060947] 
[Depend on X11 >= 1.4.3
Spencer Janssen <spencerjanssen at gmail.com>**20080921055456] 
[statusBar now supplies the action to toggle struts
Spencer Janssen <spencerjanssen at gmail.com>**20080918013858] 
[cleanup - use currentTag
Devin Mullins <me at twifkak.com>**20080921011159] 
[XPaste.hs: improve author info
gwern0 at gmail.com**20080920152342] 
[+XMonad.Util.XPaste: a module for pasting strings to windows
gwern0 at gmail.com**20080920152106] 
[UrgencyHook bug fix: cleanupUrgents should clean up reminders, too
Devin Mullins <me at twifkak.com>**20080920062117] 
[Sketch of XMonad.Config.Monad
Spencer Janssen <spencerjanssen at gmail.com>**20080917081838] 
[raiseMaster
seanmce33 at gmail.com**20080912184830] 
[Add missing space between dzen command and flags
Daniel Neri <daniel.neri at sigicom.com>**20080915131009] 
[Big DynamicLog refactor.  Added statusBar, improved compositionality for dzen and xmobar
Spencer Janssen <spencerjanssen at gmail.com>**20080913205931
 Compatibility notes:
     - dzen type change
     - xmobar type change
     - dynamicLogDzen removed
     - dynamicLogXmobar removed
] 
[Take maintainership of XMonad.Prompt
Spencer Janssen <spencerjanssen at gmail.com>**20080911230442] 
[Overhaul Prompt to use a zipper for history navigation.  Fixes issue #216
Spencer Janssen <spencerjanssen at gmail.com>**20080911225940] 
[Use the new completion on tab setting
Spencer Janssen <spencerjanssen at gmail.com>**20080911085940] 
[Only start to show the completion window with more than one match
Joachim Breitner <mail at joachim-breitner.de>**20080908110129] 
[XPrompt: Add showCompletionOnTab option
Joachim Breitner <mail at joachim-breitner.de>**20080908105758
 This patch partially implements
 http://code.google.com/p/xmonad/issues/detail?id=215
 It adds a XPConfig option that, if enabled, hides the completion window
 until the user presses Tab once. Default behaviour is preserved.
 TODO: If Tab causes a unique completion, continue to hide the completion
 window.
] 
[XMonad.Actions.Plane.planeKeys: function to make easier to configure
Marco Túlio Gontijo e Silva <marcot at riseup.net>**20080714153601] 
[XMonad.Actions.Plane: removed unneeded hiding
Marco Túlio Gontijo e Silva <marcot at riseup.net>**20080714152631] 
[Improvements in documentation
Marco Túlio Gontijo e Silva <marcot at riseup.net>**20080709002425] 
[Fix haddock typos in XMonad.Config.{Desktop,Gnome,Kde}
Spencer Janssen <spencerjanssen at gmail.com>**20080911040808] 
[add clearUrgents for your keys
Devin Mullins <me at twifkak.com>**20080909055425] 
[add reminder functionality to UrgencyHook
Devin Mullins <me at twifkak.com>**20080824200548
 I'm considering rewriting remindWhen and suppressWhen as UrgencyHookModifiers, so to speak. Bleh.
] 
[TAG 0.8
Spencer Janssen <spencerjanssen at gmail.com>**20080905195420] 
Patch bundle hash:
3417b9bd1a1cd726a9922e47b9cb96448a63ad84
-------------- next part --------------
Sat Jan 10 23:18:52 CET 2009  Daniel Schoepe <asgaroth_ at gmx.de>
  * More flexible userCode function

New patches:

[More flexible userCode function
Daniel Schoepe <asgaroth_ at gmx.de>**20090110221852] {
hunk ./XMonad/Core.hs 27
     XConf(..), XConfig(..), LayoutClass(..),
     Layout(..), readsLayout, Typeable, Message,
     SomeMessage(..), fromMessage, LayoutMessages(..),
-    runX, catchX, userCode, io, catchIO, doubleFork,
+    runX, catchX, userCode, userCodeDef, io, catchIO, doubleFork,
     withDisplay, withWindowSet, isRoot, runOnWorkspaces,
     getAtom, spawn, getXMonadDir, recompile, trace, whenJust, whenX,
     atom_WM_STATE, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, ManageHook, Query(..), runQuery
hunk ./XMonad/Core.hs 50
 import Graphics.X11.Xlib.Extras (Event)
 import Data.Typeable
 import Data.Monoid
+import Data.Maybe (fromMaybe)
 
 import qualified Data.Map as M
 import qualified Data.Set as S
hunk ./XMonad/Core.hs 167
 
 -- | Execute the argument, catching all exceptions.  Either this function or
 -- 'catchX' should be used at all callsites of user customized code.
-userCode :: X () -> X ()
-userCode a = catchX (a >> return ()) (return ())
+userCode :: X a -> X (Maybe a)
+userCode a = catchX (Just `liftM` a) (return Nothing)
+
+-- | Same as userCode but with a default argument to return instead of using
+-- Maybe, provided for convenience.
+userCodeDef :: a -> X a -> X a
+userCodeDef def a = fromMaybe def `liftM` userCode a
 
 -- ---------------------------------------------------------------------
 -- Convenient wrappers to state
hunk ./XMonad/Main.hsc 179
         s  <- io $ keycodeToKeysym dpy code 0
         mClean <- cleanMask m
         ks <- asks keyActions
-        userCode $ whenJust (M.lookup (mClean, s) ks) id
+        userCodeDef () $ whenJust (M.lookup (mClean, s) ks) id
 
 -- manage a new window
 handle (MapRequestEvent    {ev_window = w}) = withDisplay $ \dpy -> do
hunk ./XMonad/Main.hsc 282
 
 -- property notify
 handle PropertyEvent { ev_event_type = t, ev_atom = a }
-    | t == propertyNotify && a == wM_NAME = userCode =<< asks (logHook . config)
+    | t == propertyNotify && a == wM_NAME = userCodeDef () =<< asks (logHook . config)
 
 handle e = broadcastMessage e -- trace (eventName e) -- ignoring
 
hunk ./XMonad/Operations.hs 26
 import qualified XMonad.StackSet as W
 
 import Data.Maybe
-import Data.Monoid          (appEndo)
+import Data.Monoid          (Endo(..))
 import Data.List            (nub, (\\), find)
 import Data.Bits            ((.|.), (.&.), complement)
 import Data.Ratio
hunk ./XMonad/Operations.hs 71
             where i = W.tag $ W.workspace $ W.current ws
 
     mh <- asks (manageHook . config)
-    g <- fmap appEndo (runQuery mh w) `catchX` return id
+    g <- fmap appEndo $ userCodeDef (Endo id) (runQuery mh w)
     windows (g . f)
 
 -- | unmanage. A window no longer exists, remove it from the window
hunk ./XMonad/Operations.hs 172
 
     isMouseFocused <- asks mouseFocused
     unless isMouseFocused $ clearEvents enterWindowMask
-    asks (logHook . config) >>= userCode
+    asks (logHook . config) >>= userCodeDef ()
 
 -- | Produce the actual rectangle from a screen and a ratio on that screen.
 scaleRationalRect :: Rectangle -> W.RationalRect -> Rectangle
}

Context:

[Call logHook as the very last action in windows
Spencer Janssen <spencerjanssen at gmail.com>**20081209233700
 Ignore-this: 4396ad891b607780f8e4b3b6bbce87e
] 
[Accept inferior crossing events.  This patch enables fmouse-focus-follows-screen
Spencer Janssen <spencerjanssen at gmail.com>**20081205045130
 Ignore-this: 3ac329fb92839827aed0a4370784cabd
] 
[Tile all windows at once
Spencer Janssen <spencerjanssen at gmail.com>**20081118074447] 
[Factor rational rect scaling into a separate function
Spencer Janssen <spencerjanssen at gmail.com>**20081118072849] 
[Change screen focus by clicking on the root window.
Spencer Janssen <spencerjanssen at gmail.com>**20081106224031
 This is a modification of a patch from Joachim Breitner.
] 
[Fix #192.
Spencer Janssen <spencerjanssen at gmail.com>**20081021220059] 
[select base < 4 for building on ghc 6.10
Adam Vogt <vogt.adam at gmail.com>**20081013214509] 
[add killWindow function
Joachim Breitner <mail at joachim-breitner.de>**20081005001804
 This is required to kill anything that is not focused, without
 having to focus it first.
] 
[add'l documentation
Devin Mullins <me at twifkak.com>**20080927234639] 
[Regression: ungrab buttons on *non* root windows
Spencer Janssen <spencerjanssen at gmail.com>**20081007214351] 
[Partial fix for #40
Spencer Janssen <spencerjanssen at gmail.com>**20081007212053
 Improvements:
  - clicking on the root will change focus to that screen
  - moving the mouse from a window on a screen to an empty screen changes focus
    to that screen
 The only remaining issue is that moving the mouse between two empty screens
 does not change focus.  In order to solve this, we'd have to select motion events
 on the root window, which is potentially expensive.
] 
[Track mouse position via events received
Spencer Janssen <spencerjanssen at gmail.com>**20081007203953] 
[Fix haddock
Spencer Janssen <spencerjanssen at gmail.com>**20081007094641] 
[Move screen locating code into pointScreen
Spencer Janssen <spencerjanssen at gmail.com>**20081007094207] 
[Make pointWithin a top-level binding
Spencer Janssen <spencerjanssen at gmail.com>**20081007090229] 
[sp README, CONFIG, STYLE, TODO
gwern0 at gmail.com**20080913024457] 
[Use the same X11 dependency as xmonad-contrib
Spencer Janssen <spencerjanssen at gmail.com>**20080921061508] 
[Export focusUp' and focusDown' -- work entirely on stacks
Spencer Janssen <spencerjanssen at gmail.com>**20080911214803] 
[add W.shiftMaster, fix float/tile-reordering bug
Devin Mullins <me at twifkak.com>**20080911053909] 
[TAG 0.8
Spencer Janssen <spencerjanssen at gmail.com>**20080905195412] 
[Spelling.  Any bets on how long this has been there?
Spencer Janssen <spencerjanssen at gmail.com>**20080905195211] 
[Bump version to 0.8
Spencer Janssen <spencerjanssen at gmail.com>**20080905194225] 
[Remove obsolete comments about darcs X11
Spencer Janssen <spencerjanssen at gmail.com>**20080905194915] 
[Recommend latest packages rather than specific versions
Spencer Janssen <spencerjanssen at gmail.com>**20080905194837] 
[Also remove -optl from the executable section
Spencer Janssen <spencerjanssen at gmail.com>**20080820210023] 
[-optl-Wl,-s is not needed with recent Cabal versions
Spencer Janssen <spencerjanssen at gmail.com>**20080820204102] 
[Haddock links
Malebria <malebria at riseup.net>**20080601212515] 
[Haddock syntax for enumeration
Malebria <malebria at riseup.net>**20080601204951] 
[I prefer the spencerjanssen at gmail.com address now
Spencer Janssen <spencerjanssen at gmail.com>**20080714202650] 
[Raise windows in the floating layer when moving or resizing
Trevor Elliott <trevor at galois.com>**20080521215057] 
[add currentTag convenience function
Devin Mullins <me at twifkak.com>**20080511224258] 
[Make Mirror a newtype
Spencer Janssen <sjanssen at cse.unl.edu>**20080508104640] 
[Comments
Spencer Janssen <sjanssen at cse.unl.edu>**20080507013122] 
[Break long line
Spencer Janssen <sjanssen at cse.unl.edu>**20080507012608] 
[Style
Spencer Janssen <sjanssen at cse.unl.edu>**20080507012519] 
[Simplify
Spencer Janssen <sjanssen at cse.unl.edu>**20080507011309] 
[Overhaul Choose, fixes issue 183
Spencer Janssen <sjanssen at cse.unl.edu>**20080506220809] 
[Remember if focus changes were caused by mouse actions or by key commands
Klaus Weidner <kweidner at pobox.com>**20080502175603
 
 If the user used the mouse to change window focus (moving into or clicking on a
 window), this should be handled differently than focus changes due to keyboard
 commands. Specifically, it's inappropriate to discard window enter/leave events
 while the mouse is moving. This fixes the bug where a fast mouse motion across
 multiple windows resulted in the wrong window keeping focus.
 
 It's also helpful information for contrib modules such as UpdatePointer - it's
 supposed to move the mouse pointer only in response to keyboard actions, not if
 the user was moving the mouse.
] 
[Wibble
Spencer Janssen <sjanssen at cse.unl.edu>**20080506203840] 
[Added doShift function for more user-friendly hooks
Ivan N. Veselov <veselov at gmail.com>**20080506185757] 
[use named colours. fixes startup failure on the XO
Don Stewart <dons at galois.com>**20080502210149] 
[Set focus *after* revealing windows
Spencer Janssen <sjanssen at cse.unl.edu>**20080407222559] 
[Reveal windows after moving/resizing them.
Spencer Janssen <sjanssen at cse.unl.edu>**20080407220756
 This should reduce the number of repaints for newly visible windows.
] 
[Hide newly created but non-visible windows (fixes bug #172)
Spencer Janssen <sjanssen at cse.unl.edu>**20080430014012] 
[formatting, eta expansion
Don Stewart <dons at galois.com>**20080418184337] 
[XMonad.ManageHook: add 'appName', another name for 'resource'
Lukas Mai <l.mai at web.de>**20080406012006] 
[XMonad.ManageHook: make 'title' locale-aware; haddock cleanup
Lukas Mai <l.mai at web.de>**20080406011338
 
 The code for 'title' was stolen from getname.patch (bug #44).
] 
[XMonad.Main: call setlocale on startup
Lukas Mai <l.mai at web.de>**20080406011234] 
[floats always use current screen (with less bugs)
robreim at bobturf.org**20080405135009] 
[XMonad.Operations: applySizeHint reshuffle
Lukas Mai <l.mai at web.de>**20080404215615
 
 Make applySizeHints take window borders into account. Move old functionality
 to applySizeHintsContents. Add new mkAdjust function that generates a custom
 autohinter for a window.
] 
[XMonad.Layout: documentation cleanup
Lukas Mai <l.mai at web.de>**20080404215444] 
[Remove gaps from the example config
Spencer Janssen <sjanssen at cse.unl.edu>**20080329232959] 
[Remove gaps
Spencer Janssen <sjanssen at cse.unl.edu>**20080325091526] 
[TAG 0.7
Spencer Janssen <sjanssen at cse.unl.edu>**20080329210249] 
[Remove -fhpc from ghc-options (annoying hackage workaround)
Spencer Janssen <sjanssen at cse.unl.edu>**20080329205804] 
[Remove version numbers from README
Spencer Janssen <sjanssen at cse.unl.edu>**20080329204158] 
[Bump version to 0.7
Spencer Janssen <sjanssen at cse.unl.edu>**20080329191336] 
[no need to expose --resume to the user
Don Stewart <dons at galois.com>**20080328214219] 
[Rename property to stringProperty
Spencer Janssen <sjanssen at cse.unl.edu>**20080325201814] 
[ManageHook: add a 'property' Query that can get an arbitrary String property from a window (such as WM_WINDOW_ROLE, for example)
Brent Yorgey <byorgey at gmail.com>**20080325145414] 
[Main.hs: startupHook should be guarded by userCode
Brent Yorgey <byorgey at gmail.com>**20080325171241] 
[Also print compilation errors to stderr
Spencer Janssen <sjanssen at cse.unl.edu>**20080324225857] 
[clean up for style
Don Stewart <dons at galois.com>**20080322214116] 
[add sendMessageWithNoRefresh and have broadcastMessage use it
Andrea Rossato <andrea.rossato at unibz.it>**20080223130702
 
 This patch:
 - moves broadcastMessage and restart from Core to Operations (to avoid
   circular imports);
 - in Operations introduces sendMessageWithNoRefresh and move
  updateLayout outside windows.
 - broadcastMessage now uses sendMessageWithNoRefresh to obey to this
   rules:
   1. if handleMessage returns Nothing no action is taken;
   2. if handleMessage returns a Just ml *only* the layout field of the
      workspace record will be updated.
] 
[--recompile now forces recompilation of xmonad.hs
Spencer Janssen <sjanssen at cse.unl.edu>**20080324212453] 
[add --help option
Lukas Mai <l.mai at web.de>**20080129235258] 
[add mod-shift-tab to the default bindings, from Mathias Stearn
Don Stewart <dons at galois.com>**20080323211421] 
[more tests
Don Stewart <dons at galois.com>**20080323003436] 
[some tests for the size increment handling in Operations.hs
Don Stewart <dons at galois.com>**20080322234952] 
[more properties for splitting horizontally and vertically
Don Stewart <dons at galois.com>**20080322201835] 
[test message handling of Full layout
Don Stewart <dons at galois.com>**20080322192728] 
[formatting
Don Stewart <dons at galois.com>**20080322192635] 
[strict fields on layout messages
Don Stewart <dons at galois.com>**20080322192248] 
[QuickCheck properties to fully specify the Tall layout, and its messages
Don Stewart <dons at galois.com>**20080322041801] 
[clean up Layout.hs, not entirely happy about the impure layouts.
Don Stewart <dons at galois.com>**20080322041718] 
[comments
Don Stewart <dons at galois.com>**20080322041654] 
[add hpc generation script
Don Stewart <dons at galois.com>**20080322041640] 
[add QuickCheck property for Full: it produces one window, it is fullscreen, and it is the current window
Don Stewart <dons at galois.com>**20080322002026] 
[QC for pureLayout. confirm pureLayout . Tall produces no overlaps
Don Stewart <dons at galois.com>**20080322001229] 
[whitespace
Don Stewart <dons at galois.com>**20080322001208] 
[reenable quickcheck properties for layouts (no overlap, fullscreen)
Don Stewart <dons at galois.com>**20080321234015] 
[formatting
Don Stewart <dons at galois.com>**20080321230956] 
[Revert float location patch. Not Xinerama safe
Don Stewart <dons at galois.com>**20080321214129] 
[XMonad.Core: ignore SIGPIPE, let write calls throw
Lukas Mai <l.mai at web.de>**20080321171911] 
[update documentation
Brent Yorgey <byorgey at gmail.com>**20080311160727] 
[Reimplement Mirror with runLayout
Andrea Rossato <andrea.rossato at unibz.it>**20080225083236] 
[Reimplement Choose with runLayout
Andrea Rossato <andrea.rossato at unibz.it>**20080222193119] 
[runLayout is now a LayoutClass method and takes the Workspace and the screen Rectangle
Andrea Rossato <andrea.rossato at unibz.it>**20080222175815] 
[add property for ensureTags behaviour on hidden workspaces
Don Stewart <dons at galois.com>**20080310182557] 
[Small linecount fix :)
robreim at bobturf.org**20080308021939] 
[Change floats to always use the current screen
robreim at bobturf.org**20080308015829] 
[use -fhpc by default when testing. All developers should have 6.8.x
Don Stewart <dons at galois.com>**20080307184223] 
[more general properties for view, greedyView
Don Stewart <dons at galois.com>**20080307181657] 
[rework failure cases in StackSet.view
Don Stewart <dons at galois.com>**20080307181634] 
[bit more code coverage
Don Stewart <dons at galois.com>**20080307180905] 
[more tests. slightly better test coverage
Don Stewart <dons at galois.com>**20080227180113] 
[test geometry setting
Don Stewart <dons at galois.com>**20080227175554] 
[incorrect invariant test for greedyView
Don Stewart <dons at galois.com>**20080225180350] 
[Add a startupHook.
Brent Yorgey <byorgey at gmail.com>**20080204192445
 The only thing I am not sure about here is at what exact point the 
 startupHook should get run.  I picked a place that seems to make sense: 
 as late as possible, right before entering the main loop.  That way all
 the layouts/workspaces/other state are set up and the startupHook can
 manipulate them.
] 
[Core.hs: add an Applicative instance for X
Brent Yorgey <byorgey at gmail.com>**20080204192348] 
[update LOC claim in man page
gwern0 at gmail.com**20080215211420] 
[add quickstart instructions
Don Stewart <dons at galois.com>**20080212203502] 
[Remove non-existent windows on restart
Spencer Janssen <sjanssen at cse.unl.edu>**20080207091140] 
[Lift initColor exceptions into Maybe
Don Stewart <dons at galois.com>**20080206194858
 
 We should audit all X11 Haskell lib calls we make for whether
 they throw undocumented exceptions, and then banish that.
 
] 
[some things to do
Don Stewart <dons at galois.com>**20080206192533] 
[module uses CPP
Don Stewart <dons at galois.com>**20080206190521] 
[Rename runManageHook to runQuery
Spencer Janssen <sjanssen at cse.unl.edu>**20080204053336] 
[let enter dismiss compile errors
daniel at wagner-home.com**20080203202852] 
[Core.hs, StackSet.hs: some documentation updates
Brent Yorgey <byorgey at gmail.com>**20080201190653] 
[Make Mirror implement emptyLayout
Andrea Rossato <andrea.rossato at unibz.it>**20080128001834] 
[xmonad.cabal: add `build-type' to make Cabal happy
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20080131163213] 
[Get version from the Paths_xmonad module generated by Cabal
Daniel Neri <daniel.neri at sigicom.se>**20080129144037
 No need to bump version in more than one place.
] 
[Kill stale xmonad 0.1 comments
Spencer Janssen <sjanssen at cse.unl.edu>**20080128211418] 
[Point to 0.6 release of contrib
Spencer Janssen <sjanssen at cse.unl.edu>**20080128101115] 
[notes on releases
Don Stewart <dons at galois.com>**20080128171012] 
[bump output of --version
Don Stewart <dons at galois.com>**20080128170840] 
[Generalize the type of catchIO, use it in Main.hs
Spencer Janssen <sjanssen at cse.unl.edu>**20080128054651] 
[Add emptyLayout to LayoutClass, a method to be called when a workspace is empty
Andrea Rossato <andrea.rossato at unibz.it>**20080124013207] 
[clarify copyright
Don Stewart <dons at galois.com>**20080108185640] 
[TAG 0.6
Spencer Janssen <sjanssen at cse.unl.edu>**20080127220633] 
[More other-modules
Spencer Janssen <sjanssen at cse.unl.edu>**20080127220152] 
[Update example config
Spencer Janssen <sjanssen at cse.unl.edu>**20080127212331] 
[Bump version to 0.6
Spencer Janssen <sjanssen at cse.unl.edu>**20080127205000] 
[Updated ./man/xmonad.1.in to contain new command line parameters
Austin Seipp <mad.one at gmail.com>**20080122070153] 
[Depend on QuickCheck < 2 when building tests
Spencer Janssen <sjanssen at cse.unl.edu>**20080122070225] 
[Roll testing into the main executable, use Cabal to build the tests
Spencer Janssen <sjanssen at cse.unl.edu>**20080119091215] 
[Simplify duplicate/cloned screen logic
Spencer Janssen <sjanssen at cse.unl.edu>**20080118032228] 
[Put the screen removing stuff in getCleanedScreenInfo
Joachim Breitner <mail at joachim-breitner.de>**20071231181556] 
[Ignore cloned screens
Joachim Breitner <mail at joachim-breitner.de>**20071231180628
 This patch ignores screens that are just clones of existing ones,
 or are completely contained in another. Currently only for rescreen, not yet for
 xmonad start.
] 
[-Werror when flag(testing) only
Spencer Janssen <sjanssen at cse.unl.edu>**20080118014827] 
[Export doubleFork
nicolas.pouillard at gmail.com**20080114202612] 
[reword comment (previous version didn't make sense to me)
Lukas Mai <l.mai at web.de>**20071122165925] 
[The recompile function now returns a boolean status instead of ().
nicolas.pouillard at gmail.com**20080105225500] 
[Make focus-follows-mouse configurable
Spencer Janssen <sjanssen at cse.unl.edu>**20071229023301] 
[Strictify all XConfig fields, gives nice error messages when a field is forgotten on construction
Spencer Janssen <sjanssen at cse.unl.edu>**20071229021923] 
[Spelling
Spencer Janssen <sjanssen at cse.unl.edu>**20071229021628] 
[Wibble
Spencer Janssen <sjanssen at cse.unl.edu>**20071229021519] 
[Broadcast button events to all layouts, fix for issue #111
Spencer Janssen <sjanssen at cse.unl.edu>**20071227080356] 
[Config.hs: too many users seem to be ignoring/missing the polite warning not to modify this file; change it to something a bit less polite/more obvious.
Brent Yorgey <byorgey at gmail.com>**20071220201549] 
[Remove desktop manageHook rules in favor of ManageDocks
Spencer Janssen <sjanssen at cse.unl.edu>**20071222113735] 
[Wibble
Spencer Janssen <sjanssen at cse.unl.edu>**20071222041151] 
[Add support for several flags:
Spencer Janssen <sjanssen at cse.unl.edu>**20071222020520
  --version: print xmonad's version
  --recompile: recompile xmonad.hs if it is out of date
  --force-recompile: recompile xmonad.hs unconditionally
] 
[Remove getProgName capability from restart, we don't use it anymore
Spencer Janssen <sjanssen at cse.unl.edu>**20071219215011] 
[Flush pending X calls before restarting
Spencer Janssen <sjanssen at cse.unl.edu>**20071219162029] 
[Allow for sharing of home directory across architectures.
tim.thelion at gmail.com**20071218065146] 
[Call 'broadcastMessage ReleaseResources' in restart
Spencer Janssen <sjanssen at cse.unl.edu>**20071219065710] 
[Manpage now describes config in ~/.xmonad/xmonad.hs
Adam Vogt <vogt.adam at gmail.com>**20071219023918] 
[Update manpage to describe greedyView
Adam Vogt <vogt.adam at gmail.com>**20071219023726] 
[Depend on X11-1.4.1, it has crucial bugfixes
Spencer Janssen <sjanssen at cse.unl.edu>**20071215022100] 
[1.4.1 X11 dep
Don Stewart <dons at galois.com>**20071214160558] 
[Set withdrawnState after calling hide
Spencer Janssen <sjanssen at cse.unl.edu>**20071212060250] 
[Remove stale comment
Spencer Janssen <sjanssen at cse.unl.edu>**20071211084236] 
[Make windows responsible for setting withdrawn state
Spencer Janssen <sjanssen at cse.unl.edu>**20071211080117] 
[Remove stale comment
Spencer Janssen <sjanssen at cse.unl.edu>**20071211075641] 
[Clean up stale mapped/waitingUnmap state in handle rather than unmanage.
Spencer Janssen <sjanssen at cse.unl.edu>**20071211074810
 This is an attempt to fix issue #96.  Thanks to jcreigh for the insights
 necessary to fix the bug.
] 
[Delete windows from waitingUnmap that aren't waitng for any unmaps
Spencer Janssen <sjanssen at cse.unl.edu>**20071211074506] 
[man/xmonad.hs: add some documentation explaining that 'title' can be used in the manageHook just like 'resource' and 'className'.
Brent Yorgey <byorgey at gmail.com>**20071210173357] 
[normalize Module headers
Lukas Mai <l.mai at web.de>**20071210085327] 
[Add 'testing' mode, this should reduce 'darcs check' time significantly
Spencer Janssen <sjanssen at cse.unl.edu>**20071210004704] 
[Use XMonad meta-module in Main.hs
Spencer Janssen <sjanssen at cse.unl.edu>**20071210004456] 
[TAG 0.5
Spencer Janssen <sjanssen at cse.unl.edu>**20071209233044] 
[Remove references to 0.4
Spencer Janssen <sjanssen at cse.unl.edu>**20071209232336] 
[Bump version to 0.5!
Spencer Janssen <sjanssen at cse.unl.edu>**20071209231539] 
[Rename xmonad.hs to xmonad-template.hs
Spencer Janssen <sjanssen at cse.unl.edu>**20071209231426] 
[StackSet: some haddock tuning
Andrea Rossato <andrea.rossato at unibz.it>**20071209161525] 
[add a template xmonad.hs
Don Stewart <dons at galois.com>**20071209225018] 
[Remove kicker and gnome-panel from the default manageHook, these are better
Spencer Janssen <sjanssen at cse.unl.edu>**20071209135408
 handled by XMonad.Hooks.ManageDocks.  Also, remove the over-complicated list
 comprehensions.
] 
[XMonad.Layouts -> XMonad.Layout
Spencer Janssen <sjanssen at cse.unl.edu>**20071208080553] 
[Typos and formatting
Andrea Rossato <andrea.rossato at unibz.it>**20071124143221] 
[Move XMonad.Layouts to XMonad.Layout for uniformity with xmc
Andrea Rossato <andrea.rossato at unibz.it>**20071124143000] 
[Hide generalized newtype deriving from Haddock
Spencer Janssen <sjanssen at cse.unl.edu>**20071208015015] 
[Export XMonad.Layouts from XMonad
Spencer Janssen <sjanssen at cse.unl.edu>**20071208014927] 
[Export XMonad.Operations from XMonad
Spencer Janssen <sjanssen at cse.unl.edu>**20071208000636] 
[Export Graphics.X11, Graphics.X11.Xlib.Extras, and various Monad stuff from XMonad
Spencer Janssen <sjanssen at cse.unl.edu>**20071207233535] 
[Depend on X11>=1.4.0
Spencer Janssen <sjanssen at cse.unl.edu>**20071205045945] 
[Update extra-source-files
Spencer Janssen <sjanssen at cse.unl.edu>**20071205044421] 
[Update man location
Spencer Janssen <sjanssen at cse.unl.edu>**20071205043913] 
[make Query a MonadIO
Lukas Mai <l.mai at web.de>**20071128195126] 
[Add ManageHook to the XMonad metamodule
Spencer Janssen <sjanssen at cse.unl.edu>**20071127002840] 
[update todos before release
Don Stewart <dons at galois.com>**20071125052720] 
[Depend on X11 1.4.0
Don Stewart <dons at galois.com>**20071125034012] 
[add getXMonadDir (2nd try)
Lukas Mai <l.mai at web.de>**20071121183018] 
[Add 'and' and 'or' functions to ManageHook.
Spencer Janssen <sjanssen at cse.unl.edu>**20071121104613] 
[generalise type of `io'
Don Stewart <dons at galois.com>**20071121054407] 
[Add recompilation forcing, clean up recompile's documentation
Spencer Janssen <sjanssen at cse.unl.edu>**20071120223614] 
[recompile does not raise any exceptions
Spencer Janssen <sjanssen at cse.unl.edu>**20071120215835] 
[-no-recomp because we're doing our own recompilation checking
Spencer Janssen <sjanssen at cse.unl.edu>**20071120215744] 
[pointfree
Don Stewart <dons at galois.com>**20071120184016] 
[clean up fmap overuse with applicatives. more opportunities remain
Don Stewart <dons at galois.com>**20071120181743] 
[ManageHook is a Monoid
Spencer Janssen <sjanssen at cse.unl.edu>**20071119060820] 
[No more liftM
Spencer Janssen <sjanssen at cse.unl.edu>**20071119033120] 
[Refactor recompile
Spencer Janssen <sjanssen at cse.unl.edu>**20071119032255] 
[Trailing space
Spencer Janssen <sjanssen at cse.unl.edu>**20071119030658] 
[Generalize recompile to MonadIO
Spencer Janssen <sjanssen at cse.unl.edu>**20071119030436] 
[Factor out doubleFork logic
Spencer Janssen <sjanssen at cse.unl.edu>**20071119030353] 
[handle case of xmonad binary not existing, when checking recompilation
Don Stewart <dons at galois.com>**20071119030057] 
[Use executeFile directly, rather than the shell, avoiding sh interepeting
Don Stewart <dons at galois.com>**20071119025015] 
[use 'spawn' rather than runProcess, to report errors asynchronously, avoiding zombies
Don Stewart <dons at galois.com>*-20071119023712] 
[use 'spawn' rather than runProcess, to report errors asynchronously, avoiding zombies
Don Stewart <dons at galois.com>**20071119023712] 
[Use xmessage to present a failure message to users when the config file cannot be loaded
Don Stewart <dons at galois.com>**20071119022429] 
[only check xmonad.hs against the xmonad binary, not the .o file (meaning you can remove it if you like)
Don Stewart <dons at galois.com>**20071119011528] 
[Do our own recompilation checking: only launch ghc if the xmonad.hs is newer than its .o file
Don Stewart <dons at galois.com>**20071119010759] 
[reformat export list to fit on the page
Don Stewart <dons at galois.com>**20071119003900] 
[add support for Mac users and their silly case-insensitive filesystems
Devin Mullins <me at twifkak.com>**20071117024836] 
[some more tweaks
Don Stewart <dons at galois.com>**20071116184227] 
[more todos: docs
Don Stewart <dons at galois.com>**20071116182444] 
[we need examples for the managehook edsl
Don Stewart <dons at galois.com>**20071116182332] 
[more todos
Don Stewart <dons at galois.com>**20071116182033] 
[polish readme
Don Stewart <dons at galois.com>**20071116181931] 
[more polish for config doc
Don Stewart <dons at galois.com>**20071116181640] 
[tweak .cabal synopsis a little
Don Stewart <dons at galois.com>**20071116181245] 
[Config: small haddock fix
Andrea Rossato <andrea.rossato at unibz.it>**20071116113158] 
[Core: documented XConfig and ScreenDetail
Andrea Rossato <andrea.rossato at unibz.it>**20071116112826] 
[CONFIG, TODO: fix typos
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071115144151
 CONFIG: delete trailing whitespace
] 
[make default ratios in config nicer to look at
Lukas Mai <l.mai at web.de>**20071112013551] 
[refactor main, add "recompile" to XMonad.Core
Lukas Mai <l.mai at web.de>**20071108230933] 
[comments, reexport Data.Bits
Don Stewart <dons at galois.com>**20071114183759] 
[polish .cabal file. add xmonad@ as the default maintainer
Don Stewart <dons at galois.com>**20071114182716] 
[add lots more text on configuration
Don Stewart <dons at galois.com>**20071114182531] 
[refactor trace. 
Don Stewart <dons at galois.com>**20071114034109] 
[clarify comment at top of Config.hs
Devin Mullins <me at twifkak.com>**20071111191304
 There appears to be some confusion -- several people have wanted to edit
 Config.hs as was done in the past. This comment probably won't stop that, but
 it's a start.
] 
[avoid Data.Ratio and % operator in XMonad.Config
David Roundy <droundy at darcs.net>**20071111183708
 I think this'll make Config.hs more friendly as a template for folks
 to modify.
] 
[remove obviated (and confusing) comments
Devin Mullins <me at twifkak.com>**20071111055047] 
[XMonad.Main uses FlexibleContexts
Spencer Janssen <sjanssen at cse.unl.edu>**20071111214528] 
[hide existential Layout (mostly) from user API.
David Roundy <droundy at darcs.net>**20071111003055] 
[Depend on X11 1.3.0.20071111
Don Stewart <dons at galois.com>**20071111200932] 
[update README some more
Don Stewart <dons at galois.com>**20071109181203] 
[we depend on Cabal 1.2.0 or newer
Don Stewart <dons at galois.com>**20071109155934] 
[Generalize several functions to MonadIO
Spencer Janssen <sjanssen at cse.unl.edu>**20071109064214] 
[Docs for ManageHook
Spencer Janssen <sjanssen at cse.unl.edu>**20071109031810] 
[New ManageHook system
Spencer Janssen <sjanssen at cse.unl.edu>**20071109024722] 
[Generalize the type of whenJust
Spencer Janssen <sjanssen at cse.unl.edu>**20071107062126] 
[maybe False (const True) -> isJust. spotted by shachaf
Don Stewart <dons at galois.com>**20071108003539] 
[typo
Don Stewart <dons at galois.com>**20071108000259] 
[imports not needed in example now
Don Stewart <dons at galois.com>**20071107032346] 
[Provide top level XMonad.hs export module
Don Stewart <dons at galois.com>**20071107030617] 
[point to where defns for config stuff can be found
Don Stewart <dons at galois.com>**20071107020801] 
[Fix haddock comment
Spencer Janssen <sjanssen at cse.unl.edu>**20071107030510] 
[fall back to previous ~/.xmonad/xmonad if recompilation fails
Lukas Mai <l.mai at web.de>**20071107015309] 
[recommend --user
Don Stewart <dons at galois.com>**20071106221004] 
[add CONFIG with details of how to configure
Don Stewart <dons at galois.com>**20071105040741] 
[Run only 50 tests per property, decreases test time by 10 seconds on my system
Spencer Janssen <sjanssen at cse.unl.edu>**20071105064944] 
[Remove stale comment
Spencer Janssen <sjanssen at cse.unl.edu>**20071105063731] 
[Use Cabal's optimization flags rather than -O
Spencer Janssen <sjanssen at cse.unl.edu>**20071105061759] 
[Build the whole thing in the test hook
Spencer Janssen <sjanssen at cse.unl.edu>**20071105061615] 
[-Werror
Spencer Janssen <sjanssen at cse.unl.edu>**20071105060326] 
[Remove superfluous 'extensions:' field
Spencer Janssen <sjanssen at cse.unl.edu>**20071105034515] 
[Use configurations in xmonad.cabal
Spencer Janssen <sjanssen at cse.unl.edu>**20071105033428] 
[~/.xmonad/Main.hs is now ~/.xmonad/xmonad.hs !
Don Stewart <dons at galois.com>**20071105032655] 
[makeMain -> xmonad
Don Stewart <dons at galois.com>**20071105031203] 
[-Wall police
Don Stewart <dons at galois.com>**20071105022202] 
[remember to compile the xmonad library also with the usual ghc-optoins
Don Stewart <dons at galois.com>**20071105022127] 
[EventLoop -> Core, DefaultConfig -> Config
Don Stewart <dons at galois.com>**20071105021705] 
[clean up DefaultConfig.hs
Don Stewart <dons at galois.com>**20071105021142] 
[clean up some weird formatting/overboard strictness annotations
Don Stewart <dons at galois.com>**20071105011400] 
[Update pragmas for GHC 6.8 compatibility
Spencer Janssen <sjanssen at cse.unl.edu>**20071104215507] 
[Use the layout and workspaces values from the actual configuration used
Spencer Janssen <sjanssen at cse.unl.edu>**20071104020320] 
[Float handler out of makeMain, make keys and mouseBindings dependent on XConfig for easy modMask switching
Spencer Janssen <sjanssen at cse.unl.edu>**20071102025924] 
[We can't rely on the executable name, because it may be 'Main'
Spencer Janssen <sjanssen at cse.unl.edu>**20071101205057] 
[Get defaultGaps from the current config, not the default one
Spencer Janssen <sjanssen at cse.unl.edu>**20071101205025] 
[exposed-modules
Spencer Janssen <sjanssen at cse.unl.edu>**20071101193331] 
[Hierarchify
Spencer Janssen <sjanssen at cse.unl.edu>**20071101180846] 
[Main.hs -> DefaultConfig.hs, add new Main.hs with 'buildLaunch'
Spencer Janssen <sjanssen at cse.unl.edu>**20071101175749] 
[Layouts.Choose: handle ReleaseResources
Spencer Janssen <sjanssen at cse.unl.edu>**20071101152302] 
[Layouts.Choose: send Hide to non-selected layout
Spencer Janssen <sjanssen at cse.unl.edu>**20071101151147] 
[Export mirrorRect
Spencer Janssen <sjanssen at cse.unl.edu>**20071101085631] 
[Only export main from Main
Spencer Janssen <sjanssen at cse.unl.edu>**20071101082326] 
[Add readsLayout, remove the existential from XConfig
Spencer Janssen <sjanssen at cse.unl.edu>**20071101082155] 
[Delete Main.hs-boot!
Spencer Janssen <sjanssen at cse.unl.edu>**20071101080045] 
[Remove manageHook from Main.hs-boot
Spencer Janssen <sjanssen at cse.unl.edu>**20071101075308] 
[Remove workspaces from Main.hs-boot
Spencer Janssen <sjanssen at cse.unl.edu>**20071101074556] 
[-Wall police
Spencer Janssen <sjanssen at cse.unl.edu>**20071101074411] 
[Eliminate defaultTerminal
Spencer Janssen <sjanssen at cse.unl.edu>**20071101073147] 
[Store user configuration in XConf
Spencer Janssen <sjanssen at cse.unl.edu>**20071101072308] 
[This is a massive update, here's what has changed:
Spencer Janssen <sjanssen at cse.unl.edu>**20071101064318
  * Read is no longer a superclass of Layout
  * All of the core layouts have moved to the new Layouts.hs module
  * Select has been replaced by the new statically typed Choose combinator,
    which is heavily based on David Roundy's NewSelect proposal for
    XMonadContrib.  Consequently:
     - Rather than a list of choosable layouts, we use the ||| combinator to
       combine several layouts into a single switchable layout
     - We've lost the capability to JumpToLayout and PrevLayout.  Both can be
       added with some effort
] 
[cleaner version of main/config inversion.
David Roundy <droundy at darcs.net>**20071029184823] 
[make setLayout a bit more inclusive.
David Roundy <droundy at darcs.net>**20071024231250] 
[make xmonad work with inverted main/config.
David Roundy <droundy at darcs.net>**20071018170058] 
[sketch of config/main inversion.
David Roundy <droundy at darcs.net>**20071018164230] 
[more precise X11 version required
Don Stewart <dons at galois.com>**20071031203241] 
[tweaks to todo
Don Stewart <dons at galois.com>**20071031164618] 
[HEADS UP: remove X11-extras dependency, depend on X11 >= 1.3.0
Don Stewart <dons at galois.com>**20071030220824
 
 The X11-extras library has been merged into the larger X11 library,
 so we now drop the dependency on X11-extras, and instead build 
 against the new X11 library.
 
 If you apply this patch you must build and install X11-1.3.0 or greater
 first,
 
   http://hackage.haskell.org/cgi-bin/hackage-scripts/package/X11-1.3.0
 
 You can also go ahead and wipe X11-extras from GHC's memory, (for ghci to work
 out of the box with the testsuite)
 
   $ ghc-pkg unregister X11-extras
   $ ghc-pkg unregister --user X11-extras
 
] 
[New windows start in the iconic state
Spencer Janssen <sjanssen at cse.unl.edu>**20071028063949] 
[add text on using xprop to find client names
Don Stewart <dons at galois.com>**20071027163031] 
[add text reminding people to run mod-shift-space
Don Stewart <dons at galois.com>**20071026225228] 
[StackSet.hs: (insertUp): remove comments about new window being made master window, since that clearly isn't true.
Brent Yorgey <byorgey at gmail.com>**20071022210856] 
[Replace 'findIndex' with 'findTag', which more accurately describes what the function does.
Brent Yorgey <byorgey at gmail.com>**20071022204105
 I realize this is a big change, but the name 'findIndex' was confusing for me, since I expected it to return some sort of integer.  What it actually does, of course, is return a workspace tag, which might be more general than an index.
 Of course, this change breaks several contrib modules; I'll submit a patch to make the change there as well.
] 
[StackSet.hs: (ensureTags): elaborate into a more descriptive comment.
Brent Yorgey <byorgey at gmail.com>**20071022202212] 
[StackSet.hs: remove dead code.
Brent Yorgey <byorgey at gmail.com>**20071022192636] 
[StackSet.hs: (differentiate): 'Texture' doesn't mean anything to me; replace with a more descriptive comment.
Brent Yorgey <byorgey at gmail.com>**20071022191333] 
[StackSet.hs: (new): better comment; 'm' is not an integer, it is a list of screen descriptions.
Brent Yorgey <byorgey at gmail.com>**20071022183411] 
[StackSet.hs: align some comments
Brent Yorgey <byorgey at gmail.com>**20071022161601] 
[StackSet.hs: small grammar fix and better flow in comment
Brent Yorgey <byorgey at gmail.com>**20071022160858] 
[StackSet.hs: better comments regarding hidden/visible workspace tracking for Xinerama
Brent Yorgey <byorgey at gmail.com>**20071022160239
 I'm not 100% sure that I understand what's going on here, but it seems as though the comment still described an older state of affairs.  I don't see any Map Workspace Screen keeping track of visible workspaces.
] 
[Add Config.terminal
Spencer Janssen <sjanssen at cse.unl.edu>**20071024105354] 
[explain that you need ghc as well
Don Stewart <dons at galois.com>**20071024030520] 
[xmonad, not XMonad
Spencer Janssen <sjanssen at cse.unl.edu>**20071023234900] 
[STYLE: enlarge on existing principles
gwern0 at gmail.com**20071023225225
 Comments: the -Wall thing was just trying to say -Wall -Werror should work. The license thing was too narrow - or are my public domain contributions unwelcome because they are not BSD-3? I think comments are most important for exported functions users will use; it isn't so important for helper functions (used only in the module) to be very well-documented, right?
] 
[start on style guide
Don Stewart <dons at galois.com>**20071023221422] 
[Operations.hs: flip maybe id  is  fromMaybe
Eric Mertens <emertens at galois.com>**20071018231418] 
[Deobfuscate Tall layout
Eric Mertens <emertens at galois.com>**20071018231329] 
[setInitialProperties after placing windows
Spencer Janssen <sjanssen at cse.unl.edu>*-20071019201310] 
[setInitialProperties after placing windows
Spencer Janssen <sjanssen at cse.unl.edu>**20071019201310] 
[Ignore borders in the stored RationalRects of floating windows.
Spencer Janssen <sjanssen at cse.unl.edu>*-20071019063922
 Also, add 'floatWindow' which computes the actual Rectangle for that window,
 including border.
] 
[Only assign workspace keys up to xK_9.  Related to bug #63
Spencer Janssen <sjanssen at cse.unl.edu>**20071019083746] 
[Ignore borders in the stored RationalRects of floating windows.
Spencer Janssen <sjanssen at cse.unl.edu>**20071019063922
 Also, add 'floatWindow' which computes the actual Rectangle for that window,
 including border.
] 
[I prefer fmap over liftM
Spencer Janssen <sjanssen at cse.unl.edu>**20071019063104] 
[change 0/1/3 to named states, per X11-extras darcs head
Devin Mullins <me at twifkak.com>**20071018021651] 
[remove StackOrNot type synonymn.
David Roundy <droundy at darcs.net>**20071017201406] 
[Operations.hs: make use of notElem and notMember
Eric Mertens <emertens at galois.com>**20071017174357] 
[TAG 0.4
Spencer Janssen <sjanssen at cse.unl.edu>**20071016215343] 
[Bump XMonadContrib version
Spencer Janssen <sjanssen at cse.unl.edu>**20071016215244] 
[Bump X11, X11-extras versions in the README
Spencer Janssen <sjanssen at cse.unl.edu>**20071016212636] 
[reformat comments
l.mai at web.de**20071016162920] 
[Whitespace fixes for Properties.hs
Spencer Janssen <sjanssen at cse.unl.edu>**20071015022757] 
[Clean up trailing whitespace
Spencer Janssen <sjanssen at cse.unl.edu>**20071015022322] 
[explain numlockMask
Devin Mullins <me at twifkak.com>**20071014005525] 
[whitespace cleanup in Config.hs
Devin Mullins <me at twifkak.com>**20071014005342] 
[bump the version tag to 0.4, we're almost there
Don Stewart <dons at galois.com>**20071013232758] 
[document, and use better names, for serialising/existential-dispatch framework
Don Stewart <dons at galois.com>**20071013232150] 
[typo in comment
Don Stewart <dons at galois.com>**20071013230828] 
[more todos
Don Stewart <dons at galois.com>**20071013225200] 
[done
Don Stewart <dons at galois.com>**20071013223536] 
[release tasks
Don Stewart <dons at galois.com>**20071013223347] 
[some more layout clean ups
Don Stewart <dons at galois.com>**20071013222317] 
[clean up Layout code a little more
Don Stewart <dons at galois.com>**20071013221024] 
[restore magic markup comments
Don Stewart <dons at galois.com>**20071013212351] 
[defer to sjanssen's manageHook comment
Don Stewart <dons at galois.com>**20071013210346] 
[Heads up: rework the Config.hs file comments, and some variable names. Please manually resync your Config.hs if you're tracking the darcs branch
Don Stewart <dons at galois.com>**20071013210149] 
[clean up names of layout code
Don Stewart <dons at galois.com>**20071013204300] 
[Another manageHook example
Spencer Janssen <sjanssen at cse.unl.edu>**20071013205605] 
[Better comment for the default manageHook
Spencer Janssen <sjanssen at cse.unl.edu>**20071013203340] 
[add can't happen case to silence incomplete patterns in StackSet.hs
Don Stewart <dons at galois.com>**20071013185525] 
[Bump X11-extras dependency
Spencer Janssen <sjanssen at cse.unl.edu>**20071012203721] 
[Respect ExitExceptions, fixes a regression where exitWith had no effect
Spencer Janssen <sjanssen at cse.unl.edu>**20071012152801] 
[Make runX return XState
Spencer Janssen <sjanssen at cse.unl.edu>**20071012151524] 
[fix potential hole in userCode.
David Roundy <droundy at darcs.net>**20071012150253
 This makes userCode catch errors even when the
 user does something like (return undefined).
] 
[Haddox fix
Andrea Rossato <andrea.rossato at unibz.it>**20071012100551] 
[Add userCode function for the popular m `catchX` return ()
Spencer Janssen <sjanssen at cse.unl.edu>**20071012014217] 
[catch exceptions when calling user-written code.
David Roundy <droundy at darcs.net>**20071012013305
 This is a minimal approach that only catches error
 in actual user-written code.
] 
[use the right catch in catchX.
David Roundy <droundy at darcs.net>**20071012011450
 Don't ask *me* why the prelude includes a version of
 catch that is worse than useless (because it lulls you
 into a feeling of safety).
] 
[fix one last bug w.r.t. issue 55.
David Roundy <droundy at darcs.net>**20071012010509] 
[more comments
Don Stewart <dons at galois.com>**20071006154351] 
[one more comment.
David Roundy <droundy at darcs.net>**20071011154423] 
[add comments in XMonad.
David Roundy <droundy at darcs.net>**20071011152942
 This change also removes readLayout as a top level function,
 since it's only used once.
] 
[Nuke old TODOs, add a documentation TODO
Spencer Janssen <sjanssen at cse.unl.edu>**20071011022127] 
[Set the border color of new windows, nice catch by mauke
Spencer Janssen <sjanssen at cse.unl.edu>**20071011021627] 
[Bump required X11-extras version to 0.3.1
Spencer Janssen <sjanssen at cse.unl.edu>**20071010165705] 
[Only adjust floating windows that are actually larger than the screen
Spencer Janssen <sjanssen at cse.unl.edu>**20071010062604
 Also, fix a typo caught by Xiao-Yong Jin on the mailing list.
] 
[Add LANGUAGE pragmas
Shachaf Ben-Kiki <shachaf at gmail.com>**20071008021107
 It seems that GHC 6.6 just enables -fglasgow-exts when it sees any LANGUAGE
 pragma, so not all of them were added; this patch adds the rest of them, which
 is necessary for xmonad to compile in GHC >=6.7.
] 
[The empty line isntcomment.
Ferenc Wagner <wferi at niif.hu>**20071006191231
 There is a separate filter for that case.
] 
[Add event handler for PropertyNotifyEvent that calls logHook if window title changed
Christian Thiemann <mail at christian-thiemann.de>**20071006175458] 
[Moving to code.haskell.org
Spencer Janssen <sjanssen at cse.unl.edu>**20071006191843] 
[comments need to be given for all top level bindings
Don Stewart <dons at galois.com>**20071006154127] 
[a bunch of things in XMonad.hs are missing top level comments!
Don Stewart <dons at galois.com>**20071006153608] 
[add mapWorkspace tests
Devin Mullins <me at twifkak.com>**20071006073129
 (just completely duplicated the two mapLayout tests :)
] 
[change email
Don Stewart <dons at galois.com>**20071006104901] 
[style on layout class code
Don Stewart <dons at galois.com>**20071006104606] 
[avoid name class with forever in 6.8
Don Stewart <dons at galois.com>**20071006103530] 
[add pureMessage.
David Roundy <droundy at darcs.net>**20071005140553] 
[polish some syntax
Don Stewart <dons at galois.com>**20071006102918] 
[oops, need to export
Devin Mullins <me at twifkak.com>**20071006055059] 
[darcs setpref test
Devin Mullins <me at twifkak.com>**20071006054333
 Fix, per that Main extraction I made the other day.
] 
[(cleanup) extract mapWorkspace out of renameTag
Devin Mullins <me at twifkak.com>**20071006054104] 
[comment out type error'd property
Don Stewart <dons at galois.com>**20071006102225] 
[add floating property
Don Stewart <dons at galois.com>**20071006100654] 
[mention C headers
Don Stewart <dons at galois.com>**20071006094006] 
[Comment only
Spencer Janssen <sjanssen at cse.unl.edu>**20071005034445] 
[Move grabButtons/Keys into X
Spencer Janssen <sjanssen at cse.unl.edu>**20071005034102] 
[Make WindowSet serialization robust to layout changes
Spencer Janssen <sjanssen at cse.unl.edu>**20071005000031] 
[Add mapLayout
Spencer Janssen <sjanssen at cse.unl.edu>**20071004234537] 
[extract Properties module for re-use by contrib tests
Devin Mullins <me at twifkak.com>**20071004075852
 I want to reuse Properties' Arbitrary instance (as well as the T and
 NonNegative types) in an upcoming set of SwapWorkspaces QC props.
 `module Main where import Main` doesn't work too well. :)
 
 If this patch is accepted, the darcs 'test' pref should be modified to
 "-itests tests/Main.hs".
] 
[Remove commented code
Spencer Janssen <sjanssen at cse.unl.edu>**20071004200200] 
[manageHook: use the curry style, better documentation
Spencer Janssen <sjanssen at cse.unl.edu>**20071003162404] 
[Pointfree
Spencer Janssen <sjanssen at cse.unl.edu>**20071003161643] 
[Remove unused import
Spencer Janssen <sjanssen at cse.unl.edu>**20071003161621] 
[Float Gimp too
Spencer Janssen <sjanssen at cse.unl.edu>**20071003161305] 
[List possibleLayouts last, because users are less likely to modify it
Spencer Janssen <sjanssen at cse.unl.edu>**20071002214708] 
[Docs for defaultLayout and defaultLayouts
Spencer Janssen <sjanssen at cse.unl.edu>**20071002214517] 
[clean up Config a bit.
David Roundy <droundy at darcs.net>**20071002203636] 
[some renaming of classes and data types.
David Roundy <droundy at darcs.net>**20070929191320] 
[Don't manage kdesktop either
Spencer Janssen <sjanssen at cse.unl.edu>**20071002182455] 
[Refactor, ignore desktop_window too
Spencer Janssen <sjanssen at cse.unl.edu>**20071002175258] 
[Automatically float MPlayer windows
Spencer Janssen <sjanssen at cse.unl.edu>**20071002174722] 
[Add rules for gnome-panel and kicker
Spencer Janssen <sjanssen at cse.unl.edu>**20071002174243] 
[Pass window name and class info to manageHook
Spencer Janssen <sjanssen at cse.unl.edu>**20071002174024] 
[Send ClassHints to manageHook
Spencer Janssen <sjanssen at cse.unl.edu>**20071001175246] 
[Operations.windows is responsible for setting initial properties, remove redundant code from Main
Spencer Janssen <sjanssen at cse.unl.edu>**20071001170628] 
[First cut at manageHook
Spencer Janssen <sjanssen at cse.unl.edu>**20071001164627] 
[Add StackSet.allWindows
Spencer Janssen <sjanssen at cse.unl.edu>**20071001163959] 
[set border color more judiciously, so layouts can customize this.
David Roundy <droundy at darcs.net>**20070928235346] 
[deeper test for differentiate. back to 100% coverage
Don Stewart <dons at galois.com>**20070930075018] 
[properties for tag renaming
Don Stewart <dons at galois.com>**20070930074641] 
[test lookupWorkspace more deeply
Don Stewart <dons at galois.com>**20070930073822] 
[On change of keyboard mapping, grabKeys from the root window.
Aaron Denney <wnoise at ofb.net>**20070929224755] 
[Operation: coding style conformance
Andrea Rossato <andrea.rossato at unibz.it>**20070928112744] 
[StackSet uses PatternGuards
Spencer Janssen <sjanssen at cse.unl.edu>**20070928182510] 
[define defaultLayout in Config.hs.
David Roundy <droundy at darcs.net>**20070928020208] 
[merge, update test hook
Don Stewart <dons at galois.com>**20070929142041] 
[100% coverage of alternative branches
Don Stewart <dons at galois.com>**20070928235745] 
[add some more properties for failure cases
Don Stewart <dons at galois.com>**20070928233230] 
[polish
Don Stewart <dons at galois.com>**20070928232839] 
[comments and formatting only
Don Stewart <dons at galois.com>**20070928220523] 
[Use LANGUAGE pragmas over -fglasgow-exts
Spencer Janssen <sjanssen at cse.unl.edu>**20070928181438] 
[merge old workspace tags with new on restart.
David Roundy <droundy at darcs.net>**20070926183309] 
[SomeLayout: use the description of the wrapped layout
Spencer Janssen <sjanssen at cse.unl.edu>**20070928052344] 
[LayoutSelection: describe the active layout only
Spencer Janssen <sjanssen at cse.unl.edu>**20070928051858] 
[put transients completely on the screen when possible.
David Roundy <droundy at darcs.net>**20070927211014] 
[setLayout should not call sendMessage, because sendMessage calls windows
Spencer Janssen <sjanssen at cse.unl.edu>**20070928011510] 
[Add setLayout to the core
Spencer Janssen <sjanssen at cse.unl.edu>**20070928002241] 
[Document otherPossibleLayouts
Spencer Janssen <sjanssen at cse.unl.edu>**20070928000250] 
[Minor formatting
Spencer Janssen <sjanssen at cse.unl.edu>**20070928000025] 
[otherPossibleLayouts is empty by default
Spencer Janssen <sjanssen at cse.unl.edu>**20070927235845] 
[Update kind changes in the -class branch
Spencer Janssen <sjanssen at cse.unl.edu>**20070927222730] 
[Refactor floating code in manage
Spencer Janssen <sjanssen at cse.unl.edu>**20070927195534] 
[fix bug where ReleaseResources wasn't getting sent to all layouts.
David Roundy <droundy at darcs.net>**20070925215816] 
[Simplify readLayout, comment on surprising behavior
Spencer Janssen <sjanssen at cse.unl.edu>**20070925211708] 
[fix bug in reading of SomeLayouts.
David Roundy <droundy at darcs.net>**20070925202801] 
[add support for parseable layouts not in the default.
David Roundy <droundy at darcs.net>**20070925174134] 
[rename modifyLayout to handleMessage.
David Roundy <droundy at darcs.net>**20070925182906] 
[make it easier to define pure layouts.
David Roundy <droundy at darcs.net>**20070925170503] 
[Make a String description part of each Layout.
David Roundy <droundy at darcs.net>**20070924185753] 
[broadcast a ReleaseResources before restarting
Andrea Rossato <andrea.rossato at unibz.it>**20070924193915] 
[Added LayoutMessages
Andrea Rossato <andrea.rossato at unibz.it>**20070924193513
 This patch adds some more messages to manage layout: Hide is sent to
 layouts in that are not visible anymore. ReleaseReasourses is sent
 before a restart.
] 
[update screens for new kind of StackSet.
David Roundy <droundy at darcs.net>**20070924134545] 
[create default modifyLayout that ignores messages.
David Roundy <droundy at darcs.net>**20070923115219] 
[add layout selection back into core xmonad using LayoutSelection.
David Roundy <droundy at darcs.net>**20070921212159
 This is just a reimplementation of LayoutChoice.
] 
[make layouts preserved over restart
David Roundy <droundy at darcs.net>**20070921204316] 
[move Layout into StackSet.
David Roundy <droundy at darcs.net>**20070920221248
 WARNING! This changes the format of StackSet, and
 will definitely mess up your xmonad state, requiring
 at minimum a restart!
] 
[add (unused) Layout to StackSet.
David Roundy <droundy at darcs.net>**20070920212843] 
[remove unneeded Ord constraint.
David Roundy <droundy at darcs.net>**20070920210527] 
[eliminate a few Eq a constraints in StackSet.
David Roundy <droundy at darcs.net>**20070920210143] 
[Pointfree Mirror and SomeLayout instances
Spencer Janssen <sjanssen at cse.unl.edu>**20070920211042] 
[Use derived Show and Read instances for Mirror
Spencer Janssen <sjanssen at cse.unl.edu>**20070920205711] 
[define readLayout to create a SomeLayout based on a set of possible layout types.
David Roundy <droundy at darcs.net>**20070920181506] 
[add Read instance to Layout.
David Roundy <droundy at darcs.net>**20070920174529] 
[add Show instance to Layout
David Roundy <droundy at darcs.net>**20070920161208] 
[eliminate ugly OldLayout.
David Roundy <droundy at darcs.net>**20070920155237] 
[move Layout stuff into class (hokey first cut).
David Roundy <droundy at darcs.net>**20070914215959] 
[add prop for 'differentiate'
Don Stewart <dons at galois.com>**20070927231928] 
[document shiftWin
Karsten Schoelzel <kuser at gmx.de>**20070927134205] 
[new QC properties: floating a window is reversible, screens includes current screen
Don Stewart <dons at galois.com>**20070927220431] 
[Add 3 QC properties for focusMaster: local, idempotent, preserves invariant
Don Stewart <dons at galois.com>**20070927214401] 
[no regents in xmonad license
Don Stewart <dons at galois.com>**20070927214317] 
[note that we use pattern guards in the .cabal file
Don Stewart <dons at galois.com>**20070927214230] 
[Add StackSet.focusMaster (mod-m) to move focus to master
Don Stewart <dons at galois.com>**20070927213937] 
[use hPrint instead of hPutStrLn
Don Stewart <dons at galois.com>**20070927213901] 
[Split float up
Spencer Janssen <sjanssen at cse.unl.edu>**20070924090606] 
[Use the new StackSet.screens in windows
Spencer Janssen <sjanssen at cse.unl.edu>**20070924090523] 
[Add StackSet.screens
Spencer Janssen <sjanssen at cse.unl.edu>**20070924090425] 
[fmt, and tiny comment seeking clarification
Don Stewart <dons at galois.com>**20070917234658] 
[Eliminate Operations.sink too
Spencer Janssen <sjanssen at cse.unl.edu>**20070917214052] 
[Remove Operations functions which have StackSet equivalents, just use 'windows foo' instead
Spencer Janssen <sjanssen at cse.unl.edu>**20070917211953] 
[Change manpage token @@ to %! to avoid conflicts with Haddock (xmonad)
Alex Tarkovsky <alextarkovsky at gmail.com>**20070916235229] 
[Haddockify delete' comments
Spencer Janssen <sjanssen at cse.unl.edu>**20070917194114] 
[Fix float behaviour, add shiftWin.
Karsten Schoelzel <kuser at gmx.de>**20070910090329
 
 First, if float is called with window which is on a hidden workspace,
 then the window will remain on that hidden workspace.
 
 Now the focus should change more as expected:
 float w = (view current) . (shiftWin ws w)
     where
         current is the current screen/workspace
         shiftWin ws w is: - view the workspace w is on
             - set focus on w
             - shift ws
             - set focus back to window it was on that workspace
                 unless w was focused
 
 shiftWin was add to StackSet.hs 
] 
[Add delete' for use in shift
Karsten Schoelzel <kuser at gmx.de>**20070910113835
 
 Rename delete to delete' so we can clear floating status in delete,
 thus removing one special handling. 
 At the moment delete' is only used in shift, but is useful for temporarily
 removing a window from the stack.
] 
[update description field of cabal file
Don Stewart <dons at galois.com>**20070916023016] 
[pointfree looks nicer here
Don Stewart <dons at cse.unsw.edu.au>**20070911051928] 
[Remove redundant reveal
Spencer Janssen <sjanssen at cse.unl.edu>**20070910213807] 
[Add missing insert markers for generate-configs.sh in Config.hs
Alex Tarkovsky <alextarkovsky at gmail.com>**20070907120414] 
[Move lower boundary check into applySizeHints, because all users of applySizeHints
Karsten Schoelzel <kuser at gmx.de>**20070905192125
 do this manually.
] 
[export getAtom from XMonad.
Ivan Tarasov <Ivan.Tarasov at gmail.com>**20070825174156] 
[Use show rather than string hacks
Spencer Janssen <sjanssen at cse.unl.edu>**20070905202816] 
[switch WorkspaceId to String.
David Roundy <droundy at darcs.net>**20070820113658] 
[Alex Tarkovsky's docstring patch updated for conflicts
Spencer Janssen <sjanssen at cse.unl.edu>**20070905193558] 
[tasks done
Don Stewart <dons at cse.unsw.edu.au>**20070905004901] 
[TAG 0.3
Spencer Janssen <sjanssen at cse.unl.edu>**20070904195245] 
[README: spelling
Spencer Janssen <sjanssen at cse.unl.edu>**20070904193042] 
[Bump version to 0.3
Spencer Janssen <sjanssen at cse.unl.edu>**20070904192841] 
[Add a link to XMonadContrib
Spencer Janssen <sjanssen at cse.unl.edu>**20070904192759] 
[Point to X11-extras-0.3 in the README
Spencer Janssen <sjanssen at cse.unl.edu>**20070904192643] 
[Depend on X11-extras >= 0.3
Spencer Janssen <sjanssen at cse.unl.edu>**20070903215249] 
[Add location of X11-extras to README
Spencer Janssen <sjanssen at cse.unl.edu>**20070824160935] 
[Add docstrings for mouse controls
Spencer Janssen <sjanssen at cse.unl.edu>**20070824045939] 
[todos
Don Stewart <dons at cse.unsw.edu.au>**20070822022815] 
[comment only: example of 2 monitor gaps
Don Stewart <dons at cse.unsw.edu.au>**20070821032538] 
[don't refresh when setting focus to already focussed window.
David Roundy <droundy at darcs.net>**20070820150225] 
[clear out motion events when processing one motion event.
David Roundy <droundy at darcs.net>**20070820002351
 This is important if the hook is slow (e.g. try adding "float w"
 to the window-dragging hook), as it allows xmonad to keep up with
 the motion of the mouse.
] 
[remove unneeded do.
David Roundy <droundy at darcs.net>**20070813143721] 
[make splitHorizontallyBy accept any RealFrac.
David Roundy <droundy at darcs.net>**20070813143707] 
[Fix new bug in screen switching
Spencer Janssen <sjanssen at cse.unl.edu>**20070816215629] 
[-Wall police
Don Stewart <dons at cse.unsw.edu.au>**20070816033132] 
[Comment only
Spencer Janssen <sjanssen at cse.unl.edu>**20070815224031] 
[simplify code in StackSet.
David Roundy <droundy at darcs.net>**20070814010422] 
[change workspaces to [WorkspaceId]
David Roundy <droundy at darcs.net>**20070814003722] 
[Operations.windows: minor refactor
Spencer Janssen <sjanssen at cse.unl.edu>**20070815031521] 
[Cleanup
Spencer Janssen <sjanssen at cse.unl.edu>**20070810213940] 
[move event loop out of mouseDrag.
David Roundy <droundy at darcs.net>**20070807201616] 
[only display any given window once.
David Roundy <droundy at darcs.net>**20070724141310
 This change goes along with the sticky window work.  It makes xmonad
 display each window once and only once, with preference given to the
 focussed screen.  It has no effect when there are no duplicate windows,
 except to make things less efficient.  We could do better using Data.Set
 (or Data.Map) to store the set of windows that are visible.
] 
[Add greedyView, make it the default action for mod-wer
Spencer Janssen <sjanssen at cse.unl.edu>**20070815025504] 
[Remove 'Eq' constraint from StackSet.index
Spencer Janssen <sjanssen at cse.unl.edu>**20070807144346] 
[trailing whitespace only
Don Stewart <dons at cse.unsw.edu.au>**20070805072716] 
[added workspaces to hs-boot (needed by XMonadContrib.Commands and possibly other modules)
Andrea Rossato <andrea.rossato at unibz.it>**20070728131756] 
[QuickCheck filter preserves order
Karsten Schoelzel <kuser at gmx.de>**20070728184534] 
[Bugfix: reordering when filtering out the last window on a workspace
Karsten Schoelzel <kuser at gmx.de>**20070728132507
 
 Say you have three windows A B C* on a workspace with * marking the focus.
 If you close C or move it to another workspace, the resulting order will be B* A,
 thus reordering the other windows, defying the comment of filter.
] 
[shift: use guards instead of if
Spencer Janssen <sjanssen at cse.unl.edu>**20070724152340] 
[Remove unnecessary Integral constraints
Spencer Janssen <sjanssen at cse.unl.edu>**20070724152257] 
[make delete work when window is in multiple workspaces.
David Roundy <droundy at darcs.net>**20070724142045] 
[Remove redundant 'n >= 0' check from shift.  (from David Roundy's 'simplify shift, removing unneeded check.' patch)
Spencer Janssen <sjanssen at cse.unl.edu>**20070724145927] 
[Cleanup of shift code
Michael G. Sloan <mgsloan at gmail.com>**20070722205337] 
[use $HOME in examples
Don Stewart <dons at cse.unsw.edu.au>**20070719063348] 
[Tweak dmenu binding
Peter De Wachter <pdewacht at gmail.com>**20070717190722
 Add an "eval", so quotes and environment variables get evaluated
 according to sh rules.
] 
[restore focus to currently focused window after "float" (closes #32)
Jason Creighton <jcreigh at gmail.com>**20070710042631] 
[Operations.screenWorkspace: return Nothing when the screen does not exist
Spencer Janssen <sjanssen at cse.unl.edu>**20070707223842] 
[Operations.rescreen: screen indexes start at zero
Spencer Janssen <sjanssen at cse.unl.edu>**20070707223334] 
[Note and workaround bugs in Operations.float
Spencer Janssen <sjanssen at cse.unl.edu>**20070705195213] 
[refresh after starting
Spencer Janssen <sjanssen at cse.unl.edu>**20070630050346] 
[UPGRADE X11-Extras!  Manage iconified windows
Spencer Janssen <sjanssen at cse.unl.edu>**20070630021026] 
[Move screen details into StackSet
Spencer Janssen <sjanssen at cse.unl.edu>**20070629213917] 
[Change a window's workspace when dragging across screens (closes #30)
Jason Creighton <jcreigh at gmail.com>**20070628025023] 
[support self-modifying layouts.
David Roundy <droundy at darcs.net>**20070623201447] 
[comment for (dubious?) integrate'
Don Stewart <dons at cse.unsw.edu.au>**20070626052431] 
[broadcast unidentified events.
David Roundy <droundy at darcs.net>**20070623214125
 This change is independent of the doLayout change I just sent in, but fixes
 the problem that change introduces in Decoration, by ensuring that all
 Layouts get redraw events.  I think this is the correct behavior.
] 
[add 2 properties to state where focus goes on delete of focused window
Don Stewart <dons at cse.unsw.edu.au>**20070626040907] 
[fix empty case in 'filter', and note differences in semantics wrt. focus to 'delete'
Don Stewart <dons at cse.unsw.edu.au>**20070626035741] 
[clean up 'StackSet.filter' for style
Don Stewart <dons at cse.unsw.edu.au>**20070626033202] 
[minor tweaks, ideas from joachim.fasting@
Don Stewart <dons at cse.unsw.edu.au>**20070621033613] 
[only perform mouse events on managed windows. closes #28
Don Stewart <dons at cse.unsw.edu.au>**20070621011700] 
[Update Layout documentation
Spencer Janssen <sjanssen at cse.unl.edu>**20070620150858] 
[-Wall police
Spencer Janssen <sjanssen at cse.unl.edu>**20070620150823] 
[Stack windows in the order they are returned by doLayout
Spencer Janssen <sjanssen at cse.unl.edu>**20070620150419] 
[remove out of date `(Included with GHC)' text in README
Don Stewart <dons at cse.unsw.edu.au>**20070620060430] 
[make Layouts able to layout whatever they like.
David Roundy <droundy at darcs.net>**20070619150816] 
[float fixed size windows
Peter De Wachter <pdewacht at gmail.com>**20070618214657] 
[Remove all references to 'exec'
Spencer Janssen <sjanssen at cse.unl.edu>**20070618201532] 
[-Wall police, and turn on -fno-warn-orphans
Don Stewart <dons at cse.unsw.edu.au>**20070617052322] 
[make workspace tag not need to be a Num.
David Roundy <droundy at darcs.net>**20070614140709
 This change also removes the barely used 'size' field, and replaces
 it with a tagMember predicate.  The idea is to move towards the ability
 to make the workspace tag be a String, which by default might be "1".."9",
 but could also be customized to be something meaningful to the user.
] 
[Fix float stacking
Spencer Janssen <sjanssen at cse.unl.edu>**20070614213412] 
[Remove 'temporary work around' in 'windows'
Spencer Janssen <sjanssen at cse.unl.edu>**20070614211450] 
[haddock tuning for StackSet.hs
Andrea Rossato <andrea.rossato at unibz.it>**20070614064511
 with this patch the documentation of StackSet.hs will have a nice TOC
] 
[move initColor to Operations and only store the Pixel value of colors
Jason Creighton <jcreigh at gmail.com>**20070613234501
 Moving initColor to Operations allows it to be used by extensions.
 
 The Pixel component of the color is the only thing we need, so it's simpler
 just to deal with that.
] 
[haddick fine tuning
Andrea Rossato <andrea.rossato at unibz.it>**20070613185902] 
[Indentation
Spencer Janssen <sjanssen at cse.unl.edu>**20070613043018] 
[prevent keyboard focus from getting lost in some cases
Jason Creighton <jcreigh at gmail.com>**20070613025350] 
[resolve conflict in Operations.
David Roundy <droundy at darcs.net>**20070612170625] 
[add catchX to catch exceptions.
David Roundy <droundy at darcs.net>**20070612154253] 
[make focus, up and down complete functions.
David Roundy <droundy at darcs.net>**20070612150555
 This is a rerun of my change to make (Stack a) never be empty.  Gives
 us more type-safety.
] 
[add differentiate function to StackSet to go [a] -> Stack a.
David Roundy <droundy at darcs.net>**20070612132853] 
[Make 'view' a total function
Spencer Janssen <sjanssen at cse.unl.edu>**20070612143248] 
[fmt
Don Stewart <dons at cse.unsw.edu.au>**20070612134938] 
[-Wall police
Stefan O'Rear <stefanor at cox.net>**20070612060546] 
[Use a more descriptive name for the layout reversal message
Stefan O'Rear <stefanor at cox.net>**20070612055859] 
[Use broadcastMessage in windows and switchLayout, should improve Xinerama for tabbed and make xmonad robust in the presence of state-altering unlayout hooks
Stefan O'Rear <stefanor at cox.net>**20070612055510] 
[Add a broadcastMessage function, which sends to all visible workspaces without refreshing. (+6 loc)
Stefan O'Rear <stefanor at cox.net>**20070612055339] 
[TODO for scan
Spencer Janssen <sjanssen at cse.unl.edu>**20070611214217] 
[Set withdrawn state after calling windows
Spencer Janssen <sjanssen at cse.unl.edu>**20070611213327] 
[Remove obsolete 'layout' function
Spencer Janssen <sjanssen at cse.unl.edu>**20070611203622] 
[-Wall police
Spencer Janssen <sjanssen at cse.unl.edu>**20070611202007] 
[Comment only
Spencer Janssen <sjanssen at cse.unl.edu>**20070611195827] 
[Hide windows that are not supposed to be visible
Spencer Janssen <sjanssen at cse.unl.edu>**20070611191809] 
[-Wall police
Spencer Janssen <sjanssen at cse.unl.edu>**20070611185708] 
[API CHANGE: Give doLayout a Stack rather than a flattened list
Spencer Janssen <sjanssen at cse.unl.edu>**20070611182629] 
[-Wall police
Spencer Janssen <sjanssen at cse.unl.edu>**20070611180123] 
[Add StackSet.filter
Spencer Janssen <sjanssen at cse.unl.edu>**20070611165154] 
[Use catchIO in 'restart'
Spencer Janssen <sjanssen at cse.unl.edu>**20070611161152] 
[Rename safeIO to catchIO
Spencer Janssen <sjanssen at cse.unl.edu>**20070611160608] 
[add safeIO which catches and logs exceptions.
David Roundy <droundy at darcs.net>**20070611153650] 
[Ensure windows get at least 1 pixel for width/height
Spencer Janssen <sjanssen at cse.unl.edu>**20070611061930] 
[Restrict the master/slave ratio to [0, 1]
Spencer Janssen <sjanssen at cse.unl.edu>**20070611053230] 
[comment only
Jason Creighton <jcreigh at gmail.com>**20070611020249] 
[a few modifications to event-sending to make Tabbed layout work.
David Roundy <droundy at darcs.net>**20070610153836] 
[send message when "windows" is called.
David Roundy <droundy at darcs.net>**20070610013531] 
[implement Spencer's decoration suggestion.
David Roundy <droundy at darcs.net>**20070610012237] 
[haddock compatibility
Andrea Rossato <andrea.rossato at unibz.it>**20070610123746] 
[Move state logging into Config.hs, via logHook :: X ()
Don Stewart <dons at cse.unsw.edu.au>**20070610061932] 
[polish serialisation code (-7 lines)
Don Stewart <dons at cse.unsw.edu.au>**20070610045551] 
[cut incorrect comment.
David Roundy <droundy at darcs.net>**20070609173447] 
[doLayout cleanup and commented exception-handling.
David Roundy <droundy at darcs.net>**20070609145036] 
[Give refresh sole responsibility for establishing window properties (-3 loc)
Stefan O'Rear <stefanor at cox.net>*-20070609185835] 
[Give refresh sole responsibility for establishing window properties (-3 loc)
Stefan O'Rear <stefanor at cox.net>**20070609185835] 
[HEADS UP: (logging format change). use a custom pretty printer, for an easier format to parse, than 'show' produces
Don Stewart <dons at cse.unsw.edu.au>**20070609131716] 
[Add notes on using X11-extras from darcs
Don Stewart <dons at cse.unsw.edu.au>**20070609025045] 
[Fix unmap handling
Spencer Janssen <sjanssen at cse.unl.edu>**20070606214006
 According to the ICCCM, clients should send a synthetic unmap event when they
 initiate an unmap.  The old code waited for these synthetic unmaps to unmanage
 windows.  However, certain 'obsolete' clients do not send synthetic unmaps
 (notably xpdf's find dialog).  These windows entered a zombified state: xmonad
 does not manage them, yet they are still mapped and raised on screen.
 
 The new algorithm (derived from wmii):
  - track windows that are mapped on screen
  - track the number of expected unmap events for each window, increment every
    time 'hide' is called on a window that is not mapped.
  - decrement the expected unmap counter on each unmap event
  - treat an unmap event as genuine (ie. unmap the window) when:
     - the event is synthetic (per ICCCM)
     - OR there are no expected unmap events for this window
 
] 
[dead import
Don Stewart <dons at cse.unsw.edu.au>**20070606025226] 
[move extraModifiers/cleanMask to Operations.hs
Jason Creighton <jcreigh at gmail.com>**20070606005056
 so XMonadContrib can use them
] 
[temporary workaround for delete/focus issue in fullscreen mode
Don Stewart <dons at cse.unsw.edu.au>**20070606024938] 
[whitespace
Don Stewart <dons at cse.unsw.edu.au>**20070606024857] 
[simplify code
Don Stewart <dons at cse.unsw.edu.au>**20070606004603] 
[mention why StackSet needs -fglasgow-exts (for deriving Typeable)
Don Stewart <dons at cse.unsw.edu.au>**20070605092659] 
[comments only
Don Stewart <dons at cse.unsw.edu.au>**20070605091803] 
[clean size hint code
Don Stewart <dons at cse.unsw.edu.au>**20070605091354] 
[Enable logging of state changes to stdout
Don Stewart <dons at cse.unsw.edu.au>**20070605083735] 
[remove accidental logging of events
Don Stewart <dons at cse.unsw.edu.au>**20070605081452] 
[Fix lost eventNotifyMask bug
Don Stewart <dons at cse.unsw.edu.au>**20070605043040
 
 When resuming, we were (implicitly) relying on 'scan' to find all
 windows, and reset their event masks and WM_STATE. When we moved to
 Iconfified hidden workspaces, 'scan' would only find and reset states on 
 the current workspace.
 
 The result being that hidden workspace windows no longer received
 enterNotify events.
 
 Fix this by traversing the StackSet serialised during a restart, setting
 the intial X states for each window, whether visible or hidden.
 
] 
[whitespace only
Don Stewart <dons at cse.unsw.edu.au>**20070605000723] 
[Comment only
Spencer Janssen <sjanssen at cse.unl.edu>**20070604211956] 
[Wibble.
Spencer Janssen <sjanssen at cse.unl.edu>**20070604211816] 
[-Wall police
Spencer Janssen <sjanssen at cse.unl.edu>**20070604211531] 
[apply size hints to floating windows
Peter De Wachter <pdewacht at gmail.com>**20070604192943] 
[size hints infrastructure
Peter De Wachter <pdewacht at gmail.com>**20070604192753] 
[Delete stale comment
Spencer Janssen <sjanssen at cse.unl.edu>**20070604204617] 
[Comment only
Spencer Janssen <sjanssen at cse.unl.edu>**20070604203659] 
[Use 'windows' in 'focus'
Spencer Janssen <sjanssen at cse.unl.edu>**20070604201639] 
[realign guard
l.mai at web.de**20070604182045] 
[swapUp/Down are also mirrored
Spencer Janssen <sjanssen at cse.unl.edu>**20070604183535] 
[Remove redundant cases in swapUp/Down
Spencer Janssen <sjanssen at cse.unl.edu>**20070604183344] 
[focusUp/Down are the same, in reversed order
Spencer Janssen <sjanssen at cse.unl.edu>**20070604183143] 
[Simplify focusUp/Down
Spencer Janssen <sjanssen at cse.unl.edu>**20070604182228] 
[Integral implies Eq
Spencer Janssen <sjanssen at cse.unl.edu>**20070604180745] 
[Comment typo.
Spencer Janssen <sjanssen at cse.unl.edu>**20070604180554] 
[Dump state at launch (commented for now)
Spencer Janssen <sjanssen at cse.unl.edu>**20070604162450] 
[Small clean up
Spencer Janssen <sjanssen at cse.unl.edu>**20070604064418] 
[Merge windows and refresh
Spencer Janssen <sjanssen at cse.unl.edu>**20070604063657] 
[Use the new integrate function
Spencer Janssen <sjanssen at cse.unl.edu>**20070604062653] 
[Add integrate
Spencer Janssen <sjanssen at cse.unl.edu>**20070604062501] 
[Delete stale comments
Spencer Janssen <sjanssen at cse.unl.edu>**20070604061719] 
[Remove inaccurate warnings about 'hide'
Spencer Janssen <sjanssen at cse.unl.edu>**20070604060611] 
[base >= 2.0 means we can use forM_
Spencer Janssen <sjanssen at cse.unl.edu>**20070604050914] 
[Remove no-longer-needed 'dimensions' state (-5 loc)
Stefan O'Rear <stefanor at cox.net>**20070604044715] 
[Set WM_STATE, iconify invisible windows (+9 loc)
Stefan O'Rear <stefanor at cox.net>**20070604042343
 Note that this breaks compatibility with certain programs described as
 "obsolete" in the ICCCM (1994).  See the command above the UnmapEvent handler
 for details.
] 
[clean up Main.hs slightly
Don Stewart <dons at cse.unsw.edu.au>**20070604035637] 
[whitespace
Don Stewart <dons at cse.unsw.edu.au>**20070604015532] 
[-Wall
Don Stewart <dons at cse.unsw.edu.au>**20070604014630] 
[do not cache atom values within Xmonad, instead let Xlib worry about caching (a documented feature)
Stefan O'Rear <stefanor at cox.net>**20070604013938] 
[Honor configure requests from unmanaged windows
Spencer Janssen <sjanssen at cse.unl.edu>**20070603234730] 
[-Wall police
Spencer Janssen <sjanssen at cse.unl.edu>**20070603212055] 
[Correctly handle resize requests (-12 +22)
Stefan O'Rear <stefanor at cox.net>**20070603203153
 Xmonad now implements resize requests in a consistent manner.
 
 * If the window is FLOATING, we implement the program's request, and
   correctly update the StackSet; so it will keep the new size.  This
   should work correctly even for non-current windows.
 
 * Otherwise, we ignore the request.  As per ICCCM, we send a fake
   ConfigureNotify containing the new (unchanged) geometry.  This is
   perfectly ICCCM compliant, and if it breaks your client, it's your
   own fault.
 
 This patch requires setConfigureEvent, which is added to X11-extras by
 a patch approximately contemporaneous with this one.
] 
[comments only
Don Stewart <dons at cse.unsw.edu.au>**20070603071556] 
[Polish core layout code. Lifts limitation on nmaster > 1. it may be 0 now
Don Stewart <dons at cse.unsw.edu.au>**20070603064306] 
[heads up: polish config.hs. moves tiling-local values into lexical scope. removes `wide' as an explicit mode (it's `mirror tall')
Don Stewart <dons at cse.unsw.edu.au>**20070603054740] 
[set build-depends base>=2.0 so people can't miss the missing Read instance issue
Don Stewart <dons at cse.unsw.edu.au>**20070603032319] 
[Fix out-of-date comment in Config.hs.
Chris Mears <chris at cmears.id.au>**20070602114312] 
[only grab button{1,2,3} for click-to-focus (scrollwheel shouldn't focus)
Jason Creighton <jcreigh at gmail.com>**20070602052605] 
[make mouse bindings configurable
Jason Creighton <jcreigh at gmail.com>**20070602040647] 
[commented out implementation state logging. if someone has a client, we can enable this
Don Stewart <dons at cse.unsw.edu.au>**20070601085626] 
[ignore numlock/capslock on mouse bindings
Jason Creighton <jcreigh at gmail.com>**20070601015137] 
[now we handle transients properly, and restack windows, refresh from focus is ok
Don Stewart <dons at cse.unsw.edu.au>**20070601022329] 
[Rename withWorkspace to withWindowSet.
glasser at mit.edu**20070601001325] 
[Revert accidental change to border color
Spencer Janssen <sjanssen at cse.unl.edu>**20070531145509] 
[comments on why fullscreen tiling doesn't work with `implicit' floating
Don Stewart <dons at cse.unsw.edu.au>**20070531090537] 
[clean up mouse code a bit
Don Stewart <dons at cse.unsw.edu.au>**20070531085308] 
[first shot at a floating layer
Jason Creighton <jcreigh at gmail.com>**20070531044733
 
 This is a first attempting at a floating layer:
 
 mod-button1: move window
 mod-button2: swapMaster
 mod-button3: resize window
 
 mod-t: make floating window tiled again
 
 Moving or resizing a window automatically makes it floating.
 
 Known issues:
 
 Hard to manage stacking order. You can promote a window to move it to the top,
 (which you can do with mod-button2) but it should be easier than that.
 
 Moving a window by dragging it to a different Xinerama screen does not move it
 to that workspace.
 
 Code is ugly.
] 
[remove LOC cap (but still print count after tests)
Jason Creighton <jcreigh at gmail.com>**20070531043417] 
[TAG 0.2
Spencer Janssen <sjanssen at cse.unl.edu>**20070531010004] 
[Remove 0.2 TODOs
Spencer Janssen <sjanssen at cse.unl.edu>**20070531005855] 
[Bump version to 0.2
Spencer Janssen <sjanssen at cse.unl.edu>**20070530202529] 
[Minor style change.
Spencer Janssen <sjanssen at cse.unl.edu>**20070530181006] 
[log errors on executeFile in restart
nickburlett at mac.com**20070530171024
 
 I found it difficult to track down a problem in the restart code where xmonad was silently not restarting. This will log the error to stderr, which should show up in .xsession-errors
 
] 
[Depend on X11-extras >= 0.2
Spencer Janssen <sjanssen at cse.unl.edu>**20070530173607] 
[Require X11 >= 1.2.1
Spencer Janssen <sjanssen at cse.unl.edu>**20070530172909] 
[point out restart is used to propagate changes
Don Stewart <dons at cse.unsw.edu.au>**20070530021005] 
[Really change restart keybinding this time
Spencer Janssen <sjanssen at cse.unl.edu>**20070530061454] 
[HEADS UP: Change restart keybinding to mod-q
Spencer Janssen <sjanssen at cse.unl.edu>*-20070530061044] 
[HEADS UP: Change restart keybinding to mod-q
Spencer Janssen <sjanssen at cse.unl.edu>**20070530061044] 
[Fix 'refresh' doc string
Spencer Janssen <sjanssen at cse.unl.edu>**20070529020446] 
[Give link to bugtracker in "BUGS" section of manpage
Jason Creighton <jcreigh at gmail.com>**20070529015851] 
[make 'tall' layout the default on startup. more useful for new users
Don Stewart <dons at cse.unsw.edu.au>**20070529014611] 
[notes about which dependant packages already come with ghc
Don Stewart <dons at cse.unsw.edu.au>**20070529005748] 
[forgot to set focus in 'focus'. this restores the old behaviour
Don Stewart <dons at cse.unsw.edu.au>**20070528134547] 
[don't refresh on focus events
Don Stewart <dons at cse.unsw.edu.au>**20070528133127
 
 leads to a race. this will affect how gaps are redrawn when moving to a
 new screen with the mouse. 
 
] 
[ensure !! won't go out of bounds in modifyGap
Don Stewart <dons at cse.unsw.edu.au>**20070528070609] 
[mention .xinitrc
Don Stewart <dons at cse.unsw.edu.au>**20070528061252] 
[update readme
Don Stewart <dons at cse.unsw.edu.au>**20070528051444] 
[Add the HTML manpage
Spencer Janssen <sjanssen at cse.unl.edu>**20070528063122] 
[Fix manpage generator
Spencer Janssen <sjanssen at cse.unl.edu>**20070528062658] 
[apply gap to each screen
Don Stewart <dons at cse.unsw.edu.au>**20070528044722] 
[move gapcalc.c
Don Stewart <dons at cse.unsw.edu.au>**20070528040402] 
[Remove gapcalc.c from the sdist, add generated manpage
Spencer Janssen <sjanssen at cse.unl.edu>**20070528040655] 
[help man script
Don Stewart <dons at cse.unsw.edu.au>**20070528033846] 
[done with gap
Don Stewart <dons at cse.unsw.edu.au>**20070528033525] 
[Document mod-n
Spencer Janssen <sjanssen at cse.unl.edu>**20070528033536] 
[be sure to reset the gap list on rescreen
Don Stewart <dons at cse.unsw.edu.au>**20070528031835] 
[support per-screen gap settings. you can have different gaps on individual screens now
Don Stewart <dons at cse.unsw.edu.au>**20070528031501] 
[Use (Int,Int,Int,Int) for arbitrary gaps on any side of the screen
Don Stewart <dons at cse.unsw.edu.au>**20070528025135] 
[Update extra-source-files
Spencer Janssen <sjanssen at cse.unl.edu>**20070527210657] 
[Note the manpage move in xmonad.cabal
Spencer Janssen <sjanssen at cse.unl.edu>**20070527205857] 
[refactor only
Don Stewart <dons at cse.unsw.edu.au>**20070527154353] 
[comments on alternative gap movement policies
Don Stewart <dons at cse.unsw.edu.au>**20070527153211] 
[when focus is called from an event, better refresh too, since it might have switched workspaces (so gap follows screen focus)
Don Stewart <dons at cse.unsw.edu.au>**20070527151942] 
[only set gap on current physical screen
Don Stewart <dons at cse.unsw.edu.au>**20070527150805] 
[gap
Don Stewart <dons at cse.unsw.edu.au>**20070527150053] 
[todo
Don Stewart <dons at cse.unsw.edu.au>**20070527143216] 
[revert raiseWindow in focus. Leads to some funny races with pop ups. Harmless with status bar support now
Don Stewart <dons at cse.unsw.edu.au>**20070527134505] 
[mod-b, toggle on or off the status bar gap
Don Stewart <dons at cse.unsw.edu.au>**20070527125928] 
[Add new config value, defaultMenuGap, for specifying a gap for a status bar
Don Stewart <dons at cse.unsw.edu.au>**20070527122702
 
 By default, it is 0 (set in Config.hs), but set this to a pixel count to
 get a permanent gap at the top of the screen. You can then at startup
 launch dzen, and it will run in this gap, and not be obscured by other
 windows.
 
 Perfect for a persistant status bar.
 
] 
[raiseWindow when settings focus. The focused window should always be raised, I think
Don Stewart <dons at cse.unsw.edu.au>**20070527094105] 
[Be a bit more conservative with -O flags, and GC. Hope to avoid runtime GC bug
Don Stewart <dons at cse.unsw.edu.au>**20070527074438] 
[dead code
Don Stewart <dons at cse.unsw.edu.au>**20070527072652] 
[refactor code smell in Operation.hs
Don Stewart <dons at cse.unsw.edu.au>**20070527072135] 
[clean Main.hs slightly
Don Stewart <dons at cse.unsw.edu.au>**20070527072106] 
[todo
Don Stewart <dons at cse.unsw.edu.au>**20070527063740] 
[Generate keybindings section in manpage from Config.hs
Jason Creighton <jcreigh at gmail.com>**20070527062914] 
[specify --user, spotted by fasta
Don Stewart <dons at cse.unsw.edu.au>**20070527014032] 
[HEADS UP: change key binding for swapLeft/Right and IncMaster
Don Stewart <dons at cse.unsw.edu.au>**20070526111453
 
 The use of arrow keys for swapLeft/Right clash with firefox's back
 button. Use the more intuitive mod-shift-jk for this. (It's a movement
 operation, after all).
 
 This clashes with IncMaster, so we use mod+comma and mod+period for
 these (i.e. the keys mod < and mod > , to move windows to and from the
 master area).
 
 While we're here, replace the use of the terms 'left' and 'right' for
 navigation, in comments and identifiers, with 'up' and 'down' instead.
 Hence mod-j == focusDown. Far more intuitive for people (dons) who live
 in fullscreen mode and have vim movement wired into their central
 nervous system.
 
 Principle of least VI surprise: movement down or up means using j and k.
 
 
] 
[type sig for abort.
Don Stewart <dons at cse.unsw.edu.au>**20070526061450] 
[Add an abort function, called for deliberate and intentional errors
Neil Mitchell**20070523233212] 
[Delete the Catch wrapper, no longer required by the latest version of Catch
Neil Mitchell**20070523232941] 
[start on TODO list needed for 0.2 to be tagged
Don Stewart <dons at cse.unsw.edu.au>**20070526060720] 
[Add a test that the size field of StackSet is correct to QuickCheck invariant.
glasser at mit.edu**20070525163159] 
[Formatting only
Spencer Janssen <sjanssen at cse.unl.edu>**20070525214414] 
[Quickcheck property to check that delete / focus behaviour
Rob <bobstopper at bobturf.org>**20070525035432
 See patch "Deleting a window should not affect focus". Checks this property.
] 
[Fix bug in noDuplicate invariant
Rob <bobstopper at bobturf.org>**20070525060842
 ws used by noDuplicates is actually a list of list of elements which 
 will pretty rarely raise any flags even if the StackSet actually does
 contain duplicates. This patch concatenates ws to ensure the quickcheck
 property tests accurately.
] 
[Add a note about already installed packages
Spencer Janssen <sjanssen at cse.unl.edu>**20070525153143] 
[Deleting a window should not affect focus
Rob <bobstopper at bobturf.org>**20070525024118
 This fixes a bug whereby deleting a window will first move focus to
 that window before deleting it without moving focus back afterwards.
 
 The fix generalises the remove inner function to delete a window from
 the stack whether it's in focus or not. If the window is in focus,
 behaviour remains as it was.
] 
[Use --resume by default
Spencer Janssen <sjanssen at cse.unl.edu>**20070523191418] 
[add swapLeft and swapRight
bobstopper at bobturf.org**20070522050008] 
[restart: don't preserve old args
Spencer Janssen <sjanssen at cse.unl.edu>**20070522060357] 
[Wibble
Spencer Janssen <sjanssen at cse.unl.edu>**20070522043844] 
[Generalize withDisplay's type
Spencer Janssen <sjanssen at cse.unl.edu>**20070522043758] 
[refactor using whenX 
Don Stewart <dons at cse.unsw.edu.au>**20070522043116] 
[Add preliminary randr support
Spencer Janssen <sjanssen at cse.unl.edu>**20070522040228] 
[Update the Catch checking to the new interface for StackSet
Neil Mitchell**20070522015422] 
[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] 
[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] 
[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] 
[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] 
[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] 
[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] 
[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] 
[Bump version to 0.1
Spencer Janssen <sjanssen at cse.unl.edu>**20070422082948] 
[xmonad 0.1 is ready
Spencer Janssen <sjanssen at cse.unl.edu>**20070422080824] 
[Update TODO
Spencer Janssen <sjanssen at cse.unl.edu>**20070422080806] 
[Arbitrary Word64 for running tests on amd64
Alec Berryman <alec at thened.net>**20070419104652
 
 Copied from Arbitrary Word8; I don't understand the coarbitrary definition and
 the Word64 one may be erroneous, but Properties.hs now compiles and passes all
 tests.
] 
[two things gone from todo list
Don Stewart <dons at cse.unsw.edu.au>**20070419041809] 
[add 8 new QC tests, including tests of the layout algorithm
Don Stewart <dons at cse.unsw.edu.au>**20070419040833] 
[use prefixed record names in latest X11-extras
Jason Creighton <jcreigh at gmail.com>**20070419032244] 
[WindowSet is better than WorkSpace
Spencer Janssen <sjanssen at cse.unl.edu>**20070419015430] 
[Remove useless pragma
Spencer Janssen <sjanssen at cse.unl.edu>**20070419015239] 
[Parameterise StackSet by two index types, rather than breaking abstraction
Don Stewart <dons at cse.unsw.edu.au>**20070419012705] 
[2 more properties for promote.
Don Stewart <dons at cse.unsw.edu.au>**20070419001201] 
[tweak loc count to match count_lines script
Don Stewart <dons at cse.unsw.edu.au>**20070418224725] 
[Promote now swaps focused window with master window
Don Stewart <dons at cse.unsw.edu.au>**20070418224236
 
 This means other windows are unaffected.
 The change from the previous cycling behaviour was felt necessary, since
 cycling isn't a terribly useful operation.
 
 Some properties that hold:
     focus is unchanged by promotion
     promote is idempotent (promoting twice does nothing)
     the focused and master window will swap their positions in the stack
 
] 
[Add TODO to the sdist
Spencer Janssen <sjanssen at cse.unl.edu>**20070418223323] 
[Add the tests to the sdist
Spencer Janssen <sjanssen at cse.unl.edu>**20070418221326] 
[Make sdist work correctly
Spencer Janssen <sjanssen at cse.unl.edu>**20070418215546] 
[xmonad should build with future versions of mtl and X11-extras
Spencer Janssen <sjanssen at cse.unl.edu>**20070418214927] 
[Another TODO bites the dust
Spencer Janssen <sjanssen at cse.unl.edu>**20070418205725] 
[Update propaganda.
Spencer Janssen <sjanssen at cse.unl.edu>**20070418014029] 
[define test to ensure LOC doesn't jump above 400.
David Roundy <droundy at darcs.net>**20070418004533] 
[Update TODO: all the Xinerama issues I've encountered are fixed
Alec Berryman <alec at thened.net>**20070418001453
 
 As of:
 
 Fri Apr 13 04:37:02 EDT 2007  Spencer Janssen <sjanssen at cse.unl.edu>
   * Ignore window entries while moving windows.  This should fix all the focus preservation problems.
] 
[test for xmonad in path first, before restarting
Don Stewart <dons at cse.unsw.edu.au>**20070416025541] 
[added comment about windows key (mod4Mask)
Jason Creighton <jcreigh at gmail.com>**20070415233635] 
[remove unused sizeDelta setting
Jason Creighton <jcreigh at gmail.com>**20070415233244] 
[Note we must fix mod-shift-c before 0.1 can go out
Don Stewart <dons at cse.unsw.edu.au>**20070415230435] 
[fix typo.
David Roundy <droundy at darcs.net>**20070415055616] 
[added warning re: xmonad in path to mod-shift-q docs
Jason Creighton <jcreigh at gmail.com>**20070413233019] 
[Clear up documentation on mod-h/l
Spencer Janssen <sjanssen at cse.unl.edu>**20070413230706] 
[Ignore window entries while moving windows.  This should fix all the focus preservation problems.
Spencer Janssen <sjanssen at cse.unl.edu>**20070413083702] 
[Update TODO
Spencer Janssen <sjanssen at cse.unl.edu>**20070413031003] 
[mod-wer for Xinerama was inadvertently changed
Alec Berryman <alec at thened.net>**20070412132033] 
[and the tests still run
Don Stewart <dons at cse.unsw.edu.au>**20070411081500] 
[add license headers to two missing files
Don Stewart <dons at cse.unsw.edu.au>**20070411081042] 
[clean up tiling code a teensy bit, and comment on the interaction between focus, master, and cycling direction between the modes
Don Stewart <dons at cse.unsw.edu.au>**20070411080747] 
[explain what mod-return now does. it cycles
Don Stewart <dons at cse.unsw.edu.au>**20070411073636] 
[Change semantics of 'promote'. 
Don Stewart <dons at cse.unsw.edu.au>**20070411073456
 
 Previously 'promote' would move the currently focused window into the
 master position in tiled mode. This was *almost* a cycle of the windows,
 but not quite (depending on where the focus was, it was in fact a
 cycle).
 
 Now we do the obvious generalisation, and just cycle the current window
 stack. Simpler to understand, simpler to reason about.
 
] 
[clean up only
Don Stewart <dons at cse.unsw.edu.au>**20070411065607] 
[merge with toList/fromList patch
Don Stewart <dons at cse.unsw.edu.au>**20070411060947] 
[Statically distinguish Workspace and Screen indices
Don Stewart <dons at cse.unsw.edu.au>**20070411060456] 
[fromList/toList have # of screens + another QC property
Jason Creighton <jcreigh at gmail.com>**20070411044215] 
[Xinerama screen switching bugfix
Jason Creighton <jcreigh at gmail.com>**20070411041615] 
[removed xinerama-enabled dmenu action
Jason Creighton <jcreigh at gmail.com>**20070411024716
 I don't think we're going to see any Xinerama support upstream, at least not
 anytime soon. It doesn't make sense to ship something with xmonad that isn't
 going to work out of the box. So for now Xinerama users should just use this
 patch: http://www.jcreigh.com/xmonad/xinerama-dmenu.html
] 
[Move workspace fetching logic from Config.hs to Operations.hs
Spencer Janssen <sjanssen at cse.unl.edu>**20070410064714] 
[moved screen <-> workspace mapping from XMonad to StackSet
Jason Creighton <jcreigh at gmail.com>**20070410062731] 
[Add notes about StackSet redesign
Spencer Janssen <sjanssen at cse.unl.edu>**20070410021238] 
[Simplify rot
Spencer Janssen <sjanssen at cse.unl.edu>**20070409223500] 
[Rearrange TODO
Spencer Janssen <sjanssen at cse.unl.edu>**20070409075817] 
[Also done
Spencer Janssen <sjanssen at cse.unl.edu>**20070409075029] 
[Tile algorithm has been improved
Spencer Janssen <sjanssen at cse.unl.edu>**20070409074945] 
[Vertical tiling done
Spencer Janssen <sjanssen at cse.unl.edu>**20070409074853] 
[Remove redundant parens
Spencer Janssen <sjanssen at cse.unl.edu>**20070409073836] 
[Remove unused 'screen' field
Spencer Janssen <sjanssen at cse.unl.edu>**20070409073510] 
[Document XState fields
Spencer Janssen <sjanssen at cse.unl.edu>**20070409073414] 
[Use -funbox-strict-fields, rather than UNPACK pragmas. cleaner code.
Don Stewart <dons at cse.unsw.edu.au>**20070409072302] 
[Remove redundant setFocus, setFocus is called by refresh which is called by windows
Spencer Janssen <sjanssen at cse.unl.edu>**20070405215832] 
[-Wall police
Don Stewart <dons at cse.unsw.edu.au>**20070405000100] 
[take window borders into account when resizing (requires latest X11-extras)
Jason Creighton <jcreigh at gmail.com>**20070404021612] 
[summarise key bindings in a table in Config.hs
Don Stewart <dons at cse.unsw.edu.au>**20070404011441] 
[replace multiple gets with a single get and record bind
Don Stewart <dons at cse.unsw.edu.au>**20070404010524] 
[Use Tall and Wide for split screen layouts.  This should be less confusing.
Spencer Janssen <sjanssen at cse.unl.edu>**20070403050610] 
[Abusing TODO as a bug tracker: note about overlapping
Alec Berryman <alec at thened.net>**20070402222956] 
[Comment typo: more -> move
Alec Berryman <alec at thened.net>**20070402221948] 
[Note the Xinerama bugs I've experienced in the TODO
Alec Berryman <alec at thened.net>**20070402160802] 
[vertical (master area on top) tiling
Jason Creighton <jcreigh at gmail.com>**20070403040658] 
[Comment typo.
Spencer Janssen <sjanssen at cse.unl.edu>**20070402214605] 
[Comment only.
Spencer Janssen <sjanssen at cse.unl.edu>**20070402072418] 
[Revert to the old layout code.
Spencer Janssen <sjanssen at cse.unl.edu>**20070402045114] 
[Type error: lockMask :: KeyMask, not KeySym
Alec Berryman <alec at thened.net>**20070401143416
 
 Error prevents compilation on 64-bit systems.
] 
[Suggest an alternative modMask for emacs users
Alec Berryman <alec at thened.net>**20070401161027] 
[Remove trailing spaces, no content changed
Alec Berryman <alec at thened.net>**20070401144539] 
[Fix type error in dimensions field of XState record for 64-bit systems
Alec Berryman <alec at thened.net>**20070401144229
 
 Fallout from Int->CInt conversion.
] 
[Config.hs comment formatting/typo
Jason Creighton <jcreigh at gmail.com>**20070401055711] 
["dmenu" operation to spawn dmenu only on the current screen (for Xinerama)
Jason Creighton <jcreigh at gmail.com>**20070401012712
 This requires a dmenu that will accept -x and -w. Currently, This means
 applying this patch: http://www.jcreigh.com/dmenu/position-options.patch (I'm
 trying to see if I can get this into dmenu upstream; haven't heard anything
 back yet.)
] 
[sanitize key bindings
Don Stewart <dons at cse.unsw.edu.au>**20070401033522
 
 Changes mean:
 
 * gmrun is like the dmenu key, but with shift set. 
     -    , ((modMask .|. shiftMask, xK_F11   ), spawn "gmrun")
     +    , ((modMask .|. shiftMask, xK_p     ), spawn "gmrun")
 
  If no one actually uses both gmrun and dmenu, we should consider only
  using mod-p for this.
 
 * restart is like quit, but with 'ctrl' set:
     +    , ((modMask .|. shiftMask, xK_q                     ), io $ exitWith ExitSuccess)
     +    , ((modMask .|. shiftMask .|. controlMask, xK_q     ), io restart)
 
 * revert to 'wer' ordering for xinerama screens:
     -        | (key, sc) <- zip [xK_e, xK_r, xK_t] [1..]
     +        | (key, sc) <- zip [xK_w, xK_e, xK_r] [1..]
 
 that's the only binding order that makes sense, since they're meant to
 refer to screens 1 2 and 3, hence 'wer' (look at the keyboard to see why)
 
 
 
 
 
] 
[Cleaned up layout a little bit
hughes at rpi.edu**20070401023639] 
[restore dwm-style keybindings. mod-shift-{j,k} resize in vert mode
Don Stewart <dons at cse.unsw.edu.au>**20070401025433] 
[Merged things together with dons changes.
hughes at rpi.edu**20070401021846] 
[Config.hs avoids conflict with essential M-w Emacs shortcut.
hughes at rpi.edu**20070401015135] 
[Vertical/horizontal split, and resizability.
hughes at rpi.edu**20070401014706] 
[Remove evil gmrun shortcut.
hughes at rpi.edu**20070330144558] 
[formatting only
Don Stewart <dons at cse.unsw.edu.au>**20070401004726] 
[formatting fixes. the style is getting a bit dodgy in some places...
Don Stewart <dons at cse.unsw.edu.au>**20070401002803] 
[Move safeFocus from Main to Operations
Spencer Janssen <sjanssen at cse.unl.edu>**20070331010024] 
[removed refocus; moved functionality to setFocus
Jason Creighton <jcreigh at gmail.com>**20070331003442] 
[refactored "focus changed" code into "refocus"
Jason Creighton <jcreigh at gmail.com>**20070330035454] 
[Window borders
Alec Berryman <alec at thened.net>**20070329182159
 
 Colors taken from dwm's config.default.h and hard-coded in Operations instead
 of Config because of import cycle.
 
 Windows overlap slightly in the current tiling algorithm and sometimes prevent
 the active window from being completely surrounded by a red border.
] 
[Add AMD64 note to the README
Spencer Janssen <sjanssen at cse.unl.edu>**20070329055250] 
[Type error: button1 :: Button, not :: ButtonMask
Alec Berryman <alec at thened.net>**20070329024330] 
[Fix refreshKeyboardMapping issues.  Requires the latest X11-extras
Spencer Janssen <sjanssen at cse.unl.edu>**20070328215753] 
[allow mouse to change current workspace
daniel at wagner-home.com**20070328103435] 
[first shot at allowing click to focus windows
daniel at wagner-home.com**20070328101540] 
[added a quickcheck property
daniel at wagner-home.com**20070328025337] 
[Compatibility with CInt'ified X11
Spencer Janssen <sjanssen at cse.unl.edu>**20070328071436] 
[one less todo
Don Stewart <dons at cse.unsw.edu.au>**20070327231846] 
[whitespace
Jason Creighton <jcreigh at gmail.com>**20070327013350] 
[updated TODO (Config.hs completed)
Jason Creighton <jcreigh at gmail.com>**20070327014124] 
[Config supports Ctrl+Space for gmrun again.
hughes at rpi.edu**20070326151243] 
[Workspace-specific layouts
hughes at rpi.edu**20070326150213] 
[Typo: use dmenu_path instead of emenu_path
Alec Berryman <alec at thened.net>**20070326140335] 
[Focus follows mouse.
Spencer Janssen <sjanssen at cse.unl.edu>**20070326124725
 This change makes the window under the mouse pointer the focused window.  This
 isn't quite what we want, but it is a step in the right direction.  The next
 step is to somehow inhibit the CrossingEvents generated during workspace and
 layout switches.
 
] 
[Update todo
Spencer Janssen <sjanssen at cse.unl.edu>**20070326102441] 
[Extra config: defaultLayout
daniel at wagner-home.com**20070326074234] 
[updated TODO
daniel at wagner-home.com**20070326073415] 
[minor aesthetic changes
daniel at wagner-home.com**20070326073339] 
[fix
Don Stewart <dons at cse.unsw.edu.au>**20070326075812] 
[Restrain leftWidth
Spencer Janssen <sjanssen at cse.unl.edu>**20070326095034] 
[Config.lhs -> Config.hs
Jason Creighton <jcreigh at gmail.com>**20070326054004] 
[added Config.lhs and moved most things in Main.hs into Operations.hs to enable this
Jason Creighton <jcreigh at gmail.com>**20070326051341] 
[Xinerama focus bug (couldn't focus on current workspace)
Jason Creighton <jcreigh at gmail.com>**20070325203702] 
[restart (simple exec(), no state saved)
Jason Creighton <jcreigh at gmail.com>**20070323023738] 
[Add promote.  Makes the focused window the master
Spencer Janssen <sjanssen at cse.unl.edu>**20070322222333] 
[Add promote
Spencer Janssen <sjanssen at cse.unl.edu>**20070322221547] 
[I like 1%2 split.  Maintainer's prerogative :)
Spencer Janssen <sjanssen at cse.unl.edu>**20070321070649] 
[Add defaultLeftWidth in the configuration section
Spencer Janssen <sjanssen at cse.unl.edu>**20070321065807] 
[Allow dynamic width in tiling mode
daniel at wagner-home.com**20070321054245] 
[GHC 6.4 compatibility.
Spencer Janssen <sjanssen at cse.unl.edu>**20070321045211] 
[add keybindings to change screens and tag windows to screens
Jason Creighton <jcreigh at gmail.com>**20070321033807] 
[Add raiseFocus.
Spencer Janssen <sjanssen at cse.unl.edu>**20070320160135] 
[Make numlockMask configurable
Spencer Janssen <sjanssen at cse.unl.edu>**20070320145828] 
[Initial tiling support.
Spencer Janssen <sjanssen at cse.unl.edu>**20070320071812] 
[Fix indentation
Spencer Janssen <sjanssen at cse.unl.edu>**20070320054647] 
[Untabify
Spencer Janssen <sjanssen at cse.unl.edu>**20070320054045] 
[changed type of getScreenInfo in Graphics.X11.Xinerama
Jason Creighton <jcreigh at gmail.com>**20070320044253] 
[Decouple the concepts of focus and window order.  First step to tiling!
Spencer Janssen <sjanssen at cse.unl.edu>**20070320051124] 
[trace wsOnScreen when it's changed
Jason Creighton <jcreigh at gmail.com>**20070319035629] 
[don't try to change the current workspace based on an enterNotify event
Jason Creighton <jcreigh at gmail.com>**20070319035450] 
[use "windows" in "unmanage"
Jason Creighton <jcreigh at gmail.com>**20070318024825] 
[replaced "let Just x = ..." in view with "case ... of ..."
Jason Creighton <jcreigh at gmail.com>**20070318005525] 
[basic xinerama support (depends on Graphics.X11.Xinerama in X11-extras)
Jason Creighton <jcreigh at gmail.com>**20070317234904] 
[Whitespace only
Spencer Janssen <sjanssen at cse.unl.edu>**20070316194950] 
[-Wall police
Spencer Janssen <sjanssen at cse.unl.edu>**20070316022201] 
[abstract out modMask for easy user configuration
shae at ScannedInAvian.com**20070315230127] 
[tasks before 0.1
Spencer Janssen <sjanssen at cse.unl.edu>**20070315061646] 
[s/thunk/xmonad
Spencer Janssen <sjanssen at cse.unl.edu>**20070315054632] 
[Tiling notes
Spencer Janssen <sjanssen at cse.unl.edu>**20070314070752] 
[Actually fix the zombie issue.
Spencer Janssen <sjanssen at cse.unl.edu>**20070313235931] 
[Sloppy typos in spawn.
Spencer Janssen <sjanssen at cse.unl.edu>**20070313215009] 
[Fix forking issues, add unix dependency.
Spencer Janssen <sjanssen at cse.unl.edu>**20070313153310] 
[catch exceptions in spawn, so failing to fork won't kill the wm
Don Stewart <dons at cse.unsw.edu.au>**20070312062612] 
[fiddling, comments
Don Stewart <dons at cse.unsw.edu.au>**20070312014029] 
[comments, move isRoot into XMonad
Don Stewart <dons at cse.unsw.edu.au>**20070312012350] 
[wibbles
Don Stewart <dons at cse.unsw.edu.au>**20070312010756] 
[abstract out setfocus code a bit
Don Stewart <dons at cse.unsw.edu.au>**20070312005540] 
[general refactor, and call xerrorhandler to ignore certain undetectable issues
Don Stewart <dons at cse.unsw.edu.au>**20070311102653] 
[initial support for Atom-based delete protocol. makes kill client work on firefox. Quitting though still leads to a bogus notify from firefox, for a closed window
Don Stewart <dons at cse.unsw.edu.au>**20070311064515] 
[thunk is now known as xmonad!
Spencer Janssen <sjanssen at cse.unl.edu>**20070310070320] 
[XMonad
Don Stewart <dons at cse.unsw.edu.au>**20070310070152] 
[add tracing for kill window
Don Stewart <dons at cse.unsw.edu.au>**20070310062154] 
[Use 9 workspaces by default
Spencer Janssen <sjanssen at cse.unl.edu>**20070310041114] 
[Reduce flicker on workspace change.
Spencer Janssen <sjanssen at cse.unl.edu>**20070310041021] 
[typo
Don Stewart <dons at cse.unsw.edu.au>**20070310034012] 
[Add support for Enter/Leave notify events. Fixes firefox on my machine
Don Stewart <dons at cse.unsw.edu.au>**20070310032759] 
[refactor, trying to seperate out IO from W stuff, in order to QC the handler at some point
Don Stewart <dons at cse.unsw.edu.au>**20070310012940] 
[notes on the firefox bug
Don Stewart <dons at cse.unsw.edu.au>**20070309162510
 
 basically we have to set focus ourselves. This means when we start
 managing a window, and when an XCrossingEvent occurs (which we don't
 handle). 
 
 On Manage/Enter, we set focus. on Leave we set focus to root.
 See event.c and focus.c in dwm for more details.
 
] 
[grammar nazis
Don Stewart <dons at cse.unsw.edu.au>**20070309145649] 
[whitespace. and note if we get a config request for an already managed window
Don Stewart <dons at cse.unsw.edu.au>**20070309144308] 
[improved grabkeys (also handle lockMask down)
Don Stewart <dons at cse.unsw.edu.au>**20070309134211] 
[alloc the event space only once
Don Stewart <dons at cse.unsw.edu.au>**20070309134149] 
[also select for enter and leave window events (need for XCrossing?)
Don Stewart <dons at cse.unsw.edu.au>**20070309131251] 
[we should check for OverrideRedirect on initial scan too
Don Stewart <dons at cse.unsw.edu.au>**20070309130608] 
[no unix dependency
Don Stewart <dons at cse.unsw.edu.au>**20070309091951] 
[fmt only
Don Stewart <dons at cse.unsw.edu.au>**20070309091455] 
[unnec. export list
Don Stewart <dons at cse.unsw.edu.au>**20070309091328] 
[unnec. `nub'
Don Stewart <dons at cse.unsw.edu.au>**20070309091045] 
[just use Map, not int map. strict updates don't seem to help btw.
Don Stewart <dons at cse.unsw.edu.au>**20070309083706] 
[comments on whether we lose space due to lazy updates of the stack set
Don Stewart <dons at cse.unsw.edu.au>**20070309081621] 
[don't need the unix package
Don Stewart <dons at cse.unsw.edu.au>**20070309075148] 
[sneaky inline 
Don Stewart <dons at cse.unsw.edu.au>**20070309063818] 
[little bit of strictness, based on -prof output
Don Stewart <dons at cse.unsw.edu.au>**20070309063449] 
[explicit interface on StackSet. maybe it should be a seperate package ... ?
Don Stewart <dons at cse.unsw.edu.au>**20070309061255] 
[-12 lines, refactor
Don Stewart <dons at cse.unsw.edu.au>**20070309060139] 
[refactor, -10 or so loc
Don Stewart <dons at cse.unsw.edu.au>**20070309055417] 
[more QC properties on StackSets
Don Stewart <dons at cse.unsw.edu.au>**20070309054042] 
[simpler type (no need to cache size, we *could* grow new stacks on demand now)
Don Stewart <dons at cse.unsw.edu.au>**20070309043638] 
[replace Seq [a] with IntMap [a], hopefully gets 6.4 support
Don Stewart <dons at cse.unsw.edu.au>**20070309043035] 
[simplify StackSet api even further (-15 loc)
Don Stewart <dons at cse.unsw.edu.au>**20070309041707] 
[smaller api, less tests
Don Stewart <dons at cse.unsw.edu.au>**20070309035635] 
[use new StackSet api
Don Stewart <dons at cse.unsw.edu.au>**20070309035615] 
[shrink StackSet api
Don Stewart <dons at cse.unsw.edu.au>**20070309035603] 
[Update location for X11-extras
Spencer Janssen <sjanssen at cse.unl.edu>**20070309043422] 
[comments
Don Stewart <dons at cse.unsw.edu.au>**20070309031847] 
[handle MappingNotifyEvent properly, and missing test in MapRequestEvent. firefox still won't take the keyboard though
Don Stewart <dons at cse.unsw.edu.au>**20070309030644] 
[comments
Don Stewart <dons at cse.unsw.edu.au>**20070309030640] 
[stub for MappingNotifyEvent, based on dwm. But the X11-extras binding for this event needs doing (sjanssen?)
Don Stewart <dons at cse.unsw.edu.au>**20070308130517] 
[refactoring. heads up: depends on withServer in X11-extras
Don Stewart <dons at cse.unsw.edu.au>**20070308122613] 
[comments
Don Stewart <dons at cse.unsw.edu.au>**20070308120753] 
[move W -> WMonad
Don Stewart <dons at cse.unsw.edu.au>**20070308120536] 
[forgot to add Properties.hs
Don Stewart <dons at cse.unsw.edu.au>**20070308120521] 
[move tests into subdir
Don Stewart <dons at cse.unsw.edu.au>**20070308120448] 
[Switch to using abstract StackSet data type. Most workspace logic moved into StackSet.hs
Don Stewart <dons at cse.unsw.edu.au>**20070308114308] 
[unpack on our own
Don Stewart <dons at cse.unsw.edu.au>**20070308114255] 
[cleanup only
Don Stewart <dons at cse.unsw.edu.au>**20070308021901] 
[Make the number of workspaces configurable.
Spencer Janssen <sjanssen at cse.unl.edu>**20070308043614] 
[Print a message for unhandled events
Spencer Janssen <sjanssen at cse.unl.edu>**20070308013249] 
[Manage windows that are created before thunk starts
Spencer Janssen <sjanssen at cse.unl.edu>**20070307210117] 
[Add Alt-Shift-[1..5], to move the current client to a new workspace
Don Stewart <dons at cse.unsw.edu.au>**20070308010424] 
[cleaner implementation of 'view'. Only hide the current list. And shortcut if we try to move to the same screen. No flicker
Don Stewart <dons at cse.unsw.edu.au>**20070308002134] 
[Fill in missing workspace code
Don Stewart <dons at cse.unsw.edu.au>**20070308000729
 
 How do we manage workspaces? thunk keeps a list of window lists,
 corresponding each window stack on each workspace. When you switch views
 to a different workspace it moves all windows off the screen (2*w)
 (2*h), and then moves back those in the current list. There's some
 screen flicker, we could probably be smarter about this.
 
] 
[Add support for multiple workspaces
Don Stewart <dons at cse.unsw.edu.au>**20070307111247
 
 Everything is in place for multiple workspaces, bar one thing:
 the view function. It updates thunk's idea of the current visible
 windows, but I don't know how to tell X to hide the current set, and
 instead treat the new window list as the only ones visible.
 
 See notes for 'view' at bottom of Main.hs. If we can, say, switch to a
 new workspace, which is empty, 'refresh' should spot this only display
 the root window.
 
 
] 
[no -Werror
Don Stewart <dons at cse.unsw.edu.au>**20070307111240] 
[-Wall police. and strip the binary
Don Stewart <dons at cse.unsw.edu.au>**20070307074910] 
[fmt. and use a Map for keycode lookup
Don Stewart <dons at cse.unsw.edu.au>**20070307074248] 
[xKillClient -> killClient
Spencer Janssen <sjanssen at cse.unl.edu>**20070307073010] 
[formatting and comments only
Don Stewart <dons at cse.unsw.edu.au>**20070307071926] 
[Add alt-c, kill client
Don Stewart <dons at cse.unsw.edu.au>**20070307071910] 
[dead code
Don Stewart <dons at cse.unsw.edu.au>**20070307065250] 
[need Data.List
Don Stewart <dons at cse.unsw.edu.au>**20070307064827] 
[focus left and right (mod-j/mod-k)
Don Stewart <dons at cse.unsw.edu.au>**20070307064539] 
[Plan for statusbar/multithreading
Spencer Janssen <sjanssen at cse.unl.edu>**20070307064223] 
[Add TODO
Spencer Janssen <sjanssen at cse.unl.edu>**20070307064214] 
[wibble
Don Stewart <dons at cse.unsw.edu.au>**20070307062201] 
[derive MonadState, removes most accessors
Don Stewart <dons at cse.unsw.edu.au>**20070307061532] 
[Handle several more events, should fix several issues.
Spencer Janssen <sjanssen at cse.unl.edu>**20070307060447] 
[refactoring. less code
Don Stewart <dons at cse.unsw.edu.au>**20070307055007] 
[just use [Window]
Don Stewart <dons at cse.unsw.edu.au>**20070307050139] 
[url of dmenu. it now works
Don Stewart <dons at cse.unsw.edu.au>**20070307042446] 
[typo in dmenu code
Don Stewart <dons at cse.unsw.edu.au>**20070307041921] 
[X11 1.2 works too.
Spencer Janssen <sjanssen at cse.unl.edu>**20070307041540] 
[add dmenu support, seems to work, but the resulting client isn't launched
Don Stewart <dons at cse.unsw.edu.au>**20070307034738] 
[refactoring
Don Stewart <dons at cse.unsw.edu.au>**20070307033855] 
[Wm -> W, all good monads have single capital letter names. comment the W.hs file
Don Stewart <dons at cse.unsw.edu.au>**20070307033307] 
[unbox-strict-fields
Don Stewart <dons at cse.unsw.edu.au>**20070307032249] 
[comments for Main.hs, add io_, like io but return ()
Don Stewart <dons at cse.unsw.edu.au>**20070307032139] 
[comments, rename 'l' to 'io', and state explicitly that we use GeneralizedNewtypeDeriving
Don Stewart <dons at cse.unsw.edu.au>**20070307030351] 
[move thunk.hs -> Main.hs. Be precise about which versions of every package are known to work
Don Stewart <dons at cse.unsw.edu.au>**20070307025535] 
[add more readme details for finding dependencies
Don Stewart <dons at cse.unsw.edu.au>**20070307025310] 
[depend on the X11-extras package
Don Stewart <dons at cse.unsw.edu.au>**20070307024838] 
[Flatten module hierarchy
Don Stewart <dons at cse.unsw.edu.au>**20070307022332] 
[add readme
Don Stewart <dons at cse.unsw.edu.au>**20070307022301] 
[add license stuff to .cabal
Don Stewart <dons at cse.unsw.edu.au>**20070307022252] 
[more stuff for .cabal file. Add example of include path to use on OpenBSD
Don Stewart <dons at cse.unsw.edu.au>**20070307021504] 
[Initial import.
Spencer Janssen <sjanssen at cse.unl.edu>**20070307013527] 
Patch bundle hash:
25f06851d07aeb2ac3e0c665cfb0f3bcc0c92d78


More information about the xmonad mailing list