[xmonad] my proposal for a Xinerama safe PerWorkspace

Andrea Rossato andrea.rossato at unibz.it
Fri Feb 22 13:12:31 EST 2008


Hi,

this is my proposal for a Xinerama safe PerWorkspace.

It includes a new LayoutClass method:

runLayout :: Workspace WorkspaceId (layout a) a -> Rectangle -> X ([(a, Rectangle)], Maybe (layout a))

This is just some code moved around:

Fri Feb 22 18:58:15 CET 2008  Andrea Rossato <andrea.rossato at unibz.it>
  * runLayout is now a LayoutClass method and takes the Workspace and the screen Rectangle
    M ./XMonad/Core.hs -7 +7
    M ./XMonad/Operations.hs -5 +5


This is the patch to PerWorkspace:

Fri Feb 22 18:59:54 CET 2008  Andrea Rossato <andrea.rossato at unibz.it>
  * PerWorkspace: reimplemented using runLayout
  This way we have a Xinerama safe PerWorkspace and the emptyLayout
  method for free.
    M ./XMonad/Layout/PerWorkspace.hs -73 +27

Some lines were left there just because I'm lazy....;)

Cheers,
Andrea


ps: I must confess that if the runLayout method could be accepted in
the core my request of changing the 'description' type would be gone.
While my sense of symmetry would require it for implementing a
LayoutCombinator class as I have it mind, still I'm coming to thing
that, from the practical point of view, the restrictions imposed by
that signature are irrelevant for our purposes. And, probably, the
fact of restricting the class to what I call pure combinators only,
would be just fine.

This is quite a common pattern of mine when it comes to type classes:
I cannot see where I'll end up when I start implementing them. There
must be some hidden weirdness I cannot grasp entirely.
;)
-------------- next part --------------

New patches:

[runLayout is now a LayoutClass method and takes the Workspace and the screen Rectangle
Andrea Rossato <andrea.rossato at unibz.it>**20080222175815] 
<
> {
hunk ./XMonad/Core.hs 26
     ScreenId(..), ScreenDetail(..), XState(..),
     XConf(..), XConfig(..), LayoutClass(..),
     Layout(..), readsLayout, Typeable, Message,
-    SomeMessage(..), fromMessage, runLayout, LayoutMessages(..),
+    SomeMessage(..), fromMessage, LayoutMessages(..),
     runX, catchX, userCode, io, catchIO, doubleFork,
     withDisplay, withWindowSet, isRoot, runOnWorkspaces, broadcastMessage,
     getAtom, spawn, restart, getXMonadDir, recompile, trace, whenJust, whenX,
hunk ./XMonad/Core.hs 204
 --
 class Show (layout a) => LayoutClass layout a where
 
+    -- | This calls doLayout if there are any windows to be laid out, and
+    --   emptyLayout otherwise.
+    runLayout :: Workspace WorkspaceId (layout a) a -> Rectangle -> X ([(a, Rectangle)], Maybe (layout a))
+    runLayout (Workspace _ l ms) r = maybe (emptyLayout l r) (doLayout l r) ms
+
     -- | Given a Rectangle in which to place the windows, and a Stack
     -- of windows, return a list of windows and their corresponding
     -- Rectangles.  If an element is not given a Rectangle by
hunk ./XMonad/Core.hs 234
     -- 'handleMessage' returns Nothing, then the layout did not respond to
     -- that message and the screen is not refreshed.  Otherwise, 'handleMessage'
     -- returns an updated 'Layout' and the screen is refreshed.
-    --
     handleMessage :: layout a -> SomeMessage -> X (Maybe (layout a))
     handleMessage l  = return . pureMessage l
 
hunk ./XMonad/Core.hs 248
     description      = show
 
 instance LayoutClass Layout Window where
+    runLayout (Workspace i (Layout l) ms) r = fmap (fmap Layout) `fmap` runLayout (Workspace i l ms) r
     doLayout (Layout l) r s  = fmap (fmap Layout) `fmap` doLayout l r s
     emptyLayout (Layout l) r = fmap (fmap Layout) `fmap` emptyLayout l r
     handleMessage (Layout l) = fmap (fmap Layout) . handleMessage l
hunk ./XMonad/Core.hs 256
 
 instance Show (Layout a) where show (Layout l) = show l
 
--- | This calls doLayout if there are any windows to be laid out, and
---   emptyLayout otherwise.
-runLayout :: LayoutClass l a => l a -> Rectangle -> Maybe (Stack a) -> X ([(a, Rectangle)], Maybe (l a))
-runLayout l r = maybe (emptyLayout l r) (doLayout l r)
-
 -- | Based on ideas in /An Extensible Dynamically-Typed Hierarchy of Exceptions/,
 -- Simon Marlow, 2006. Use extensible messages to the handleMessage handler.
 --
hunk ./XMonad/Operations.hs 131
     let allscreens     = W.screens ws
         summed_visible = scanl (++) [] $ map (W.integrate' . W.stack . W.workspace) allscreens
     visible <- fmap concat $ forM (zip allscreens summed_visible) $ \ (w, vis) -> do
-        let n      = W.tag (W.workspace w)
-            this   = W.view n ws
-            l = W.layout (W.workspace w)
-            flt = filter (flip M.member (W.floating ws)) (W.index this)
+        let wsp   = W.workspace w
+            this  = W.view n ws
+            n     = W.tag wsp
+            flt   = filter (flip M.member (W.floating ws)) (W.index this)
             tiled = (W.stack . W.workspace . W.current $ this)
                     >>= W.filter (`M.notMember` W.floating ws)
                     >>= W.filter (`notElem` vis)
hunk ./XMonad/Operations.hs 145
 
         -- just the tiled windows:
         -- now tile the windows on this workspace, modified by the gap
-        (rs, ml') <- runLayout l viewrect tiled `catchX` runLayout (Layout Full) viewrect tiled
+        (rs, ml') <- runLayout wsp { W.stack = tiled } viewrect`catchX` runLayout wsp { W.layout = Layout Full, W.stack = tiled } viewrect
         mapM_ (uncurry tileWindow) rs
         whenJust ml' $ \l' -> runOnWorkspaces (\ww -> if W.tag ww == n
                                                       then return $ ww { W.layout = l'}
}

Context:

[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] 
[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] 
[Make Mirror implement emptyLayout
Andrea Rossato <andrea.rossato at unibz.it>**20080128001834] 
[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] 
[Add emptyLayout to LayoutClass, a method to be called when a workspace is empty
Andrea Rossato <andrea.rossato at unibz.it>**20080124013207] 
[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] 
Patch bundle hash:
c7f6d22d6c0013b5115c15802e7ecbfa118884fc
-------------- next part --------------

New patches:

[Combo: updated to latest runLayout changes
Andrea Rossato <andrea.rossato at unibz.it>**20080222175924] 
<
> {
hunk ./XMonad/Layout/Combo.hs 28
 import Data.List ( delete, intersect, (\\) )
 import Data.Maybe ( isJust )
 import XMonad hiding (focus)
-import XMonad.StackSet ( integrate, Stack(..) )
+import XMonad.StackSet ( integrate, Workspace (..), Stack(..) )
 import XMonad.Layout.WindowNavigation ( MoveWindowToWindow(..) )
 import qualified XMonad.StackSet as W ( differentiate )
 
hunk ./XMonad/Layout/Combo.hs 103
                          s2 = differentiate f' w2'
                          f' = focus s:delete (focus s) f
                      ([((),r1),((),r2)], msuper') <- doLayout super rinput superstack
-                     (wrs1, ml1') <- runLayout l1 r1 s1
-                     (wrs2, ml2') <- runLayout l2 r2 s2
+                     (wrs1, ml1') <- runLayout (Workspace "" l1 s1) r1
+                     (wrs2, ml2') <- runLayout (Workspace "" l2 s2) r2
                      return (wrs1++wrs2, Just $ C2 f' w2'
                                      (maybe super id msuper') (maybe l1 id ml1') (maybe l2 id ml2'))
     handleMessage (C2 f ws2 super l1 l2) m
}
[PerWorkspace: reimplemented using runLayout
Andrea Rossato <andrea.rossato at unibz.it>**20080222175954
 This way we have a Xinerama safe PerWorkspace and the emptyLayout
 method for free.
] 
<
> {
hunk ./XMonad/Layout/PerWorkspace.hs 13
 -- Stability   :  unstable
 -- Portability :  unportable
 --
--- Configure layouts on a per-workspace basis.  NOTE that this module
--- does not (yet) work in conjunction with multiple screens! =(
---
--- Note also that when using PerWorkspace, on initial startup workspaces
--- may not respond to messages properly until a window has been opened.
--- This is due to a limitation inherent in the way PerWorkspace is
--- implemented: it cannot decide which layout to use until actually
--- required to lay out some windows (which does not happen until a window
--- is opened).
+-- Configure layouts on a per-workspace basis.
 -----------------------------------------------------------------------------
 
hunk ./XMonad/Layout/PerWorkspace.hs 16
-module XMonad.Layout.PerWorkspace (
-                                    -- * Usage
-                                    -- $usage
-
-                                    onWorkspace, onWorkspaces
-                                  ) where
+module XMonad.Layout.PerWorkspace
+    ( -- * Usage
+      -- $usage
+      onWorkspace, onWorkspaces
+    ) where
 
 import XMonad
 import qualified XMonad.StackSet as W
hunk ./XMonad/Layout/PerWorkspace.hs 46
 -- layout D instead of C.  You could do that as follows:
 --
 -- > layoutHook = A ||| B ||| onWorkspace "foo" D C
---
--- NOTE that this module does not (yet) work in conjunction with
--- multiple screens. =(
 
 -- | Specify one layout to use on a particular workspace, and another
 --   to use on all others.  The second layout can be another call to
hunk ./XMonad/Layout/PerWorkspace.hs 55
                -> (l1 a)      -- ^ layout to use on the matched workspace
                -> (l2 a)      -- ^ layout to use everywhere else
                -> PerWorkspace l1 l2 a
-onWorkspace wsId l1 l2 = PerWorkspace [wsId] Nothing l1 l2
+onWorkspace wsId l1 l2 = PerWorkspace [wsId] True l1 l2
 
 -- | Specify one layout to use on a particular set of workspaces, and
 --   another to use on all other workspaces.
hunk ./XMonad/Layout/PerWorkspace.hs 64
                 -> (l1 a)         -- ^ layout to use on matched workspaces
                 -> (l2 a)         -- ^ layout to use everywhere else
                 -> PerWorkspace l1 l2 a
-onWorkspaces wsIds l1 l2 = PerWorkspace wsIds Nothing l1 l2
+onWorkspaces wsIds l1 l2 = PerWorkspace wsIds True l1 l2
 
 -- | Structure for representing a workspace-specific layout along with
hunk ./XMonad/Layout/PerWorkspace.hs 67
---   a layout for all other workspaces.  We store the tags of workspaces
---   to be matched, and the two layouts.  Since layouts are stored\/tracked
---   per workspace, once we figure out whether we're on a matched workspace,
---   we can cache that information using a (Maybe Bool).  This is necessary
---   to be able to correctly implement the 'description' method of
---   LayoutClass, since a call to description is not able to query the
---   WM state to find out which workspace it was called in.
+-- a layout for all other workspaces. We store the tags of workspaces
+-- to be matched, and the two layouts. We save the layout choice in
+-- the Bool, to be used to implement description.
 data PerWorkspace l1 l2 a = PerWorkspace [WorkspaceId]
hunk ./XMonad/Layout/PerWorkspace.hs 71
-                                         (Maybe Bool)
+                                         Bool
                                          (l1 a)
                                          (l2 a)
     deriving (Read, Show)
hunk ./XMonad/Layout/PerWorkspace.hs 76
 
-instance (LayoutClass l1 a, LayoutClass l2 a) => LayoutClass (PerWorkspace l1 l2) a where
-
-    -- do layout with l1, then return a modified PerWorkspace caching
-    --   the fact that we're in the matched workspace.
-    doLayout p@(PerWorkspace _ (Just True) lt _) r s = do
-        (wrs, mlt') <- doLayout lt r s
-        return (wrs, Just $ mkNewPerWorkspaceT p mlt')
-
-    -- do layout with l1, then return a modified PerWorkspace caching
-    --   the fact that we're not in the matched workspace.
-    doLayout p@(PerWorkspace _ (Just False) _ lf) r s = do
-        (wrs, mlf') <- doLayout lf r s
-        return (wrs, Just $ mkNewPerWorkspaceF p mlf')
+instance (LayoutClass l1 a, LayoutClass l2 a, Show a) => LayoutClass (PerWorkspace l1 l2) a where
+    runLayout (W.Workspace i p@(PerWorkspace wsIds _ lt lf) ms) r
+        | i `elem` wsIds = do (wrs, mlt') <- runLayout (W.Workspace i lt ms) r
+                              return (wrs, Just $ mkNewPerWorkspaceT p mlt')
+        | otherwise      = do (wrs, mlt') <- runLayout (W.Workspace i lf ms) r
+                              return (wrs, Just $ mkNewPerWorkspaceF p mlt')
 
hunk ./XMonad/Layout/PerWorkspace.hs 83
-    -- figure out which layout to use based on the current workspace.
-    doLayout (PerWorkspace wsIds Nothing l1 l2) r s = do
-        t <- getCurrentTag
-        doLayout (PerWorkspace wsIds (Just $ t `elem` wsIds) l1 l2) r s
+    handleMessage (PerWorkspace wsIds bool lt lf) m
+        | bool      = handleMessage lt m >>= maybe (return Nothing) (\nt -> return . Just $ PerWorkspace wsIds bool nt lf)
+        | otherwise = handleMessage lf m >>= maybe (return Nothing) (\nf -> return . Just $ PerWorkspace wsIds bool lt nf)
 
hunk ./XMonad/Layout/PerWorkspace.hs 87
-    -- handle messages; same drill as doLayout.
-    handleMessage p@(PerWorkspace _ (Just True) lt _) m = do
-        mlt' <- handleMessage lt m
-        return . Just $ mkNewPerWorkspaceT p mlt'
-
-    handleMessage p@(PerWorkspace _ (Just False) _ lf) m = do
-        mlf' <- handleMessage lf m
-        return . Just $ mkNewPerWorkspaceF p mlf'
-
-    handleMessage (PerWorkspace _ Nothing _ _) _ = return Nothing
-
-    description (PerWorkspace _ (Just True ) l1 _) = description l1
-    description (PerWorkspace _ (Just False) _ l2) = description l2
-
-    -- description's result is not in the X monad, so we have to wait
-    -- until a doLayout for the information about which workspace
-    -- we're in to get cached.
-    description _ = "PerWorkspace"
+    description (PerWorkspace _ True  l1 _) = description l1
+    description (PerWorkspace _ _     _ l2) = description l2
 
 -- | Construct new PerWorkspace values with possibly modified layouts.
 mkNewPerWorkspaceT :: PerWorkspace l1 l2 a -> Maybe (l1 a) ->
hunk ./XMonad/Layout/PerWorkspace.hs 93
                       PerWorkspace l1 l2 a
-mkNewPerWorkspaceT (PerWorkspace wsIds b lt lf) mlt' =
-    (\lt' -> PerWorkspace wsIds b lt' lf) $ fromMaybe lt mlt'
+mkNewPerWorkspaceT (PerWorkspace wsIds _ lt lf) mlt' =
+    (\lt' -> PerWorkspace wsIds True lt' lf) $ fromMaybe lt mlt'
 
 mkNewPerWorkspaceF :: PerWorkspace l1 l2 a -> Maybe (l2 a) ->
                       PerWorkspace l1 l2 a
hunk ./XMonad/Layout/PerWorkspace.hs 98
-mkNewPerWorkspaceF (PerWorkspace wsIds b lt lf) mlf' =
-    (\lf' -> PerWorkspace wsIds b lt lf') $ fromMaybe lf mlf'
-
--- | Get the tag of the currently active workspace.  Note that this
---   is only guaranteed to be the same workspace for which doLayout
---   was called if there is only one screen.
-getCurrentTag :: X WorkspaceId
-getCurrentTag = gets windowset >>= return . W.tag . W.workspace . W.current
+mkNewPerWorkspaceF (PerWorkspace wsIds _ lt lf) mlf' =
+    (\lf' -> PerWorkspace wsIds False lt lf') $ fromMaybe lf mlf'
}

Context:

[Decoration: some haddock updates
Andrea Rossato <andrea.rossato at unibz.it>**20080220214934] 
[Decoration: fix an issue with decoration window creation and more
Andrea Rossato <andrea.rossato at unibz.it>**20080220204355
 - fix a bug reported by Roman Cheplyaka: when decorate returned
   Nothing the window was never going to be created, even if decorate
   was reporting a Just Rectangle in the next run. Quite a deep issue,
   still visible only with TabbedDecoration at the present time.
 - remove decorateFirst (decorate has enough information to decide
   whether a window is the first one or not, am I right, David?)
 - some point free.
] 
[DynamicLog.hs: haddock fix
Andrea Rossato <andrea.rossato at unibz.it>**20080220204033
 
 Someone forgot to check if her patch was going to break haddock docs
 generation or not. So, while I was recording a patch with quite a long
 description I had to manually write - sound strange? -, I found out
 that my patch did not pass the tests, because of this haddock problem
 left behind.
 
 And so I fixed it, recorded this patch, with the hope the my next
 description of the next patch I'm going to record will survive the
 test suite we created to avoid this kind of problems for.
] 
[improvements to XMonad.Hooks.DynamicLog, and new contrib module XMonad.Util.Loggers
Brent Yorgey <byorgey at gmail.com>**20080219210128
 Improvements to DynamicLog include:
   * Greatly expanded and improved documentation and examples
   * remove seemingly useless makeSimpleDzenConfig function
   * factor out xmobarPP
   * add new ppExtras field to PP record, for specifying 'extra'
     loggers which can supply information other than window title,
     layout, and workspace status to a status bar (for example, time and date,
     battery status, mail status, etc.)
 
 The new XMonad.Util.Loggers module provides some example loggers that 
 can be used in the new ppExtras field of the PP record.  Create your own,
 add them to this module, go crazy! =)
 
] 
[LayoutHints: fix a wrong fix
Andrea Rossato <andrea.rossato at unibz.it>**20080219165127
 The case analisys of my fix should be the other way around... this is
 the real fix.
] 
[Arossato: updated to latest changes
Andrea Rossato <andrea.rossato at unibz.it>**20080219163058] 
[Decoration: comment only
Andrea Rossato <andrea.rossato at unibz.it>**20080219161339
 This is a detailed commentary of all the code.
] 
[Fix doc for Tabbed
Roman Cheplyaka <roma at ro-che.info>**20080219055650] 
[Decoratione: generate rectangles first, and create windows accordingly
Andrea Rossato <andrea.rossato at unibz.it>**20080219122115
 With this patch Decoration will first generate a rectangle and only if
 there is a rectangle available a window will be created.
 
 This makes the Decoration state a bit more difficult to process, but
 should reduce resource consumption.
] 
[Tabbed and TabBarDecoration: no need to implement decorateFirst (the default is used)
Andrea Rossato <andrea.rossato at unibz.it>**20080218184950] 
[TabBarDecoration: simpleTabBar automatically applies resizeVertical
Andrea Rossato <andrea.rossato at unibz.it>**20080218180922
 Added some comments too.
] 
[DwmStyle: comment fix only
Andrea Rossato <andrea.rossato at unibz.it>**20080218180727] 
[ResizeScreen: add resizeHorizontalRight and resizeVerticalBottom
Andrea Rossato <andrea.rossato at unibz.it>**20080218180504] 
[Add TabBarDecoration, a layout modifier to add a bar of tabs to any layout
Andrea Rossato <andrea.rossato at unibz.it>**20080218161121
 ... and port DecorationMadness to the new system.
] 
[add Eq superclass to DecorationStyle and change styles in order not to decorate non managed windows
Andrea Rossato <andrea.rossato at unibz.it>**20080218131320] 
[Refactor MouseResize, remove isDecoration and introduce isInStack, isVisible, isInvisible
Andrea Rossato <andrea.rossato at unibz.it>**20080218105726
 This patch includes several changes, which are strictly related and
 cannot be recorded separately:
 - remove Decoraion.isDecoartion and introduce Decoration.isInStack
   (with the related change to LayoutHints)
 - in Decoration introduce useful utilities: isVisible, isInvisible,
   isWithin and lookFor'
 - MouseResize: - invisible inputOnly windows will not be created;
 	       - fix a bug in the read instance which caused a failure
                  in the state deserialization.
] 
[Prompt: regenerate completion list if there's just one completion
Andrea Rossato <andrea.rossato at unibz.it>**20080217132734] 
[Prompt.Theme: use mkComplFunFromList' to generate completions
Andrea Rossato <andrea.rossato at unibz.it>**20080217124453] 
[some code formatting
Andrea Rossato <andrea.rossato at unibz.it>**20080217124434] 
[Prompt: comment only (clafiry completionToCommand uses)
Andrea Rossato <andrea.rossato at unibz.it>**20080216181620] 
[Prompt: comment only (remove confusing remarks about commandToComplete)
Andrea Rossato <andrea.rossato at unibz.it>**20080216180412] 
[Prompt: haddock fixes only
Andrea Rossato <andrea.rossato at unibz.it>**20080216172331] 
[Prompt.XMonad: use mkComplFunFromList' to get all the completions with an empty command line
Andrea Rossato <andrea.rossato at unibz.it>**20080216133949] 
[Prompt.Window: remove unneeded and ugly escaping/unescaping
Andrea Rossato <andrea.rossato at unibz.it>**20080216133842] 
[Theme: move theme's nextCompletion implementation to Prompt.getNextCompletion
Andrea Rossato <andrea.rossato at unibz.it>**20080216133738] 
[Shell: escape the string in the command line only
Andrea Rossato <andrea.rossato at unibz.it>**20080216133651] 
[Prompt: add some methods to make completions more flexible
Andrea Rossato <andrea.rossato at unibz.it>**20080216133454
 - now it is possible to decide if the prompt will complete the last
   word of the command line or the whole line (default is the last
   word);
 - completing the last word can be fine tuned by implementing
   'commandToComplete' and 'completionToCommand': see comments for
   details;
 - move mkComplFunFromList' from TagWindows to Prompt.
] 
[Prompt.Theme: display all theme information and handle completion accordingly
Andrea Rossato <andrea.rossato at unibz.it>**20080216114159] 
[Prompt.Shell: if there's just one completion and it is a directory add a trailing slash
Andrea Rossato <andrea.rossato at unibz.it>**20080216114005] 
[Prompt: added nextCompletion and commandToComplete methods to fine tune prompts' completion functions
Andrea Rossato <andrea.rossato at unibz.it>**20080216113723] 
[Util.Themes: add ppThemeInfor to render the theme info
Andrea Rossato <andrea.rossato at unibz.it>**20080216113635] 
[DecorationMadness: resizable layouts now use MouseResize too
Andrea Rossato <andrea.rossato at unibz.it>**20080212173645] 
[SimpleFloat now uses MouseResize
Andrea Rossato <andrea.rossato at unibz.it>**20080212173615] 
[Add Actions.MouseResize: a layout modifier to resize windows with the mouse
Andrea Rossato <andrea.rossato at unibz.it>**20080212173455] 
[Decoration: remove mouse resize and more
Andrea Rossato <andrea.rossato at unibz.it>**20080212165306
 - since mouse resize is not related to decoration, I removed the code
   from here. Mouse resize will be handled by a separated layout
   modifier (in a separated module)
 - now also stacked decoration will be removed (I separated insert_dwr
   from remove_stacked)
] 
[Refactor XMonad.Hooks.DynamicLog
Roman Cheplyaka <roma at ro-che.info>**20080210222406
 This allows using DynamicLog not only for statusbar.
] 
[Decoration.hs: variable names consistency only
Andrea Rossato <andrea.rossato at unibz.it>**20080211123056] 
[Tabbed and SimpleTabbed (in DecorationMadness) define their own decorationMouseDragHook method
Andrea Rossato <andrea.rossato at unibz.it>**20080211114043
 ... to disable mouse drag in tabbed layouts
] 
[Decoration: DecorationStyle class cleanup and focus/drag unification
Andrea Rossato <andrea.rossato at unibz.it>**20080211113650
 - moved decoEventHook to decorationEventHook
 - added decorationMouseFocusHook, decorationMouseDragHook,
   decorationMouseResizeHook methods
 - added a handleMouseFocusDrag to focus and drag a window (which makes
   it possible to focus *and* drag unfocused windows too
] 
[DecorationMadness: comment only
Andrea Rossato <andrea.rossato at unibz.it>**20080210131427] 
[DecorationMadness: added a few floating layouts
Andrea Rossato <andrea.rossato at unibz.it>**20080210122523] 
[SimpleFloat: export SimpleFloat and add documentation
Andrea Rossato <andrea.rossato at unibz.it>**20080210113159] 
[Move DefaultDecoration from DecorationMadness to Decoration
Andrea Rossato <andrea.rossato at unibz.it>**20080210104304] 
[Themes: added robertTheme and donaldTheme
Andrea Rossato <andrea.rossato at unibz.it>**20080210083016] 
[DecorationMadness: make tunable tabbed layouts respect the Theme decoHeight field
Andrea Rossato <andrea.rossato at unibz.it>**20080210075322] 
[WindowGo.hs: fix syntax in example
Brent Yorgey <byorgey at gmail.com>**20080209225135] 
[+doc for WindowGo.hs: I've discovered a common usecase for me for raiseMaybe
gwern0 at gmail.com**20080205032155] 
[Run.hs: add an option to runinterms
gwern0 at gmail.com**20080205031824
 It turns out that for urxvt, and most terminal, apparently, once you give a '-e' option, that's it.
 They will not interpret anything after that as anything but input for /bin/sh, so if you wanted to go 'runInTerm "'screen -r session' -title IRC"',
 you were SOL - the -title would not be seen by urxvt. This, needless to say, is bad, since then you can't do stuff like set the title which means
 various hooks and extensions are helpless. This patch adds an extra options argument which is inserted *before* the -e. If you want the old behaivour,
 you can just go 'runInTerm "" "executable"', but now if you need to do something extra, 'runInTerm "-title mutt" "mutt"' works fine.
 
 This patch also updates callers.
] 
[ScreenResize: vertical and horizontal now respond to SetTheme
Andrea Rossato <andrea.rossato at unibz.it>**20080210074544
 And so they will change the screen dimension accordingly.
] 
[Add DecorationMadness: a repository of weirdnesses
Andrea Rossato <andrea.rossato at unibz.it>**20080209182515] 
[Decoration: change mouseEventHook to decoEventHook and more
Andrea Rossato <andrea.rossato at unibz.it>**20080209165101
 Fix also the problem with window's movement when the grabbing starts
] 
[Tabbed: add simpleTabbed and fx documentation
Andrea Rossato <andrea.rossato at unibz.it>**20080209163917
 simpleTabbed is just a version of tabbed with default theme and
 default srhinker.
] 
[Arossato: update to latest changes
Andrea Rossato <andrea.rossato at unibz.it>**20080208140604] 
[Decoration: enable mouse dragging of windows
Andrea Rossato <andrea.rossato at unibz.it>**20080208083602] 
[WindowArranger: add a SetGeometry message - needed to enable mouseDrag
Andrea Rossato <andrea.rossato at unibz.it>**20080208083413] 
[Decoration: add a mouseEventHook methohd and move mouse button event there
Andrea Rossato <andrea.rossato at unibz.it>**20080208073514] 
[Util.Thems: some more typos in comments
Andrea Rossato <andrea.rossato at unibz.it>**20080207233341] 
[Util.Themes: documentation and export list (added themes that have been left out)
Andrea Rossato <andrea.rossato at unibz.it>**20080207232251] 
[Prompt.Theme: comments and some point-free
Andrea Rossato <andrea.rossato at unibz.it>**20080207232155] 
[oxymor00nTheme
<its.sec at gmx.net>**20080207213100] 
[add swapScreen to CycleWS
<its.sec at gmx.net>**20080206191032
 * add support for swapping the workspaces on screens to CycleWS
] 
[Decoration: consistency of variable names
Andrea Rossato <andrea.rossato at unibz.it>**20080207191442
 Since the configuration is now called Theme, the variable 'c' is now a
 't'
] 
[Add Prompt.Theme: a prompt for dynamically applying a theme to the current workspace
Andrea Rossato <andrea.rossato at unibz.it>**20080207184321] 
[Decoration: add a SetTheme message and releaseResources
Andrea Rossato <andrea.rossato at unibz.it>**20080207184048
 ...which should make it harder to forget to release the font structure.
] 
[cabal file: respect alphabetic order for modules
Andrea Rossato <andrea.rossato at unibz.it>**20080207183153] 
[Add Util.Themes to collect user contributed themes
Andrea Rossato <andrea.rossato at unibz.it>**20080207182843] 
[SimpleFloat: comment only
Andrea Rossato <andrea.rossato at unibz.it>**20080207182438] 
[Update to safer initColor api
Don Stewart <dons at galois.com>**20080206192232] 
[ XMonad.Actions.WindowGo: add a runOrRaise module for Joseph Garvin with the help of Spencer Janssen
gwern0 at gmail.com**20080204173402] 
[use Util.WorkspaceCompare in Prompt.Workspace.
David Roundy <droundy at darcs.net>**20080206004057] 
[roll back to previous version of Droundy.hs.
David Roundy <droundy at darcs.net>**20080205204043
 
 A cleaner WindowNavigation fix made the separation of tabbed and addTabs
 not strictly necessary (but still a desireable possibility in my opinion,
 as it allows pretty decoration of non-composite layouts that might want to
 have some of their windows tabbed.
] 
[make WindowNavigation ignore decorations.
David Roundy <droundy at darcs.net>**20080205203556] 
[make tabbed work nicely with LayoutCombinators and WindowNavigation.
David Roundy <droundy at darcs.net>**20080205202343
 The problem is that WindowNavigation assumes all windows are navigable, and
 it was getting confused by decorations.  With a bit of work, we can
 decorate windows *after* combining layouts just fine.
] 
[make WindowNavigation work when windows are stacked.
David Roundy <droundy at darcs.net>**20080205202027] 
[enable proper handling of panels in droundy config.
David Roundy <droundy at darcs.net>**20080204030843] 
[enable button click for focus in tabbed.
David Roundy <droundy at darcs.net>**20080204010536
 Note that this patch doesn't work with
 
 Thu Dec 27 03:03:56 EST 2007  Spencer Janssen <sjanssen at cse.unl.edu>
   * Broadcast button events to all layouts, fix for issue #111
 
 but this isn't a regression, since button events have never worked with
 tabbed and this change.
] 
[in Decoration, remove windows that are precisely hidden underneath other windows.
David Roundy <droundy at darcs.net>**20080204005413
 This is needed for WindowNavigation to work properly with the new
 Decorations framework.
] 
[switch tabbed back to using Simplest (so tabs will be shown).
David Roundy <droundy at darcs.net>**20080204005350] 
[CycleWS: change example binding for toggleWS from mod-t to mod-z.  example bindings shouldn't conflict with default key bindings.
Brent Yorgey <byorgey at gmail.com>**20080201202126] 
[REMOVE RotView: use CycleWS instead.
Brent Yorgey <byorgey at gmail.com>**20080201180618
 See CycleWS docs for info on switching, or just look at the changes to
 XMonad.Config.Droundy.
] 
[CycleWS: add more general functionality that now subsumes the functionality of RotView.  Now with parameterized workspace sorting and predicates!
Brent Yorgey <byorgey at gmail.com>**20080201121524] 
[WorkspaceCompare: some refactoring.
Brent Yorgey <byorgey at gmail.com>**20080201120430
   * Export WorkspaceCompare and WorkspaceSort types.
   * Extract commonality in sort methods into mkWsSort, which creates
     a workspace sort from a workspace comparison function.
   * Rename getSortByTag to getSortByIndex, since it did not actually sort
     by tag at all; it sorts by index of workspace tags in the user's config.
   * Create a new getSortByTag function which actually does sort
     lexicographically by tag.
   * Enhance documentation.
] 
[Search.hs: haddock cleanup
Brent Yorgey <byorgey at gmail.com>**20080131161948] 
[Added a handy tip to the documentation of XMonad.Actions.Search
v.dijk.bas at gmail.com**20080131122620
 The tip explains how to use the submap action to create a handy submap of keybindings for searching.
] 
[Make LayoutHints a decoration aware layout modifier
Andrea Rossato <andrea.rossato at unibz.it>**20080131082314] 
[Remove LayoutCombinator class and revert PerWorkspace to its Maybe Bool state
Andrea Rossato <andrea.rossato at unibz.it>**20080131063929
 As I said in order to have a CombinedLayout type instace of
 LayoutClass and a class for easily writing pure and impure combinators
 to be feeded to the CombinedLayout together with the layouts to be
 conbined, there's seems to be the need to change the type of the
 LayoutClass.description method from l a -> String to l a -> X String.
 
 Without that "ugly" change - loosing the purity of the description
 (please note the *every* methods of that class unless description
 operates in the X monad) - I'm plainly unable to write something
 really useful and maintainable. If someone can point me in the right
 direction I would really really appreciate.
 
 Since, in the meantime, PerWorkspace, which has its users, is broken
 and I broke it, I'm reverting it to it supposedly more beautiful
 PerWorkspac [WorkspaceId] (Maybe Bool) (l1 a) (l2 a) type.
] 
[Extending.hs: documentation update
Brent Yorgey <byorgey at gmail.com>**20080131012728] 
[DynamicLog: lots of additional documentation; add byorgeyPP as an example dzen config
Brent Yorgey <byorgey at gmail.com>**20080130205219] 
[Extended PP with sorting algorithm specification and added xinerama sorting
Juraj Hercek <juhe_xmonad at hck.sk>**20080109154923
   algorithm
   - idea is to specify sorting algorithm from user's xmonad.hs
   - xinerama sorting algorithm produces same ordering as
     pprWindowSetXinerama
   - default ppSort is set to getSortByTag, so the default functionality
     is the same as it was before
] 
[SimpleDecoration: export defaultTheme
Andrea Rossato <andrea.rossato at unibz.it>**20080130124609] 
[Various decorations related updates
Spencer Janssen <sjanssen at cse.unl.edu>**20080130064624
  * remove deprecated TConf stuff
  * Remove 'style' from DeConf
  * Change DeConf to Theme
  * share defaultTheme across all decorations
] 
[TwoPane: add description string
Joachim Fasting <joachim.fasting at gmail.com>**20080126141332] 
[add XMonad.Actions.CycleSelectedLayouts
Roman Cheplyaka <roma at ro-che.info>**20080116205020] 
[Search.hs: add documentation and two more search engines (MathWorld and Google Scholar)
Brent Yorgey <byorgey at gmail.com>**20080128190443] 
[xmonad-contrib.cabal: add build-type field to get rid of Cabal warning
Brent Yorgey <byorgey at gmail.com>**20080128190137] 
[LayoutCombinator class: code clean up
Andrea Rossato <andrea.rossato at unibz.it>**20080129224952
 - ComboType becomes CombboChooser
 - removed the stupid doFirst
 - better comboDescription default implemenation
] 
[add emptyLayout to MultiToggle
Lukas Mai <l.mai at web.de>**20080128175313] 
[grammar fix
Lukas Mai <l.mai at web.de>**20080128175059] 
[Add a LayoutCombinator class and a CombinedLayout and port PerWorkspace to the new system
Andrea Rossato <andrea.rossato at unibz.it>**20080129192903] 
[Named: reimplemented as a LayoutModifier and updated Config.Droundy accordingly
Andrea Rossato <andrea.rossato at unibz.it>**20080128161343] 
[LayoutModifier: add modifyDescription for completely override the modified layout description
Andrea Rossato <andrea.rossato at unibz.it>**20080128160614] 
[Make ToggleLayouts and Named implement emptyLayout
Andrea Rossato <andrea.rossato at unibz.it>**20080128151535] 
[Decoration: the fontset must be released even when we don't decorate the first window
Andrea Rossato <andrea.rossato at unibz.it>**20080128004411
 This is quite an old bug! It affected Tabbed since the very beginning..;)
] 
[TAG 0.6
Spencer Janssen <sjanssen at cse.unl.edu>**20080127222114] 
[depend on xmonad-0.6
Spencer Janssen <sjanssen at cse.unl.edu>**20080127221101] 
[Bump version to 0.6
Spencer Janssen <sjanssen at cse.unl.edu>**20080127211504] 
[I use urxvtc now
Spencer Janssen <sjanssen at cse.unl.edu>**20080127211452] 
[Update the test hook
Spencer Janssen <sjanssen at cse.unl.edu>**20080127205148] 
[add 'single' helper function
Lukas Mai <l.mai at web.de>**20080117234550] 
[documentation fix
Lukas Mai <l.mai at web.de>**20080117234401] 
[style assimilation
Lukas Mai <l.mai at web.de>**20080117234059] 
[Decoration: I forgot we need to release the fontset too!
Andrea Rossato <andrea.rossato at unibz.it>**20080127233521] 
[Decoration: after deleting the windows we must update the layout modifier
Andrea Rossato <andrea.rossato at unibz.it>**20080127231815
 Thanks to Feuerbach for reporting this.
] 
[Reflect: reimplemented as a layout modifier (which makes it compatible with windowArranger and decoration)
Andrea Rossato <andrea.rossato at unibz.it>**20080127165854] 
[SimpleFLoat: change the description to Float (Simple is the decoration description)
Andrea Rossato <andrea.rossato at unibz.it>**20080127144556] 
[ManageDocks: implement AvoidStruts as a layout modifier
Andrea Rossato <andrea.rossato at unibz.it>**20080127144301] 
[ResizeScreen has been rewritten as a layout modifier
Andrea Rossato <andrea.rossato at unibz.it>**20080127140837] 
[LayoutModifier add a modifyLayout
Andrea Rossato <andrea.rossato at unibz.it>**20080127140219
 Many layouts are written as layout modifiers because they need to
 change the stack of the rectangle before executing doLayout.
 
 This is a major source of bugs. all layout modifiers should be using the
 LayoutModifier class. This method (modifyLayout) can be used to
 manipulate the rectangle and the stack before running doLayout by the
 layout modifier.
] 
[Make LayoutCombinators deal with emptyLayout
Andrea Rossato <andrea.rossato at unibz.it>**20080127092415] 
[Add ResizeScreen, a layout modifier for modifing the screen geometry
Andrea Rossato <andrea.rossato at unibz.it>**20080127010755] 
[WindowArranger can now arrange all windows
Andrea Rossato <andrea.rossato at unibz.it>**20080126233053
 This is useful for SimpleFloat, whose state can now persists across
 layout switches.
] 
[Arossato: updated my config to recent changes
Andrea Rossato <andrea.rossato at unibz.it>**20080126205638] 
[Add SimpleFloat a very basic floating layout that will place windows according to their size hints
Andrea Rossato <andrea.rossato at unibz.it>**20080126205410] 
[WindoWrranger: export the WindowArranger type (see the upcoming SimpleFloat)
Andrea Rossato <andrea.rossato at unibz.it>**20080126204605] 
[ShowWName: show the name of empty layouts too
Andrea Rossato <andrea.rossato at unibz.it>**20080126190214] 
[ManageDocks: add emptyLayout definition for supporting the new decoration framework
Andrea Rossato <andrea.rossato at unibz.it>**20080126185936] 
[Decoration: code formatting only
Andrea Rossato <andrea.rossato at unibz.it>**20080126101354] 
[export DeConfig to avoid importing Decoration
Andrea Rossato <andrea.rossato at unibz.it>**20080126101049] 
[Prompt: code formatting only
Andrea Rossato <andrea.rossato at unibz.it>**20080126093234] 
[Don't export TConf anymore and export DeConfig instead
Andrea Rossato <andrea.rossato at unibz.it>**20080126092141
 WARNING: this patch may be breaking your configuration. While it is
 still possible to use:
 
 tabbed shrinkText defaultTConf
 
 updating the fields of the defaultTConf record is not possible
 anymore, since the type TConf is now hidden.
 
 WARNING: "tabSize" has been substituted by "decoHeight"
 
 You can change your configuration this way:
 myTConf :: TConf
 myTConf = defaultTConf
        { tabSize = 15
        , etc....
 
 becomes:
 myTConf :: DeConfig TabbedDecoration Window
 myTConf = defaultTabbedConfig
        { decoHeight = 15
        , etc....
 
 and
 tabbed shrinkText myTConf
 
 becomes:
 tabDeco shrinkText myTConf
 
] 
[Tabbed now uses Decoration
Andrea Rossato <andrea.rossato at unibz.it>**20080125152311] 
[Add DwmStyle, a layout modifier to add dwm-style decorations to windows in any layout
Andrea Rossato <andrea.rossato at unibz.it>**20080125152152] 
[Adde SimpleDecoration, a layout modifier to add simple decorations to windows in any layout
Andrea Rossato <andrea.rossato at unibz.it>**20080125152106] 
[Add Layout.Simplest, the simplest layout
Andrea Rossato <andrea.rossato at unibz.it>**20080125152015] 
[Add Decoration, a layout modifier and a class for easily writing decorated layouts
Andrea Rossato <andrea.rossato at unibz.it>**20080125151726] 
[Add WindowArranger, a layout modifier to move and resize windows with the keyboard
Andrea Rossato <andrea.rossato at unibz.it>**20080125151633] 
[ShowWName: moved fi to XUtils
Andrea Rossato <andrea.rossato at unibz.it>**20080124134725] 
[XUtils: add functions for operating on lists of windows and export fi
Andrea Rossato <andrea.rossato at unibz.it>**20080124134638] 
[LayoutModifier: add emptyLayoutMod for dealing with empty workspaces
Andrea Rossato <andrea.rossato at unibz.it>**20080124015605] 
[LayoutModifier: add pureMess and pureModifier to the LayoutModifier class
Andrea Rossato <andrea.rossato at unibz.it>**20080122111319] 
[cleared up transience to better highlight how to use ManageHooks properly
xmonad-contrib at hexago.nl**20080102074810
 
 The initial patch that extended the EDSL for writing ManageHook rules did not come with a good example on how to use it.  This patch ammends that. 'move' is an example of how to write a rule to resolve a Query (Maybe a) into something tangible.  'move'' is an example of how to write a rule isolating window managing code from the rest ofthe mess the EDSL creates.
] 
[expands the EDSL for performing actions on windows
xmonad-contrib at hexago.nl**20080101174446
 
 This patch adds a few types of relationships and operators for managing windows with rules.  It provides grouping operators so the X action can access the quantifier that was matched or not matched.  It provides a formalism for predicates that work in both grouping and non grouping rules.  It could do with some classes, so that there are fewer operators that always do the Right Thing (TM), but the Haskell Type system currently has some problems resolving types.  Since I don't know enough about these high level things, it would be hard to create a GHC patch just to make it all work.
] 
[-Werror when flag(testing) only
Spencer Janssen <sjanssen at cse.unl.edu>**20080118015207] 
[Reflect.hs: minor haddock fix
Brent Yorgey <byorgey at gmail.com>**20080116203546] 
[Reflect.hs: use -fglasgow-exts for now instead of LANGUAGE pragmas, for compatibility with ghc 6.6
Brent Yorgey <byorgey at gmail.com>**20080115194811] 
[Reflect.hs: add MultiToggle support
Brent Yorgey <byorgey at gmail.com>**20080115193519] 
[MultiToggle.hs: improve 'description' implementation in LayoutClass instance to display the current transformed layout rather than just 'MultiToggle'
Brent Yorgey <byorgey at gmail.com>**20080115193311] 
[Layout.ShowWName: generalize the instance
Andrea Rossato <andrea.rossato at unibz.it>**20080115045139] 
[Layout.Reflect: new contrib module for reflecting layouts horizontally/vertically
Brent Yorgey <byorgey at gmail.com>**20080115030947] 
[Timer: some code cleanup
Andrea Rossato <andrea.rossato at unibz.it>**20080114211114] 
[Use doubleFork instead of manual double fork, or buggy single fork.
nicolas.pouillard at gmail.com**20080114202833
 
 This fixes showWName because Timer was leaking zombie processes.
 You should update xmonad, since doubleFork was not exported.
] 
[ShowWName.hs: switch color/bgcolor in call to paintAndWrite
Brent Yorgey <byorgey at gmail.com>**20080114153821] 
[Prompt: clean up and optimize moveWord a bit
Andrea Rossato <andrea.rossato at unibz.it>**20080113164745] 
[Prompt: added moveWord to move the cursor to the word boundaries
Andrea Rossato <andrea.rossato at unibz.it>**20080113123529
 The actions have been bound to ctrl+Left and Right
] 
[Doc.Extending: added links and description of recent module addition
Andrea Rossato <andrea.rossato at unibz.it>**20080113093211] 
[Action.Search: small haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20080113092646] 
[ShowWName now uses Timer and XUtils to display the workspace name
Andrea Rossato <andrea.rossato at unibz.it>**20080113091107] 
[Add XMonad.Util.Timer, a module to set up timers and to handle them
Andrea Rossato <andrea.rossato at unibz.it>**20080113090140] 
[de-obfuscate the initState and set the init offset to the length of the default text
Andrea Rossato <andrea.rossato at unibz.it>**20080110140951] 
[prompt: Allow to provide a default text in the prompt config.
nicolas.pouillard at gmail.com**20080109213916] 
[Correct caps in module header.
Joachim Fasting <joachim.fasting at gmail.com>**20071230061920] 
[Use LANGUAGE pragma.
Joachim Fasting <joachim.fasting at gmail.com>**20071230061817] 
[shiftPrevScreen and shiftNextScreen, to make CycleWS consistent
mail at joachim-breitner.de**20071231171609] 
[formatting
Don Stewart <dons at galois.com>**20071204174920] 
[PerWorkspace.hs: add an explanatory note
Brent Yorgey <byorgey at gmail.com>**20071231135806] 
[Add ShowWName a layout modifier to show the workspace name
Andrea Rossato <andrea.rossato at unibz.it>**20071231130441
 This module requires dzen
] 
[ManageDocks: some documentation fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071231101820] 
[-Wall police (again)
Spencer Janssen <sjanssen at cse.unl.edu>**20071228061841] 
[-Wall police
Spencer Janssen <sjanssen at cse.unl.edu>**20071228061822] 
[Fulfill the EWMH specification by listing the supported ATOMs, doesnt really make a differene AFAIK
mail at joachim-breitner.de**20071227215607] 
[display all visible windows on the current desktop in the pager
mail at joachim-breitner.de**20071227204349
 This is my best shot at modeling xmonad’s WM behaviour in a way that
 the Extended Window Manager Hints specification allows.
 
 Unfortunately, we can not tell the panel what size and position it should
 think the apps are.
] 
[Although I do not need the curr variable after all, this is nicer
mail at joachim-breitner.de**20071227190113] 
[Add support for cycling through screens to CycleWS
mail at joachim-breitner.de**20071227182635] 
[Clear _NET_ACTIVE_WINDOW when nothing is focused
mail at joachim-breitner.de**20071228154222] 
[textExtentsXMF doesn't require the display
Andrea Rossato <andrea.rossato at unibz.it>**20071228125913] 
[Don't bother checking executable bits of items in $PATH, yields a significant speed-up
Spencer Janssen <sjanssen at cse.unl.edu>**20071226032412] 
[ResizableTile.hs: fix resizing to work in the presence of floating windows (resolves issue #100)
Brent Yorgey <byorgey at gmail.com>**20071225135839] 
[LayoutScreens: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071225105316] 
[XMonad.Actions.Search: haddock fix
Andrea Rossato <andrea.rossato at unibz.it>**20071224171115] 
[Fix isssue 105
Andrea Rossato <andrea.rossato at unibz.it>**20071224171020
 issue 105 was due to the fact that tab windows created when
 bootstrapping the windowset after a restart where managed. Setting the
 override_redirect attributes to True fixes the issue.
 
 Added the possibility to set the override_redirect attribute with
 XMonad.Util.XUtils.creationNewWindow
] 
[Prompt.hs: mv .xmonad_history into .xmonad/
gwern0 at gmail.com**20071224054610
 See my email to mailing list. This will slightly break anyone who upgrades while running and expects to see their prompt history, and leave a stray file, I think, but nothing else, and it'll permanently improve tab-completion, and is tidier.
] 
[Search.hs: +docs, and export simpleEngine so users can define their own
gwern0 at gmail.com**20071224043828] 
[Search.hs: mv into Actions/ per IRC suggestion
gwern0 at gmail.com**20071224043735] 
[add XMonad.Actions.NoBorders
Lukas Mai <l.mai at web.de>**20071220203953] 
[AvoidStruts: add support for partial struts
Spencer Janssen <sjanssen at cse.unl.edu>**20071222133425] 
[Search.hs: add hoogle
Brent Yorgey <byorgey at gmail.com>**20071222184912] 
[ManageDocks: ignore desktop windows also
Spencer Janssen <sjanssen at cse.unl.edu>**20071222113808] 
[Wibble
Spencer Janssen <sjanssen at cse.unl.edu>**20071222110641] 
[EwmhDesktops: add _NET_ACTIVE_WINDOW support
Spencer Janssen <sjanssen at cse.unl.edu>**20071222110552] 
[A few short comments for WorkspaceCompare
Spencer Janssen <sjanssen at cse.unl.edu>**20071222105045] 
[EwmhDesktops: drop 'Workspace' from displayed workspace names
Spencer Janssen <sjanssen at cse.unl.edu>**20071222104559] 
[Factor workspace sorting into a separate module
Spencer Janssen <sjanssen at cse.unl.edu>**20071222104114] 
[No more tabs
Spencer Janssen <sjanssen at cse.unl.edu>**20071222050439] 
[Refactor Search.hs
Spencer Janssen <sjanssen at cse.unl.edu>**20071222044714] 
[Generalize XSelection functions to MonadIO
Spencer Janssen <sjanssen at cse.unl.edu>**20071222044514] 
[Search.hs: +imdb & amazon engines for unk_red
gwern0 at gmail.com**20071222035837] 
[Search.hs: cleanup and refactor
gwern0 at gmail.com**20071220174001] 
[Update various restart bindings
Spencer Janssen <sjanssen at cse.unl.edu>**20071219220634] 
[Fix typo.
Roman Cheplyaka <roma at ro-che.info>**20071219073857] 
[Doc/Developing.hs: add some information about Haddock documentation.
Brent Yorgey <byorgey at gmail.com>**20071219215300] 
[require haddock documentation to build successfully in order to record a patch.
Brent Yorgey <byorgey at gmail.com>**20071219215217] 
[Remove inaccurate comment about 'banish'
Spencer Janssen <sjanssen at cse.unl.edu>**20071217231540] 
[Warp.hs: haddock fixes
Brent Yorgey <byorgey at gmail.com>**20071217224712] 
[Warp.hs: +doc
gwern0 at gmail.com**20071216030015
 Describe how to emulate Ratpoison's 'banish' functionality on one's config
] 
[Util/Search.hs: a few updates/fixes
Brent Yorgey <byorgey at gmail.com>**20071217222930
   * fix shadowing warning (ghc 6.8.2 complains)
   * export a few more of the functions
   * re-de-obfuscate generated URLs by not escaping alphanumerics or punct.
] 
[Util.Search: import escapeURIString, and fall back on the ugly const false hack to avoid copy-pasting even more
gwern0 at gmail.com**20071215211638] 
[update Config.Droundy to use a few nice hooks.
David Roundy <droundy at darcs.net>**20071216185653] 
[Add UrgencyHook support to Tabbed
Shachaf Ben-Kiki <shachaf at gmail.com>**20071215171617] 
[DynamicLog.hs: some documentation updates.
Brent Yorgey <byorgey at gmail.com>**20071215143727] 
[DynamicLog.hs: fix shadowing warning
Brent Yorgey <byorgey at gmail.com>**20071215143227] 
[Add UrgencyHook support to DynamicLog
Shachaf Ben-Kiki <shachaf at gmail.com>**20071214043528
 Someone with Xinerama should look at this -- I don't know exactly how that
 should behave.
] 
[Depend on X11-1.4.1, it has crucial bugfixes
Spencer Janssen <sjanssen at cse.unl.edu>**20071215022151] 
[Remove network dependency, potentially breaking XMonad.Util.Search
Spencer Janssen <sjanssen at cse.unl.edu>**20071214231859] 
[Search.hs: fix shadowing warning and haddock errors
Brent Yorgey <byorgey at gmail.com>**20071214163119] 
[+cabal support for XMonad.Util.Search
gwern0 at gmail.com**20071213205654] 
[+XMonad.Util.Search: new module
gwern0 at gmail.com**20071213205159
 This module is intended to provide helpful functions for easily running web searchs; just hit a bound key, enter your query, and up opens a new tab/browser/window with the search results. In theory anyway; the Wikipedia and Google ones work fine for me, but the Internet Archive's docs on how to do don't necessarily seem to be correct. If you were, like me, previously running shell commands to call Surfraw or similar shell scripts to do the same thing, you can now scrap them and replace them.
 
 There aren't too many search engines defined here; new ones would be good, and they're easy to add!
] 
[Add support for _NET_WM_STRUT_PARTIAL
Spencer Janssen <sjanssen at cse.unl.edu>**20071213021704] 
[ManageDocks: when there are struts on opposing edges, the right/bottom strut
Spencer Janssen <sjanssen at cse.unl.edu>**20071210021030
 was ignored.  TODO: quickchecks
] 
[Run.hs: fix documentation, cleanup whitespace
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071212091516] 
[Man.hs: input speedup
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071212090256
 
 Descend manpage directories once -- when `manPrompt' is called.
 (Previous version used to search directories upon each character
 arrival.)
] 
[new XMonad.Hooks.ManageHelpers module
Lukas Mai <l.mai at web.de>**20071211183040] 
[Magnifier: custom zoom ratio for magnifier' too
intrigeri at boum.org**20071211015554] 
[Magnifier.hs: minor haddock fixes
Brent Yorgey <byorgey at gmail.com>**20071211011154] 
[fix haddock on Magnifier
tim.thelion at gmail.com**20071210231942] 
[Custom zoom levels for magnifier
tim.thelion at gmail.com**20071208230844] 
[TAG 0.5
Spencer Janssen <sjanssen at cse.unl.edu>**20071209233056] 
Patch bundle hash:
627a40f80938da71c35e20e006456a373e6a7eba


More information about the xmonad mailing list