[xmonad] XMonad.Actions.Volume

wagnerdm at seas.upenn.edu wagnerdm at seas.upenn.edu
Thu Jun 18 08:30:20 EDT 2009


I've written a module to interface with the command-line utility  
"amixer".  It tries to be relatively smart about dealing with devices  
with lots of different controls, and has a fallback interface for when  
smart is wrong.  It includes a full parser for amixer's output, as  
well, though currently it only reports two aggregate statistics: total  
volume among all channels and mute-ness.

This is probably something of a controversial patch: it adds two  
dependencies.  I don't think the "parsec" dependency is a big deal,  
since that comes with GHC, and we can therefore expect most users to  
have it already. The other dependency is the "split" package.  Let me  
know if you want me to just pull in the definition of the particular  
splitting function I'm using.

Cheers!
~d
-------------- next part --------------
Thu Jun 18 07:58:54 EDT 2009  daniel at wagner-home.com
  * XMonad.Actions.Volume for controlling and grokking amixer within xmonad

New patches:

[XMonad.Actions.Volume for controlling and grokking amixer within xmonad
daniel at wagner-home.com**20090618115854
 Ignore-this: dc29b3738db8c1db932b6adb71699cf8
] {
addfile ./XMonad/Actions/Volume.hs
hunk ./XMonad/Actions/Volume.hs 1
+-- boilerplate {{{
+----------------------------------------------------------------------------
+-- |
+-- Module       : XMonad.Actions.Volume
+-- Copyright    : (c) daniel at wagner-home.com
+-- License      : BSD3-style (see LICENSE)
+--
+-- Maintainer   : daniel at wagner-home.com
+-- Stability    : unstable
+-- Portability  : unportable
+--
+-- A minimal interface to the "amixer" command-line utility.
+--
+----------------------------------------------------------------------------
+module XMonad.Actions.Volume (
+    -- * Usage
+    -- $usage
+
+    -- * Common functions
+    toggleMute,
+    raiseVolume,
+    lowerVolume,
+
+    -- * Low-level interface
+    getVolume,
+    getMute,
+    getVolumeMute,
+    setVolume,
+    setMute,
+    setVolumeMute,
+    modifyVolume,
+    modifyMute,
+    modifyVolumeMute,
+
+    -- * Variants that take a list of channels
+    defaultChannels,
+
+    toggleMuteChannels,
+    raiseVolumeChannels,
+    lowerVolumeChannels,
+    getVolumeChannels,
+    getMuteChannels,
+    getVolumeMuteChannels,
+    setVolumeChannels,
+    setMuteChannels,
+    setVolumeMuteChannels,
+    modifyVolumeChannels,
+    modifyMuteChannels,
+    modifyVolumeMuteChannels
+) where
+
+import Control.Monad
+import Control.Monad.Trans
+import Data.List.Split (splitOn)
+import Data.Maybe
+import System.IO
+import System.Process
+import Text.ParserCombinators.Parsec
+import XMonad.Core
+
+infixl 1 <*
+(<*) :: Monad m => m a -> m b -> m a
+pa <* pb = pa >>= \a -> pb >> return a
+
+{- $usage
+You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
+
+> import XMonad.Actions.Volume
+
+then add appropriate keybinds to adjust the volume; for example:
+
+> , ((modMask x, xK_F8 ), lowerVolume 3 >> return ())
+> , ((modMask x, xK_F9 ), raiseVolume 3 >> return ())
+> , ((modMask x, xK_F10), toggleMute    >> return ())
+
+For detailed instructions on editing your key bindings, see
+"XMonad.Doc.Extending#Editing_key_bindings".
+-}
+-- }}}
+-- API {{{
+-- | Toggle mutedness on the default channels.  Returns 'True' when this attempts to mute the speakers and 'False' when this attempts to unmute the speakers.
+toggleMute          :: MonadIO m => m Bool
+-- | Raise the volume on the default channels the given number of percentage points.  Returns the volume it attempts to set.
+raiseVolume         :: MonadIO m => Double -> m Double
+-- | Lower the volume on the default channels the given number of percentage points.  Returns the volume it attempts to set.
+lowerVolume         :: MonadIO m => Double -> m Double
+-- | Get the geometric mean of the volumes on the default channels.
+getVolume           :: MonadIO m => m Double
+-- | Get the mutedness of the default channels.  Returns 'True' if any of the channels are muted, and 'False' otherwise.
+getMute             :: MonadIO m => m Bool
+-- | Get both the volume and the mutedness of the default channels.
+getVolumeMute       :: MonadIO m => m (Double, Bool)
+-- | Attempt to set the default channels to a volume given in percentage of maximum.
+setVolume           :: MonadIO m => Double         -> m ()
+-- | Attempt to set the muting on the default channels.
+setMute             :: MonadIO m => Bool           -> m ()
+-- | Attempt to set both the volume in percent and the muting on the default channels.
+setVolumeMute       :: MonadIO m => Double -> Bool -> m ()
+-- | Apply a function to the volume of the default channels, and return the modified value.
+modifyVolume        :: MonadIO m => (Double         -> Double        ) -> m Double
+-- | Apply a function to the muting on the default channels, and return the modified value.
+modifyMute          :: MonadIO m => (Bool           -> Bool          ) -> m Bool
+-- | Apply a function to both the volume and the muting of the default channels, and return the modified values.
+modifyVolumeMute    :: MonadIO m => (Double -> Bool -> (Double, Bool)) -> m (Double, Bool)
+
+toggleMute          = toggleMuteChannels       defaultChannels
+raiseVolume         = raiseVolumeChannels      defaultChannels
+lowerVolume         = lowerVolumeChannels      defaultChannels
+getVolume           = getVolumeChannels        defaultChannels
+getMute             = getMuteChannels          defaultChannels
+getVolumeMute       = getVolumeMuteChannels    defaultChannels
+setVolume           = setVolumeChannels        defaultChannels
+setMute             = setMuteChannels          defaultChannels
+setVolumeMute       = setVolumeMuteChannels    defaultChannels
+modifyVolume        = modifyVolumeChannels     defaultChannels
+modifyMute          = modifyMuteChannels       defaultChannels
+modifyVolumeMute    = modifyVolumeMuteChannels defaultChannels
+
+-- | Channels are what amixer calls \"simple controls\".  The most common ones are \"Master\", \"Wave\", and \"PCM\", so these are included in 'defaultChannels'.  It is guaranteed to be safe to pass channel names that don't exist on the default sound device to the *Channels family of functions.
+defaultChannels :: [String]
+defaultChannels = ["Master", "Wave", "PCM"]
+
+toggleMuteChannels          :: MonadIO m => [String] -> m Bool
+raiseVolumeChannels         :: MonadIO m => [String] -> Double -> m Double
+lowerVolumeChannels         :: MonadIO m => [String] -> Double -> m Double
+getVolumeChannels           :: MonadIO m => [String] -> m Double
+getMuteChannels             :: MonadIO m => [String] -> m Bool
+getVolumeMuteChannels       :: MonadIO m => [String] -> m (Double, Bool)
+setVolumeChannels           :: MonadIO m => [String] -> Double         -> m ()
+setMuteChannels             :: MonadIO m => [String] -> Bool           -> m ()
+setVolumeMuteChannels       :: MonadIO m => [String] -> Double -> Bool -> m ()
+modifyVolumeChannels        :: MonadIO m => [String] -> (Double         -> Double        ) -> m Double
+modifyMuteChannels          :: MonadIO m => [String] -> (Bool           -> Bool          ) -> m Bool
+modifyVolumeMuteChannels    :: MonadIO m => [String] -> (Double -> Bool -> (Double, Bool)) -> m (Double, Bool)
+
+toggleMuteChannels  cs = modifyMuteChannels   cs not
+raiseVolumeChannels cs = modifyVolumeChannels cs . (+)
+lowerVolumeChannels cs = modifyVolumeChannels cs . (subtract)
+
+getVolumeChannels     = liftIO . fmap fst . amixerGetAll
+getMuteChannels       = liftIO . fmap snd . amixerGetAll
+getVolumeMuteChannels = liftIO            . amixerGetAll
+
+setVolumeChannels     cs v   = liftIO (amixerSetVolumeOnlyAll v   cs)
+setMuteChannels       cs   m = liftIO (amixerSetMuteOnlyAll     m cs)
+setVolumeMuteChannels cs v m = liftIO (amixerSetAll           v m cs)
+
+modifyVolumeChannels = modify getVolumeChannels setVolumeChannels
+modifyMuteChannels   = modify getMuteChannels   setMuteChannels
+modifyVolumeMuteChannels cs = modify getVolumeMuteChannels (\cs' -> uncurry (setVolumeMuteChannels cs')) cs . uncurry
+-- }}}
+-- internals {{{
+geomMean :: Floating a => [a] -> a
+geomMean xs = product xs ** (recip . fromIntegral . length $ xs)
+
+modify :: Monad m => (arg -> m value) -> (arg -> value -> m ()) -> arg -> (value -> value) -> m value
+modify get set cs f = do
+    v <- liftM f $ get cs
+    set cs v
+    return v
+
+outputOf :: String -> IO String
+outputOf s = do
+    uninstallSignalHandlers
+    (hIn, hOut, hErr, p) <- runInteractiveCommand s
+    mapM_ hClose [hIn, hErr]
+    hGetContents hOut <* waitForProcess p <* installSignalHandlers
+
+amixerSetAll :: Double -> Bool -> [String] -> IO ()
+amixerSet    :: Double -> Bool ->  String  -> IO String
+amixerGetAll :: [String] -> IO (Double, Bool)
+amixerGet    ::  String  -> IO String
+amixerSetAll    = (mapM_ .) . amixerSet
+amixerSet v m s = outputOf $ "amixer set '" ++ s ++ "' " ++ show v ++ "% " ++ (if m then "" else "un") ++ "mute"
+amixerGetAll    = fmap parseAmixerGetAll . mapM amixerGet
+amixerGet     s = outputOf $ "amixer get \'" ++ s ++ "\'"
+
+amixerSetVolumeOnlyAll :: Double -> [String] -> IO ()
+amixerSetVolumeOnly    :: Double ->  String  -> IO String
+amixerSetVolumeOnlyAll  = mapM_ . amixerSetVolumeOnly
+amixerSetVolumeOnly v s = outputOf $ "amixer set '" ++ s ++ "' " ++ show v ++ "% "
+
+amixerSetMuteOnlyAll :: Bool -> [String] -> IO ()
+amixerSetMuteOnly    :: Bool ->  String  -> IO String
+amixerSetMuteOnlyAll  = mapM_ . amixerSetMuteOnly
+amixerSetMuteOnly m s = outputOf $ "amixer set '" ++ s ++ "' " ++ (if m then "" else "un") ++ "mute"
+
+parseAmixerGetAll :: [String] -> (Double, Bool)
+parseAmixerGetAll ss = (geomMean vols, mute) where
+    (vols, mutings)  = unzip [v | Right p <- map (parse amixerGetParser "") ss, v <- p]
+    mute             = or . catMaybes $ mutings
+
+amixerGetParser :: Parser [(Double, Maybe Bool)]
+amixerGetParser = headerLine >> playbackChannels >>= volumes <* eof
+
+headerLine       :: Parser  String
+playbackChannels :: Parser [String]
+volumes          :: [String] -> Parser [(Double, Maybe Bool)]
+headerLine = string "Simple mixer control " >> upTo '\n'
+playbackChannels = keyValueLine >>= \kv -> case kv of
+    ("Playback channels", v) -> return (splitOn " - " v)
+    _                        -> playbackChannels
+volumes channels = fmap concat . many1 $ keyValueLine >>= \kv -> return $ case kv of
+    (k, v) | k `elem` channels -> parseChannel v
+           | otherwise         -> []
+
+upTo         :: Char -> Parser String
+keyValueLine :: Parser (String, String)
+upTo c = many (satisfy (/= c)) <* char c
+keyValueLine = do
+    string "  "
+    key   <- upTo ':'
+    value <- upTo '\n'
+    return (key, drop 1 value)
+
+parseChannel  :: String -> [(Double, Maybe Bool)]
+channelParser :: Parser    [(Double, Maybe Bool)]
+parseChannel  = either (const []) id . parse channelParser ""
+channelParser = fmap catMaybes (many1 playbackOrCapture) <* eof
+
+playbackOrCapture :: Parser (Maybe (Double, Maybe Bool))
+playbackOrCapture = do
+    f <- (string "Playback " >> return Just) <|>
+         (string "Capture "  >> return (const Nothing))
+    many1 digit
+    char ' '
+    es <- extras
+    case filter ('%' `elem`) es of
+        [volume] -> return . f . (,) (read (init volume) :: Double) $ case ("off" `elem` es, "on" `elem` es) of
+            (False, False) -> Nothing
+            (mute, _)      -> Just mute
+        _        -> fail "no percentage-volume found in playback section"
+
+extras :: Parser [String]
+extras = sepBy' (char '[' >> upTo ']') (char ' ')
+
+sepBy' :: Parser a -> Parser b -> Parser [a]
+sepBy' p sep = liftM2 (:) p loop where
+    loop = (sep >> (liftM2 (:) p loop <|> return [])) <|> return []
+-- }}}
hunk ./xmonad-contrib.cabal 52
         extensions: ForeignFunctionInterface
         cpp-options: -DXFT
 
-    build-depends:      mtl, unix, X11>=1.4.3, xmonad>=0.8, xmonad<0.9, utf8-string
+    build-depends:      mtl, unix, X11>=1.4.3, xmonad>=0.8, xmonad<0.9, utf8-string, parsec, split
     ghc-options:        -Wall
     extensions:         ForeignFunctionInterface
 
hunk ./xmonad-contrib.cabal 102
                         XMonad.Actions.TopicSpace
                         XMonad.Actions.UpdatePointer
                         XMonad.Actions.UpdateFocus
+                        XMonad.Actions.Volume
                         XMonad.Actions.Warp
                         XMonad.Actions.WindowNavigation
                         XMonad.Actions.WindowGo
}

Context:

[use 'take 1' instead of custom truncHead function in L.WindowNavigation
Adam Vogt <vogt.adam at gmail.com>**20090618010118
 Ignore-this: ecbb2063337bb87108c12a3c3f8ceeba
] 
[Correct many typos in the documentation, consistent US spellingg
Adam Vogt <vogt.adam at gmail.com>**20090618003729
 Ignore-this: cf6dcf340fa6cc010f7879f188d376f5
] 
[minor typo in ./XMonad/Layout/StackTile.hs
Joachim Breitner <mail at joachim-breitner.de>**20090617210345
 Ignore-this: ddb5dff32e332cf378f2204e23335d43
] 
[X.L.ResizableTile: make sure windows aren't resized to a height larger than the screen (fixes #298)
Brent Yorgey <byorgey at cis.upenn.edu>**20090604123509] 
[X.A.PhysicalScreens: fix typo
Roman Cheplyaka <roma at ro-che.info>**20090602172148] 
[X.L.AutoMaster: fix warning
Roman Cheplyaka <roma at ro-che.info>**20090602171754] 
[AutoMaster.dpatch
Ilya Portnov <portnov84 at rambler.ru>**20090426155401
 Ignore-this: e5cbb04882671d6fcc56f181f7d0d292
 Provides layout modifier AutoMaster. It separates screen in two parts -
 master and slave. Size of slave area automatically changes depending on
 number of slave windows.
] 
[UpdatePointer - Don't warp while dragging with mouse
Anders Engstrom <ankaan at gmail.com>**20090530185752
 Ignore-this: 4c3769dc96041608660789573b670c23
] 
[FlexibleResize - Resize from edge, don't move adjust at opposite edge
Anders Engstrom <ankaan at gmail.com>**20090530185437
 Ignore-this: 3c6c0748a4b0d14bd39bcb88f10aade6
 
 When resizing other corners than bottom-right, instead of adjusting to even columns/rows on the opposite side to it the same way as if resizing was made from the bottom right.
 
 Also add the possibility to add an area in the middle of an edge where only that edge is resized, not the closest corner.
 
] 
[Remove USE_UTF8 defines.
Khudyakov Alexey <alexey.skladnoy at gmail.com>**20090419130909
 They are not needed any more since utf8-string is mandatory dependence.
] 
[FloatSnap - calculate gaps instead of snapping against unmanaged windows
Anders Engstrom <ankaan at gmail.com>**20090526222942
 Ignore-this: 4378f4c6c4f383c9a35acb503409d865
 
 This patch will remove snapping against unmanaged windows, but instead calculate a new rectangle with all gaps (computed by ManageDocks) removed. This new rectangle is used to snap against. (Both the inside and outside of the rectangle.)
 
 This will remedy the issue of snapping against multiple layers of the same window, additionally there will be no snap-points between windows on the same side. So if you are running two dzen side by side with half the screen each. You will not automatically have a snap-point in the middle.
 
 Naturally, this patch will change which function is exported from ManageDocks.
] 
[Fix L.Mosaic bug where stored [Rational] was not extended
Adam Vogt <vogt.adam at gmail.com>**20090525030734
 Ignore-this: 55bb5b7fabc00f3dcc89e45cc416fc97
] 
[X.A.Search: add Wolfram|Alpha search
Brent Yorgey <byorgey at cis.upenn.edu>**20090525010419] 
[Remove L.ThreeColumnsMiddle compatiblity module
Adam Vogt <vogt.adam at gmail.com>**20090525003245
 Ignore-this: daac5841cf203c0e0df865a6fb0db3a1
 
 Signed off here too:
 http://www.haskell.org/pipermail/xmonad/2009-May/007883.html
] 
[A.FloatSnap snap to unmanaged docks too
Adam Vogt <vogt.adam at gmail.com>**20090525001834
 Ignore-this: 46a856cae139d2e224ded985a9866ecf
] 
[LayoutBuilder fix maintainer
Anders Engstrom <ankaan at gmail.com>**20090524205957
 Ignore-this: 380c279320cff67c60a9bbf9a49ec509
] 
[FloatSnap fix maintainer
Anders Engstrom <ankaan at gmail.com>**20090524205854
 Ignore-this: d3932d211e9dc755be799d863b7d58e3
] 
[X.A.FloatSnap - More configuration for magic resize, adaption for mouse bindings and some minor fixes
Anders Engstrom <ankaan at gmail.com>**20090524201143
 Ignore-this: d5fd9356e101b019735d54267a120ed
] 
[X.A.FloatSnap - Assisted move/resize of windows
Anders Engstrom <ankaan at gmail.com>**20090523235230
 Ignore-this: 53af93bdf537cf3417cedd313e36bcbd
 
 TODO: Try to snap against unmanaged windows such as dzen/xmobar.
 
] 
[Simplyify L.Mosaic interface, and support resizing specific windows
Adam Vogt <vogt.adam at gmail.com>**20090524193810
 Ignore-this: acea22bec582ee5eb076ac3bc862a9ea
 
 The order previously was not as documented, which prevented resizing specific
 windows.
 
 The Mosaic constructor is hidden in favour of mosaic :: Rational -> [Rational] -> Mosaic a
 
 Expand and Shrink messages are added, requiring another argument.
 
 Remove useless demonstration of SlopeMod message since resizing the focused
 window is better.
] 
[L.ResizableTile document ResizableTall parameters with records
Adam Vogt <vogt.adam at gmail.com>**20090519024258
 Ignore-this: a29502bc1302f18b9ae0062105a0e109
] 
[L.LayoutHints, add layoutHintsToCentre
Adam Vogt <vogt.adam at gmail.com>**20090519013806
 Ignore-this: a49106d5abb683d805e59beb29c727a9
 
 layoutHintsToCentre attempts to apply hints in a way that eliminates gaps
 between windows. The excess space ends up on all edges.
] 
[Remove excess whitespace from L.LayoutHints
Adam Vogt <vogt.adam at gmail.com>**20090519013350
 Ignore-this: b4bb5b6aeba95be047a102d07d916c48
] 
[new layout module X.L.Spacing, put blank space around each window
Brent Yorgey <byorgey at cis.upenn.edu>**20090514215552] 
[X.L.LayoutBuilder doc fix and cleaning
Anders Engstrom <ankaan at gmail.com>**20090509195254
 Ignore-this: 7cbf72ba48a2222b65615a02125d87ef
] 
[X.L.LayoutBuilder custom layouts
Anders Engstrom <ankaan at gmail.com>**20090509174627
 Ignore-this: 65c251663f02a083c5838ae1d1bd112a
 
 A layout combinator that sends a specified number of windows to one rectangle and the rest to another.
] 
[submapDefault fix key leakage
Anders Engstrom <ankaan at gmail.com>**20090426171002
 Ignore-this: edb0a2a03b2ed2959cb7068ae601fa28
] 
[Fix typo in L.Mosaic hints
Adam Vogt <vogt.adam at gmail.com>**20090508202937
 Ignore-this: 5f2163e64d876f4982b0d6baf13e0614
] 
[U.Loggers: add maildirNew, other loggers, and logger formatting utilities
wirtwolff at gmail.com**20090412041356
 Ignore-this: 73240ab34348ad895c3d66c2a2e8e40f
 Rework of the Logger portions of patches originally from seanmce33 at gmail.com
 to apply without conflicts, plus several formatting utilities for use with
 X (Maybe String) aka Loggers.
] 
[ThreeCol - Update docs to match reality
Anders Engstrom <ankaan at gmail.com>**20090503190755
 Ignore-this: e63f3ee533dd9bcf0f32da2316dde1dd
] 
[Remove some excess whitespace in XMonad.AppLauncher
Adam Vogt <vogt.adam at gmail.com>**20090503183416
 Ignore-this: b5bfa9625b5b080c20398cf1aa396a08
] 
[Export ThreeColMid from L.ThreeColumnsMiddle
Adam Vogt <vogt.adam at gmail.com>**20090425161710
 Ignore-this: f08d23d108ae9aa4ad176fd9dd275409
 
 The configs that import it should continue to work with this module, though the
 type of the ThreeColMid constructor is now ThreeCol (previously ThreeColMid).
] 
[ThreeColumns support middle column, with more backwards compatiblity
Adam Vogt <vogt.adam at gmail.com>**20090414061819
 Ignore-this: 5a8991269904986e0e012e955c6d4712
] 
[X.L.ThreeColumnsMiddle merged into X.L.ThreeColumns with some new features
Anders Engstrom <ankaan at gmail.com>**20090411113636
 Ignore-this: 1d5bb8de98f8ade3780444ed99f5a12f
] 
[nameTail - Remove the first word of a layout description
Anders Engstrom <ankaan at gmail.com>**20090503105950
 Ignore-this: a44c5e38163ed98ffc244cdd206632d1
] 
[Add H.InsertPosition: add new windows to different positions in a workspace
Adam Vogt <vogt.adam at gmail.com>**20090503020303
 Ignore-this: 7e7d5fa5b42698799cabe600159a75f7
] 
[Add changeMaster function to L.Mosaic
Adam Vogt <vogt.adam at gmail.com>**20090501233136
 Ignore-this: eca2a48fb987bb871ad93e6c6bf1a186
] 
[Optimizer bug does not affect 6.10.2 (issue 226)
Adam Vogt <vogt.adam at gmail.com>**20090430034823
 Ignore-this: f43f9bf9502ebb19743c3b417ef02347
] 
[Remove -XScopedTypeVariables requirement with L.SubLayouts
Adam Vogt <vogt.adam at gmail.com>**20090428222749
 Ignore-this: dbb08e3c1641796603fdaf7b929cdf6d
 
 This should keep the code -Wall clean on ghc-6.8 in addition to ghc-6.10
] 
[Add SubLayouts: a layout combinator for nesting layouts.
Adam Vogt <vogt.adam at gmail.com>**20090423013135
 Ignore-this: abb21b19bfbc567953419b3035b6a295
] 
[Document and extend BoringWindows to support multiple sources of boring.
Adam Vogt <vogt.adam at gmail.com>**20090406041301
 Ignore-this: 7375c8912ede6a6a44db4a4b91ffbc33
 
 The Replace and Merge messages are added to support layouts sending a list of
 windows that should be skipped over. The sources are tagged by a string key, so
 it is possible though unlikely for different sources of boring windows to
 interfere with eachother.
] 
[Add Apply message to L.WindowNavigation
Adam Vogt <vogt.adam at gmail.com>**20090303065701
 Ignore-this: e808729ddd2375778a96775568b8b621
] 
[X.A.TopicSpace: remove the allTopics lists from the configuration.
Nicolas Pouillard <nicolas.pouillard at gmail.com>**20090423172939
 Ignore-this: 1ac344b32865b38e53b968cc037b0a01
] 
[added colour themes
perlkat at katspace.org**20090227065315
 These themes are colour themes only; they use the default font settings.
 I thought the existing themes were rather dull, so these give more bright
 (but tasteful) colours; shades of peacock feathers, shades of autumn.
] 
[Prompt.hs: setSuccess True also on Keypad Enter
sean.escriva at gmail.com**20090409162609
 Ignore-this: cf04f87c546f89bd32a94de3a2a93b22
] 
[Update focus on mouse moves within inactive windows
Daniel Schoepe <asgaroth_ at gmx.de>**20090407191819
 Ignore-this: 36c05c60420520dab708401d8a80fc85
 
 This patch adds functionality to update the focus on moves in unfocused windows, which would make sense if one wanted the focus to follow the mouse.
 Currently this only happens when the mouse enters/leaves a window. 
 This patch should fix issue #205.
] 
[Add promoteWarp event to L.MagicFocus
Adam Vogt <vogt.adam at gmail.com>**20090322221456
 Ignore-this: 12ad5fc144a35fb605f53b744d8146ef
 
 This event enables A.UpdatePointer behavior without causing infinite loops in
 combination with magicFocus
] 
[Add TowardsCentre option to UpdatePointer
Adam Vogt <vogt.adam at gmail.com>**20090322215811
 Ignore-this: d543d8f090b03a6c26b3a0427be3a051
 
 This option is like Nearest, but it places the pointer a configurable
 percentage towards the centre of the window, instead of right at the edge.
] 
[Remove excess whitespace in A.UpdatePointer
Adam Vogt <vogt.adam at gmail.com>**20090322215553
 Ignore-this: 6fbc63642b946461e0fafcb44016824
] 
[Combo fix ReleaseResources when no windows are available, new fix
Anders Engstrom <ankaan at gmail.com>**20090224172018
 Ignore-this: b59603df8e4cfc1fb2cf9070cea615b3
] 
[OneBig_resize.dpatch
portnov84 at rambler.ru**20090221142300
 Ignore-this: c02b25bd370ee449aab28005eb4418cf
 Add Shrink/Expand messages handling for OneBig layout.
] 
[OneBig_layout.dpatch
portnov84 at rambler.ru**20090220172634
 Ignore-this: 9d4f308d13f003aa4236417307a66c15
 Add the OneBig layout, which places one (master) window at top left corner of
 screen (width and height of master window are parameters of layout), and other
 (slave) windows at bottom and at right of master, trying to give equal space
 for each slave window.
] 
[Properly encode destop names before sending them to X server in XMonad.Hooks.EwmhDesktops
Khudyakov Alexey <alexey.skladnoy at gmail.com>**20090220184137
 Ignore-this: 6a22ea8bdc49f8484e18f04aaeb545ae
] 
[Make utf8-string regular dependency
Khudyakov Alexey <alexey.skladnoy at gmail.com>**20090220183318
 Ignore-this: b38936b037c1172ec69905fa345f7afe
 
 The reason for this is that EWMH specification require 
 utf8 encoded strings.
] 
[Update haddock description for Actions.GridSelect
Daniel Schoepe <asgaroth_ at gmx.de>**20090422172510
 Ignore-this: db5a2c009f7e88647f168ccb225d6219
] 
[X.H.DynamicLog: provides trim, inverse of pad
sean.escriva at gmail.com**20090409163513
 Ignore-this: 9d92ff592f2bc4f041b85d1314058fdc
] 
[Mouse support for GridSelect
Daniel Schoepe <asgaroth_ at gmx.de>**20090409223302
 Ignore-this: 38669e39c8676233d71f457c0b697500
 
 GridSelect now allows selecting an element by a click with the left mouse button.
] 
[Generalize GridSelect to arbitrary elements
Daniel Schoepe <asgaroth_ at gmx.de>**20090409155704
 Ignore-this: 69fbce85232871482adcce06c1a5fe62
 
 This patch generalizes Actions.GridSelect to work for arbitrary (String,a)-lists. The changes break configurations that used `gridSelect' directly, which is now named gridSelectWindow. As an example for uses of the GridSelect-UI, I included a function to spawn an application from a list of commands(`spawnSelected').
] 
[Improve composability of X.H.Place, drop simple(st)Float support
quentin.moser at unifr.ch**20090415184550
 Ignore-this: 8a0fb64aa0db27b242b7ad4bcba1a3ca
] 
[Fixed X.H.Place.position
quentin.moser at unifr.ch**20090409084946
 Ignore-this: 29e3936800194916a859976ff126dbfe
] 
[Module for automatic placement of floating windows
quentin.moser at unifr.ch**20090408080953
 Ignore-this: 1874df995fc02a0b80051db39d91a2e1
] 
[X.H.FloatNext: new module, float the next spawned window(s)
quentin.moser at unifr.ch**20090415181907
 Ignore-this: 95e1c9daa3ca43bfb058f6a881a97f3a
] 
[ComboP
konstantin.sobolev at gmail.com**20090415014327
 Ignore-this: 73bb986165a7bba466aae789a5448170
] 
[New module: XMonad.Actions.TopicSpace
Nicolas Pouillard <nicolas.pouillard at gmail.com>**20090419085239
 Ignore-this: 4c20592ea6ca74f38545c5a1a002ef91
] 
[NamedScratchpad
konstantin.sobolev at gmail.com**20090419045542
 Ignore-this: b442cb08123d2413e0bb144a73bf3f57
] 
[More configurability for Layout.NoBorders (typeclass method)
Adam Vogt <vogt.adam at gmail.com>**20090325050206
 Ignore-this: 91fe0bc6217b910b7348ff497b922e11
 
 This method uses a typeclass to pass a function to the layoutmodifier. It is
 flexible, but a bit indirect and perhaps the flexibility is not required.
] 
[Add XMonad.Actions.PhysicalScreens
nelhage at mit.edu**20090321001320
 
 Add an XMonad.Actions.PhysicalScreens contrib module that allows
 addressing of screens by physical ordering, rather than the arbitrary
 ScreenID.
] 
[pointWithin has moved to the core
Joachim Breitner <mail at joachim-breitner.de>**20081008154245] 
[UpdatePointer even to empty workspaces
Joachim Breitner <mail at joachim-breitner.de>**20081007080041
 This makes UpdatePointer more Xinerama-compatible: If the user switches to a
 screen with an empty workspace, the pointer is moved to that workspace, which I
 think is expected behavoiur.
] 
[More predictable aspect ratio in GridVariants.Grid
Norbert Zeh <nzeh at cs.dal.ca>**20090311013617
 
 The old version fairly arbitrarily decided to prefer windows that are too
 high over those that are too wide.  The new version chooses the number of
 columns so that all windows on the screen are as close as possible to the
 desired aspect ratio.  As a side effect, the layout changes much more
 predictably under addition and removal of clients.
] 
[X.L.Master: fix number of windows
Ismael Carnales <icarnales at gmail.com>**20090301051509
 Ignore-this: 2af132159450d4fb72eb52024eda71b5
] 
[U.EZConfig: add xK_Print <Print> to special keys
wirtwolff at gmail.com**20090302230741
 Ignore-this: 9560b7c7c4424edb5cea6eec45e2b41d
 Many setups are expecting xK_Print rather than
 xK_Sys_Req, so make it available in additionalKeysP.
] 
[More flexibility for H.FadeInactive
Daniel Schoepe <asgaroth_ at gmx.de>**20090309160020
 Ignore-this: ebfa2eadb439763276b372107cdf8d6c
] 
[Prompt.Shell: escape ampersand
Valery V. Vorotyntsev <valery.vv at gmail.com>**20090312091314
 Ignore-this: 7200b76af8109bab794157da46cb0030
 
 Ampersand (&) is a special character and should be escaped.
] 
[Cleanup X.L.Mosaic, without breaking it
Adam Vogt <vogt.adam at gmail.com>**20090219022417
 Ignore-this: d49ed55fe8dc2204256dff9252384745
] 
[X.L.Mosaic: prevent users from causing non-termination with negative elements
Adam Vogt <vogt.adam at gmail.com>**20090210022727
 Ignore-this: 370a7d6249906f1743c6692758ce5aeb
] 
[better Layout.NoBorders.smartBorders behavior on xinerama
Adam Vogt <vogt.adam at gmail.com>**20090314170058
 Ignore-this: 36737ce2fa2087c4a16ddf226d3b0f0a
 
 Now smartBorders shows borders when you have multiple screens with one window
 each. In the case where only one window is visible, no borders are drawn.
] 
[H.DynamicLog: revised dzenStrip and xmobarStrip functions
wirtwolff at gmail.com**20090314041517
 Ignore-this: 9897c60b8dfc59344939b7aebc370953
 Reconcile darcswatch patch with pushed version of dzenStrip.
] 
[X.H.DynamicLog: Add dzenStrip to remove formatting, for use in dzenPP's ppUrgent.
Braden Shepherdson <Braden.Shepherdson at gmail.com>**20090314032818
 Ignore-this: fd96a1a4b112d0f71589b639b83ec3e
 This function was written by Wirt Wolff. This change should allow UrgencyHook
 to work out of the box with dzen and dzenPP, rather than the colours being
 overridden so even though UrgencyHook is working, it doesn't change colours.
] 
[X.H.ManageHelpers: export isInProperty
Roman Cheplyaka <roma at ro-che.info>**20090308201112] 
[L.Cross: clarify documentation
wirtwolff at gmail.com**20090222042220
 Ignore-this: 4a5dcf71e63d045f27e2340e1def5cc8
 Amend-record earlier patch to work with byorgey's fix,
 this one is just the documentation typo fixes and 
 clarifications.
] 
[documentation for IndependentScreens
daniel at wagner-home.com**20090221235959] 
[eliminate a haddock warning in BoringWindows
daniel at wagner-home.com**20090221235836] 
[merge IndependentScreens
daniel at wagner-home.com**20090221232142] 
[add IndependentScreens to xmonad-contrib.cabal
daniel at wagner-home.com**20090221231632] 
[add type information for IndependentScreens
daniel at wagner-home.com**20090221231525] 
[add some boilerplate comments at the top of IndependentScreens
Brent Yorgey <byorgey at cis.upenn.edu>**20090221230850] 
[IndependentScreens, v0.0
daniel at wagner-home.com**20090221225229] 
[U.Run: remove waitForProcess to close Issue 268
wirtwolff at gmail.com**20090220214153
 Ignore-this: a6780565fde40a4aac9023cc55fc2273
 http://code.google.com/p/xmonad/issues/detail?id=268
 Submitting with some trepidation, since I've nearly no
 understanding of process handling. Should be ok, no 
 warnings by sjanssen when asking about it in hpaste or
 earlier email, and tested locally by spawning excessive
 numbers of dzens: did not leave zombies or raise exceptions.
] 
[change Cross data declaration into a record so that Haddock will parse the per-argument comments
Brent Yorgey <byorgey at cis.upenn.edu>**20090221224742] 
[X.L.Master: turn it to a Layout modifier and update the code
Ismael Carnales <icarnales at gmail.com>**20090213020453
 Ignore-this: 69513ad2b60dc4aeb49d64ca30e6f9f8
] 
[Use doShift in my config
Spencer Janssen <spencerjanssen at gmail.com>**20090219042040
 Ignore-this: 1f103d21bbceec8d48384f975f18eaec
] 
[SpawnOn: use doShift.  This resolves problems where SpawnOn would shift the wrong window
Spencer Janssen <spencerjanssen at gmail.com>**20090219041856
 Ignore-this: 6ae639a638db8eff77203f3f2e481a4e
] 
[SpawnOn: delete seen pids
Spencer Janssen <spencerjanssen at gmail.com>**20090213013011
 Ignore-this: 8b15a60bba1edf1bab5fb77ac54eb12f
] 
[X.U.Loggers: handle possible EOF (reported by dyfrgi)
Roman Cheplyaka <roma at ro-che.info>**20090216213842] 
[U.Scratchpad: add general spawn action to close issue 249
wirtwolff at gmail.com**20090214003642
 Ignore-this: 925ad9db4ecc934dcd86320f383ed44a
 Adds scratchpadSpawnActionCustom where user specifies how to set
 resource to "scratchpad". This allows use of gnome-terminal, etc.
 Add detail to RationalRectangle documentation; strip trailing spaces.
] 
[SpawnOn: add 'exec' to shell strings where possible
Spencer Janssen <spencerjanssen at gmail.com>**20090212234608
 Ignore-this: c7de4e05803d60b10f38004dcbda4732
] 
[Add Cross Layout
'Luis Cabellos <zhen.sydow at gmail.com>'**20090209174802] 
[Fix an undefined in EwmhDesktops
Daniel Schoepe <asgaroth_ at gmx.de>**20090209152308
 Ignore-this: f60a43d7ba90164ebcf700090dfb2480
] 
[X.U.WindowProperties: docs (description and sections)
Roman Cheplyaka <roma at ro-che.info>**20090208231422] 
[X.U.WindowProperties: Add getProp32 and getProp32s, helpers to get properties from windows
Ismael Carnales <icarnales at gmail.com>**20090205013031
 Ignore-this: c5481fd5d97b15ca049e2da2605f65c1
] 
[cleanup and make X.L.Mosaic behavior more intuitive wrt. areas
Adam Vogt <vogt.adam at gmail.com>**20090208221629
 Ignore-this: 3c3c6faa203cbb1c1db909e5bf018b6f
] 
[minor typo in XMonad/Util/EZConfig.hs
Joachim Breitner <mail at joachim-breitner.de>**20090208192224
 Ignore-this: 7ffee60858785c3e31fdd5383c9bb784
] 
[Multimedia keys support for EZConfig
Khudyakov Alexey <alexey.skladnoy at gmail.com>**20090207173330
 Ignore-this: 21183dd7c192682daa18e3768828f88d
] 
[+A.CycleWindows: bindings to cycle windows in new ways
wirtwolff at gmail.com**20090207170622
 Ignore-this: 51634299addf224cbbc421adb4b048f5
 Provides binding actions and customizable pure stack operations
 to cycle through a list of permutations of the stack (recent),
 cycle nth into focus, cycle through focus excluding a neighbor,
 cycle unfocused, shift a window halfway around the stack.
 Esp. for Full, two or three pane layouts, but useful for any
 layout with many windows.
] 
[XMonad.Actions.CopyWindow: fmt & qualify stackset import
gwern0 at gmail.com**20090206171833
 Ignore-this: 4d08f5a7627020b188f59fc637b53ae8
] 
[XMonad.Actions.CopyWindow runOrCopy
lan3ny at gmail.com**20080602205742] 
[ManageHelpers: reduce duplicated code in predicates
Ismael Carnales <icarnales at gmail.com>**20090204021847
 Ignore-this: e28a912d4f897eba68ab3edfddf9f26b
] 
[Remove X.U.SpawnOnWorkspace (superseded by X.A.SpawnOn)
Roman Cheplyaka <roma at ro-che.info>**20090204103635] 
[X.A.SpawnOn: add docs
Roman Cheplyaka <roma at ro-che.info>**20090204102424
 Add more documentation, including documentation from
 X.U.SpawnOnWorkspace by Daniel Schoepe.
] 
[Remove silliness from XMonad.Doc.Configuring
Spencer Janssen <spencerjanssen at gmail.com>**20090204055626] 
[Adjustments to use the new event hook feature instead of Hooks.EventHook
Daniel Schoepe <asgaroth_ at gmx.de>**20090203160046
 Ignore-this: f8c239bc8e301cbd6fa509ef748af542
] 
[Easier Colorizers for X.A.GridSelect
quentin.moser at unifr.ch**20090128001702
 Ignore-this: df3e0423824e40537ffdb4bc7363655d
] 
[X.A.SpawOn: fix usage doc
Roman Cheplyaka <roma at ro-che.info>**20090202102042] 
[Added GridVariants.SplitGrid
Norbert Zeh <nzeh at cs.dal.ca>**20090129152146
 
 GridVariants.TallGrid behaved weird when transformed using Mirror
 or Reflect.  The new layout SplitGrid does away with the need for
 such transformations by taking a parameter to specify horizontal
 or vertical splits.
] 
[FixedColumn: added missing nmaster to the usage doc
Ismael Carnales <icarnales at gmail.com>**20090130195239
 Ignore-this: 642aa0bc9e68e7518acc8af30324b97a
] 
[XMonad.Actions.Search: fix whitespace & tabs
gwern0 at gmail.com**20090129025246
 Ignore-this: 894e479ccc46160848c4d70c2361c929
] 
[xmonad-action-search-intelligent-searchengines
Michal Trybus <komar007 at gmail.com>**20090128101938
 Changed the XMonad.Action.Search to use a function instead of String to prepare the search URL.Added a few useful functions used to connect many search engines together and do intelligent prefixed searches (more doc in haddock)The API has not changed with the only exception of search function, which now accepts a function instead of String.
] 
[XMonad.Prompt autocompletion fix
quentin.moser at unifr.ch**20090127184145
 Ignore-this: 635cbf6420722a4edef1ae9c40b36e1b
] 
[X.A.SinkAll: re-add accidentally deleted usage documentation
Brent Yorgey <byorgey at cis.upenn.edu>**20090127222533] 
[move XMonad.Actions.SinkAll functionality to more general XMonad.Actions.WithAll, and re-export sinkAll from X.A.SinkAll for backwards compatibility
Brent Yorgey <byorgey at cis.upenn.edu>**20090127222355] 
[adds generic 'all windows on current workspace' functionality
loupgaroublond at gmail.com**20081221224850] 
[placement patch to XMonad.Layout.LayoutHints
quentin.moser at unifr.ch**20090126195950
 Ignore-this: 87a5efa9c841d378a808b1a4309f18
] 
[XMonad.Actions.MessageFeedback module
quentin.moser at unifr.ch**20090126181059
 Ignore-this: 82e58357a44f98c35ccf6ad0ef98b552
] 
[submapDefault
Anders Engstrom <ankaan at gmail.com>**20090118152933
 Ignore-this: c8958d47eb584a7de04a81eb087f05d1
 Add support for a default action to take when the entered key does not match any entry.
] 
[X.A.CycleWS: convert tabs to spaces (closes #266)
Roman Cheplyaka <roma at ro-che.info>**20090127185604] 
[Mosaic picks the middle aspect layout, unless overriden
Adam Vogt <vogt.adam at gmail.com>**20090126032421
 Ignore-this: aaa31da14720bffd478db0029563aea5
] 
[Mosaic: stop preventing access to the widest layouts
Adam Vogt <vogt.adam at gmail.com>**20090125045256
 Ignore-this: c792060fe2eaf532f433cfa8eb1e8fe3
] 
[X.L.Mosaic add documentation, update interface and aspect ratio behavior
Adam Vogt <vogt.adam at gmail.com>**20090125041229
 Ignore-this: e78027707fc844b3307ea87f28efed73
] 
[Use currentTag, thanks asgaroth
Spencer Janssen <spencerjanssen at gmail.com>**20090125213331
 Ignore-this: dd1a3d96038de6479eca3b9798d38437
] 
[Support for spawning most applications on a specific workspace
Daniel Schoepe <asgaroth_ at gmx.de>**20090125191045
 Ignore-this: 26076d54b131e037b42c87e4fde63200
] 
[X.L.Mosaic: haddock fix
Roman Cheplyaka <roma at ro-che.info>**20090124235908] 
[A mosaic layout based on MosaicAlt
Adam Vogt <vogt.adam at gmail.com>**20090124022058
 Ignore-this: 92bad7498f1ac402012e3eba6cbb2693
 
 The position of a window in the stack determines its position and layout. And
 the overall tendency to make wide or tall windows can be changed, though not
 all of the options presented by MosaicAlt can be reached, the layout changes
 with each aspect ratio message.
 
] 
[uninstallSignalHandlers in spawnPipe
Spencer Janssen <spencerjanssen at gmail.com>**20090122002745
 Ignore-this: e8cfe0f18f278c95d492628da8326fd7
] 
[Create a new session for spawnPiped processes
Spencer Janssen <spencerjanssen at gmail.com>**20090122000441
 Ignore-this: 37529c5fe8b4bf1b97fffb043bb3dfb0
] 
[TAG 0.8.1
Spencer Janssen <spencerjanssen at gmail.com>**20090118220647] 
[Use spawnOn in my config
Spencer Janssen <spencerjanssen at gmail.com>**20090117041026
 Ignore-this: 3f92e4bbe4f2874b86a6c7ad66a31bbb
] 
[Add XMonad.Actions.SpawnOn
Spencer Janssen <spencerjanssen at gmail.com>**20090117040432
 Ignore-this: 63869d1ab11f2ed5aab1690763065800
] 
[Bump version to 0.8.1
Spencer Janssen <spencerjanssen at gmail.com>**20090116223607
 Ignore-this: 1c201e87080e4404f51cadc108b228a1
] 
[Compile without optimizations on x86_64 and GHC 6.10
Spencer Janssen <spencerjanssen at gmail.com>**20090108231650
 Ignore-this: a803235b8022793f648e8953d9f05e0c
 This is a workaround for http://xmonad.org/bugs/226
] 
[Update all uses of doubleFork/waitForProcess
Spencer Janssen <spencerjanssen at gmail.com>**20090116210315
 Ignore-this: 4e15b7f3fd6af3b7317449608f5246b0
] 
[Update to my config
Spencer Janssen <spencerjanssen at gmail.com>**20090116204553
 Ignore-this: 81017fa5b99855fc8ed1fe8892929f53
] 
[Adjustments to new userCode function
Daniel Schoepe <asgaroth_ at gmx.de>**20090110221310] 
[X.U.EZConfig: expand documentation
Brent Yorgey <byorgey at cis.upenn.edu>**20090116153143] 
[add a bit of documentation to HintedTile
Brent Yorgey <byorgey at cis.upenn.edu>**20090114065126] 
[ManageHelpers: add isDialog
johanngiwer at web.de**20090108232505] 
[CenteredMaster
portnov84 at rambler.ru**20090111134513
 
 centerMaster layout modifier places master window at top of other, at center of screen. Other windows are managed by base layout.
 topRightMaster is similar, but places master window at top right corner.
] 
[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] 
[Bump version to 0.8
Spencer Janssen <spencerjanssen at gmail.com>**20080905194415] 
[Take maintainership of X.L.WindowNavigation
Devin Mullins <me at twifkak.com>**20080902070247
 Since I've been working on a rewrite, it seems only fair that I be forced to
 better understand the existing code / issues.
] 
[Take maintainership of NoBorders
Spencer Janssen <spencerjanssen at gmail.com>**20080829201325] 
[Only move pointers over managed windows
Joachim Breitner <mail at joachim-breitner.de>**20080610195916] 
[Fix window region checking in UpdatePointer
robreim at bobturf.org**20080511094056] 
[remove myself as maintainer from modules I don't maintain or use.
David Roundy <droundy at darcs.net>**20080828151830] 
[change withUrgencyHookC api
Devin Mullins <me at twifkak.com>**20080821052046
 Now it takes an UrgencyConfig record type.
] 
[Accept a range of xmonad versions
Spencer Janssen <spencerjanssen at gmail.com>**20080820214056] 
[StackTile_fix
acura at allyourbase.se**20080820061918] 
[X.H.UrgencyHook: haddock fixes
Devin Mullins <me at twifkak.com>**20080816195220] 
[Improve documentation for XMonad.Hooks.EwmhDesktops
Spencer Janssen <spencerjanssen at gmail.com>**20080813191857] 
[simplify WindowBringer code, and change greedyView to focusWindow
Devin Mullins <me at twifkak.com>**20080811033137] 
[Updates to my config
Spencer Janssen <spencerjanssen at gmail.com>**20080812050124] 
[Added XMonad.Hooks.DynamicHooks
Braden Shepherdson <Braden.Shepherdson at gmail.com>**20080724222054
 Allows runtime creation and modification of ManageHooks. Also allows one-shot
 ManageHooks that are removed after the fire. Note that if several transient
 hooks fire at once, only the most recently defined is executed, and all
 are removed.
] 
[XMonad.Hooks.UrgencyHook: +FocusHook
gwern0 at gmail.com**20080716224745
 This is a hook for simply traveling to whatever window has just set an urgent flag, instead of doing something more involved like printing to a status bar and letting the user do something manually.
] 
[Grid/HintedGrid: prefer wider windows
Lukas Mai <l.mai at web.de>**20080717205138] 
[I prefer the spencerjanssen at gmail.com address
Spencer Janssen <spencerjanssen at gmail.com>**20080714204005] 
[callUrgencyHook after adjustUrgents
Devin Mullins <me at twifkak.com>**20080714043020
 So folks can readUrgents inside their urgencyHook, should they so desire.
] 
[XMonad/Doc/Developing.hs: update haddock ln, cpedit
gwern0 at gmail.com**20080708205058] 
[XMonad/Doc.hs: why link to a specific version instead of the latest?
gwern0 at gmail.com**20080708202236] 
[XMonad.Actions.Plane.Linear
leoserra at minaslivre.org**20080706175303] 
[XMonad.Actions.Plane: Improvements in code quality
Marco Túlio Gontijo e Silva <marcot at riseup.net>**20080706172829] 
[XMonad.Actions.Plane: Treat error in read
Marco Túlio Gontijo e Silva <marcot at riseup.net>**20080710135342] 
[XMonad.Actions.Plane: GConf support
Marco Túlio Gontijo e Silva <marcot at riseup.net>**20080709001900
 Thanks to Johan Dahlin.
] 
[X.A.WindowNavigation: comments
Devin Mullins <me at twifkak.com>**20080710041028] 
[add autoComplete option to XMonad.Prompt
Devin Mullins <me at twifkak.com>**20080704073415
 Maybe this will get Gwern one step closer to a complete Ratpoison binding.
] 
[XMonad.Actions.Plane: Copyright update
Marco Túlio Gontijo e Silva <marcot at riseup.net>**20080709001548] 
[XMonad.Actions.Plane: removed missing haddock chunck
Marco Túlio Gontijo e Silva <marcot at riseup.net>**20080709010530] 
[Added function to filter out scratchpad workspace for use with ewmhLogHookCustom.
Braden Shepherdson <Braden.Shepherdson at gmail.com>**20080706161027] 
[Added ewmhLogHookCustom, which allows arbitrary transformation of the workspace list.
Braden Shepherdson <Braden.Shepherdson at gmail.com>**20080706160847] 
[adding thesaurus.reference.com and Google Labs Code Search searches
brian at lorf.org**20080701090142] 
[fillout banish example in Warp.hs
gwern0 at gmail.com**20080629202047
 We also include a nice little type to avoid specifying 0 0 stuff.
] 
[fix Actions.Wap doc
gwern0 at gmail.com**20080629115504
 warp 1 1 has a comment claiming that this moves the cursor to the lower *left*, but if you look at the warpToWindow haddock, it says that 1 1 is actually lower *right* - as indeed it proved to do. This was annoying as it led me astray for a minute or so.
] 
[allow function keys up to F24
brian at lorf.org**20080626040516] 
[Now using -name instead of -title as the term app argument, and correspondingly resource for the ManageHook.
Braden Shepherdson <Braden.Shepherdson at gmail.com>**20080608180748] 
[Actions/Search.hs: export SearchEngine constructor
Brent Yorgey <byorgey at gmail.com>**20080620212016] 
[Export PerWorkspace to allow type signatures
Malebria <malebria at riseup.net>**20080620015046] 
[XMonad.Util.EZConfig: add keypad bindings
Lukas Mai <l.mai at web.de>**20080615143702] 
[XMonad.Util.EZConfig: minor cleanups
Lukas Mai <l.mai at web.de>**20080528165450] 
[make default highlighting a bit dimmer for neighbors in WindowNavigation.
David Roundy <droundy at darcs.net>**20080610174200] 
[keep drag panes on the bottom of the window stack.
David Roundy <droundy at darcs.net>**20080610174044] 
[add support to Magnifier for vertical zooming.
David Roundy <droundy at darcs.net>**20080610173747] 
[XMonad.Hooks.EwmhDesktops export EwmHDesktopsHook
Malebria <malebria at riseup.net>**20080610130614
 Any function that a user may write in his configuration file that is related to ewmhDesktopsLayout cannot have it's type signature if this type is not exported.
] 
[XMonad.Config.Desktop type problem (monomorphism?)
Malebria <malebria at riseup.net>**20080610182856
 With main = xmonad defaultConfig {layoutHook = desktopLayoutModifiers Full} I got a type error, that's not present with the patch.
] 
[Make prompt keybindings work when numLock or capsLock are active
Justin Bogner <mail at justinbogner.com>**20080608172057] 
[Replaced old "spawn on mod+s" semantics with "spawn/summon or banish on mod+s".
Braden Shepherdson <Braden.Shepherdson at gmail.com>**20080608045457
 Originally the key binding just spawned a new floating terminal on every keypress.
 Now it spawns if it doesn't exist, summons from another workspace if it does but
 isn't visible, or banishes it to a dynamically created workspace if it is on the
 current workspace.
] 
[Exporting addHiddenWorkspace, it's needed by the new Scratchpad
Braden Shepherdson <Braden.Shepherdson at gmail.com>**20080608045318] 
[Added scratchpadSpawnActionTerminal to specify the terminal program directly as a String.
Braden Shepherdson <Braden.Shepherdson at gmail.com>**20080608032619] 
[Removed odd scratchpadSpawnDefault, improved documentation.
Braden Shepherdson <Braden.Shepherdson at gmail.com>**20080608032439] 
[Actions.Search.hs: switch inappropriate use of getShellCompl for a historyCompletion
gwern0 at gmail.com**20080607071331
 It's inappropriate because if I am searching Wikipedia, say, why on earth do I want completion of files and executables on my PC? A previous search query is much more likely to be what I want.
] 
[Prompt.hs: +a historyCompletion function for use in XPrompts
gwern0 at gmail.com**20080607071225] 
[Add C-w to XMonad.Prompt
Trevor Elliott <trevor at galois.com>**20080605220656
 
  * Bind C-w to kill the previous word
 
] 
[Add missing xfce module to .cabal
Don Stewart <dons at galois.com>**20080602174219] 
[Use lines instead of columns in configuration (similar to GNOME and KDE)
Malebria <malebria at riseup.net>**20080526225337] 
[Bug correction when areasColumn > 1
Malebria <malebria at riseup.net>**20080526223220] 
[more documentation for WindowNavigation and UrgencyHook
Devin Mullins <me at twifkak.com>**20080525050231] 
[X.A.WindowNavigation: add logHook for better state tracking
Devin Mullins <me at twifkak.com>**20080525032325] 
[doco tweaks
Devin Mullins <me at twifkak.com>**20080524211849] 
[made fadeInactiveLogHook take an argument amount to fade
Justin Bogner <mail at justinbogner.com>**20080523213937] 
[add FadeInactive to fade out inactive windows using xcompmgr
Justin Bogner <mail at justinbogner.com>**20080523205838] 
[add close window functionality to EwmhDesktops
Justin Bogner <mail at justinbogner.com>**20080523185908] 
[Add XMonad.Actions.Plane
Malebria <malebria at riseup.net>**20080523004357] 
[Default Xfce config, this time with me holding the copyright, maintainership, etc.
Ivan.Miljenovic at gmail.com**20080522105316] 
[StackTile: minor documentation fix
Joachim Fasting <joachim.fasting at gmail.com>**20080521182637
 That '[]' in the example seems incorrect
] 
[StackTile
acura at allyourbase.se**20080520195559
 
 A simple patch to get a dishes like stacking, but with the ability to resize master pane.
] 
[revamp Search.hs to export a replacement for simpleEngine
gwern0 at gmail.com**20080519190912
 It's called searchEngine now, and is a wrapper around the SearchEngine type. Different type as well
] 
[sp ShowWName.hs
gwern0 at gmail.com**20080519190520] 
[remove ScratchWorkspace.
David Roundy <droundy at darcs.net>**20080516185729
 It's ugly code, and I'd be surprised if anyone actually uses it.  I see no
 reason to continue to maintain it.
] 
[Fixed location of xmonad.conf
Roman Cheplyaka <roma at ro-che.info>**20080518204602] 
[add site name in search prompt dialog
zhen.sydow at gmail.com**20080518101357] 
[add youtube to search engines
zhen.sydow at gmail.com**20080513212508] 
[SwapWorkspaces: swapTo Next|Prev
Devin Mullins <me at twifkak.com>**20080518024121] 
[UrgencyHook: removeVisiblesFromUrgents -> cleanupUrgents
Devin Mullins <me at twifkak.com>**20080515164436
 Now only removes windows based on SuppressWhen setting.
] 
[Added XMonad.Config.PlainConfig: proof-of-concept GHC-less plain text configuration file parser
Braden Shepherdson <Braden.Shepherdson at gmail.com>**20080517222916
 
 An example of the config file format can be found in the Haddock.
 Notably missing features are docks and more layouts than just the standard three.
] 
[XMonad.Hooks.SetWMName: Update documentation to reflect the addition of startupHook.
lithis <xmonad at selg.hethrael.org>**20080516221011] 
[I no longer use ScratchWorkspace.
David Roundy <droundy at darcs.net>**20080516185715] 
[fix bug in smartBorders when combined with decorated windows.
David Roundy <droundy at darcs.net>**20080516184855] 
[decent documentation for UrgencyHook
Devin Mullins <me at twifkak.com>**20080515082222
 Blame it on lack of sleep. Or perhaps the causation is the reverse.
] 
[X.A.WindowNavigation: currentPosition and setPosition share the same `inside` logic, now
Devin Mullins <me at twifkak.com>**20080515062211
 Aside from documentation, this is pretty much usable, now.
] 
[X.A.WindowNavigation: have currentPosition handle axes independently
Devin Mullins <me at twifkak.com>**20080515053330
 This improves some subtle interactions between mod-j/k and mod-w/a/s/d, though
 that might not become very apparent until I fix setPosition.
] 
[fix compile warnings in BoringWindows
Devin Mullins <me at twifkak.com>**20080515051728] 
[add BoringWindows module to make certain windows skipped when rotating focus.
David Roundy <droundy at darcs.net>**20080514162846] 
[UrgencyHook: some documentation (more is needed)
Devin Mullins <me at twifkak.com>**20080514080104] 
[UrgencyHook: got rid of the need for instances to know about suppressWhen
Devin Mullins <me at twifkak.com>**20080514072217
 This changes the API a little bit, but that's what you get for using a day-old feature from darcs.
] 
[move AppLauncher from Actions module to Prompt module
zhen.sydow at gmail.com**20080513201252] 
[X.A.WindowNavigation: comment cleanup
Devin Mullins <me at twifkak.com>**20080513091313] 
[windowRect now compensates for border width
Devin Mullins <me at twifkak.com>**20080513090151
 Odd that I have to do (Rectangle x y (w + 2 * bw) (h + 2 * bw)) -- you'd think
 the window would be centered within the bordered area.
] 
[X.A.WindowNavigation: update TODO
Devin Mullins <me at twifkak.com>**20080513044229] 
[X.A.WindowNavigation: minor cleanup
Devin Mullins <me at twifkak.com>**20080512170410] 
[X.A.WindowNavigation: simplify inr somewhat
Devin Mullins <me at twifkak.com>**20080512090647] 
[X.A.WindowNavigation: clarity
Devin Mullins <me at twifkak.com>**20080512085338] 
[X.A.WindowNavigation: ugh, typo
Devin Mullins <me at twifkak.com>**20080512082228] 
[X.A.WindowNavigation: implement swap, extract withTargetWindow commonality
Devin Mullins <me at twifkak.com>**20080512064715
 Why doesn't mapWindows exist already?
] 
[add more flexible withWindowNavigationKeys
Devin Mullins <me at twifkak.com>**20080512050637
 Names aren't permanent yet, so don't cry if they change.
] 
[X.A.WindowNavigation: TODO
Devin Mullins <me at twifkak.com>**20080511222116] 
[X.A.WindowNavigation: add withWindowNavigation, for easy setup
Devin Mullins <me at twifkak.com>**20080511220458
 This should be more flexible than it is -- I've got an idea, but am interested to hear others.
] 
[X.A.WindowNavigation: fix currentPosition
Devin Mullins <me at twifkak.com>**20080511212128
 Now properly deals with an unitialized state (e.g. from a restart) or an
 inconsistent state (e.g. from using mod-j/k). Deserves cleanup.
] 
[X.A.WindowNavigation: add TODOs
Devin Mullins <me at twifkak.com>**20080511211326] 
[X.A.WindowNavigation state is now workspace-specific
Devin Mullins <me at twifkak.com>**20080511071656
 racking up some code debt, here...
] 
[X.A.WindowNavigation: minor doco changes
Devin Mullins <me at twifkak.com>**20080506074235] 
[add draft XMonad.Actions.WindowNavigation
Devin Mullins <me at twifkak.com>**20080504050022
 This is an experiment with replacing the WindowNavigation LayoutModifier with
 one that simply adds keybindings and stores state in an IORef. Credit to
 droundy for the original code -- hopefully I'm not butchering it. The end
 intent is to add Xinerama support, but it'll be a little while before I get
 there.
] 
[new contrib module to launch apps with command line parameters
zhen.sydow at gmail.com**20080513134754] 
[pull suppressWhen logic into main WithUrgencyHook handler
Devin Mullins <me at twifkak.com>**20080513075247
 In order for this to work, I added a new UrgencyHook method to communicate the
 SuppressWhen value. I'm not sure if this is actually better than just providing
 a convenience function, but it's an easy switch.
] 
[add suppressWhen option to dzenUrgencyHook
Devin Mullins <me at twifkak.com>**20080513054615] 
[WindowNavigation: extract navigable function
Devin Mullins <me at twifkak.com>**20080422045248] 
[UrgencyHook: doc typo
Devin Mullins <me at twifkak.com>**20080512052137] 
[UrgencyHook: extract whenNotVisible
Devin Mullins <me at twifkak.com>**20080512041852] 
[SpawnUrgencyHook, FWIW
Devin Mullins <me at twifkak.com>**20080512040449] 
[make UrgencyHook an EventHook
Devin Mullins <me at twifkak.com>**20080512024822
 This gets rid of the stupid bug that led to a need for the clearBit hack, and
 allowed me to simplify the types (since EventHooks aren't required to
 parameterize on the window type). Config files need not change, unless they
 declare instances of UrgencyHook, in which case, they should remove "Window" as
 is seen in this patch.
 
] 
['xmobar' function added to DynamicLog for running xmobar with some defaults
Ivan N. Veselov <veselov at gmail.com>**20080508194918] 
[HintedTile: Fix mistake in documentation.
lithis <xmonad at selg.hethrael.org>**20080508003552] 
[Use gnome-session-save for the mod-shift-q binding
Spencer Janssen <sjanssen at cse.unl.edu>**20080507082205] 
[Use the named constant 'none' rather than 0
Spencer Janssen <sjanssen at cse.unl.edu>**20080507081854] 
[HintedTile: Improve documentation.
lithis <xmonad at selg.hethrael.org>**20080508000245] 
[Whitespace only
Spencer Janssen <sjanssen at cse.unl.edu>**20080507031306] 
[Add a binding for Gnome's "Run Application" dialog
Spencer Janssen <sjanssen at cse.unl.edu>**20080507031127] 
[Add some keybindings to the Kde config
Spencer Janssen <sjanssen at cse.unl.edu>**20080507022658] 
[Indentation
Spencer Janssen <sjanssen at cse.unl.edu>**20080507022553] 
[Add ToggleStruts to the desktop config
Spencer Janssen <sjanssen at cse.unl.edu>**20080507022516] 
[Refactor my config
Spencer Janssen <sjanssen at cse.unl.edu>**20080507021504] 
[Add XMonad.Config.Kde
Spencer Janssen <sjanssen at cse.unl.edu>**20080507020833] 
[Don't move the pointer if the user is moving the mouse
Klaus Weidner <kweidner at pobox.com>**20080417022234
 
 This patch depends on the following xmonad core patch:
 
   Remember if focus changes were caused by mouse actions or by key commands
 
 If the user was moving the mouse, it's not appropriate to move the pointer
 around in resonse to focus changes. Do that only in response to keyboard
 commands.
] 
[Missing pragmas
Don Stewart <dons at galois.com>**20080506053402] 
[Add full documentation
Don Stewart <dons at galois.com>**20080505210546] 
[minor cleanup on getName
Devin Mullins <me at twifkak.com>**20080504054923] 
[bug doco for UrgencyHook
Devin Mullins <me at twifkak.com>**20080426203638] 
[NamedWindows: when converting the text property, handle the empty list.
Spencer Janssen <sjanssen at cse.unl.edu>**20080502104249
 This fixes a "Prelude.head" exception observed with windows that have no title.
 Reproduce by placing several windows in the tabbed layout, then starting
 'xterm -name ""'.  Thanks to Andrea for pointing out the issue.
] 
[Fix issue #179 by handling events correctly
Andrea Rossato <andrea.rossato at unibz.it>**20080501062357] 
[My monitor is larger now :)
Spencer Janssen <sjanssen at cse.unl.edu>**20080430083026] 
[manageHooks for my config
Spencer Janssen <sjanssen at cse.unl.edu>**20080430082536] 
[Remove redundant type signature
Spencer Janssen <sjanssen at cse.unl.edu>**20080430082447] 
[Add XMonad.Config.Desktop and XMonad.Config.Gnome
Spencer Janssen <sjanssen at cse.unl.edu>**20080430082253] 
[Alphabetize exposed-modules
Spencer Janssen <sjanssen at cse.unl.edu>**20080430035453] 
[new contrib layout: XMonad.Layout.SimplestFloat - A floating layout like SimpleFloat, but without decoration
joamaki at gmail.com**20080424220957] 
[stricitfy some gap fields
Don Stewart <dons at galois.com>**20080427191247] 
[XMonad.Hooks.ManageHelpers: quick&dirty support for _NET_WM_STATE_FULLSCREEN
Lukas Mai <l.mai at web.de>**20080426132745] 
[XMonad.Hooks.Script: haddock fixes
Lukas Mai <l.mai at web.de>**20080426132629] 
[Error fix for Tabbed when tabbar always shown
Ivan.Miljenovic at gmail.com**20080424063135] 
[remove my config file -- the wiki is where its at.
Don Stewart <dons at galois.com>**20080419195650] 
[tweaks to docs for SimpleDecoration
Don Stewart <dons at galois.com>**20080418215155] 
[Allow tabbar to always be shown.
Ivan.Miljenovic at gmail.com**20080415043728
 Patch take 4, hopefully the final version.  Includes droundy's suggestions.
] 
[polish
Don Stewart <dons at galois.com>**20080418033133] 
[Script-based hooks
Trevor Elliott <trevor at galois.com>**20080416213024] 
[Don't strictify the Display component, this triggers a bug in GHC 6.6
Spencer Janssen <sjanssen at cse.unl.edu>**20080416185733] 
[Fix to IM modifier.
Roman Cheplyaka <roma at ro-che.info>**20080414232437
 Avoid differentiating integrated stack by using StackSet.filter.
] 
[IM layout converted to LayoutModifier, which can be applied to any layout
Ivan N. Veselov <veselov at gmail.com>**20080413205824] 
[stictify some fields
Don Stewart <dons at galois.com>**20080413070117] 
[strictify some fields
Don Stewart <dons at galois.com>**20080413065958] 
[Fix window order in EWMH
Joachim Breitner <mail at joachim-breitner.de>**20080411134411
 For pagers to draw the stacking order correctly, the focused window has to
 be the last in the list. Thus put an appropriate implementation of allWindows
 into the Module.
 This does not work perfectly with floating windows.
] 
[remove myself as maintainer of CopyWindow.
David Roundy <droundy at darcs.net>**20080409144333
 I'm not sure who's maintaining this, but it's not me.
] 
[XMonad.Util.WindowProperties: add WM_WINDOW_ROLE as Role
Roman Cheplyaka <roma at ro-che.info>**20080409174935] 
[Generalize copyWindow, minor style change
Spencer Janssen <sjanssen at cse.unl.edu>**20080408210050] 
[XMonad.Actions.CopyWindow: added copyToAll and killAllOtherCopies functions
Ivan N. Veselov <veselov at gmail.com>**20080408195111] 
[XMonad.Actions.UpdatePointer: doc fix
Lukas Mai <l.mai at web.de>**20080407152741] 
[XMonad.Util.Font: minor reformatting
Lukas Mai <l.mai at web.de>**20080406020935] 
[DynamicLog: resolve merge conflict
Lukas Mai <l.mai at web.de>**20080406020527] 
[Encode the entire DynamicLog output, instead of just window title.
lithis <xmonad at selg.hethrael.org>**20080329031537] 
[DynamicLog: add support for UTF-8 locales when compiled with XFT or UFT-8 support
Andrea Rossato <andrea.rossato at unibz.it>**20080313102643] 
[XMonad.Util.Font: don't call setlocale; core does it for us
Lukas Mai <l.mai at web.de>**20080406013123] 
[XMonad.Util.NamedWindows: fix imports
Lukas Mai <l.mai at web.de>**20080326172745] 
[Changed getName to use locale-aware functions
Mats Jansborg <mats at jansb.org>**20070819132104
 Rewrote getName using getTextProperty and wcTextPropertyToTextList.
] 
[Added next-window versions of the raise* functions.
Ian Zerny <ian at zerny.dk>**20080405182900] 
[XMonad.Layout.Master: initial import
Lukas Mai <l.mai at web.de>**20080404220734] 
[update contrib for applySizeHints changes
Lukas Mai <l.mai at web.de>**20080404220558] 
[XMonad.Hooks.ManageDocks: haddock fix
Lukas Mai <l.mai at web.de>**20080404220532] 
[MultiToggle/Instances: ghc 6.6 can't parse LANGUAGE pragma
Brent Yorgey <byorgey at gmail.com>**20080404200157] 
[Document _NET_ACTIVE_WINDOW behaviour more exactly
Joachim Breitner <mail at joachim-breitner.de>**20080404072944] 
[_NET_ACTIVE_WINDOW moves windows if necessary
Joachim Breitner <mail at joachim-breitner.de>*-20080402143811
 This makes EWMH behave a bit more like metacity: If _NET_ACTIVE_WINDOW is
 received and the window is not on the current worspace, it is brought here 
 (instead of the workspace switched to the other one). So for example, if you
 click on the pidgin icon in the panel and the buddy list is already open some
 where it is moved here.
] 
[onstart=lower, solves floating dzen issue
Don Stewart <dons at galois.com>**20080403203425] 
[some bang patterns
Don Stewart <dons at galois.com>**20080403172246] 
[have 'dzen' use autoStruts to detect the gaps
Don Stewart <dons at galois.com>**20080403003130] 
[Actions/Search.hs: add dictionary.com search
Brent Yorgey <byorgey at gmail.com>**20080402150521] 
[_NET_ACTIVE_WINDOW moves windows if necessary
Joachim Breitner <mail at joachim-breitner.de>**20080402143811
 This makes EWMH behave a bit more like metacity: If _NET_ACTIVE_WINDOW is
 received and the window is not on the current worspace, it is brought here 
 (instead of the workspace switched to the other one). So for example, if you
 click on the pidgin icon in the panel and the buddy list is already open some
 where it is moved here.
] 
[HintedGrid: guesstimate window flexibility and layout rigid windows first
Lukas Mai <l.mai at web.de>**20080402042846] 
[HintedGrid: try both bottom-up/top-down window placement to minimize unused space
Lukas Mai <l.mai at web.de>**20080402012538] 
[Grid/HintedGrid: use an ncolumns formula inspired by dwm's "optimal" mode
Lukas Mai <l.mai at web.de>**20080402012126] 
[XMonad.Layout.Gaps: new contrib module for manual gap support, in the few cases where ManageDocks is not appropriate (dock apps that don't set STRUTS properly, adjusting for a display that is cut off on one edge, etc.)
Brent Yorgey <byorgey at gmail.com>**20080402003742] 
[improve WindowGo.hs Haddock formatting
gwern0 at gmail.com**20080401023130] 
[forgot a haddock for getEditor in Shell.hs
gwern0 at gmail.com**20080401022012] 
[WindowGo.hs: +raiseBrowser, raiseEditor
gwern0 at gmail.com**20080401021740
 Specialize runOrRaise in the same way as with Actions.Search, for one's browser and one's editors.
] 
[RunOrRaise.hs: FF 3 doesn't use the "Firefox-bin" classname
gwern0 at gmail.com**20080401015049] 
[Search.hs: remove an argument from selectSearch and promptSearch
gwern0 at gmail.com**20080401013947
 The new getBrowser function allows us to mv the old selectSearch and promptSearch aside as too-general functions, and replace them with new versions, which employ getBrowser to supply one more argument. This allows us to replace the tedious 'selectSearch google "firefox"; selectSearch yahoo "firefox"...' with shorter 'selectSearch google' and so on. One less argument.
 
 Also, update the docs.
] 
[Shell.hs: +getBrowser, getEditor, helper function
gwern0 at gmail.com**20080401013447
 The helper function asks the shell for the value of a variable, else returns the second argument.
 getBrowser and getEditor obviously specialize it for two particular possibly queries
] 
[XMonad.Layout.HintedGrid: initial import
Lukas Mai <l.mai at web.de>**20080401231722] 
[Documentation improvement.
Roman Cheplyaka <roma at ro-che.info>**20080401134305] 
[Remove broken link to screenshot.
Roman Cheplyaka <roma at ro-che.info>**20080331210854] 
[MultiToggle: add new XMonad.Layout.MultiToggle.Instances module for common instances of Transformer, update MultiToggle docs accordingly
Brent Yorgey <byorgey at gmail.com>**20080331201739] 
[XMonad.Actions.CycleRecentWS: initial import
Michal Janeczek <janeczek at gmail.com>**20080331111906] 
[XMonad.Hooks.ManageDocks: export checkDoc
Lukas Mai <l.mai at web.de>**20080331012911] 
[XMonad.Layout.Grid: fix indentation
Lukas Mai <l.mai at web.de>**20080330004859] 
[move Direction type from WindowNavigation to ManageDocks (ManageDocks will move into the core, taking Direction with it)
Brent Yorgey <byorgey at gmail.com>**20080331010127] 
[ManageDocks: clean up + add more documentation
Brent Yorgey <byorgey at gmail.com>**20080331002929] 
[Util.Run, Hooks.DynamicLog: re-export hPutStrLn and hPutStr from Util.Run for convenience, and update DynamicLog documentation to show proper imports
Brent Yorgey <byorgey at gmail.com>**20080328205446] 
[ManageDocks: add avoidStrutsOn, for covering some docks and not others by default.
Brent Yorgey <byorgey at gmail.com>**20080327203940] 
[ManageDocks: add ability to toggle individual gaps independently
Brent Yorgey <byorgey at gmail.com>**20080327111722] 
[PerWorkspace: add modWorkspace(s) combinators, for selectively applying layout modifiers to certain workspaces but not others
Brent Yorgey <byorgey at gmail.com>**20080326214351] 
[Haddock fix
Roman Cheplyaka <roma at ro-che.info>**20080330134435] 
[Remove stale status gaps code
Spencer Janssen <sjanssen at cse.unl.edu>**20080329230737] 
[TAG 0.7
Spencer Janssen <sjanssen at cse.unl.edu>**20080329202416] 
[Bump version to 0.7
Spencer Janssen <sjanssen at cse.unl.edu>**20080329192400] 
[Fix haddock error
Spencer Janssen <sjanssen at cse.unl.edu>**20080329191752] 
[XMonad.Layout.MultiToggle: let runLayout modify the base layout if no transformer is active
Lukas Mai <l.mai at web.de>**20080328190903] 
[Spiral: add documentation
Brent Yorgey <byorgey at gmail.com>**20080328192231] 
[corrected version of make workspaceDir work even in workspaces with no windows.
David Roundy <droundy at darcs.net>**20080327142257] 
[cleanup in Tabbed (make 'loc' be actual location).
David Roundy <droundy at darcs.net>**20080326151004] 
[make workspaceDir work even in workspaces with no windows.
David Roundy <droundy at darcs.net>*-20080326152708
 This also fixes a (minor) bug when the focussed window is present on
 multiple visible workspaces.
] 
[clean up Config.Droundy.
David Roundy <droundy at darcs.net>**20080327002159] 
[make workspaceDir work even in workspaces with no windows.
David Roundy <droundy at darcs.net>**20080326152708
 This also fixes a (minor) bug when the focussed window is present on
 multiple visible workspaces.
] 
[ManageDocks: add warning about making sure gaps are set to zero before switching to avoidStruts, since ToggleStruts won't work otherwise
Brent Yorgey <byorgey at gmail.com>**20080326231928] 
[update documentation in XMonad/Doc in preparation for 0.7 release
Brent Yorgey <byorgey at gmail.com>**20080326195741] 
[XMonad.Hooks.ManageHelpers: reformatting
Lukas Mai <l.mai at web.de>**20080326182707] 
[XMonad.Layout.NoBorders: fix floating fullscreen logic
Lukas Mai <l.mai at web.de>**20080326172844] 
[UpdatePointer: Make pointer position configurable.
xmonad at selg.hethrael.org**20080326075759] 
[Fix bugs in Tabbed and TabBarDecoration -- please remember multi-head!
Spencer Janssen <sjanssen at cse.unl.edu>**20080326034541] 
[my current config
Don Stewart <dons at galois.com>**20080326023303] 
[I don't use DwmStyle
Spencer Janssen <sjanssen at cse.unl.edu>**20080325213818] 
[fix bug in TabBarDecoration leading to gaps in corner.
David Roundy <droundy at darcs.net>**20080325210327] 
[fix bug leading to gaps in tabs at the corner of the screen.
David Roundy <droundy at darcs.net>**20080325210211
 Besides being ugly, this had the effect of making me fail to click on the
 tab I aimed for, if it was in the corner.
] 
[XMonad.Layout.LayoutModifier: add a metric crapload of documentation
Brent Yorgey <byorgey at gmail.com>**20080325205006] 
[XMonad.Layout.Reflect: update documentation to reflect (haha) recent updates to MultiToggle
Brent Yorgey <byorgey at gmail.com>**20080325185630] 
[XMonad.Layout.HintedTile: make alignment of shrunk windows configurable
Lukas Mai <l.mai at web.de>**20080325202958] 
[XMonad.Actions.Commands: documentation fix
Brent Yorgey <byorgey at gmail.com>**20080325165707] 
[focusedHasProperty
redbeard0531 at gmail.com**20080325040412] 
[XMonad.Util.Themes: improve documentation to make it clear that themes only apply to decorated layouts
Brent Yorgey <byorgey at gmail.com>**20080324185946] 
[Doc/Extending: remove references to "XMonad.Layouts" -- it's now called "XMonad.Layout", and in any case, importing it explicitly is not needed anyway.
Brent Yorgey <byorgey at gmail.com>**20080324143503] 
[XMonad.Actions.Search: add Google Maps search
Brent Yorgey <byorgey at gmail.com>**20080324143348] 
[XMonad.Layout.Magnifier: add documentation
Brent Yorgey <byorgey at gmail.com>**20080324143214] 
[wfarrTheme
wcfarrington at gmail.com**20080324011625
 Add a new color theme using blue and black.
] 
[added RunOrRaisePrompt, exported getCommands from Shell
Justin Bogner <mail at justinbogner.com>**20080323222632] 
[XMonad.Actions.MouseGestures: reexport Direction from WindowNavigation, avoid type duplication
Lukas Mai <l.mai at web.de>**20080322193457] 
[use ewmhDesktopsLayout in Droundy.
David Roundy <droundy at darcs.net>**20080322153610] 
[cut Anneal and Mosaic.
David Roundy <droundy at darcs.net>**20080322153546] 
[fix WorkspaceDir to work when there are multiple screens.
David Roundy <droundy at darcs.net>**20080311221201
 In particlar, ScratchWorkspace broke this.
] 
[fix various compilation errors
Lukas Mai <l.mai at web.de>**20080322074113] 
[XMonad.Layout.NoBorders: first attempt at documenting smartBorders
Lukas Mai <l.mai at web.de>**20080321221315] 
[allow magnifier to toggle whether it's active
daniel at wagner-home.com**20080321104605] 
[a magnifier that defaults to not magnifying any windows
daniel at wagner-home.com**20080321104441] 
[XMonad.Layout.Magnifier: remove references to Data.Ratio.% from documentation
Lukas Mai <l.mai at web.de>**20080320223816] 
[mark Mosaic as broken. use MosaicAlt
Don Stewart <dons at galois.com>**20080320223717] 
[add ewmhDesktopsLayout for EWMH interaction
Joachim Breitner <mail at joachim-breitner.de>**20080319195736
 
 This is based on Andrea?s EventHook thingy. Note that I could not merge
 this with some of my earlier EWHM interaction patches (darcs was failing on me),
 so I copied some code. Do not try to merge it with those patches either.
 
 Note that the docs are saying what should work. There are still some bugs
 to be resolved, but it works sometimes and should work similar to what we have.
] 
[Export HandleEvent type to be able to use it in type annotations
Joachim Breitner <mail at joachim-breitner.de>**20080319195603] 
[I now use ServerMode
Andrea Rossato <andrea.rossato at unibz.it>**20080226115347] 
[EventHook: handle events after the underlying layout and more
Andrea Rossato <andrea.rossato at unibz.it>**20080224230854
 - check the first time the Bool is True
 - coding and naming style
] 
[Add Hooks.ServerMode: an event hook to execute commands sent by an external client
Andrea Rossato <andrea.rossato at unibz.it>**20080224133706] 
[Add EventHook: a layout modifier to handle X events
Andrea Rossato <andrea.rossato at unibz.it>**20080224112432] 
[tabs
Don Stewart <dons at galois.com>**20080317224758] 
[WindowProperties: fix documentation
Brent Yorgey <byorgey at gmail.com>**20080318204540] 
[Move window properties to a separate Util module
Roman Cheplyaka <roma at ro-che.info>**20080318165658
 Add XMonad.Util.WindowProperties
 Modify XMonad.Layout.IM.hs to use WindowProperties.
] 
[XMonad.Layout.NoBorders: always unborder fullscreen floating windows, even when there are multiple screens
Lukas Mai <l.mai at web.de>**20080317183043] 
[MagicFocus: reimplement as a LayoutModifier, fix bug (MagicFocus didn't pass on messages to underlying layouts)
Brent Yorgey <byorgey at gmail.com>**20080317193008] 
[WindowGo.hs: improve description
gwern0 at gmail.com**20080316223946
 I'm still not sure whether the description makes sense if you don't already understand the idea.
] 
[Run.hs: improve haddock
gwern0 at gmail.com**20080316223219
 This module too was causing horizontal scrolling because of the shell command. I managed to discover that you only need to specify 'png:' *or* "foo.png", not both, which trimmed off enough characters.
 Also, I improved the docs for my functions.
] 
[XSelection.hs: improved haddockf formatting, more links, & cpedit
gwern0 at gmail.com**20080316222050] 
[Search.hs: try to add a more descriptive type
gwern0 at gmail.com**20080316215728] 
[improve the formatting for WindowGo.hs
gwern0 at gmail.com**20080316215642] 
[Search.hs: haddock fmt
gwern0 at gmail.com**20080316213914
 This removes whitespace in source code snippets. Because Haddock renders quoted source code as monospaced unwrappable text, the excess whitespace meant you would have to scroll horizontally, unpleasantly.
] 
[Add XMonad.Actions.Promote
xmonad at s001.hethrael.com**20080316205722] 
[LayoutCombinators: improve documentation (closes ticket #136)
Brent Yorgey <byorgey at gmail.com>**20080316195826] 
[Xmonad.Layout.NoBorders: make smartBorders unborder fullscreen floating windows (bug 157)
Lukas Mai <l.mai at web.de>**20080316042941] 
[Xmonad.Prompt.DirExec: fix haddock error
Lukas Mai <l.mai at web.de>**20080316042840] 
[EwmhDesktops: advertise support for _NET_CLIENT_LIST_STACKING
Alec Berryman <alec at thened.net>**20080315212631] 
[ScratchWorkspace: update to work with runLayout changes
Brent Yorgey <byorgey at gmail.com>**20080311212908] 
[Scratchpad: update to work with runLayout changes
Brent Yorgey <byorgey at gmail.com>**20080311181715] 
[MagicFocus: update to work with runLayout changes
Brent Yorgey <byorgey at gmail.com>**20080311181625] 
[LayoutScreens: update to work with runLayout changes
Brent Yorgey <byorgey at gmail.com>**20080311181537] 
[Combo: update to work with runLayout changes
Brent Yorgey <byorgey at gmail.com>**20080311181400] 
[MultiToggle: fix to work with runLayout changes to core
Brent Yorgey <byorgey at gmail.com>**20080311172046] 
[PerWorksapce: use a safer False as default
Andrea Rossato <andrea.rossato at unibz.it>**20080223075531] 
[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.
] 
[ToggleLayouts: reimplemented with runLayout
Andrea Rossato <andrea.rossato at unibz.it>**20080223081553] 
[LayoutCombinators: NewSelect reimplemented with runLayout
Andrea Rossato <andrea.rossato at unibz.it>**20080223080958] 
[LayoutModifier: reimplement ModifiedLayout using runLayout and more
Andrea Rossato <andrea.rossato at unibz.it>**20080223075610
 - change modifyLayout type to get the Workspace
 - updated ResizeScreen and ManageDocks accordingly.
] 
[Combo: updated to latest runLayout changes
Andrea Rossato <andrea.rossato at unibz.it>**20080222175924] 
[EZConfig: add documentation and a warning, so no one repeats my silly hard-to-track-down mistake.
Brent Yorgey <byorgey at gmail.com>**20080311172610] 
[Fix to work with "floats always use current screen" patch
robreim at bobturf.org**20080308024928] 
[make smartBorders ignore screens with no dimensions.
David Roundy <droundy at darcs.net>**20080308224244] 
[rewrite ScratchWorkspace to make scratch always visible, but not always on screen.
David Roundy <droundy at darcs.net>**20080308223830] 
[add HiddenNonEmptyWS to CycleWS to avoid workspaces already visible.
David Roundy <droundy at darcs.net>**20080308223717] 
[Fix ThreeColumns doc.
Roman Cheplyaka <roma at ro-che.info>**20080307203022] 
[Shell: add support for UTF-8 locales
Andrea Rossato <andrea.rossato at unibz.it>**20080302095924] 
[Font and XUtils: add UTF-8 support and various fixes related to XFT
Andrea Rossato <andrea.rossato at unibz.it>**20080302095712
 - printStringXMF: use the background color for XFT fonts too
 - textWidthXMF now returns the text width even with xft fonts
 - textExtentsXMF will now return only the ascend and the descent of a
   string.
 - stringPosition now takes the display too
 - add support for UTF-8 locales: if the contrib library is compiled
   with the 'with_xft' or the 'with_utf8' option the prompt and the
   decoration system will support UTF-8 locales - this requires
   utf8-strings.
] 
[Ssh: coding style
Andrea Rossato <andrea.rossato at unibz.it>**20080229100346] 
[Ssh: complete known hosts with non standard ports too
Andrea Rossato <andrea.rossato at unibz.it>**20080229095014] 
[Fix xmonadPromptC and use it.
nicolas.pouillard at gmail.com**20080306163928] 
[Documentation typo about UpdatePointer.
nicolas.pouillard at gmail.com**20080306163516] 
[Fix ToggleOff: It was adding 0.1 to the magnification.
Braden Shepherdson <Braden.Shepherdson at gmail.com>**20080305222302] 
[Removed WmiiActions module.
Juraj Hercek <juhe_xmonad at hck.sk>**20080305082336] 
[Adjusted signature of DirExec module functions.
Juraj Hercek <juhe_xmonad at hck.sk>**20080301171905
   - added parameter for function which executes the selected program
   - renamed dirExecPromptWithName to dirExecPromptNamed
] 
[Import of new DirExec module.
Juraj Hercek <juhe_xmonad at hck.sk>**20080229212257
   - allows execution of executable files from specific directory
] 
[Hooks.DynamicLog: export xmobarPP
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20080303215637] 
[Magnifier: fix behavior for windows on the bottom + right of the screen.  Now all magnified windows will be the same size, possibly shifted in order to fit completely on the screen.
Brent Yorgey <byorgey at gmail.com>**20080303204619] 
[Changed semantics of UpdatePointer to move to nearest point
robreim at bobturf.org**20080301143126] 
[UpdatePointer XMonadContrib module
robreim at bobturf.org**20080301134401] 
[Util.Run: minor clarification in comment
gwern0 at gmail.com**20080303051513] 
[Add XMonad.Actions.PerWorkspaceKeys
Roman Cheplyaka <roma at ro-che.info>**20080302202346] 
[Haddock fix: Changed URL-Markup
Dominik Bruhn <dominik at dbruhn.de>**20080302185435] 
[switch Droundy to smartBorders (which works better with ScratchWorkspace).
David Roundy <droundy at darcs.net>**20080301191103] 
[XMonad.Layout.Simplest: add FlexibleInstances pragma
Lukas Mai <l.mai at web.de>**20080301061714] 
[XMonad.Layout.ScratchWorkspace: avoid warnings, make tests compile again
Lukas Mai <l.mai at web.de>**20080301061625] 
[implement ScratchWorkspace.
David Roundy <droundy at darcs.net>**20080229224316] 
[in Prompt.Workspace sort by official workspace order.
David Roundy <droundy at darcs.net>**20080229223047] 
[simplify Simplest--allow it to apply to non-Windows.
David Roundy <droundy at darcs.net>**20080229221326] 
[XMonad.Actions.MouseGestures.mkCollect: generalize type
Lukas Mai <l.mai at web.de>**20080229211732] 
[Add bottom-tabbed layout.
Roman Cheplyaka <roma at ro-che.info>**20080229155120] 
[XMonad.Actions.MouseGestures: refactoring, code simplification
Lukas Mai <l.mai at web.de>**20080229002136
 
 It is now possible to get "live" status updates while the gesture handler
 is running. I use this in my xmonad.hs to print the current gesture to my
 status bar. Because collecting movements is now the callback's job, the
 implementation of mouseGestureH got quite a bit simpler. The interface is
 incompatible with the previous mouseGestureH but the old mouseGesture
 function works as before.
 
] 
[EZConfig: additional documentation
Brent Yorgey <byorgey at gmail.com>**20080227164602] 
[XMonad.Util.Scratchpad: change 'XConfig Layout' to 'XConfig l', to avoid type mismatches; the exact layout type doesn't actually matter
Brent Yorgey <byorgey at gmail.com>**20080227014201] 
[EZConfig: add an emacs-style keybinding parser!
Brent Yorgey <byorgey at gmail.com>**20080226222723
 Now, instead of writing out incredibly dull things like
 
   ((modMask conf .|. controlMask .|. shiftMask, xK_F2), ...)
 
 you can just write
 
   ("M-C-S-<F2>", ...)
 
 Hooray!
] 
[Xmonad.Actions.MouseGestures: generalize interface, allow hooks
Lukas Mai <l.mai at web.de>**20080226202639] 
[update inactive debugging code in MouseGestures; no visible changes
Lukas Mai <l.mai at web.de>**20071109020755] 
[Scratchpad terminal
Braden Shepherdson <Braden.Shepherdson at gmail.com>**20080225183633
 
 Key binding and ManageHook to pop up a small, floating terminal window for a few quick commands.
 
 Combined with a utility like detach[1], makes a great X application launcher.
 
 Requires my two new ManageHooks (doRectFloat, specifically).
 
 [1] http://detach.sourceforge.net
] 
[Two new floating window ManageHooks.
Braden Shepherdson <Braden.Shepherdson at gmail.com>**20080225183337
 
 Adds doRectFloat, which floats the new window in the given rectangle; and doCenterFloat, which floats the 
 new window with its original size, but centered.
] 
[Fix usage doc.
Roman Cheplyaka <roma at ro-che.info>**20080225062330] 
[Fix haddock hyperlink.
Roman Cheplyaka <roma at ro-che.info>**20080224205416] 
[Add XMonad.Layout.IM
Roman Cheplyaka <roma at ro-che.info>**20080221085752] 
[Export XMonad.Layout.Grid.arrange (for use in XMonad.Layout.IM)
Roman Cheplyaka <roma at ro-che.info>**20080221062204] 
[Decoration: some haddock updates
Andrea Rossato <andrea.rossato at unibz.it>**20080220214934] 
[Small refactoring.
Nils Anders Danielsson <nils.anders.danielsson at gmail.com>**20080210224756] 
[Fixed off-by-one error which broke strut handling for some panels.
Nils Anders Danielsson <nils.anders.danielsson at gmail.com>**20080210222600] 
[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.
] 
[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.
] 
[Fix doc for Tabbed
Roman Cheplyaka <roma at ro-che.info>**20080219055650] 
[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)
] 
[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
] 
[Refactor XMonad.Hooks.DynamicLog
Roman Cheplyaka <roma at ro-che.info>**20080210222406
 This allows using DynamicLog not only for statusbar.
] 
[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] 
[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.
] 
[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.
] 
[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] 
[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] 
[ XMonad.Actions.WindowGo: add a runOrRaise module for Joseph Garvin with the help of Spencer Janssen
gwern0 at gmail.com**20080204173402] 
[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 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..;)
] 
[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] 
[Layout.ShowWName: generalize the instance
Andrea Rossato <andrea.rossato at unibz.it>**20080115045139] 
[add emptyLayout to MultiToggle
Lukas Mai <l.mai at web.de>**20080128175313] 
[grammar fix
Lukas Mai <l.mai at web.de>**20080128175059] 
[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] 
[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] 
[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.
] 
[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.Reflect: new contrib module for reflecting layouts horizontally/vertically
Brent Yorgey <byorgey at gmail.com>**20080115030947] 
[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] 
[Remove references to xmonad 0.4
Spencer Janssen <sjanssen at cse.unl.edu>**20071209232324] 
[Bump version to 0.5!
Spencer Janssen <sjanssen at cse.unl.edu>**20071209231622] 
[Extending: updated to the lates config changes - manageHook simplification
Andrea Rossato <andrea.rossato at unibz.it>**20071209164731] 
[I use ManageDocks now
Spencer Janssen <sjanssen at cse.unl.edu>**20071209134445] 
[Update ManageDocks to the new ManageHook system, remove the gap setting code in favor of AvoidStruts
Spencer Janssen <sjanssen at cse.unl.edu>**20071209134225] 
[Extending: some fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071209123623] 
[Arossato: my teaTime application.
Andrea Rossato <andrea.rossato at unibz.it>**20071209123327] 
[XPropManage: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071209123246] 
[SetWMName: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071209123227] 
[EwmhDesktops: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071209123204] 
[DynamicLog: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071209123148] 
[Sshprompt: Add explanation for the completion in sshprompt
dominik at dbruhn.de**20071207000904] 
[More import pruning
Spencer Janssen <sjanssen at cse.unl.edu>**20071208014846] 
[Remove XMonad.Operations imports
Spencer Janssen <sjanssen at cse.unl.edu>**20071208000547] 
[Prune more imports
Spencer Janssen <sjanssen at cse.unl.edu>**20071207235116] 
[I use CopyWindow now
Spencer Janssen <sjanssen at cse.unl.edu>**20071207234018] 
[Remove redundant imports
Spencer Janssen <sjanssen at cse.unl.edu>**20071207233827] 
[Typo in extra-source-files
Spencer Janssen <sjanssen at cse.unl.edu>**20071205050311] 
[Depend on X11>=1.4.0
Spencer Janssen <sjanssen at cse.unl.edu>**20071205050012] 
[Remove TilePrime, it is subsumed by HintedTile
Spencer Janssen <sjanssen at cse.unl.edu>**20071205045746] 
[Update Sjanssen.hs
Spencer Janssen <sjanssen at cse.unl.edu>**20071205045648] 
[LayoutScreens and Square: haddock updates
Brent Yorgey <byorgey at gmail.com>**20071204204039] 
[Droundy.hs: add spaces so haddock isn't confused by commented-out ||| combinator
Brent Yorgey <byorgey at gmail.com>**20071204203622] 
[my urgency-hook code also seems to crach... change in Droundy.
David Roundy <droundy at darcs.net>**20071201162310] 
[disable avoidStruts in Droundy again.
David Roundy <droundy at darcs.net>**20071201160226
 Apparently, ManageDocks still crashes on X86-64...
] 
[fix bug where we failed to hide combo decorations.
David Roundy <droundy at darcs.net>**20071201155859] 
[add to Droundy a non-working urgency hook and enable avoidStruts.
David Roundy <droundy at darcs.net>**20071201132910] 
[update XSelection.hs; apparently the utf8-string library has updated
gwern0 at gmail.com**20071130161429
 Note that this does not fix the apparent problems with actually using getSelection, even though it works fine from a GHCi prompt...
] 
[LayoutScreens: documentation fix
Brent Yorgey <byorgey at gmail.com>**20071130165423] 
[tune Droundy config.
David Roundy <droundy at darcs.net>**20071130145138] 
[more coding on Mosaic.
David Roundy <droundy at darcs.net>**20071123192455] 
[make Mosaic read (and partially try to obey) WM hints.
David Roundy <droundy at darcs.net>**20071123162538] 
[refactor XMonad.Prompt, add new modules XMonad.Prompt.{Input,Email}
Brent Yorgey <byorgey at gmail.com>**20071128142417
 XMonad.Prompt.Input is a new module which provides a framework for
 prompting the user for input and passing it along to some other action,
 useful for building actions which require user input.
 XMonad.Prompt.Email is a simple example of the use of XMonad.Prompt.Input,
 which prompts the user for a recipient, subject, and body, and sends
 a one-line email.
 I also made a small refactoring to XMonad.Prompt in order to support
 XMonad.Prompt.Input.
] 
[AppendFile: initial import
Brent Yorgey <byorgey at gmail.com>**20071127224258
 XMonad.Prompt.AppendFile is a new module which provides a prompt for
 appending a single line of text to a file.  I use it for quickly
 writing down ideas/todos/etc. to a special file when I can't be 
 bothered to stop what I'm doing to write things down properly.
] 
[DynamicWorkspaces: haddock updates
Brent Yorgey <byorgey at gmail.com>**20071127220033] 
[WorkspaceDir: minor haddock update
Brent Yorgey <byorgey at gmail.com>**20071127215652] 
[WmiiActions: haddock updates
Brent Yorgey <byorgey at gmail.com>**20071127194427] 
[WindowBringer: haddock updates
Brent Yorgey <byorgey at gmail.com>**20071127193948] 
[Warp: haddock updates
Brent Yorgey <byorgey at gmail.com>**20071127193717] 
[TagWindows: haddock updates
Brent Yorgey <byorgey at gmail.com>**20071127193213] 
[SwapWorkspaces: haddock updates
Brent Yorgey <byorgey at gmail.com>**20071127192634] 
[SimpleDate, Submap: modMask --> modMask x
Brent Yorgey <byorgey at gmail.com>**20071127192039] 
[Submap: haddock updates
Brent Yorgey <byorgey at gmail.com>**20071127191841] 
[SinkAll: haddock updates
Brent Yorgey <byorgey at gmail.com>**20071127191318] 
[SimpleDate: haddock updates; more specific imports
Brent Yorgey <byorgey at gmail.com>**20071127190832] 
[Doc/Developing: various edits
Brent Yorgey <byorgey at gmail.com>**20071127190345] 
[RotView: haddock updates
Brent Yorgey <byorgey at gmail.com>**20071127185741] 
[LayoutCombinators: a few minor haddock fixes
Brent Yorgey <byorgey at gmail.com>**20071127163106] 
[LayoutCombinators: changes infixes and added many other combinators.
Andrea Rossato <andrea.rossato at unibz.it>**20071127161807] 
[CopyWindow: fixed docs
Andrea Rossato <andrea.rossato at unibz.it>**20071125121418] 
[Alleviate clashing symbols with XMonad.ManageHook.<||>
Spencer Janssen <sjanssen at cse.unl.edu>**20071127004258] 
[xmonad-contrib.cabal: better order for the documentation links
Brent Yorgey <byorgey at gmail.com>**20071125171745] 
[links to documentatoin subsections in generated docs
Don Stewart <dons at galois.com>**20071125052206] 
[depend on X11 1.4.0
Don Stewart <dons at galois.com>**20071125034656] 
[RotSlaves: haddock updates
Brent Yorgey <byorgey at gmail.com>**20071124174518] 
[MouseGestures: haddock updates
Brent Yorgey <byorgey at gmail.com>**20071124173351] 
[Extending.hs: a few edits
Brent Yorgey <byorgey at gmail.com>**20071124171452] 
[Developing: a start
Andrea Rossato <andrea.rossato at unibz.it>**20071124141133] 
[Extending: some more stuff
Andrea Rossato <andrea.rossato at unibz.it>**20071124141106] 
[Arossato: some changes. I now use Magnifier among my layouts
Andrea Rossato <andrea.rossato at unibz.it>**20071124140918] 
[DynamicLog: added a dynamicLogXmobar
Andrea Rossato <andrea.rossato at unibz.it>**20071124125202] 
[Haddock docs: modMask --> modMask x
Brent Yorgey <byorgey at gmail.com>**20071124022635] 
[FocusNth: haddock updates
Brent Yorgey <byorgey at gmail.com>**20071124022249] 
[FloatKeys: haddock updates
Brent Yorgey <byorgey at gmail.com>**20071124003702] 
[FlexibleResize: haddock updates
Brent Yorgey <byorgey at gmail.com>**20071124002013] 
[FlexibleManipulate: add link to mouse binding documentation
Brent Yorgey <byorgey at gmail.com>**20071124001927] 
[FlexibleManipulate: haddock updates
Brent Yorgey <byorgey at gmail.com>**20071124000754] 
[FindEmptyWorkspace: haddock updates
Brent Yorgey <byorgey at gmail.com>**20071123235427] 
[Doc/Extending.hs: edits
Brent Yorgey <byorgey at gmail.com>**20071123232743] 
[Extending: added manageHook and logHook sections
Andrea Rossato <andrea.rossato at unibz.it>**20071123212943] 
[Magnifier: typo
Andrea Rossato <andrea.rossato at unibz.it>**20071123212900] 
[LayoutCombinators: fix doc
Andrea Rossato <andrea.rossato at unibz.it>**20071123175723] 
[DwmPromote: haddock updates
Brent Yorgey <byorgey at gmail.com>**20071123202204] 
[DeManage: haddock updates
Brent Yorgey <byorgey at gmail.com>**20071123201702] 
[CycleWS: haddock updates
Brent Yorgey <byorgey at gmail.com>**20071123201122] 
[CopyWindow: haddock updates
Brent Yorgey <byorgey at gmail.com>**20071123200643] 
[ConstrainedResize: haddock updates
Brent Yorgey <byorgey at gmail.com>**20071123195643] 
[Doc/Extending.hs: add a section about configuring mouse bindings.
Brent Yorgey <byorgey at gmail.com>**20071123184501] 
[Commands.hs: haddock updates
Brent Yorgey <byorgey at gmail.com>**20071123171619] 
[dafaultConfig --> defaultConfig
Brent Yorgey <byorgey at gmail.com>**20071123164722] 
[LayoutCombinators: haddock documentation
Andrea Rossato <andrea.rossato at unibz.it>**20071123154311] 
[ToggleLayout: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071123142934] 
[LayoutHints: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071123142859] 
[LayouModifier: haddock docs
Andrea Rossato <andrea.rossato at unibz.it>**20071123142519] 
[MagicFocus: haddock docs
Andrea Rossato <andrea.rossato at unibz.it>**20071123141657] 
[Maximize: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071123141304] 
[MosaicAlt: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071123141021] 
[Named: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071123140557] 
[NoBorders: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071123140535] 
[ResizableTile: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071123140511] 
[Roledex: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071123140451] 
[Spiral: haddock docs
Andrea Rossato <andrea.rossato at unibz.it>**20071123135023] 
[clean up mosaic a bit more.
David Roundy <droundy at darcs.net>**20071123153617] 
[Mosaic: fix docs
Andrea Rossato <andrea.rossato at unibz.it>**20071123125339] 
[ThreeColumns: haddock docs
Andrea Rossato <andrea.rossato at unibz.it>**20071123124659] 
[TilePrime: haddock docs
Andrea Rossato <andrea.rossato at unibz.it>**20071123124456] 
[TwoPane: haddock docs
Andrea Rossato <andrea.rossato at unibz.it>**20071123123155] 
[WindowNavigation: haddock documentation
Andrea Rossato <andrea.rossato at unibz.it>**20071123121129] 
[WorkspaceDir: docs
Andrea Rossato <andrea.rossato at unibz.it>**20071123115635] 
[HntedTile: alignement
Andrea Rossato <andrea.rossato at unibz.it>**20071123115031] 
[Combo: some haddock formatting
Andrea Rossato <andrea.rossato at unibz.it>**20071123114904] 
[make CopyWindow export a fancy copy-window-anywhere function.
David Roundy <droundy at darcs.net>**20071123121020] 
[remove need for faulty Read instance of NamedWindow.
David Roundy <droundy at darcs.net>**20071122170448] 
[Magnifier: more refactoring and a few message handlers
Andrea Rossato <andrea.rossato at unibz.it>**20071123113353] 
[cabal: build Magnifier again.
Andrea Rossato <andrea.rossato at unibz.it>**20071122190427] 
[Magnifier: some fixes and refactoring. It now works properly.
Andrea Rossato <andrea.rossato at unibz.it>**20071122190124] 
[Mosaic: unbreak build, remove unused import that ghc complains about
Alec Berryman <alec at thened.net>**20071122175925] 
[Extending: editing the key bindings require importing Data.Map
Andrea Rossato <andrea.rossato at unibz.it>**20071122133901] 
[cabal: added mosaic and anneal
Andrea Rossato <andrea.rossato at unibz.it>**20071122133837] 
[NamedWindow: Mosaic requires NamedWindow to have a Read instance
Andrea Rossato <andrea.rossato at unibz.it>**20071122133802] 
[Added Anneal used by the original mosaic
Andrea Rossato <andrea.rossato at unibz.it>**20071122133732] 
[Make the original Mosaic work with LayoutClass
Andrea Rossato <andrea.rossato at unibz.it>**20071122133658] 
[Prompt/Man.hs: fixing haddock
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071122091828] 
[Don't show HintedTile in the description
Spencer Janssen <sjanssen at cse.unl.edu>**20071122072615] 
[UrgencyHook: haddock fixes
Devin Mullins <me at twifkak.com>**20071122065616] 
[updated XPropManage to ManageHook type
joel.suovaniemi at iki.fi**20071122053203] 
[More HintedTile refactoring
Spencer Janssen <sjanssen at cse.unl.edu>**20071122053154] 
[HintedTile:
Spencer Janssen <sjanssen at cse.unl.edu>**20071122051157
  - code formatting
  - refactoring, based on TilePrime work by Eric Mertens
  - use the current border width of the window, this improves interaction with
    the No/SmartBorders extensions
] 
[HintedTile: orientation bug fix, remove wide and tall in favor of the Tall and Wide constructors.
Spencer Janssen <sjanssen at cse.unl.edu>**20071122042720] 
[Hooks/DynamicLog.hs: minor typo.
Joachim Fasting <joachim.fasting at gmail.com>**20071119131218] 
[Extending.hs: more edits and additions.
Brent Yorgey <byorgey at gmail.com>**20071122034432] 
[Doc.hs: edits and additions
Brent Yorgey <byorgey at gmail.com>**20071121204329] 
[Extending.hs: edits and additions
Brent Yorgey <byorgey at gmail.com>**20071121203631] 
[Configuring.hs: edits and additions
Brent Yorgey <byorgey at gmail.com>**20071121203312] 
[README: update reference to documentation
Brent Yorgey <byorgey at gmail.com>**20071121202643] 
[Tabbed: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071121181710] 
[HintedTile: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071121181635] 
[Grid: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071121181616] 
[DragPane: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071121181555] 
[Dishes: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071121181529] 
[Combo: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071121181507] 
[Circle: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071121181441] 
[Accordion: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071121181409] 
[Updated documentation of all prompts in XMonad.Prompt
Andrea Rossato <andrea.rossato at unibz.it>**20071121142715] 
[Font: haddock fix
Andrea Rossato <andrea.rossato at unibz.it>**20071121141618] 
[NamedWindows: haddock fix
Andrea Rossato <andrea.rossato at unibz.it>**20071121141424] 
[XUtils: haddock fix
Andrea Rossato <andrea.rossato at unibz.it>**20071121141319] 
[Shell: small doc fix
Andrea Rossato <andrea.rossato at unibz.it>**20071121141013] 
[Tabbed: haddock documentation and code formatting
Andrea Rossato <andrea.rossato at unibz.it>**20071121140908] 
[HintedTile: typo
Andrea Rossato <andrea.rossato at unibz.it>**20071121140828] 
[HintedTile: ported to the LayoutClass
Andrea Rossato <andrea.rossato at unibz.it>**20071121112331] 
[PerWorkspace.hs: various fixes and updates
Brent Yorgey <byorgey at gmail.com>**20071120173307] 
[Doc.hs: remove modules from export list.
Brent Yorgey <byorgey at gmail.com>**20071120172947
 Apparently GHC 6.8.1 issues a warning when a re-exported module does not
 itself export anything.
] 
[A new documentation system
Andrea Rossato <andrea.rossato at unibz.it>**20071120151552
 What to see a real Haddock abuse? Here you go. Removed
 Documentation.hs and added a new name space: XMonad.Doc. By importing
 other documentation modules we may also use the synopsis in XMonad.Doc.
 
 If you believe that we should not have modules without code, well this
 code is not for you: just that strange -- stuff ...;)
] 
[PerWorkspace.hs: minor haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071120103250
 Also, we don't need to add those docstring annotation (%...), since
 that system is not used anymore.
] 
[new contrib module: Layout.PerWorkspace
Brent Yorgey <byorgey at gmail.com>**20071120024612
 This module allows you to configure layouts on a per-workspace basis,
 rather than specifying the same layout for all workspaces.  (Of course,
 you still really *are* specifying the same layout for all workspaces,
 it just acts differently depending on the workspace. =)
] 
[NoBorders.hs: Haddock markup fix
Brent Yorgey <byorgey at gmail.com>**20071120024415] 
[xmc/README: fix xmonad capitalisation, spelling fix
Brent Yorgey <byorgey at gmail.com>**20071120024118] 
[Port overview from contrib.html to Documentation.hs
Don Stewart <dons at galois.com>**20071119183127] 
[remove Mosaic and Anneal.
David Roundy <droundy at darcs.net>**20071119153005] 
[remove MessageHooks
Devin Mullins <me at twifkak.com>**20071119070417
 Duplicating xmonad-core and working around static-linking issues was getting
 old quick. MessageHooks is now a branch of core, located at:
   http://code.haskell.org/~twifkak/xmonad-MessageHooks
] 
[make handle Just Another Message Hook
Devin Mullins <me at twifkak.com>**20071119041731] 
[Anneal is only used by Mosaic which is disabled
Spencer Janssen <sjanssen at cse.unl.edu>**20071119061440] 
[Prompt: comment only
Andrea Rossato <andrea.rossato at unibz.it>**20071119000357] 
[Port XPrompt to XMonad.Util.Font, various other refactorings
Spencer Janssen <sjanssen at cse.unl.edu>**20071116232743] 
[Miscellaneous spell-checking
Shachaf Ben-Kiki <shachaf at gmail.com>**20071118230319] 
[RotSlaves.hs: documentation fix.
Brent Yorgey <byorgey at gmail.com>**20071118215858] 
[Documentation.hs: a lot more edits and additions.
Brent Yorgey <byorgey at gmail.com>**20071118215541] 
[Prompt/*: add XConfig variable to keybindings in doc.
Joachim Fasting <joachim.fasting at gmail.com>**20071118144849] 
[Prompt/XMonad.hs: minor typo in doc.
Joachim Fasting <joachim.fasting at gmail.com>**20071118144722] 
[Actions/SinkAll.hs: update usage doc.
Joachim Fasting <joachim.fasting at gmail.com>**20071118144153] 
[Prompt/Man.hs: remove docstring.
Joachim Fasting <joachim.fasting at gmail.com>**20071118143240] 
[Documentation: added the section on editing layoutHook
Andrea Rossato <andrea.rossato at unibz.it>**20071118121240] 
[needs pattern guards
Don Stewart <dons at galois.com>**20071118053204] 
[Prompt/Workspace.hs: suggest using defaultXPConfig in usage doc.
Joachim Fasting <joachim.fasting at gmail.com>**20071117230940] 
[Prompt/Workspace.hs: update module description.
Joachim Fasting <joachim.fasting at gmail.com>**20071117230931] 
[Prompt/Window.hs: fix import statements in usage doc.
Joachim Fasting <joachim.fasting at gmail.com>**20071117230854] 
[Prompt/Ssh.hs: fix import statements in usage doc.
Joachim Fasting <joachim.fasting at gmail.com>**20071117230814] 
[Prompt/Man.hs: tweak import stuff in usage doc.
Joachim Fasting <joachim.fasting at gmail.com>**20071117230734] 
[Prompt/Layout.hs: add missing import to usage doc.
Joachim Fasting <joachim.fasting at gmail.com>**20071117230627] 
[Prompt/Shell.hs: fix invalid module  import in usage doc.
Joachim Fasting <joachim.fasting at gmail.com>**20071117224614] 
[experimental MessageHooks "branch" of main
Devin Mullins <me at twifkak.com>**20071118010836
 Doesn't do much now, but is enough to allow me to define noFollow again. :)
 I believe the need to change XConfig may force this to be an *actual* branch of
 xmonad core, but I'm not sure yet.
] 
[Grid: tabs -> spaces
Devin Mullins <me at twifkak.com>**20071117201140] 
[Documentation.hs: various stylistic edits, add a few more details
Brent Yorgey <byorgey at gmail.com>**20071117173924] 
[Documentation: added library description coding style and licensing policy - xmonad in small caps
Andrea Rossato <andrea.rossato at unibz.it>**20071117134631] 
[Documentation: added more stuff
Andrea Rossato <andrea.rossato at unibz.it>**20071117114217] 
[cpp-options requires Cabal 1.2.1
Devin Mullins <me at twifkak.com>**20071117012659] 
[Use cpp-options
Spencer Janssen <sjanssen at cse.unl.edu>**20071116232301] 
[Config/Droundy.hs: -Wall police, add -fno-warn-orphans
Brent Yorgey <byorgey at gmail.com>**20071116155202] 
[Move XMonad.Util.Font to fix haddock generation
Spencer Janssen <sjanssen at cse.unl.edu>**20071116215720] 
[cabal: I don't know how Hackage handles that so adopt a more general approach
Andrea Rossato <andrea.rossato at unibz.it>**20071116201644] 
[Documentation.hs: minor fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071116201600] 
[Arossato: my terminal is urxvt
Andrea Rossato <andrea.rossato at unibz.it>**20071116201533] 
[Documentation: added the section for adding and removing key bindings
Andrea Rossato <andrea.rossato at unibz.it>**20071116155110] 
[Documentation: more stuff added
Andrea Rossato <andrea.rossato at unibz.it>**20071116154059] 
[utf8-string isn't needed
Spencer Janssen <sjanssen at cse.unl.edu>**20071116133738] 
[Depend on X11-xft >= 0.2
Spencer Janssen <sjanssen at cse.unl.edu>**20071116130926] 
[XUtils: remove stringToPixel
Spencer Janssen <sjanssen at cse.unl.edu>**20071116125247] 
[Export XMonadFont's constructors, use those constructors in XMonad.Prompt
Spencer Janssen <sjanssen at cse.unl.edu>**20071116125157] 
[Use Xft automatically if available
Spencer Janssen <sjanssen at cse.unl.edu>**20071116124211] 
[Font.hs: CPP around Xft calls, use a data type rather than Either
Spencer Janssen <sjanssen at cse.unl.edu>**20071116123552] 
[Font.hs: tabs
Spencer Janssen <sjanssen at cse.unl.edu>**20071116122551] 
[Add Font layer supporting an Xft backend. Make Tabbed.hs a user of this layer.
Clemens Fruhwirth <clemens at endorphin.org>**20071116120653] 
[Documentation: typos and formatting
Andrea Rossato <andrea.rossato at unibz.it>**20071116122929] 
[XUtils: a small haddock fix
Andrea Rossato <andrea.rossato at unibz.it>**20071116122359] 
[XMonad.Util.Run: meny haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071116120938
 I've also trasnformed gwern's comments to use '--' instead of {- -},
 for uniformity.
] 
[CustomKeys.hs: typo
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071116112531] 
[README: wrap long lines
Andrea Rossato <andrea.rossato at unibz.it>**20071116105037] 
[Add Documentation.hs for documentation purposes
Andrea Rossato <andrea.rossato at unibz.it>**20071116104827
 An empty module for documentation purpose with configuration
 instructions.
] 
[Arossato: removed unneeded bits
Andrea Rossato <andrea.rossato at unibz.it>**20071116104753] 
[RotSlaves: small haddock fix
Andrea Rossato <andrea.rossato at unibz.it>**20071116104730] 
[update run xmonad script
Don Stewart <dons at galois.com>**20071115225704] 
[Prompt: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071115204828] 
[Arossato: documentation
Andrea Rossato <andrea.rossato at unibz.it>**20071115191039] 
[Prompt: just code formatting
Andrea Rossato <andrea.rossato at unibz.it>**20071115191012] 
[Prompt: add killWord edit action
Andrea Rossato <andrea.rossato at unibz.it>**20071115190734
 With this bindings:
 ^ - Delete kill forward
 ^ - BackSpace kill backward
] 
[remove unneeded Data.Bits imports.
David Roundy <droundy at darcs.net>**20071115161346] 
[CustomKeys.hs: "complete rebinding" mechanism explained
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071115151410
 Thanks to Don Stewart for his suggestion:
   http://article.gmane.org/gmane.comp.lang.haskell.xmonad/3339
] 
[Tabbed.hs, SetWMName.hs: the modules need bitwise "or"
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071115143758
 Tabbed.hs cleaned of trailing whitespace.
] 
[fix bug in WindowNavigation.
David Roundy <droundy at darcs.net>**20071114231914
 We weren't properly cleaning up in some cases, because we called focus,
 which calls windows, while handling a message, which had the result that
 changes to the layout were overwritten.  This had the result that
 windowNavigation combined with DragPane left stray drag bars hanging
 around.
] 
[ Tabbed: removed -fno-warn-orphans
Andrea Rossato <andrea.rossato at unibz.it>**20071114230544
 I added it by mistake, but it is not needed. Sorry.
] 
[simplify NewSelect code.
David Roundy <droundy at darcs.net>**20071114223538] 
[fix bug in LayoutCombinators.
David Roundy <droundy at darcs.net>**20071114210139] 
[no need to import Data.Bits
Don Stewart <dons at galois.com>**20071114183955] 
[ManageDocks.hs: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071114191327] 
[EZConfig.hs: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071114191109] 
[CustomKeys.hs: moved into `Util' directory
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071114153418
 I still wonder why do we need all those configuration examples. :)
] 
[Arossato: removed unneeded bits
Andrea Rossato <andrea.rossato at unibz.it>**20071114172500] 
[improve shrinking in Droundy.hs
David Roundy <droundy at darcs.net>**20071114142127] 
[Arossato: just code formatting
Andrea Rossato <andrea.rossato at unibz.it>**20071114142213] 
[Arossato: typo
Andrea Rossato <andrea.rossato at unibz.it>**20071114142046] 
[Arossato: some keybindings tuning
Andrea Rossato <andrea.rossato at unibz.it>**20071114141719] 
[Tabbed: added -fno-warn-orphans
Andrea Rossato <andrea.rossato at unibz.it>**20071114135525] 
[Arossato: just code formattings
Andrea Rossato <andrea.rossato at unibz.it>**20071114135352] 
[Config.Arossato: my hand has been forced to pick up a true combinator set...
Andrea Rossato <andrea.rossato at unibz.it>**20071114133848] 
[UrgencyHook.hs: small haddock fix
Andrea Rossato <andrea.rossato at unibz.it>**20071114104844] 
[fix EZConfig documentation
Devin Mullins <me at twifkak.com>**20071114120442] 
[remove dead code
Devin Mullins <me at twifkak.com>**20071112184857] 
[CustomKeys.hs (customKeysFrom): new function
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071113201852
 Update third-party configuration to fit your key preferences.
 Extended documentation.
] 
[pattern guards and newtype deriving required for ManageDocks.hs to build!
Don Stewart <dons at galois.com>**20071114032625] 
[add ToggleStruts capability to avoidStruts.
David Roundy <droundy at darcs.net>**20071113203434] 
[Arossato: cleanup and fine-tuning
Andrea Rossato <andrea.rossato at unibz.it>**20071113163906] 
[make shrinker preserved over restart in tabbed.
David Roundy <droundy at darcs.net>**20071113163116] 
[REAME: one more try
gwern0 at gmail.com**20071112220523] 
[scripts/generate-configs: update docs
gwern0 at gmail.com**20071112144643] 
[HEADS UP: Rename XMonadContrib library as xmonad-contrib. 
Don Stewart <dons at galois.com>**20071112180919
 
 After building and install as normal, be sure to unregister your
 old XMonadContrib library:
 
     $ ghc-pkg unregister --user XMonadContrib-0.4
     $ ghc-pkg unregister XMonadContrib-0.4
 
 And then your ~/.xmonad/* stuff should link as normal.
 
] 
[XMonad.Config.CustomKeys - new module
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071112175530
 This module is another key bindings customization helper.
 
 Differences from XMonad.Util.EZConfig by Devin Mullins:
   EZConfig   -- M.union/M.difference
   CustomKeys -- Monad.Reader + foldr'ed M.insert/M.delete
 
 IMHO, both modules could evolve into something nice. :)
 Please discuss at the mailing list.
] 
[prune Droundy.hs.
David Roundy <droundy at darcs.net>**20071112172032] 
[NoBorders.hs: remove modifierDescription definitions, so NoBorders and SmartBorder don't change the layout description.
Brent Yorgey <byorgey at gmail.com>**20071112154525] 
[NoBorder.hs: documentation updates
Brent Yorgey <byorgey at gmail.com>**20071112154411] 
[fix intro doco for UrgencyHook
Devin Mullins <me at twifkak.com>**20071112044102
 Ooh, this new XConfig l -> XConfig l' function makes the docs disappear!
] 
[revert UrgencyHook behavior back to ICCCM non-compliance
Devin Mullins <me at twifkak.com>**20071112043325
 Note: If you're using UrgencyHook, this will break your config.
 @withUrgencyHook SomeUrgencyHook@ is XConfig -> XConfig, now. The layout hook
 has been renamed to urgencyLayoutHook.
 
 It may also be worth noting that, in order to recreate the old behavior without
 using redoLayout (so that this may be ported to an eventHook), I had to hijack
 logHook. Shouldn't harm anything, though.
 
 TODO: update main docs
] 
[add StdoutUrgencyHook, to help debug weird client behavior
Devin Mullins <me at twifkak.com>**20071112015855] 
[EZConfig: update for kind change in XConfig
Spencer Janssen <sjanssen at cse.unl.edu>**20071111215314] 
[changes to work with XConfig of kind * -> *.
David Roundy <droundy at darcs.net>**20071111005629] 
[depend on X11==1.3.0.20071111 for new type defns and 64 bit clean
Don Stewart <dons at galois.com>**20071111201055] 
[font size 15 pixels is the dzen default
Don Stewart <dons at galois.com>**20071109190328] 
[add two new modules, one to name layouts, another to select a layout.
David Roundy <droundy at darcs.net>**20071111195036
 The latter is pretty useless, as there's no way to find out what
 layouts are available, but it can at least allow you to select between
 any layouts that you happen to be using already (in one workspace or
 another).  The former is handy any time you'd rather have a short name
 for a layout (either for selecting, or for viewing in a status bar).
] 
[add helper module for writing configs
Devin Mullins <me at twifkak.com>**20071111075222
 Looking for suggestions on this module. Does it belong here? Is there a better
 name? Should the additional* functions pass the modMask to their second
 argument? etc.
] 
[let clients track their urgency, per ICCCM
Devin Mullins <me at twifkak.com>**20071111021241
 This removes the dependency on redoLayout -- now WithUrgencyHook defines handleMess only.
] 
[wrap user code in userCode, go figure
Devin Mullins <me at twifkak.com>**20071111002617
 (thanks à shachaf for that suggestion)
] 
[add LANGUAGE PatternGuards to UrgencyHook
Devin Mullins <me at twifkak.com>**20071111002238] 
[remove dead doco
Devin Mullins <me at twifkak.com>**20071111001443] 
[clarify config code... a bit
Devin Mullins <me at twifkak.com>**20071111000933] 
[fix doco for UrgencyHook
Devin Mullins <me at twifkak.com>**20071111000046] 
[add NoUrgencyHook, for shachaf's sake
Devin Mullins <me at twifkak.com>**20071110235857] 
[oops, export the configuration options
Devin Mullins <me at twifkak.com>**20071110233313] 
[add dzenUrgencyHook back
Devin Mullins <me at twifkak.com>**20071110232706
 TODO: fix all the doco
] 
[remove dzenUrgencyHook* from Dzen module
Devin Mullins <me at twifkak.com>**20071110231115
 To be replaced by UrgencyHook instances defined in the UrgencyHook module.
] 
[get UrgencyHook to compile
Devin Mullins <me at twifkak.com>**20071110224303
 (The boilerplate, it burns!) Still isn't useful (to me) yet, as I haven't
 ported dzenUrgencyHook to the new UrgencyHook class.
] 
[fix bug in avoidStruts.
David Roundy <droundy at darcs.net>**20071110214205] 
[typo fix in Util.Run
Devin Mullins <me at twifkak.com>**20071110211328] 
[add a few docs (very sparse) to DynamicWorkspaces.
David Roundy <droundy at darcs.net>**20071109152649] 
[add withWorkspace prompt, which automatically creates workspace if nonexistent.
David Roundy <droundy at darcs.net>**20071109152124] 
[Generalize safe/unsafeSpawn to MonadIO
Spencer Janssen <sjanssen at cse.unl.edu>**20071109073810] 
[Magnifier.hs: update so it at least compiles
gwern0 at gmail.com**20071108012522
 Code modified on advice of Wachter; note I make absolutely no claims that the code runs correctly or doesn't eat your pets or does anything besides compile without any warnings.
] 
[Dzen.hs: resend doc update
gwern0 at gmail.com**20071106211537] 
[Update docs in Util
gwern0 at gmail.com**20071106190258] 
[fix types to work with Mats fix to X11.
David Roundy <droundy at darcs.net>**20071108192318] 
[Change the type of properties from Word32 to CLong
Mats Jansborg <mats at jansb.org>**20071101192730] 
[fix bug in avoidStruts.
David Roundy <droundy at darcs.net>**20071108175250
 I've now tested this module, and it works on x86--but doesn't work on
 x86-64, because ManageDocks doesn't work on 64-bit.  But in any case, it
 works almost perfectly, with no user intervention needed (and no special
 hooks).  The only catch is that it doesn't notice when a panel disappears,
 so the layout won't adjust until the next refresh (e.g. if you change
 focus, layout or workspace).
] 
[clean up Droundy.hs.
David Roundy <droundy at darcs.net>**20071107144106] 
[DynamicLog: typo in docs
Andrea Rossato <andrea.rossato at unibz.it>**20071108010104] 
[over pararenthesised arty fibonacci
Don Stewart <dons at galois.com>**20071107230601] 
[Remove spurious import in Arossato's config.
Chris Mears <chris at cmears.id.au>**20071107215630] 
[Add my configuration file
Andrea Rossato <andrea.rossato at unibz.it>**20071107191305
 Spencer and David: you really did a great job. Thank you guys!
] 
[add higher order 'dzen' function
Don Stewart <dons at galois.com>**20071107183107
 
 The intent is that:
 
     main = dzen xmonad
 
 should just work, and indeed it does now, for launching a cool status
 bar with minimal effort.
] 
[Set defaultGaps for makeSimpleDzenConfig
Spencer Janssen <sjanssen at cse.unl.edu>**20071107092037] 
[DynamicLog: Add makeSimpleDzenConfig function
Eric Mertens <emertens at galois.com>**20071107085514
 
 This function serves as an example for spawning a dzen2 instance and printing
 the defaultPP to it.
] 
[Use spawnPipe in sjanssenConfig
Spencer Janssen <sjanssen at cse.unl.edu>**20071107082637] 
[Add spawnPipe
Spencer Janssen <sjanssen at cse.unl.edu>**20071107075009] 
[DynamicLog: add ppOutput field to PP
Eric Mertens <emertens at galois.com>**20071107055805
 
 This allows the user to specify an alternate destination for logging output
 instead of outputing to stdout (which is still the default).
] 
[Add EwmhDesktops to exposed-modules
Spencer Janssen <sjanssen at cse.unl.edu>**20071107031135] 
[Actions: update SinkAll doc
gwern0 at gmail.com**20071106192158] 
[Prompt.hs: update names
gwern0 at gmail.com**20071106192054] 
[EwmhDesktops: move to correct name, update so it compiles
gwern0 at gmail.com**20071106191751] 
[Man.hs: -Wall option not necessary as that's turned on in the Cabal files
gwern0 at gmail.com**20071106190659] 
[make Setup haddock work again
Lukas Mai <l.mai at web.de>**20071106141829] 
[change MultiToggle interface; add docs
Lukas Mai <l.mai at web.de>**20071106141729] 
[Remove SwitchTrans
Spencer Janssen <sjanssen at cse.unl.edu>**20071106065933] 
[Remove MetaModule
Spencer Janssen <sjanssen at cse.unl.edu>**20071106023713] 
[add serializable SwitchTrans (a.k.a. MultiToggle)
Lukas Mai <l.mai at web.de>**20071106005819] 
[make TilePrime compile again
l.mai at web.de**20071105233218] 
[add LayoutHints to MetaModule
l.mai at web.de**20071105233143] 
[make LayoutHints compile again
l.mai at web.de**20071105233020] 
[Expose LayoutCombinators
Spencer Janssen <sjanssen at cse.unl.edu>**20071106021611] 
[Add LANGUAGE pragmas for ManageDocks
Spencer Janssen <sjanssen at cse.unl.edu>**20071106021507] 
[Combo builds now
Spencer Janssen <sjanssen at cse.unl.edu>**20071106021341] 
[Make Combo build on GHC 6.8
Spencer Janssen <sjanssen at cse.unl.edu>**20071106021126] 
[Stupid mistake
Spencer Janssen <sjanssen at cse.unl.edu>**20071105101052] 
[-Werror
Spencer Janssen <sjanssen at cse.unl.edu>**20071105060223] 
[fix Config.Droundy to compile again.
David Roundy <droundy at darcs.net>**20071105205339] 
[-Wall police
Spencer Janssen <sjanssen at cse.unl.edu>**20071105060036] 
[Minor updates to Sjanssen.hs
Spencer Janssen <sjanssen at cse.unl.edu>**20071105055022] 
[Use configurations
Spencer Janssen <sjanssen at cse.unl.edu>**20071105034109] 
[-Wall is on
Don Stewart <dons at galois.com>**20071105031815] 
[Revert ghc-options changes
Spencer Janssen <sjanssen at cse.unl.edu>**20071105030327] 
[forgot to add my config file
Don Stewart <dons at galois.com>**20071105025856] 
[build with optimisations on as usual, fix a few compile errors
Don Stewart <dons at galois.com>**20071105024858] 
[Add XMonad.Config.Sjanssen
Spencer Janssen <sjanssen at cse.unl.edu>**20071105005832] 
[Move configs/droundy.hs to an actual library module
Spencer Janssen <sjanssen at cse.unl.edu>**20071104202957] 
[Improve test hook.
Spencer Janssen <sjanssen at cse.unl.edu>**20071104202919
 --disable-optimizations makes testing much faster.
 --user allows Cabal to satisfy dependencies from the user package database.
] 
[fix warnings in Combo.
David Roundy <droundy at darcs.net>**20071101214504] 
[make WorkspaceDir always store absolute pathnames.
David Roundy <droundy at darcs.net>**20071101214401] 
[add new off-center layout combinators.
David Roundy <droundy at darcs.net>**20071101214216] 
[add configs demo directory
David Roundy <droundy at darcs.net>**20071101203720] 
[Add Cabal stuff
Spencer Janssen <sjanssen at cse.unl.edu>**20071101202041] 
[make Hierarchical LayoutCombinators.
David Roundy <droundy at darcs.net>**20071101185418] 
[fix selectWorkspace to work with new config.
David Roundy <droundy at darcs.net>**20071101183546] 
[Hierarchify
Spencer Janssen <sjanssen at cse.unl.edu>**20071101201059] 
[Use hierarchical module names from the core
Spencer Janssen <sjanssen at cse.unl.edu>**20071101182824] 
[code to define a strut-avoiding layout.
David Roundy <droundy at darcs.net>**20071023220025] 
[reenable JumpToLayout in NewSelect.
David Roundy <droundy at darcs.net>**20071101181128] 
[-Wall police in Run.
David Roundy <droundy at darcs.net>**20071101152028] 
[port Combo (dropping combo).
David Roundy <droundy at darcs.net>**20071101152915] 
[Port ToggleLayouts
Spencer Janssen <sjanssen at cse.unl.edu>**20071101091853] 
[Port WorkspacePrompt
Spencer Janssen <sjanssen at cse.unl.edu>**20071101090425] 
[Port Accordion
Spencer Janssen <sjanssen at cse.unl.edu>**20071101090341] 
[Port Dishes
Spencer Janssen <sjanssen at cse.unl.edu>**20071101090312] 
[Dishes: tabs
Spencer Janssen <sjanssen at cse.unl.edu>**20071101090237] 
[Port DragPane
Spencer Janssen <sjanssen at cse.unl.edu>**20071101085733] 
[Port MosaicAlt
Spencer Janssen <sjanssen at cse.unl.edu>**20071101085524] 
[Port ResizableTile
Spencer Janssen <sjanssen at cse.unl.edu>**20071101085500] 
[Port Roledex
Spencer Janssen <sjanssen at cse.unl.edu>**20071101085430] 
[Port Spiral
Spencer Janssen <sjanssen at cse.unl.edu>**20071101085402] 
[Port TagWindows
Spencer Janssen <sjanssen at cse.unl.edu>**20071101085335] 
[Port ThreeColumns
Spencer Janssen <sjanssen at cse.unl.edu>**20071101085229] 
[Port TwoPane
Spencer Janssen <sjanssen at cse.unl.edu>**20071101085151] 
[Port XMonadPrompt
Spencer Janssen <sjanssen at cse.unl.edu>**20071101085037] 
[XMonadPrompt: tabs
Spencer Janssen <sjanssen at cse.unl.edu>**20071101084939] 
[Port WindowNavigation
Spencer Janssen <sjanssen at cse.unl.edu>**20071101084852] 
[Port Submap
Spencer Janssen <sjanssen at cse.unl.edu>**20071101084744] 
[Port CycleWS
Spencer Janssen <sjanssen at cse.unl.edu>**20071101084431] 
[NO TABS
Spencer Janssen <sjanssen at cse.unl.edu>**20071101083954] 
[Port Commands
Spencer Janssen <sjanssen at cse.unl.edu>**20071101083236] 
[XPrompt: don't import XMonad.config
Spencer Janssen <sjanssen at cse.unl.edu>**20071101074149] 
[More porting
Spencer Janssen <sjanssen at cse.unl.edu>**20071101073506] 
[Port DynamicLog
Spencer Janssen <sjanssen at cse.unl.edu>**20071101072606] 
[Port NoBorders
Spencer Janssen <sjanssen at cse.unl.edu>**20071101070859] 
[LayoutModifier: LayoutMessages have moved
Spencer Janssen <sjanssen at cse.unl.edu>**20071101070724] 
[Remove Config import from Run
Spencer Janssen <sjanssen at cse.unl.edu>**20071101070408] 
[Remove 'descriptions' stuff from NewSelect.  I think we can do this without make LayoutClass larger
Spencer Janssen <sjanssen at cse.unl.edu>**20071101033844] 
[add NewSelect layout combinator.
David Roundy <droundy at darcs.net>**20071024152648
 This patch adds a selection layout combinator ||| which
 replaces Select, and makes the Layout data type unnecessary.
 This combinator isn't yet feature-complete, as I didn't implement
 backwards rotation (PrevLayout), but that's obviously doable.  This
 patch requires the descriptions function be added to LayoutClass in
 core.
] 
[ManPrompt.hs: auto-complete explicit paths (those with `/')
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071104202056
 Bash's compgen is used for this (like in ShellPrompt.hs).
 
 Enable all GHC warnings.
 
 Improve documentation (slightly).
] 
[clean up destroyed windows from urgents list
Devin Mullins <me at twifkak.com>**20071103150358] 
[add focusUrgent action, for those too lazy to read
Devin Mullins <me at twifkak.com>**20071103055458] 
[changed urgent state from Set to list
Devin Mullins <me at twifkak.com>**20071103055143] 
[fix examples
Devin Mullins <me at twifkak.com>**20071103022011] 
[add haddock for top-level Dzen bindings
Devin Mullins <me at twifkak.com>**20071103021705] 
[expose dzenWithArgs, dzenUrgencyHookWithArgs (for colors!)
Devin Mullins <me at twifkak.com>**20071030072455] 
[use a global IORef to keep list of urgent windows
Devin Mullins <me at twifkak.com>**20071027064810] 
[fix parse error in pattern match
Brent Yorgey <byorgey at gmail.com>**20071029174150] 
[allow use of multiple toggles in ToggleLayouts.
David Roundy <droundy at darcs.net>**20071026210643] 
[WindowNavigation.hs: documentation fix (navigateBorder -> navigateColor)
Brent Yorgey <byorgey at gmail.com>**20071029155731] 
[MetaModule.hs: add ManPrompt, remove ViewPrev
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071029075621] 
[XMonadPrompt: use a single blank
Andrea Rossato <andrea.rossato at unibz.it>**20071029091618] 
[Added xmonadPromptC
cardboard42 at gmail.com**20071027014811
 
 I added xmonadPromptC which takes a user defined list of commands as in Command.runCommand
 
] 
[Factor out some of dzenPP's goodies
Spencer Janssen <sjanssen at cse.unl.edu>**20071029015556] 
[Don't reverse sjanssenPP
Spencer Janssen <sjanssen at cse.unl.edu>**20071028224843] 
[MetaModule.hs: someone forgot the (), so GHC was giving a warning. Small fix to quiet the warning.
gwern0 at gmail.com**20071027150847] 
[ViewPrev.hs: deleted
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071027090937
 Its functionality is now part of CycleWS module.
 CycleWS.hs: Nelson Elhage added to authors.
] 
[add more details on using smartBorders
Don Stewart <dons at galois.com>**20071026224510] 
[add dynamicLogDzen, a dwm status bar, using dzen colour codes
Don Stewart <dons at galois.com>**20071026221944] 
[XPrompt: removed unneeded parenteses
Andrea Rossato <andrea.rossato at unibz.it>**20071026221505] 
[XPrompt.hs: use a single blank
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071022192310
 Excessive blanks in prompts originate from here. Eliminate. :)
 Rewrite `getLastWord' and `skipLastWord' in pointfree style.
] 
[ShellPrompt.hs (showXPrompt): use a single blank
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071022191741] 
[ShellPrompt: remove harcoded path when calling bash
Andrea Rossato <andrea.rossato at unibz.it>**20071026212334] 
[ShellPrompt: reformat the comments to complay with the module style
Andrea Rossato <andrea.rossato at unibz.it>**20071026211956] 
[XPrompt: catch exceptions when running the completion function
Andrea Rossato <andrea.rossato at unibz.it>**20071026211859] 
[CycleWS: StackSet.findIndex is now findTag
Andrea Rossato <andrea.rossato at unibz.it>**20071026211802] 
[Dzen.hs: replace 'findIndex' by 'findTag' to match renaming in core.
Brent Yorgey <byorgey at gmail.com>**20071022204335] 
[XPrompt.hs: add sensible bindings for Home and End
gwern0 at gmail.com**20071026035026] 
[XPrompt.hs: add a pasteString function and keybinding
gwern0 at gmail.com**20071026034920] 
[Run.hs: documentation fix
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071024144244] 
[XPrompt.hs (uniqSort): new function
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071024142241
 Moved from ShellPrompt. There are at least three happy users
 of this function -- ShellPrompt, SshPrompt, and ManPrompt.
] 
[SshPrompt.hs: use `uniqSort' from XPrompt.hs
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071024144128
 Remove excessive import lists.
] 
[SshPrompt.hs (showXPrompt): use a single blank
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071022192037
 Delete trailing whitespace. Fix documentation typo.
] 
[ShellPrompt.hs: move `uniqSort' to XPrompt.hs
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071024143820] 
[ManPrompt.hs: use `uniqSort' from XPrompt.hs
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071024143905
 TODO list extended.
] 
[TilePrime.hs: Handle nmaster = 0 reasonably
Eric Mertens <emertens at galois.com>**20071025001750] 
[oops, add period
Devin Mullins <me at twifkak.com>**20071024125448] 
[expand Invisible comments
Devin Mullins <me at twifkak.com>**20071024125213] 
[Remove excessive import lists from ShellPrompt
Spencer Janssen <sjanssen at cse.unl.edu>**20071024113106] 
[Use new terminal config option
Spencer Janssen <sjanssen at cse.unl.edu>**20071024110219] 
[Run.hs: do my usual segregation into safe and unsafe runInTerms
gwern0 at gmail.com**20071024003911] 
[Run.hs: specialize runInXTerm to use runInTerm per my mailing list suggestion
gwern0 at gmail.com**20071024001856] 
[Run.hs: +my suggested runInTerm general function
gwern0 at gmail.com**20071024001628] 
[Run.hs, SshPrompt.hs, ShellPrompt.hs: mv runInXTerm back into Run.hs per suggestions
gwern0 at gmail.com**20071024001341] 
[Comments for ConstrainedResize
Dougal Stanton <dougal at dougalstanton.net>**20071020092509] 
[Add ConstrainedResize module
Dougal Stanton <dougal at dougalstanton.net>**20071019173508
 Constrain the aspect ratio of floated windows by holding down shift
] 
[fix stupid dzenUrgencyHook bug
Devin Mullins <me at twifkak.com>**20071021061308] 
[CycleWS.hs (toggleWS): new function
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071019205323
 This is a pointfree adaptation of ViewPrev.viewPrev;
 after this patch is applied, it may be a good idea to merge
 ViewPrev.hs into CycleWS.hs.
] 
[XPrompt.hs: fix vertical alignment of completions.
Dmitry Kurochkin <dmitry.kurochkin at gmail.com>**20071023183129] 
[fix bug in DragPane (where we forgot that r was mirrored).
David Roundy <droundy at darcs.net>**20071023152448] 
[ManPrompt.hs: a manual page prompt (new module)
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071022191443] 
[STRUT aware gap toggling (clean patch)
mail at joachim-breitner.de**20071022220132
 
 Without this patch, ManageDocks would only set the gap according to a window?s
 STRUT when the window is first mapped. This information would then get lost when
 the user toggle the gap.
    
 Now, when the user toggles the Gap, all present windows are scanned for STRUT
 settings, and the gap is set accordingly. No need to manually configure the gap
 anymore.
 
 This is the same patch as before, but independant of the Hooks patches, and with
 more documentation.
] 
[add new LayoutCombinators module.
David Roundy <droundy at darcs.net>**20071023135638] 
[export DragPane type.
David Roundy <droundy at darcs.net>**20071023134933] 
[make DragPane work with any type (not just Windows).
David Roundy <droundy at darcs.net>**20071023134911] 
[SshPrompt.hs: while I'm here, replace nub with the faster Set trick
gwern0 at gmail.com**20071019181514] 
[ShellPrompt.hs: fmt imports and update
gwern0 at gmail.com**20071019181317] 
[SshPrompt.hs: fmt imports and update
gwern0 at gmail.com**20071019181255] 
[XSelection.hs: fmt imports and sigs
gwern0 at gmail.com**20071019181232] 
[XSelection.hs: +2 functions, safePromptSelection and unsafePromptSelection
gwern0 at gmail.com**20071019181137
 Analogous to Run.hs patch; these use safeSpawn and unsafeSpawn respectively.
] 
[Run.hs: +2 functions, safeSpawn & unsafeSpawn
gwern0 at gmail.com**20071019181009
 See their documentation. This is part of a re-organization of various 'run' commands; this two
 make it easier to go through the shell or not, and will be re-used elsewhere.
] 
[Run.hs: fmt
gwern0 at gmail.com**20071019180953] 
[Run.hs, ShellPrompt.sh: mv runInXTerm to ShellPrompt.hs
gwern0 at gmail.com**20071019180900] 
[XSelection.hs: documentation format changes.
gwern0 at gmail.com**20071019010057] 
[XSelection.hs: +type signature for auxiliary function
gwern0 at gmail.com**20071019010034] 
[XSelection.hs: simplify creation of window
gwern0 at gmail.com**20071019010013
 While spelunking in the xclip source code, I noticed it had much the same call to createSimpleWindow but with a simpler geometry - just 1x1 pixels, not the odd 200x100 of the original code. It seems to work the same and looks better and less mysterious, so unless arossato had a specific reason for those particular two numbers...
] 
[XPrompt.hs (keyPressHandle): Ctrl-g and Ctrl-c added to quit keystrokes
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071020170936
 Obvious comments removed.
] 
[XPrompt.hs: trailing whitespace cleaned
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071020170719] 
[Fix pragmas in XMonadContrib
Shachaf Ben-Kiki <shachaf at gmail.com>**20071022011738] 
[test_XPrompt.hs: there is no ShellPrompt.rmPath
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071019205830] 
[introduce new combineTwo layout combinator.
David Roundy <droundy at darcs.net>**20071020191748
 This layout combinator is similar in spirit (and in code) to
 the old combo combinator, but only allows two sublayouts.  As
 a result, we don't need to wrap these in existentials, and reading
 works seamlessly.  Also, we add the feature (which could also be
 added to combo) of being able to change which sublayout a given
 window is in through integration with WindowNavigation.
 
 I envision combo being deprecated soon.  combineTwo isn't quite
 so flexible, but it's much easier and is better-coded also.
] 
[allow layout modifiers to modify a Message in transit.
David Roundy <droundy at darcs.net>**20071020191542
 This is a helpful feature (for, e.g. WindowNavigation) that
 allows modifiers (if they so choose... the old API remains
 supported) to easily send a single Message to the modified
 layout in response to a Message.
] 
[update UrgencyHook example config to reflect changes to WindowNavigation and core Config.hs
Brent Yorgey <byorgey at gmail.com>**20071019145526] 
[add ToggleLayouts module.
David Roundy <droundy at darcs.net>**20071018214525] 
[default to empty description for layout modifiers.
David Roundy <droundy at darcs.net>**20071018202604
 This is because modifierDescription is designed to be human-readable,
 and show rarely creates a human-readable description.  And in many (if
 not most) cases, an empty description is precisely what we want.
] 
[beautify description code for empty modifier-description.
David Roundy <droundy at darcs.net>**20071018202438] 
[change definition of 'description' function for LayoutModifier so an extra space is not added if the modifier description is empty.
Brent Yorgey <byorgey at gmail.com>**20071018183054] 
[-Wall police
l.mai at web.de**20071018033000] 
[DynamicLog.hs: Add dzenColor
Eric Mertens <emertens at galois.com>**20071018174523] 
[add function to rename workspaces.
David Roundy <droundy at darcs.net>**20071018145604] 
[fix WindowNavigation comment
l.mai at web.de**20071018054315] 
[change example to dzenUrgencyHook
Devin Mullins <me at twifkak.com>**20071018022026] 
[add dzenUrgencyHook as example (and the one I use)
Devin Mullins <me at twifkak.com>**20071018021742] 
[fixed Dzen and gave it a configurable timeout
Devin Mullins <me at twifkak.com>**20071018012910] 
[rename LayoutSelect & defaultLayout in comments
Devin Mullins <me at twifkak.com>**20071016051819] 
[add import to comments, for clarity
Devin Mullins <me at twifkak.com>**20071012044555] 
[documentation for UrgencyHook
Devin Mullins <me at twifkak.com>**20071012034506] 
[d'oh, minor UrgencyHook cleanup
Devin Mullins <me at twifkak.com>**20071012032558] 
[brand new UrgencyHook contrib, depends on X11-extras WMHints binding
Devin Mullins <me at twifkak.com>**20071011051641
 It's a LayoutModifier which lets you define an urgencyHook function -- the
 action gets performed wheneveran X client sends an XUrgencyHint message (i.e.
 tries to "flash" the "taskbar").
 
 This statically points to Config.urgencyHook, which requires that the user add
 a line to Config.hs-boot, in addition to defining the urgencyHook.
 
 Documentation forthcoming.
] 
[TilePrime.hs: Give a description that distinguishs between horizontal/vertical
Eric Mertens <emertens at galois.com>**20071018063749] 
[Truncate title at 80 characters
Spencer Janssen <sjanssen at cse.unl.edu>**20071018003013] 
[shorten in sjanssenPP too
Spencer Janssen <sjanssen at cse.unl.edu>**20071018002821] 
[Truncate long window titles
Spencer Janssen <sjanssen at cse.unl.edu>**20071018002511] 
[DynamicLog.hs: Add ppWsSep field to PP to specify workspace separator.
Eric Mertens <emertens at galois.com>**20071018001652
 
 This can be useful when you are using colors to distinguish between
 workspaces and simply provides more functionality. The default behavior
 remains the same.
] 
[Wrapping the empty string yields the empty string
Spencer Janssen <sjanssen at cse.unl.edu>**20071018001542] 
[DynamicLog: documentation only
Spencer Janssen <sjanssen at cse.unl.edu>**20071017211427] 
[Allow the user to change the order of workspaces, layout, title
Spencer Janssen <sjanssen at cse.unl.edu>**20071017211303] 
[Don't wrap the layout description by default
Spencer Janssen <sjanssen at cse.unl.edu>**20071017211011] 
[DynamicLog: not . null. Duh.
Spencer Janssen <sjanssen at cse.unl.edu>**20071017210912] 
[A big dynamicLog refactor
Spencer Janssen <sjanssen at cse.unl.edu>**20071017210431
 We introduce the PP type to allow user customization of dynamicLog.
 dynamicLogWithTitle has been eliminated because this is the default behavior
 for dynamicLog now.
] 
[Don't toLower the layout description.
Spencer Janssen <sjanssen at cse.unl.edu>**20071017202953
 If we'd really like lower case layout descriptions, the 'description' method
 in the LayoutClass instances should be changed instead.
] 
[TilePrime.hs: Correct behavior when number of windows <= nmaster
Eric Mertens <emertens at galois.com>**20071017205153
 
 Additionally this patch does various clean-ups that should not
 affect functionality.
] 
[Remove RunInXTerm in favor of Run
Spencer Janssen <sjanssen at cse.unl.edu>**20071017202201] 
[Move runXXX functions to one module
Christian Thiemann <mail at christian-thiemann.de>**20071012145233
 This patch takes runProcessWithInput out of Dmenu, runProcessWithInputAndWait
 out of Dzen, and runInXTerm out of RunInXTerm and collects them in one central
 module called Run.  This way, other modules may include Run instead of Dmenu
 to get what they want without giving the impression of making use of dmenu.
] 
[Fix LANGUAGE pragmas
Shachaf Ben-Kiki <shachaf at gmail.com>**20071017194622] 
[use full screen for single window in TilePrime
l.mai at web.de**20071017191421] 
[RotSlaves.hs: Add rotAll functions
Eric Mertens <emertens at galois.com>**20071017173256] 
[TilePrime.hs: add usage info.
Joachim Fasting <joachim.fasting at gmail.com>**20071017192612] 
[TilePrime.hs: add LANGAUGE pragma.
Joachim Fasting <joachim.fasting at gmail.com>**20071017182042] 
[MetaModule.hs: add WorkspacePrompt.
Joachim Fasting <joachim.fasting at gmail.com>**20071017182027] 
[add TilePrime to MetaModule.
David Roundy <droundy at darcs.net>**20071017133202] 
[Initial import of TilePrime
Eric Mertens <emertens at galois.com>**20071017052017
 
 This layout provides a standard tiling layout with support for resize hints
 and filling the gaps created by them.
] 
[code cleanup in selectWorkspace.
David Roundy <droundy at darcs.net>**20071016231218] 
[allow users to go to dynamically-added workspaces with mod-n.
David Roundy <droundy at darcs.net>**20071016230301] 
[add modules to deal with Workspaces (select, etc) by name using XPrompt.
David Roundy <droundy at darcs.net>**20071016223347] 
[make windowNavigation simpler to use in simplest case.
David Roundy <droundy at darcs.net>**20071016214337] 
[compute nice window border for WindowNavigation properly.
David Roundy <droundy at darcs.net>**20071016213316] 
[fix docs on WindowNavigation.
David Roundy <droundy at darcs.net>**20071016210349] 
[compute a reasonable navigation color based on focussed color.
David Roundy <droundy at darcs.net>**20071015165504] 
[WindowNavigation: don't export the config constructor and some haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071013090524
 I told to David I would have taken care of that: instead of exporting
 the config constructor we export 2 functions: navigateColor and
 noNavigateBorders. Updated documentation accordingly.
] 
[improvements in Combo.
David Roundy <droundy at darcs.net>**20071015132839] 
[TAG 0.4
Spencer Janssen <sjanssen at cse.unl.edu>**20071016212343] 
[Spiral.hs: add 'description' function to LayoutClass instance for SpiralWithDir.
Brent Yorgey <byorgey at gmail.com>**20071016140959] 
[ShellPrompt: traverse $PATH once per invocation.  Major speed improvement
Spencer Janssen <sjanssen at cse.unl.edu>**20071016090552] 
[ShellPrompt.hs: a quick optimization of nub
gwern0 at gmail.com**20071015234850
 I saw some complaints about ShellPrompt being slow - and noticed it myself - and it seems ShellPrompt uses 'nub' in an awkward place to uniquefy input. Nub doesn't perform well on long lists, but I once ran into a similar problem and the suggested solution was something clever: convert to a Set and then back to a List. Sets can't have duplicate entries, and they uniquefy faster than nub. The price is that the output is not sorted the same as nub's output would be, but this is OK because the output of (toList . fromList) is immediately passed to 'sort' - which should then produce the same output for both versions. I haven't really tested this but on long directories this should help.
] 
[defaultLayout -> layoutHook
Spencer Janssen <sjanssen at cse.unl.edu>**20071015205901] 
[LayoutSelection -> Select
Spencer Janssen <sjanssen at cse.unl.edu>**20071015205804] 
[defaultLayouts -> layouts
Spencer Janssen <sjanssen at cse.unl.edu>**20071015205542] 
[fix float bug in CopyWindow.
David Roundy <droundy at darcs.net>**20071015161529] 
[Various docstring fixes
Spencer Janssen <sjanssen at cse.unl.edu>**20071013230529] 
[TwoPane: Fix syntax error in example
Alex Tarkovsky <alextarkovsky at gmail.com>**20071013014151] 
[note combo broken under head
Don Stewart <dons at galois.com>**20071013232524] 
[New features for generate-configs.sh; renamed to generate-configs
Alex Tarkovsky <alextarkovsky at gmail.com>**20071013090251] 
[WorkspaceDir introduces dependency on directory package
Don Stewart <dons at galois.com>**20071013230102] 
[Dmenu.hs introduces process dependency
Don Stewart <dons at galois.com>**20071013230051] 
[serialisedLayouts
Don Stewart <dons at galois.com>**20071013230040] 
[Combo requires FlexibleContexts (but still doesn't compile under ghc head)
Don Stewart <dons at galois.com>**20071013230020] 
['Anneal' requires 'random' package in ghc 6.8
Don Stewart <dons at galois.com>**20071013230007] 
[use leading % for magic comments in ./scripts/generate-configs.sh
Don Stewart <dons at galois.com>**20071013212429] 
[WindowPrompt: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071013160735] 
[Fix more config docstrings
Alex Tarkovsky <alextarkovsky at gmail.com>**20071013085133] 
[DragPane: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071013090437] 
[TagWindows.hs: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071013090413] 
[Tabbed: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071013090342] 
[Roledex.hs: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071013090323] 
[ResizableTile.hs: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071013090233] 
[CycleWS: typo
Andrea Rossato <andrea.rossato at unibz.it>**20071013090145] 
[CopyWindow.hs: type signature for copy
Andrea Rossato <andrea.rossato at unibz.it>**20071013090122] 
[Circle.hs: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071013090100] 
[Accordion.hs: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071013090038] 
[clean up DynamicLog.hs
Don Stewart <dons at galois.com>**20071013195129] 
[remove old TODOs (fix darcs conflict)
Devin Mullins <me at twifkak.com>**20071012154859] 
[haddock improvement
Devin Mullins <me at twifkak.com>**20071012145447] 
[MetaModule.hs: add RunInXTerm and XUtils.
Joachim Fasting <joachim.fasting at gmail.com>**20071012114252] 
[Add documentation to Dishes.hs
nornagon at gmail.com**20071012072953] 
[doco fix: s/SomeLayout/Layout/g
Devin Mullins <me at twifkak.com>**20071012025953] 
[Haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071012100416] 
[Fix EwmhDesktops, ManageDocks, and SetWMName compilation for amd64
Alex Tarkovsky <alextarkovsky at gmail.com>**20071010213853] 
[Export hasTag
Karsten Schoelzel <kuser at gmx.de>**20071011095504] 
[Improve readability of RotView
Eric Mertens <emertens at galois.com>**20071011175200] 
[Added wmii like actions extension.
Juraj Hercek <juhe_xmonad at hck.sk>**20071010201452] 
[Remove spurious output from ShellPrompt
Spencer Janssen <sjanssen at cse.unl.edu>**20071011182816] 
[add/reformat (commented out) tracing code to SwitchTrans
l.mai at web.de**20071011022139] 
[NoBorders bugfix (I hope)
l.mai at web.de**20071011021756
 
 David Roundy should probably have a look at this, but this change makes sense
 to me. Plus it makes NoBorders work in combination with SwitchTrans. :-)
 
] 
[XSelection.hs: Implement Andrea's idea for handling non-UTF-8 string cases
gwern0 at gmail.com**20071010020616] 
[Add XSelection to MetaModule
Spencer Janssen <sjanssen at cse.unl.edu>**20071010160340] 
[XSelection.hs: a new module for XMonadContrib dealing with copy-and-paste
gwern0 at gmail.com**20071008222706
 This is based on Andrea Rossato's standalone tools and is meant for integration straight into a Config.hs. It offers two main functions, 'getSelection' and 'putSelection', whose names should be self-explanatory.
] 
[Add WindowPrompt: the XPrompt equivalent of WindowBringer
Andrea Rossato <andrea.rossato at unibz.it>**20071009164047] 
[WindowBringer: export windowMapWith used by WindowPrompt
Andrea Rossato <andrea.rossato at unibz.it>**20071009163505] 
[MetaModule: added WindowPrompt
Andrea Rossato <andrea.rossato at unibz.it>**20071009163445] 
[LayoutScreens: update docs
Spencer Janssen <sjanssen at cse.unl.edu>**20071008161441] 
[TwoPane: update docs
Spencer Janssen <sjanssen at cse.unl.edu>**20071008161345] 
[DragPane: no need to deal with expose events in this simplified version
Andrea Rossato <andrea.rossato at unibz.it>**20071008143801] 
[make createNewWindow set background and foreground to a given color.
David Roundy <droundy at darcs.net>**20071008125206
 This means we don't need to draw colors that are this color.  Also
 speeds up redrawing, since the X server can do all the drawing on its
 own, without talking with xmonad.
] 
[Fix more LANGUAGE pragmas
Shachaf Ben-Kiki <shachaf at gmail.com>**20071008115229
 This patch should go after my other one -- I'd missed some files that used
 -fglasgow-exts.
] 
[Add LANGUAGE pragams
Shachaf Ben-Kiki <shachaf at gmail.com>**20071008022141
 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.
] 
[fix SwitchTrans some more
l.mai at web.de**20071007224116] 
[update doco
Devin Mullins <me at twifkak.com>**20071007215906] 
[add bringMenu, and extract duplication
Devin Mullins <me at twifkak.com>**20071007215532] 
[DragPane must handle ExposeEvent too
Andrea Rossato <andrea.rossato at unibz.it>**20071008074702] 
[ShellPrompt.hs: add getShellCompl to export list
gwern0 at gmail.com**20071007220236
 getShellCompl is useful for writing prompts in Config.hs or even full standalone prompts; and personally, if a  small utility function like 'split' can be exported, how much more so something useful like getShellCompl?
] 
[Tabbed and XPrompt updated to lates Extras changes
Andrea Rossato <andrea.rossato at unibz.it>**20071007163825] 
[doc fixes for ManageDocks
Devin Mullins <me at twifkak.com>**20071007204016] 
[fix(?) SwitchTrans (makes noBorders work again)
l.mai at web.de**20071007193055] 
[avoid compiler warning in FlexibleManipulate
l.mai at web.de**20071007163509] 
[update NoBorders.hs configuration documentation
gwern0 at gmail.com**20071007190621
 It seems 'noBorder full' no longer hacks it.
] 
[d'oh, add WindowBringer to MetaModule
Devin Mullins <me at twifkak.com>**20071007185138] 
[Maybe? What Maybe? (rollback earlier dmenu change)
Devin Mullins <me at twifkak.com>**20071007185915] 
[Enter WindowBringer, Bringer of Windows.
Devin Mullins <me at twifkak.com>**20071007173633] 
[add dmenuMap function
Devin Mullins <me at twifkak.com>**20071007172543] 
[ShellPrompt: check for executables and better error handling
Andrea Rossato <andrea.rossato at unibz.it>**20071007110133
 Code contributed by Spencer (basically I just removed FilePath
 depenency).
] 
[Move my NextWorkspace functionality into CycleWS
mail at joachim-breitner.de**20071007103933
 Hi,
 
 This patch merges the additional functionality of my NextWorkspace into CycleWS,
 using a compatible interface for what was there before.
 
 Greetings,
 Joachim
] 
[ManageDocks now handles STRUT windows as well
mail at joachim-breitner.de**20071007103116
 It now also detects window with STRUT set and modifies the gap accordingly.
 Cheveats:
  * Only acts on STRUT apps on creation, not if you move or close them
  * To reset the gap, press Mod-b twice and restart xmonad (Mod-q)
] 
[NextWorkspace haddock improvement
mail at joachim-breitner.de**20071007083216
 I just added to the docs how to move a window to the next workspace 
 _and_ switch to that (by >>?ing the two actions). Some users (like me, it
 seems) probably prefer that behaviour.
 
 Greetings,
 Joachim
] 
[NextWorkspace: Go forward or backward
mail at joachim-breitner.de**20071006233010
 Hi,
 
 inspired by RotView, I implemented an Extension that allows the user to go
 forward or backward in the list of workspaces, or to move the current
 window to the next or previous workspace. Haddock included. Works here, but
 hardly tested (and while tired).
 
 Cu torrow @ HacII, if you are there.
 
 Greetings,
 Joachim
] 
[Better EWMH support
mail at joachim-breitner.de**20071007091648
 Yay, SetWMName contains just what I need! Thanks Ivan, that saved me quite
 some work. Now the panel switch should work even when you start with xmonad
 right away, and don?t run it after metacity has run before :-]
 
 Greetings,
 Joachim
] 
[Add ShellPrompt to MetaModule
Andrea Rossato <andrea.rossato at unibz.it>**20071007075937] 
[Tabbed: updated to the last (unannounced) API changes
Andrea Rossato <andrea.rossato at unibz.it>**20071007072018] 
[ShellPrompt: fromMaybe requires importing Data.Maybe
Andrea Rossato <andrea.rossato at unibz.it>**20071007070148] 
[add MouseGestures to MetaModule
l.mai at web.de**20071006230735] 
[re-add SwitchTrans to MetaModule
l.mai at web.de**20071006230711] 
[add MouseGestures.hs to darcs
l.mai at web.de**20071006230425] 
[document noBorders breakage
l.mai at web.de**20071006230316] 
[Replace -fglasgow-exts with LANGUAGE pragma in WindowNavigation.hs
nornagon at gmail.com**20071006224156] 
[Replace -fglasgow-exts with LANGUAGE pragma in ResizableTile.hs
nornagon at gmail.com**20071006223156] 
[Replace -fglasgow-exts with LANGUAGE pragma in MosaicAlt.hs
nornagon at gmail.com**20071006223025] 
[Replace -fglasgow-exts with LANGUAGE pragma in Grid.hs
nornagon at gmail.com**20071006222320] 
[Replace -fglasgow-exts with LANGUAGE pragma in Dishes.hs
nornagon at gmail.com**20071006222155] 
[update SwitchTrans for the new layout system
l.mai at web.de**20071006212008] 
[Two new dynamic log functions that display the title of the currently focused window
Christian Thiemann <mail at christian-thiemann.de>**20071006173113
 I liked the window-title-in-statusbar feature of dwm very much and wanted to
 have that in XMonad as well.  Somewhere on the net I found some code to put
 into Config.hs (and sorry, that was last week and I already forgot where I got
 it from) which I modified and put into the DynamicLog extension.  One can now
 set the logHook in Config.hs either to dynamicLogWithTitle to get the usual
 layout description and workspace list plus window title enclosed in angle
 brackets, or dynamicLogWithTitleColored "white" (or "red" etc.) to have xmonad
 print out some ^fg() markers for dzen to display the window title in the given
 color.
 
 Some windows (like terminals or browsers) change their window title from time
 to time but xmonad does not recognize this.  So I started learning Haskell to
 provide patches for X11-extras and xmonad so that PropertyNotify events are
 captured and, if the event notifies about a WM_NAME property change, call the
 logHook to update the status bar.
 
 Hope you find this useful,
   Christian
] 
[change Dmenu functions to return IO/X (Maybe String)
Devin Mullins <me at twifkak.com>**20071006070959
 dmenu exits with code 1 when you hit Escape, and I wanna create a contrib that
 takes advantage of that.
 
 This required changes in four contribs (Commands, DirectoryPrompt, ShellPrompt,
 and WorkspaceDir), and might require changes in users' Configs. Also, I'm not
 sure some of the changes I made to the client code are very Haskelly. Would
 appreciate input there.
] 
[fix problem found by Heffalump in CopyWindow.
David Roundy <droundy at darcs.net>**20071005143746] 
[(un)Manage Docks based on WINDOW_TYPE
mail at joachim-breitner.de**20071006132802
 Hi,
 
 this is a replacement for the example code in Config.hs that should detect
 and unamange, for example, the gnome-panel.
 
 The problem with that code is that it also unamangs dialog boxes from gnome-panel
 which then are not usable (no keyboard intput, at least here).
 
 Greetings,
 Joachim
] 
[MetaModule.hs: add Dishes.
Joachim Fasting <joachim.fasting at gmail.com>**20071006123900] 
[Dishes.hs: needs -fglasgow-exts.
Joachim Fasting <joachim.fasting at gmail.com>**20071006123851] 
[ResizableTile.hs: needs -fglasgow-exts.
Joachim Fasting <joachim.fasting at gmail.com>**20071006123550] 
[MetaModule.hs: whitespace.
Joachim Fasting <joachim.fasting at gmail.com>**20071006123540] 
[MetaModule.hs: add some missing imports.
Joachim Fasting <joachim.fasting at gmail.com>**20071006123525] 
[MetaModule.hs: typo.
Joachim Fasting <joachim.fasting at gmail.com>**20071006123214] 
[NoBorders.hs: unused bindings.
Joachim Fasting <joachim.fasting at gmail.com>**20071006102316] 
[NoBorders.smartBorders: add type signature.
Joachim Fasting <joachim.fasting at gmail.com>**20071006102210] 
[Grid.hs: needs -fglasgow-exts.
Joachim Fasting <joachim.fasting at gmail.com>**20071006102204] 
[EwmhWindows wrap up for inclusion
mail at joachim-breitner.de**20071006110529
 Now with haddock documentation, a proper header and nicer, warningfree code, ready
 for a first release and inclusion in XMonadConrib. It works for me, but needs more
 testing. If you run xmonad with gnome-panel or something similar, please try it.
 
 Thanks,
 Joachim
] 
[EwmhDesktops initial patch
mail at joachim-breitner.de**20071005222540
 What works so far, quit hackerish:
  * Number of Workspaces
  * Active current workspace
  * Names of workspaces
 More to come..
] 
[get rid of obviated comment
Devin Mullins <me at twifkak.com>**20071006055652] 
[get rid of duplicate mapWorkspaces function
Devin Mullins <me at twifkak.com>**20071006055404] 
[add Grid to MetaModule
l.mai at web.de**20071005230032] 
[basic docs for Grid
l.mai at web.de**20071005225934] 
[import Grid.hs into repository
l.mai at web.de**20071005013412] 
[Dishes layout. Stacks windows underneath masters.
nornagon at gmail.com**20071005230038] 
[ShellPrompt: removed readline dependency and added escape character support
Andrea Rossato <andrea.rossato at unibz.it>**20071005112250] 
[XPrompt: added ^A and ^E and more
Andrea Rossato <andrea.rossato at unibz.it>**20071005112122
 - added ^A (start of line) and ^E (end of line)
 - added support for escaping spaces (see an example of it's use in the
   new ShellPrompt)
 - some code cleanup: I'm now tracking changes to XPrompt also in
   modified version that supports i18n. This is the reason of some name
   changes.
] 
[Tabbed: check if we really have a window to focus
Andrea Rossato <andrea.rossato at unibz.it>**20071005111733] 
[add QC tests for SwapWorkspaces
Devin Mullins <me at twifkak.com>**20071004081534
 run with -i..:../tests
] 
[add man page doco
Devin Mullins <me at twifkak.com>**20071004081504] 
[Maximize layout modifier
Jamie Webb**20071004061202] 
[Add ^K and ^U support to XPrompt
Eric Mertens <emertens at galois.com>**20071002210814] 
[Rename ResizableTile.Tall to ResizableTall
Jamie Webb**20071003023000
 Having two layouts named Tall was upsetting the deserialization code.
] 
[MosaicAlt take 2
Jamie Webb**20071003162533] 
[Mark modules that haven't been ported to the new API yet.
Spencer Janssen <sjanssen at cse.unl.edu>**20071003164516
 These need to be ported or removed before the 0.4 release.
] 
[More LANGUAGE pragmas
Spencer Janssen <sjanssen at cse.unl.edu>**20071003164257] 
[Add XPropManage to MetaModule
Spencer Janssen <sjanssen at cse.unl.edu>**20071003164236] 
[add swapping capability in WindowNavigation.
David Roundy <droundy at darcs.net>**20071003151755
 This allows you to reorder your windows geometrically, by
 swapping the currently focussed window with ones that are
 up/down/right/left of it.  The idea is that we should be
 able to manipulate windows based on the visual layout of
 the screen rather than some (possibly obscure) logical ordering.
] 
[export constructor to make ThreeColumns layout usable again
Daniel Neri <daniel.neri at sigicom.se>**20071003093103] 
[WindowNavigation: add configurable colors and the possibility to turn them off
Andrea Rossato <andrea.rossato at unibz.it>**20071003090017] 
[Add SwapWorkspaces to MetaModule
Spencer Janssen <sjanssen at cse.unl.edu>**20071003163405] 
[add SwapWorkspaces (to reorder them on your number keys)
Devin Mullins <me at twifkak.com>**20071002212407] 
[Layout -> LayoutClass for ResizableTile and MosaicAlt
Jamie Webb**20071003010849] 
[NoBorders: reduce flicker
Spencer Janssen <sjanssen at cse.unl.edu>**20071002213053] 
[TagWindows
Karsten Schoelzel <kuser at gmx.de>**20071002190526
 
 Functions to work with window tags, including a XPrompt interface.
 These are stored in the window property "_XMONAD_TAGS"
 
 Adding also functions shiftHere and shiftToScreen (move to another module?).
] 
[Add XPropManage, a manageHook using XProperties
Karsten Schoelzel <kuser at gmx.de>**20071002190231] 
[make Spiral work with new layout class.
David Roundy <droundy at darcs.net>**20071002164735] 
[some renaming of classes and data types.
David Roundy <droundy at darcs.net>**20070929191238] 
[SimpleStacking is deprecated
Spencer Janssen <sjanssen at cse.unl.edu>**20071002185604] 
[Make Tabbed use XUtils.releaseFont
Andrea Rossato <andrea.rossato at unibz.it>**20071002062709] 
[XUtils: added releaseFont
Andrea Rossato <andrea.rossato at unibz.it>**20071002062640] 
[An alternative mosaic layout implementation
Jamie Webb**20071002011716] 
[Fix infinite loop in ResizableTile serialization
Jamie Webb**20071002001254] 
[Use newtype deriving for Invisible
Spencer Janssen <sjanssen at cse.unl.edu>**20071001151555] 
[Tabbed: updated usage information
Andrea Rossato <andrea.rossato at unibz.it>**20071001082219] 
[XMonadContrib.ResizableTile in darcs patch.
matsuyama3 at ariel-networks.com**20071001091411
 
 I have fixed error "" to return Nothing. Thanks Andrea.
 
 
 
] 
[Commands: added recent layout commands
Andrea Rossato <andrea.rossato at unibz.it>**20070930213225] 
[Removed fromIMaybe from Tabbed ad added it to Invisible
Andrea Rossato <andrea.rossato at unibz.it>**20070930181912] 
[Tabbed: reintroduced shrinker configuration option and removed the unneeded Read instance
Andrea Rossato <andrea.rossato at unibz.it>**20070930131936] 
[Tabbed: moved string positioning to XUtils
Andrea Rossato <andrea.rossato at unibz.it>**20070930095441] 
[refactor paintAndWrite to take the alignment and hide string positioning
Andrea Rossato <andrea.rossato at unibz.it>**20070930095215] 
[make DraPane use XUtils
Andrea Rossato <andrea.rossato at unibz.it>**20070929172849] 
[make Tabbed use XUtils
Andrea Rossato <andrea.rossato at unibz.it>**20070929172823] 
[Added XUtils: a library for drawing
Andrea Rossato <andrea.rossato at unibz.it>**20070929172754] 
[enable color setting in WindowNavigation.
David Roundy <droundy at darcs.net>**20070929114531
 This is still somewhat experimental, comments welcome.
] 
[Add smartBorders
Spencer Janssen <sjanssen at cse.unl.edu>**20070929010946] 
[Give Invisible a definition for fail.
Spencer Janssen <sjanssen at cse.unl.edu>**20070929051527
 The default definition of fail calls error.  This is very bad, as we rely on a
 non-bottom result.  We should consider moving to MonadZero, to be on the safe
 side.
] 
[Tabbed: fixed a bug: when only one window is in the stack doLayout must still return a Tabbed (I Nothing) TConf
Andrea Rossato <andrea.rossato at unibz.it>**20070928223136] 
[Added Invisible to store layout state
Andrea Rossato <andrea.rossato at unibz.it>**20070928190107
 Invisible is a data type to store information that will be lost when
 restarting XMonad (the idea came from David Roundy)
] 
[WindowNavigation now uses Invisible (plus some vertical alignement)
Andrea Rossato <andrea.rossato at unibz.it>**20070928185907] 
[DragPane now uses Invisible
Andrea Rossato <andrea.rossato at unibz.it>**20070928185832] 
[Tabbed now uses Invisible
Andrea Rossato <andrea.rossato at unibz.it>**20070928185808] 
[add new WindowNavigation module.
David Roundy <droundy at darcs.net>**20070928131906] 
[Tabbed: removed two little bugs due to the mess during the transition (my fault, sorry ;)
Andrea Rossato <andrea.rossato at unibz.it>**20070928085513] 
[DeManage.hs: doesn't need -fglasgow-exts.
Joachim Fasting <joachim.fasting at gmail.com>**20070928083639] 
[Use LANGUAGE pragmas over -fglasgow-exts
Spencer Janssen <sjanssen at cse.unl.edu>**20070928181614] 
[remove SetLayout.
David Roundy <droundy at darcs.net>**20070928015855] 
[Various fixes to NoBorders.  Hopefully fixes bug #42
Spencer Janssen <sjanssen at cse.unl.edu>**20070928174615] 
[Use LANGUAGE pragmas
Spencer Janssen <sjanssen at cse.unl.edu>**20070928174602] 
[LayoutModifier: call unhook after releaseResources
Spencer Janssen <sjanssen at cse.unl.edu>**20070928174510] 
[DynamicLog: sort first by index in the workspaces list, then by tag name
Spencer Janssen <sjanssen at cse.unl.edu>**20070928144900] 
[Make modifier descriptions prettier
Spencer Janssen <sjanssen at cse.unl.edu>**20070928053257] 
[Give Hinted a nice description
Spencer Janssen <sjanssen at cse.unl.edu>**20070928053121] 
[LayoutModifier should have descriptions too
Spencer Janssen <sjanssen at cse.unl.edu>**20070928053106] 
[Tabbed: give a nice description
Spencer Janssen <sjanssen at cse.unl.edu>**20070928052608] 
[DynamicLog: print a description of the current layout
Spencer Janssen <sjanssen at cse.unl.edu>**20070928051606] 
[Update docs
Spencer Janssen <sjanssen at cse.unl.edu>**20070928034350] 
[Add simpler layoutHints
Spencer Janssen <sjanssen at cse.unl.edu>**20070928034008] 
[NewTabbed: after a ReleaseResources we should return Tabbed Nothing...
Andrea Rossato <andrea.rossato at unibz.it>**20070928011645] 
[Move NewTabbed to Tabbed
Spencer Janssen <sjanssen at cse.unl.edu>**20070927231840] 
[Remove Tabbed.hs
Spencer Janssen <sjanssen at cse.unl.edu>**20070927231002] 
[Remove Decoration.hs
Spencer Janssen <sjanssen at cse.unl.edu>**20070927230947] 
[DragPane:just code formatting
Andrea Rossato <andrea.rossato at unibz.it>**20070927083814] 
[NewTabbed: fixes a (reintroduced) bug and some code formatting
Andrea Rossato <andrea.rossato at unibz.it>**20070927083551
 - The InvisibleMaybe patch reintroduced the rectangle bug.
 - Some code formatting
 - Corrected usage information
] 
[make NewTabbed use InvisibleMaybe to hide its cache.
David Roundy <droundy at darcs.net>**20070926202330] 
[make DragPane code a bit more compact.
David Roundy <droundy at darcs.net>**20070926191656] 
[hide implementation of DragPane from users.
David Roundy <droundy at darcs.net>**20070926191630] 
[make DragPane a bit more succinct.
David Roundy <droundy at darcs.net>**20070926190900] 
[make DragPane work with the new Layout class
Andrea Rossato <andrea.rossato at unibz.it>**20070926190439] 
[make MagicFocus work with the new Layout class
Andrea Rossato <andrea.rossato at unibz.it>**20070926114307] 
[NewTabbed: we must check if the sceen rectangle changed
Andrea Rossato <andrea.rossato at unibz.it>**20070926114056
 - Check if rectangle changed
 - removed orphan instances warnings
 - some code formatting
] 
[fix DynamicWorkspaces.
David Roundy <droundy at darcs.net>**20070925220659] 
[Remove LayoutChoice, this functionality is in the core
Spencer Janssen <sjanssen at cse.unl.edu>**20070925214912] 
[new SetLayout module.
David Roundy <droundy at darcs.net>**20070925205333] 
[make Accordian use pureLayout.
David Roundy <droundy at darcs.net>**20070925192117] 
[modifyLayout -> handleMessage.
David Roundy <droundy at darcs.net>**20070925182930] 
[Make Square work with class.
David Roundy <droundy at darcs.net>**20070925174446] 
[make Combo work with class
David Roundy <droundy at darcs.net>**20070925174417] 
[NewTabbed: fixed a bug and some code formatting
Andrea Rossato <andrea.rossato at unibz.it>**20070925133749
 - Since now Operations.windows doesn't call sendMessage UnDoLayout
 anymore, doLayout must take care of destroying all tabs when only one
 window ( or none) is left on the workspace.
 - Some code formatting.
] 
[make Roledex work with Layout class
Andrea Rossato <andrea.rossato at unibz.it>**20070925153237] 
[make Accordion work with Layout class
Andrea Rossato <andrea.rossato at unibz.it>**20070925152307] 
[fix embarrassing bugs in LayoutModifier.
David Roundy <droundy at darcs.net>**20070924195726] 
[Added a NewTabbed module with a new tabbed layout to test
Andrea Rossato <andrea.rossato at unibz.it>**20070924193419] 
[LayoutModifier updated to use LayoutMessages
Andrea Rossato <andrea.rossato at unibz.it>**20070924193345] 
[move ThreeCol over to new class.
David Roundy <droundy at darcs.net>**20070924191632] 
[Use the new modifiers in LayoutHints
Spencer Janssen <sjanssen at cse.unl.edu>**20070924062000] 
[Use the new layout switcher in Commands
Spencer Janssen <sjanssen at cse.unl.edu>**20070924060541] 
[Follow kind changes in FindEmptyWorkspace
Spencer Janssen <sjanssen at cse.unl.edu>**20070924055928] 
[update WorkspaceDir.
David Roundy <droundy at darcs.net>**20070923221456] 
[rename LayoutHelpers to LayoutModifier.
David Roundy <droundy at darcs.net>**20070923215956] 
[convert LayoutScreens to class.
David Roundy <droundy at darcs.net>**20070923215942] 
[Update NoBorders and LayoutHelpers.
David Roundy <droundy at darcs.net>**20070923192640] 
[add a hook to LayoutHelpers.
David Roundy <droundy at darcs.net>**20070923121723] 
[use default modifyLayout in Circle.
David Roundy <droundy at darcs.net>**20070923115257] 
[update LayoutHelpers to work with new Layout class.
David Roundy <droundy at darcs.net>**20070923114929] 
[make TwoPane work with Layout class
Andrea Rossato <andrea.rossato at unibz.it>**20070922124210] 
[Circle: must export type constructor
Andrea Rossato <andrea.rossato at unibz.it>**20070922124126] 
[make Circle work with Layout class.
David Roundy <droundy at darcs.net>**20070921215525] 
[Cope with StackSet export changes
Spencer Janssen <sjanssen at cse.unl.edu>**20070924091031] 
[Rolodex.hs: add missing type signature.
Joachim Fasting <joachim.fasting at gmail.com>**20070919215436
 div' is only used with Dimension, used Integral to keep it general.
] 
[Warp.hs: remove seemingly unused code.
Joachim Fasting <joachim.fasting at gmail.com>**20070919214634] 
[CopyWindow.hs: -Wall police.
Joachim Fasting <joachim.fasting at gmail.com>**20070919214556] 
[CopyWindow.copy: remove seemingly unnecessary parameter from helper func.
Joachim Fasting <joachim.fasting at gmail.com>**20070919214526] 
[DirectoryPrompt.hs: add missing type signature.
Joachim Fasting <joachim.fasting at gmail.com>**20070919213736] 
[LayoutChoice.hs: update module header.
Joachim Fasting <joachim.fasting at gmail.com>**20070919213101] 
[LayoutChoice.hs: add LANGUAGE pragma.
Joachim Fasting <joachim.fasting at gmail.com>**20070919212815] 
[SinkAll.hs: -Wall police.
Joachim Fasting <joachim.fasting at gmail.com>**20070919212359] 
[XPrompt.hs: replace 'borderWidth' with 'borderPixel'
gwern0 at gmail.com**20070918162950
 borderWidth is already defined in Config.hs. Thus, if one attempted to use a prompt configuration different than defaultXPConfig, and one defined it in one's Config.hs where it should be, then the borderWidth field would cause a warning by -Wall, since borderWidth is already a name being used by XMonad at large.
] 
[Operations.sink is gone
Spencer Janssen <sjanssen at cse.unl.edu>**20070917214113] 
[Match 'Remove Operations functions which have StackSet equivalents' from the core
Spencer Janssen <sjanssen at cse.unl.edu>**20070917213329] 
[SshPrompt.hs: fix some copy/paste errors, rebind sshPrompt to not conflict with xmonadPrompt
Brandon S Allbery KF8NH <allbery at ece.cmu.edu>**20070916182520
 Just a minor patch to the comments/documentation, which was clearly copied
 unchanged from ShellPrompt.hs.
] 
[make fixedLayout accept a list of Rectangles.
David Roundy <droundy at darcs.net>**20070911134845
 This works nicely for describing a fixed xinerama-like layout.
 (e.g. when using two distinct VNC clients to log into a single
 VNC server and attain multiheadedness).
] 
[Fixing some typos and grammar in documentation.
Michael Fellinger <m.fellinger at gmail.com>**20070911023158] 
[Typo in Tabbed.hs documentation
Michael Fellinger <m.fellinger at gmail.com>**20070911021815] 
[ssh-global-known-hosts
Brandon S Allbery KF8NH <allbery at ece.cmu.edu>**20070909222432
 Add support for global ssh known hosts file, which is checked for via
 $SSH_KNOWN_HOSTS or a standard list of locations.  This is stripped of
 comments and hashed hosts, combined with the local hosts file (which is
 trated the same way), and duplicates eliminated.
] 
[add LayoutChoice module.
David Roundy <droundy at darcs.net>**20070906154955] 
[FloatKeys.hs: needs -fglasgow-exts to compile.
Joachim Fasting <joachim.fasting at gmail.com>**20070909144215] 
[DragPane.hs: needs -fglasgow-exts to compile.
Joachim Fasting <joachim.fasting at gmail.com>**20070909144205] 
[Unify Drag(UpDown)Pane
Karsten Schoelzel <kuser at gmx.de>**20070904210312] 
[add function and comment assisting use in resizing the screen.
David Roundy <droundy at darcs.net>**20070906125543] 
[Add FloatKeys for moving and resizing of floating windows with the keyboard
Karsten Schoelzel <kuser at gmx.de>**20070905212531] 
[Fix FlexibleResize for change in applySizeHints
Karsten Schoelzel <kuser at gmx.de>**20070905193926] 
[make dragPane handle thinner.
David Roundy <droundy at darcs.net>**20070905124139] 
[cleanup in WorkspaceDir.
David Roundy <droundy at darcs.net>**20070827185833] 
[new SetWMName module, useful for working around problems running Java GUI applications.
Ivan Tarasov <Ivan.Tarasov at gmail.com>**20070826004411] 
[remove LayoutHooks module (which is unused).
David Roundy <droundy at darcs.net>**20070823154520] 
[cleanup in DwmPromote.
David Roundy <droundy at darcs.net>**20070823155437] 
[cleanup in ViewPrev.
David Roundy <droundy at darcs.net>**20070823155405] 
[clean up CopyWindow.
David Roundy <droundy at darcs.net>**20070823155912] 
[Add CycleWS to MetaModule
Spencer Janssen <sjanssen at cse.unl.edu>**20070905203137] 
[CycleWS: a couple of simple functions to cycle between workspaces
Andrea Rossato <andrea.rossato at unibz.it>**20070821061132] 
[make Contrib use WorkspaceId = type String.
David Roundy <droundy at darcs.net>**20070820113813] 
[Add HintedTile docstring
Spencer Janssen <sjanssen at cse.unl.edu>**20070905200310] 
[Docstring parser for generating xmonad build configs with default settings for extensions
Alex Tarkovsky <alextarkovsky at gmail.com>**20070905200128] 
[TAG 0.3
Spencer Janssen <sjanssen at cse.unl.edu>**20070905022947] 
[docs not generated in DragPane.hs
Don Stewart <dons at cse.unsw.edu.au>**20070904232447] 
[HintedTile typo
Spencer Janssen <sjanssen at cse.unl.edu>**20070904202804] 
[HintedTile
Spencer Janssen <sjanssen at cse.unl.edu>**20070904202219] 
[Doc fixes for DragPane
Spencer Janssen <sjanssen at cse.unl.edu>**20070904201847] 
[XPrompt: a very long string in the completion list can lead to a division by zero
Andrea Rossato <andrea.rossato at unibz.it>**20070830141524] 
[XPrompt.hs: remove debugging bits
Andrea Rossato <andrea.rossato at unibz.it>**20070828081235] 
[make code more compact in XPrompt.
David Roundy <droundy at darcs.net>**20070827191830] 
[XPrompt: just code formatting
Andrea Rossato <andrea.rossato at unibz.it>**20070822193220] 
[fix bug leading to early exit in XPrompt.
David Roundy <droundy at darcs.net>**20070827185858] 
[fix bug where we draw divider for DragPane even if there's just one window.
David Roundy <droundy at darcs.net>**20070823155810] 
[CopyWindow: update usage info
Spencer Janssen <sjanssen at cse.unl.edu>**20070820232834] 
[add DragPane.
David Roundy <droundy at darcs.net>**20070813144007] 
[fix bug in Combo where we ignored changes in super.
David Roundy <droundy at darcs.net>**20070813143500] 
[remove redundant fromIntegral from Commands.
David Roundy <droundy at darcs.net>**20070820000925] 
[Mosaic.hs (really) Fix incorrect usage example
Jason Creighton <jcreigh at gmail.com>**20070818215725
 "tall" and "wide" are anachronisms as well. It makes me wonder how we can
 and/or should give examples like this that don't bitrot and confuse newbies.
] 
[Mosaic.hs: Fix incorrect usage example
Jason Creighton <jcreigh at gmail.com>**20070818212854] 
[XPrompt: haddock tuning and more comments
Andrea Rossato <andrea.rossato at unibz.it>**20070818083423] 
[SwitchTrans:: haddock tuning
Andrea Rossato <andrea.rossato at unibz.it>**20070818083401] 
[RunInXTerm: haddock tuning
Andrea Rossato <andrea.rossato at unibz.it>**20070818083329] 
[RotSlaves: haddock tuning
Andrea Rossato <andrea.rossato at unibz.it>**20070818083306] 
[Roledex: haddock tuning
Andrea Rossato <andrea.rossato at unibz.it>**20070818083244] 
[LayoutHelpers: haddock tuning
Andrea Rossato <andrea.rossato at unibz.it>**20070818083220] 
[DirectoryPrompt: removed ShellPrompt usage info and added pointer to WorkspaceDir
Andrea Rossato <andrea.rossato at unibz.it>**20070818083105] 
[DeManage: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20070818083036] 
[MetaModule: removed BackCompat no longer in the repository
Andrea Rossato <andrea.rossato at unibz.it>**20070818071916] 
[fix MagicFocus/floats interaction
Peter De Wachter <pdewacht at gmail.com>**20070816185217] 
[fix Circle/floats interaction
Peter De Wachter <pdewacht at gmail.com>**20070816185144] 
[XPrompt: documentation only
Andrea Rossato <andrea.rossato at unibz.it>**20070817162806] 
[ShellPrompt: quickcheck related refactoring
Andrea Rossato <andrea.rossato at unibz.it>**20070817155725] 
[added a tests directory with quickcheck tests for XPrompt and ShellPrompt
Andrea Rossato <andrea.rossato at unibz.it>**20070817155634] 
[XPrompt: quickcheck related refactoring
Andrea Rossato <andrea.rossato at unibz.it>**20070817155454
 With this patch XPrompt can be tested with quickcheck. As a result
 getLastWord and skipLastWord has been refactored to avoid possible
 exceptions.
] 
[XPrompt: fixes a nasty bug in getLastWord
Andrea Rossato <andrea.rossato at unibz.it>**20070815163457
 This patch fixes a nasty bug in getLastWord, a bug that causes XMonad
 to crash as soon as the command line consists of only 2 empty spaces.
 *PLEASE UPDATE* if you are running XPrompt.
] 
[ghc thinks I don't need those fromIntegrals
l.mai at web.de**20070815231852] 
[use XPrompt in WorkspaceDir.
David Roundy <droundy at darcs.net>**20070814191103] 
[clean up DynamicWorkspaces to handle layouts properly.
David Roundy <droundy at darcs.net>**20070814183542] 
[make DynamicWorkspace more thorough.
David Roundy <droundy at darcs.net>**20070814014548
 Note: there's still a bug due to our failure to inform
 the old layouts to clean up.
] 
[new module DynamicWorkspaces to add and remove workspaces.
David Roundy <droundy at darcs.net>**20070814011501] 
[fix Commands to work with new workspaces.
David Roundy <droundy at darcs.net>**20070814004146] 
[Make FlexibleManipulate comply with new mouse dragging system
Spencer Janssen <sjanssen at cse.unl.edu>**20070815032619] 
[make FlexibleResize use new mouseDrag properly.
David Roundy <droundy at darcs.net>**20070807202016] 
[fix Expand/Shrink for spiralWithDir
bobstopper at bobturf.org**20070808204752] 
[Remove GreedyView: the functionality is now in StackSet
Spencer Janssen <sjanssen at cse.unl.edu>**20070815022101] 
[Use maskEvent rather than nextEvent.  Fixes rare segfaults
Spencer Janssen <sjanssen at cse.unl.edu>**20070814170416] 
[Decoration: don't crash when given a non-existent font
Andrea Rossato <andrea.rossato at unibz.it>**20070810182433] 
[actually use the selected font in XPrompt.
David Roundy <droundy at darcs.net>**20070810174543] 
[increase default contrast in XPrompt.
David Roundy <droundy at darcs.net>**20070810174724] 
[center prompt text in window.
David Roundy <droundy at darcs.net>**20070810173746] 
[don't crash when given a non-existent font in XPrompt.
David Roundy <droundy at darcs.net>**20070810170445] 
[Add ViewPrev to MetaModule
Spencer Janssen <sjanssen at cse.unl.edu>**20070810211242] 
[ViewPrev.hs
nelhage at mit.edu**20070810032653
 Add a ViewPrev extension which gives a viewPrev command to view the
 previously visible workspace.
] 
[fix CopyWindow to not require Integral WorkspaceId.
David Roundy <droundy at darcs.net>**20070801144543] 
[SshPrompt now uses RunInXTerm to launch the command
Andrea Rossato <andrea.rossato at unibz.it>**20070807101911] 
[RunInXTerm: a simple module to run commands in an X terminal
Andrea Rossato <andrea.rossato at unibz.it>**20070807101603
 This is just a wrapper around spawn to launch commands in an X
 terminal: runInXTerm will check the for the XTERMCMD environmental
 variable, and use it to run the command. If the variable is not set
 the command will be executed with xterm.
] 
[XPrompt: removed touchFile (which is not the equivalent of touch!)
Andrea Rossato <andrea.rossato at unibz.it>**20070805225906] 
[LayoutScreen: haddock cleanup
Andrea Rossato <andrea.rossato at unibz.it>**20070805215800] 
[XPrompt.hs: getCompletion should check for completions of the last word of the command line
Andrea Rossato <andrea.rossato at unibz.it>**20070805124130] 
[work around Magnifier's problems with floating windows
Peter De Wachter <pdewacht at gmail.com>**20070805141051] 
[Add Roledex to MetaModule
Spencer Janssen <sjanssen at cse.unl.edu>**20070806151628] 
[XPrompt.hs: read history lazily
Andrea Rossato <andrea.rossato at unibz.it>**20070804185914
 Instead of forcing the reading of all the history file we read it lazily.
] 
[XPrompt.hs: removed defaultPromptConfig. use defautlXPConfig instead
Andrea Rossato <andrea.rossato at unibz.it>**20070804183252] 
[weird formatting fixed
Don Stewart <dons at cse.unsw.edu.au>**20070806032739] 
[rolodex
tim.thelion at gmail.com**20070804235730
 Cascading windows...
] 
[XPrompt.hs: haddock corrections and some comments
Andrea Rossato <andrea.rossato at unibz.it>**20070804104622] 
[XMonadPrompt.hs: minor haddock corrections
Andrea Rossato <andrea.rossato at unibz.it>**20070804104534] 
[SwitchTrans.hs: minor haddock corrections
Andrea Rossato <andrea.rossato at unibz.it>**20070804104458] 
[SshPrompt.hs: minor haddock corrections
Andrea Rossato <andrea.rossato at unibz.it>**20070804104441] 
[ShellPrompt.hs: minor haddock corrections
Andrea Rossato <andrea.rossato at unibz.it>**20070804104408] 
[FlexibleManipulate.hs: minor haddock corrections
Andrea Rossato <andrea.rossato at unibz.it>**20070804104330] 
[MetaModule: added XPrompt and others
Andrea Rossato <andrea.rossato at unibz.it>**20070804093049
 XPrompt, XMonadPrompt, SshPrompt.
 ShellPrompt is commented out since it requires readline and the related
 xmonad.cabal modifications.
] 
[XPrompt: fixes a couple of bugs
Andrea Rossato <andrea.rossato at unibz.it>**20070804090817
 - we run the action passed to mkXPrompt only if we have a command;
 - updateWindows must call destroyComplWin if there are no completions;
 - some comments (more to come)
 - a shorthand in keyPressHandle
 - removed all warnings
] 
[RotSlaves rework
Karsten Schoelzel <kuser at gmx.de>**20070803185337
 
 Rework the logic of RotSlaves and rename it RotSlavesDown, add RotSlavesUp. These rotate
 the slaves in different directions.
 Also changed the usage, eliminating the need for "windows" in the keybinding.
] 
[XPrompt: code cleanup
Andrea Rossato <andrea.rossato at unibz.it>**20070803181905
 The completion list is not cached anymore: this greatly simplify the code
 making its runtime behaviour more predictable...;-) Suggested by Spencer.
] 
[Make 'compList :: [String]', rather than Maybe.  No completions is represented by []
Spencer Janssen <sjanssen at cse.unl.edu>**20070803160424] 
[Rename 'setCompletionList' to 'refreshCompletionList'
Spencer Janssen <sjanssen at cse.unl.edu>**20070803155942] 
[XPrompt: added comletion and history support
Andrea Rossato <andrea.rossato at unibz.it>**20070803154531
 This is a long patch the brings us a real prompt, more or less: completions
 now work. Added history support, with a configuration option: defaul history
 size is 256.  
 defaultPromptConfig is now deprecated: please use defaultXPConfig instead
] 
[Prompts: updated and corrected usage info
Andrea Rossato <andrea.rossato at unibz.it>**20070803130158] 
[Make the XPrompt appear on the current screen
Spencer Janssen <sjanssen at cse.unl.edu>**20070802184231] 
[XPrompt: a module for easily writing graphical prompts
Andrea Rossato <andrea.rossato at unibz.it>**20070802171552] 
[ XMonadPrompt: a graphical prompt for running XMonad internal commands
Andrea Rossato <andrea.rossato at unibz.it>**20070802165336] 
[SshPrompt: a graphical prompt for ssh connection
Andrea Rossato <andrea.rossato at unibz.it>**20070802155943] 
[ShellPrompt: a graphical shell prompt
Andrea Rossato <andrea.rossato at unibz.it>**20070802155845
 This module requires readline and so a modification to xmonad.cabal. See
 usage for instructions.
] 
[FlexibleManipulate.hs: needs -fglasgow-exts to compile.
joachim.fasting at gmail.com**20070802144042] 
[MetaModule.hs: add FocusNth.
joachim.fasting at gmail.com**20070802144023] 
[Add ThreeColumns to MetaModule
Spencer Janssen <sjanssen at cse.unl.edu>**20070802143356] 
[Add RotSlaves to MetaModule
Spencer Janssen <sjanssen at cse.unl.edu>**20070802143334] 
[RotSlaves
Hans Philipp Annen <haphi at gmx.net>**20070802094408] 
[DeManage.hs: haddock compatibility.
joachim.fasting at gmail.com**20070725100910] 
[Fix warnings in FlexibleManipulate (Sorry!)
Michael G. Sloan <mgsloan at gmail.com>**20070729032407] 
[Add FlexibleManipulate extension
Michael G. Sloan <mgsloan at gmail.com>**20070729031402] 
[Commands: refactoring to include in MetaModule
Andrea Rossato <andrea.rossato at unibz.it>**20070728132029
 Just a small refactooring (well, now runCommand requires a command list, and
 I added runCommand's that will take a string to run it against the default
 command list) to include this module in MetaModule so that we can track it
 in case of API changes (this patch has been requested by Spencer).
] 
[SwitchTrans.hs, initial version
l.mai at web.de**20070728153826] 
[fix WorkspaceDir (which was broken) using LayoutHelpers.
David Roundy <droundy at darcs.net>**20070726133520] 
[FocusNth initial import
Karsten Schoelzel <kuser at gmx.de>**20070725203305] 
[use a little more contrast in default tabs.
David Roundy <droundy at darcs.net>**20070724143723] 
[3col fix: do not switch to tall layout on resize/incmastern
Kai Grossjohann <kai at emptydomain.de>**20070723212754] 
[3col rounding
Kai Grossjohann <kai at emptydomain.de>**20070721204026] 
[fix 3col layout for nmaster + 1 windows
Kai Grossjohann <kai at emptydomain.de>**20070721150825
 Do like two column layout if there are nmaster+1 windows (putting 1 window
 in the right column).
] 
[Three column layout
Kai Grossjohann <kai at emptydomain.de>**20070721144654
 This layout is similar to tall, but has three columns.  The first column
 is the master column.
] 
[Made the direction of spiral in Spiral.hs optionally configurable
bobstopper at bobturf.org**20070721002307] 
[DeManage: take a Window as argument
Spencer Janssen <sjanssen at cse.unl.edu>**20070718204410] 
[Typo
Spencer Janssen <sjanssen at cse.unl.edu>**20070718204041] 
[Add XMonadContrib.DeManage: a module for unmanaging windows (like panels)
Spencer Janssen <sjanssen at cse.unl.edu>**20070718203107] 
[Tabbed.hs: corrected error in Usage reported by Xavier Maillard
Andrea Rossato <andrea.rossato at unibz.it>**20070717050034] 
[fixes Commands.hs
Andrea Rossato <andrea.rossato at unibz.it>**20070716164017] 
[MetaModule.hs: add missing modules.
joachim.fasting at gmail.com**20070715205857] 
[Magnifier: unbreak: raise focus window
Peter De Wachter <pdewacht at gmail.com>**20070630072206] 
[Spiral.hs: correct module header.
joachim.fasting at gmail.com**20070707212836] 
[LayoutScreens.hs: correct module header.
joachim.fasting at gmail.com**20070701215712] 
[add FlexibleResize to MetaModule
l.mai at web.de**20070708130229] 
[link to xinerama-dmenu patch for dmenu 3.2
Jason Creighton <jcreigh at gmail.com>**20070708021413
 Thanks to Dave Harrison for an updated version of the patch.
] 
[Tabbed: updated usage information
Andrea Rossato <andrea.rossato at unibz.it>**20070707065123] 
[Tabs should stay beneath any floating window
Andrea Rossato <andrea.rossato at unibz.it>**20070707064941
 This ifxes the issue reported by Geoffrey Alan Washburn: " Sometimes the
 tabs will be drawn on top of floating windows." Not anymore!
] 
[Tabbed: added more configuration options
Andrea Rossato <andrea.rossato at unibz.it>**20070706130845
 It is now possible to configure active and inactive border colors, and
 active and inactive text colors (i.e. tabs are now very similar to Ion3
 tabs: former Ion users may appreciate).
] 
[NamedWindows: if fetchName returns Nothing sets the name to resName ClassHint
Andrea Rossato <andrea.rossato at unibz.it>**20070706130644
 fetchName may return a Nothing if the window's name contains multi byte
 characters. In such a case the resName string of the ClassHints of that
 window will be used instead.
] 
[the gaps list should be filled with the default value from Config.hs
Andrea Rossato <andrea.rossato at unibz.it>**20070704224110] 
[SimpleStacking: -Wall police
Alec Berryman <alec at thened.net>**20070704201255] 
[SimpleStacking: remove note about Xinerama incompatability, works fine now
Alec Berryman <alec at thened.net>**20070704200626] 
[ScreenLayouts.hs: updates to the last API changes
Andrea Rossato <andrea.rossato at unibz.it>**20070703201145
 A silent API change broke this nice piece of David's code: Spencer decided
 to move screen details into StackSet, and there we went to manipulate them!
] 
[More ScreenDetails fixes
Spencer Janssen <sjanssen at cse.unl.edu>**20070630065916] 
[Make GreedyView work with ScreenDetails
Spencer Janssen <sjanssen at cse.unl.edu>**20070630065643] 
[flexible resizing for floating windows
l.mai at web.de**20070629171038
 
 The default resize handler for floating windows warps the mouse pointer to
 the bottom right corner of the window (fixing the opposite, upper left,
 corner). This extension lets you use any of the four window corners as
 grabbing points, allowing more flexible resizing.
 
] 
[resolve conflicts in Decoration and Tabbed.
David Roundy <droundy at darcs.net>**20070629204518
 Note that you no longer need simpleStacking when using tabbed.
] 
[resolve conflict in Square.
David Roundy <droundy at darcs.net>**20070629201636] 
[clean up code in Combo.
David Roundy <droundy at darcs.net>**20070624171346
 This adds some type safety, since the super-layout is now of a distinct
 type from the sublayouts.  This avoids the ugliness we had, of passing
 "fake" windows to the super layout.  Now we directly lay out the layouts.
] 
[add CopyWindow module, to support sticky/tagged windows.
David Roundy <droundy at darcs.net>**20070624155648
 This module allows dwm-style tagging (as I understand dwm).  You can have a
 given window visible in multiple workspaces.  If it's visible in two
 workspaces both of which are visible, a gap will show up in one of them
 (which is something that needs fixing in xmonad core).  Also defines a
 kill1 which is like kill, but only removes from the current workspace a
 window if it's in multiple workspaces.
] 
[make everything work with new doLayout.
David Roundy <droundy at darcs.net>**20070623210952
 This modifies all the contrib modules to work (so far as I know) with the
 new contrib layout.  The exception is the LayoutHooks module, which isn't
 used.  It exports an API that is inherently unsafe, so far as I can tell
 (and always has been).
] 
[move Accordian to use idModify.
David Roundy <droundy at darcs.net>**20070623143745] 
[introduce idModify which is just "const (return Nothing)".
David Roundy <droundy at darcs.net>**20070623143542] 
[move Spiral to LayoutHelpers.
David Roundy <droundy at darcs.net>**20070623143516] 
[Note that SimpleStacking is incompatible with Xinerama
Jason Creighton <jcreigh at gmail.com>**20070627035426
 It's unclear to me what SimpleStacking is supposed to accomplish, so I'm just
 going to note that it doesn't work with Xinerama. (Due to assuming that the
 current workspace is the one being laid out)
] 
[Tabbed: Make use of the Stack to get focused window
Jason Creighton <jcreigh at gmail.com>**20070627033910] 
[Accordion.hs: whitespace.
joachim.fasting at gmail.com**20070626071449
 Makes Haddock not complain about not finding documentation for '$'.
] 
[MetaModule.hs: add LayoutHelpers.
joachim.fasting at gmail.com**20070626065522
 Also tweaks import ordering slightly.
] 
[Tabbed.hs: updated usage information
Andrea Rossato <andrea.rossato at unibz.it>**20070625140735] 
[added configration options and moved font stuff to Decorations.hs
Andrea Rossato <andrea.rossato at unibz.it>**20070625140112
 Added a new data type to keep configuration options. tabbed now takes the shrinker and the configuration
 type.
 Fixed a bug related to vertical alignment of text.
] 
[Decoration.hs: added automatic font managment
Andrea Rossato <andrea.rossato at unibz.it>**20070625135722
 newDecoration now takes also a fontname to set fonts in decorations that use them.
 If an empty string is send the the default Xorg fonts will be loaded.
] 
[fix usage instructions on NoBorders.
David Roundy <droundy at darcs.net>**20070624141631] 
[remove BackCompat.hs
daniel at wagner-home.com**20070624171740] 
[Square.hs: put usage instructions after imports for Haddock compatibility.
joachim.fasting at gmail.com**20070623184938] 
[Magnifier.hs: quote screenshot url for Haddock compatibility.
joachim.fasting at gmail.com**20070623223227] 
[add new LayoutHelpers module.
David Roundy <droundy at darcs.net>**20070622142950] 
[Add SinkAll module.
joachim.fasting at gmail.com**20070623050510
 Provides a means of pushing all windows on the current workspace back into
 tiling. Not all that useful, but might be preferable to restarting or manually
 pushing windows.
] 
[Magnifier.hs: needs -fglasgow-exts to compile.
joachim.fasting at gmail.com**20070622111442] 
[fix usage info for LayoutScreens.
David Roundy <droundy at darcs.net>**20070622132618] 
[add new LayoutScreens module.
David Roundy <droundy at darcs.net>**20070622131300] 
[Magnifier: raise the focus window
Peter De Wachter <pdewacht at gmail.com>**20070621192541] 
[Circle: raise the focus window
Peter De Wachter <pdewacht at gmail.com>**20070621191207] 
[Circle cleanups
Peter De Wachter <pdewacht at gmail.com>**20070621191125] 
[make Mosaic lay thigs out a bit better.
David Roundy <droundy at darcs.net>**20070621162632] 
[add SimpleStacking module to make Combo and Tabbed work together.
David Roundy <droundy at darcs.net>**20070621151524
 WARNING! This change will break existing Tabbed configurations.  The
 problem is that there is no way within a Layout's "doLayout" to safely
 modify the layout itself.  This makes LayoutHooks fragile, and more to the
 point, makes SimpleStacking fragile, so we can't safely define a
 
 tabbed' = simpleStacking . tabbed
 
 A workaround would have been to duplicate the tabbed code, but I'd rather
 leave the ugliness and get this fixed.
] 
[Make Magnifier's master window behavior customizable
Peter De Wachter <pdewacht at gmail.com>**20070620170020
 based on a suggestion by Tim Hobbs
] 
[Whitespace.
joachim.fasting at gmail.com**20070620115852] 
[Make Mosaic compile without warnings
Spencer Janssen <sjanssen at cse.unl.edu>**20070620153111] 
[make some layouts more general.
David Roundy <droundy at darcs.net>**20070620125420] 
[Mosaic.hs: get rid off some of the warnings generated by -Wall.
joachim.fasting at gmail.com**20070620123449
 Unused definitions and imports left in, as I assume they'll be used for
 something later on.
] 
[MetaModule.hs: add LayoutHooks.
joachim.fasting at gmail.com**20070620115457] 
[Combo.hs: use case instead of non-standard pattern matching.
joachim.fasting at gmail.com**20070620112805
 Also uses fmap/maybe instead of do/case, which makes the code look a little
 cleaner (imo).
 Please note that I've only been able to test this briefly, but it seems to be
 working like it's supposed to.
] 
[Combo.hs: tweak usage instructions.
joachim.fasting at gmail.com**20070620112555
 tabbed needs an additional argument.
] 
[README: change reference to 'examples/'.
joachim.fasting at gmail.com**20070620093753] 
[Use Data.Ord.comparing in DynamicLog
Shachaf Ben-Kiki <shachaf at gmail.com>**20070620011016
 This patch replaces (compare `on`) with Data.ord.comparing, so on doesn't have
 to be defined.
] 
[Fix type signatures.
joachim.fasting at gmail.com**20070619220323
 Think this fixes the rest of the errors caused by the Layout change.
] 
[MagicFocus.magicFocus: fix type signature.
joachim.fasting at gmail.com**20070619214839
 Layout change caused because of missing type argument.
] 
[LayoutHooks.hs: add module header.
joachim.fasting at gmail.com**20070619204504] 
[Factor out pprWindowSet (and Xinerama version) from dynamicLog.
Shachaf Ben-Kiki <shachaf at gmail.com>**20070619183657
 This patch lets you pretty-print a WindowSet to a string, rather than always
 printing it out to stdout directly.
] 
[clean up TwoPane to work on Stacks as it ought.
David Roundy <droundy at darcs.net>**20070619150928] 
[run-xmonad.sh: don't hard-code path to mkfifo.
joachim.fasting at gmail.com**20070619124212
 mkfifo isn't located in /sbin on all distributions (Gentoo puts it in /bin).
 By temporarily appending /sbin to PATH both setups are supported.
 'which' and friends are not viable options since /sbin usually isn't in
 user's PATH by default.
] 
[Anneal.hs: add module header.
joachim.fasting at gmail.com**20070619002849] 
[run-xmonad.sh: use $HOME when setting PATH.
joachim.fasting at gmail.com**20070618234703] 
[Circle.hs: only compute sqrt 2 once.
joachim.fasting at gmail.com**20070618232051] 
[Magnifier.hs: add usage instructions.
joachim.fasting at gmail.com**20070618212215] 
[MagicFocus.hs: add module header and usage instructions.
joachim.fasting at gmail.com**20070618205421] 
[MagicFocus.magicFocus: add type signature.
joachim.fasting at gmail.com**20070618205222] 
[Accordion.hs: add module header and usage instructions.
joachim.fasting at gmail.com**20070618193626] 
[LayoutHints.hs: add usage thingie for Haddock.
joachim.fasting at gmail.com**20070618143234] 
[LayoutHints.hs: add module header.
joachim.fasting at gmail.com**20070618143059] 
[Dzen.hs: add module header.
joachim.fasting at gmail.com**20070618142915] 
[MetaModule.hs: correct module header.
joachim.fasting at gmail.com**20070618191905] 
[Remove all references to exec
Spencer Janssen <sjanssen at cse.unl.edu>**20070618201652] 
[Add Accordion to MetaModule
Spencer Janssen <sjanssen at cse.unl.edu>**20070618190526] 
[Add an "accordion" layout which puts non-focused windows in ribbons at the top and bottom of the screen.
glasser at mit.edu**20070618153943] 
[RotView.rotView: use Data.Ord.comparing.
joachim.fasting at gmail.com**20070618144502
 Looks a bit cleaner than '\x y -> compare (tag x) (tag y)'
] 
[shrink window names to fit tabs.
David Roundy <droundy at darcs.net>**20070617152340] 
[Tabbed.hs: fixed centerText issues and some binding shadowing warnings
Andrea Rossato <andrea.rossato at unibz.it>**20070617104219
 This patch fixes the centerText issue due to the inappropriate use of
 textExtends and textWidth. Those functions need a FontStruct id to
 operate, and this cannot be retrieved with queryFont (see comments in
 Graphics.X11.Xlib.Font).
 So we now get the FontStruct with loadQueryFont, we set the default
 Xorg fonts and we calculate things for (vertical and horizontal)
 centering.
 It also removes some binding shadows compiler warnings 
] 
[fix leak in Combo.
David Roundy <droundy at darcs.net>**20070616191052
 We leaked decorations, since UnDoLayout wasn't passed to the actual layouts
 that had decorations attached.  :(
] 
[Typo
Spencer Janssen <sjanssen at cse.unl.edu>**20070617000924] 
[Comment only
Spencer Janssen <sjanssen at cse.unl.edu>**20070617000805] 
[Import typo
Spencer Janssen <sjanssen at cse.unl.edu>**20070614211337] 
[Magnifier layout hack
Peter De Wachter <pdewacht at gmail.com>**20070614203219
 This layout hack increases the size of the window that has focus (the master
 window excepted). This causes it to overlap with nearby windows, so not for
 tiling purists :)
 
 Screenshot: http://caladan.rave.org/magnifier.png
] 
[Use Haskell '98 data declaration rather than GADT-style
Spencer Janssen <sjanssen at cse.unl.edu>**20070614205211] 
[WorkspaceDir.hs: info and documentation
Andrea Rossato <andrea.rossato at unibz.it>**20070614144443] 
[Warp.hs: info and documentation
Andrea Rossato <andrea.rossato at unibz.it>**20070614144426] 
[TwoPane.hs: info and documentation
Andrea Rossato <andrea.rossato at unibz.it>**20070614144409] 
[Submap.hs: info and documentation
Andrea Rossato <andrea.rossato at unibz.it>**20070614144348] 
[Square.hs: info and documentation
Andrea Rossato <andrea.rossato at unibz.it>**20070614144317] 
[Spiral.hs: info and documentation
Andrea Rossato <andrea.rossato at unibz.it>**20070614144300] 
[SimpleDate.hs: info and documentation
Andrea Rossato <andrea.rossato at unibz.it>**20070614144241] 
[RotView.hs: info and documentation
Andrea Rossato <andrea.rossato at unibz.it>**20070614144225] 
[NoBorders.hs: info and documentation
Andrea Rossato <andrea.rossato at unibz.it>**20070614144200] 
[NamedWindows.hs: info and documentation
Andrea Rossato <andrea.rossato at unibz.it>**20070614144135] 
[Mosaic.hs: info and documentation
Andrea Rossato <andrea.rossato at unibz.it>**20070614144118] 
[metaModule.hs: info and documentation
Andrea Rossato <andrea.rossato at unibz.it>**20070614144102] 
[HintedTile.hs: info and documentation
Andrea Rossato <andrea.rossato at unibz.it>**20070614144019] 
[GreedyView.hs: info and documentation
Andrea Rossato <andrea.rossato at unibz.it>**20070614143953] 
[FindEmptyWorkspace.hs: info and documentation
Andrea Rossato <andrea.rossato at unibz.it>**20070614143909] 
[DynamicLog.hs: info and documentation
Andrea Rossato <andrea.rossato at unibz.it>**20070614143839] 
[DwmPromote.hs: info and documentation
Andrea Rossato <andrea.rossato at unibz.it>**20070614143813] 
[Dmenu.hs: info and documentation
Andrea Rossato <andrea.rossato at unibz.it>**20070614143753] 
[Decoration.hs: info and documentation
Andrea Rossato <andrea.rossato at unibz.it>**20070614143731] 
[Combo.hs: info and documentation
Andrea Rossato <andrea.rossato at unibz.it>**20070614143700] 
[Circle.hs: info and documentation
Andrea Rossato <andrea.rossato at unibz.it>**20070614143550] 
[BackCompat.hs info e documentation
Andrea Rossato <andrea.rossato at unibz.it>**20070614064850] 
[Tabbed.hs: Get correct color values instead of assuming a 24-bit display
Jason Creighton <jcreigh at gmail.com>**20070613235049
 Using, eg, 0xBBBBBB directly makes assumptions about the server's colormap and
 only works on 24-bit displays.
 
 This patch fetches the colors on every doLayout call, which is ugly, but works.
 It would be nice if we could do all the required initColors only once.
] 
[added info to Commands.hs
Andrea Rossato <andrea.rossato at unibz.it>**20070613190908
 Haddock stuff.
] 
[add bsd-style license for xmonad contrib
Don Stewart <dons at cse.unsw.edu.au>**20070614025454] 
[Update license information
Spencer Janssen <sjanssen at cse.unl.edu>**20070613152829] 
[template for module information e documentation
Andrea Rossato <andrea.rossato at unibz.it>**20070613131029] 
[Remove some debugging statements I forgot about earlier
Stefan O'Rear <stefanor at cox.net>**20070613041112] 
[Update MagicFocus to the new StackSet
Spencer Janssen <sjanssen at cse.unl.edu>**20070613035323] 
[Magic Focus
Peter De Wachter <pdewacht at gmail.com>**20070612175357
 Automatically puts the focused window in the master position. It's magic.
 I wrote this for the Circle layout, but it's actually usable with other
 layouts as well.
] 
[add -fglasgow-exts to some modules that use it.
David Roundy <droundy at darcs.net>**20070612170349] 
[changes to work with Stacks that can't be empty.
David Roundy <droundy at darcs.net>**20070612151209] 
[add Combo and Square to MetaModule.
David Roundy <droundy at darcs.net>**20070612133753] 
[new module NoBorders to let a given layout have windows without borders.
David Roundy <droundy at darcs.net>**20070612133727
 This is designed for layouts like full and tabbed, where the red square
 around the screen actually conveys no information (except for weird windows
 that use the shape extension or something, so that more than one window is
 actually visible).  Save some real estate at no cost.
] 
[make combo sort of work with new doLayout.
David Roundy <droundy at darcs.net>**20070612133027
 For some reason (not entirely clear to me) this doesn't work properly just
 yet with the tabbed layout.  :( But at least it'll compile.  The trouble is
 that we have no way of tracking which tab ought to be visible without
 adding a *lot* of infrastructure.  I'd rather have that infrastructure in
 xmonad proper than reimplement all the focus-handling in combo, so for now
 I'll just delay upgrading my xmonad at work...
] 
[make square work with new doLayout.
David Roundy <droundy at darcs.net>**20070612133009] 
[add "Square" layout.
David Roundy <droundy at darcs.net>**20070612021048
 This is probably only ever useful in combination with Combo.
 It sticks one window in a square region, and makes the rest
 of the windows live with what's left (in a full-screen sense).
] 
[add new combo layout combiner.
David Roundy <droundy at darcs.net>**20070611224922] 
[In Decoration.hs, track rename of ModifyWindows
Stefan O'Rear <stefanor at cox.net>**20070612060713] 
[Refactor Decoration into a general layout-level hooks interface, and a decoration support module on top of that
Stefan O'Rear <stefanor at cox.net>**20070612060210] 
[the Stack can be Empty
Andrea Rossato <andrea.rossato at unibz.it>**20070612055144] 
[Documentation fix
Spencer Janssen <sjanssen at cse.unl.edu>**20070612035655] 
[Comment only
Spencer Janssen <sjanssen at cse.unl.edu>**20070612031305] 
[Fix LayoutHints in the presence of nonzero border widths
Stefan O'Rear <stefanor at cox.net>**20070611005407] 
[add keybinding to make aspect ratio flexible.
David Roundy <droundy at darcs.net>**20070611165915] 
[Note the modules I maintain
Spencer Janssen <sjanssen at cse.unl.edu>**20070611184830] 
[Add MetaModule
Spencer Janssen <sjanssen at cse.unl.edu>**20070611184601] 
[Updates to work with recent API changes
Spencer Janssen <sjanssen at cse.unl.edu>**20070611183439] 
[Rename safeIO to catchIO
Spencer Janssen <sjanssen at cse.unl.edu>**20070611162028] 
[add WorkspaceDir, which sets the current directory in a workspace.
David Roundy <droundy at darcs.net>**20070611154041
 Actually, it sets the current directory in a layout, since there's no way I
 know of to attach a behavior to a workspace.  This means that any terminals
 (or other programs) pulled up in that workspace (with that layout) will
 execute in that working directory.  Sort of handy, I think.
] 
[fmt 
Don Stewart <dons at cse.unsw.edu.au>**20070611053450] 
[added dynamicLogXinerama, a workspace logger that's nicer for Xinerama
Jason Creighton <jcreigh at gmail.com>**20070611051810] 
[redraw decorations on PropertyNotify
Jason Creighton <jcreigh at gmail.com>**20070611021408
 newDecoration now takes a Window parameter, which is the window the decoration
 is "for". If there is a PropertyNotify for that window, the decoration is
 redrawn.
] 
[use safe peek instead of unsafe focus
Jason Creighton <jcreigh at gmail.com>**20070611015437
 Fixes crashing bug with Xinerama where you have a tabbed layout on one screen
 and attempt to switch to an empty workspace on the other.
] 
[make Tabbed respect the y position of the layout rect (statusbar bugfix)
Jason Creighton <jcreigh at gmail.com>**20070610231510] 
[tune layout of Tabbed just a bit.
David Roundy <droundy at darcs.net>**20070610203513] 
[make Decoration set the input mask appropriately.
David Roundy <droundy at darcs.net>**20070610203451] 
[Updates for Layout API change
Spencer Janssen <sjanssen at cse.unl.edu>**20070610203840] 
[color focussed tab differently.
David Roundy <droundy at darcs.net>**20070610195743] 
[update Mosaic for latest changes.
David Roundy <droundy at darcs.net>**20070610145816] 
[maximize rather than minimize the rating.
David Roundy <droundy at darcs.net>**20070601183240] 
[fix error in select.
David Roundy <droundy at darcs.net>**20070601183147] 
[improve changeMosaic.
David Roundy <droundy at darcs.net>**20070601175042] 
[cut obsolete description of mosaic.
David Roundy <droundy at darcs.net>**20070609131456] 
[start switching over to a Monte Carlo algorithm for Mosaic
David Roundy <droundy at darcs.net>**20070601170505] 
[new layout algorithm for Mosaic.
David Roundy <droundy at darcs.net>**20070527191153] 
[display names of windows on tabs.
David Roundy <droundy at darcs.net>**20070610163729] 
[make Decoration draw the window initially.
David Roundy <droundy at darcs.net>**20070610163651
 We still don't respond to expose events.  :(
] 
[Fix name of xmonad-clock in compilation instructions.
glasser at mit.edu**20070610155204] 
[add Decoration module to be used to easily define decorations.
David Roundy <droundy at darcs.net>**20070610153939] 
[add sketch of tabbed layout.
David Roundy <droundy at darcs.net>**20070610153926] 
[make LayoutHints work with new modifyLayout (in X).
David Roundy <droundy at darcs.net>**20070610145740] 
[tag visibles with <N>
Don Stewart <dons at cse.unsw.edu.au>**20070610111931] 
[tweak pkill
Don Stewart <dons at cse.unsw.edu.au>**20070610093027] 
[greedydoc
dave at nullcube.com**20070610091056
 Add documentation on how to use GreedyView as your default workspace switcher.
] 
[use all 3 load values
Don Stewart <dons at cse.unsw.edu.au>**20070610090959] 
[Modified xmonad-clock.c to display battery information from ACPI (will work only on linux though). Also restored three load averages instead of only one.
buisse at cs.chalmers.se**20070610090228] 
[example xinitrc
Don Stewart <dons at cse.unsw.edu.au>**20070610085715] 
[update run-xmonad.sh
Don Stewart <dons at cse.unsw.edu.au>**20070610063915] 
[no need for ./scripts/xmonad-status.c, update run-xmonad.sh
Don Stewart <dons at cse.unsw.edu.au>**20070610062806] 
[add DynamicLog.hs
Don Stewart <dons at cse.unsw.edu.au>**20070610062757] 
[make LayoutHints robust with regard to future addition of Layout fields.
David Roundy <droundy at darcs.net>**20070609173725] 
[remove out of date ./scripts/xmonad-status.hs
Don Stewart <dons at cse.unsw.edu.au>**20070610005107] 
[add new LayoutHints module that makes layouts respect size hints.
David Roundy <droundy at darcs.net>**20070604213716] 
[improve xmonad-status.c
Don Stewart <dons at cse.unsw.edu.au>**20070609140258] 
[Add C script for parsing new logging encoding, and displaying workspace info
Don Stewart <dons at cse.unsw.edu.au>**20070609131856] 
[missing unsetenv
Don Stewart <dons at cse.unsw.edu.au>**20070609090127] 
[add tiny clock program (C) i'm using in the status bar
Don Stewart <dons at cse.unsw.edu.au>**20070609080435] 
[remove obsolete 'examples' dir
Don Stewart <dons at cse.unsw.edu.au>**20070609061450] 
[latest version of xmonad-status.hs
Don Stewart <dons at cse.unsw.edu.au>**20070609060913] 
[remove dead version
Don Stewart <dons at cse.unsw.edu.au>**20070609060857] 
[Circle layout
Peter De Wachter <pdewacht at gmail.com>**20070606064153
 Windows are arranged in a circle around the master window. Rather nice to use
 with a mouse, if you got many windows open.
 
 Screenshot: http://caladan.rave.org/circle.png
] 
[Submap: For creating keyboard submappings
Jason Creighton <jcreigh at gmail.com>**20070606061941] 
[nicer format for dynamic workspaces
Don Stewart <dons at cse.unsw.edu.au>**20070606045705] 
[add script which only draws current workspace, and those with clients
Don Stewart <dons at cse.unsw.edu.au>**20070606044544] 
[In docs, change name of program from mux to xmonad-status.
glasser at mit.edu**20070605140045] 
[Add xmonad-status.hs
Don Stewart <dons at cse.unsw.edu.au>**20070605132108
 
 An external status bar client for xmonad. 
 
 See screenshots:
 
     http://www.cse.unsw.edu.au/~dons/tmp/dons-dzen-status.png
     http://www.cse.unsw.edu.au/~dons/tmp/xmonad-dzen-tags.png
 
] 
[gapless tiled layout obeying size hints
Peter De Wachter <pdewacht at gmail.com>**20070605071716] 
[Contrib package for 6.4 users
daniel at wagner-home.com**20070604225534] 
[XMonadContrib.ReadMap: a Read instance of Map for GHC 6.4 users
daniel at wagner-home.com**20070602064318] 
[keybindings to warp pointer to window center
daniel at wagner-home.com**20070602062328] 
[XMonadContrib.Commands: for workspace and screen commands, leave out W/S tag
glasser at mit.edu**20070601161351] 
[New contrib module: run internal xmonad commands via dmenu
glasser at mit.edu**20070601043849] 
[Note that my xinerama patch is now in dzen.
glasser at mit.edu**20070601041112] 
[Rescreen is in main xmonad now
Spencer Janssen <sjanssen at cse.unl.edu>**20070528050656] 
[replace "name" in NamedWindow with a Show instance.
David Roundy <droundy at darcs.net>**20070526185114] 
[[Spiral] blend in the scale factor so it doesn't have any effect on the smallest windows
joe.thornber at gmail.com**20070525032732] 
[[Spiral] last rect takes all available space
joe.thornber at gmail.com**20070524120239] 
[[Spiral] Introduce a simpler Rect data type to remove a lot of the fromIntegrals
joe.thornber at gmail.com**20070524100423] 
[[Spiral] divideRects now takes a list of directions to split in
joe.thornber at gmail.com**20070524090211] 
[[Spiral] misc tidying
joe.thornber at gmail.com**20070524085537] 
[[Spiral] remove old spiral code
joe.thornber at gmail.com**20070524084805] 
[[Spiral] add fibonacci spiral
joe.thornber at gmail.com**20070524084423] 
[Allow clients of NamedWindows to get at the name.
glasser at mit.edu**20070523184251] 
[dzen module (with xinerama support, which requires glasser's Xinerama patch to dzen)
glasser at mit.edu**20070523184315] 
[Extract NamedWindow support from Mosaic into its own module
glasser at mit.edu**20070523155855] 
[remove SwapFocus (which is no longer possible)
David Roundy <droundy at darcs.net>**20070523153841
 This module depended on the focus stack.
] 
[Fix Spiral's module name
Spencer Janssen <sjanssen at cse.unl.edu>**20070522170909] 
[[SPIRAL] add spiral tiling layout
joe.thornber at gmail.com**20070522062537] 
[Make RotView compile.
Miikka Koskinen <arcatan at kapsi.fi>**20070522075338
 
 As I'm not a Xinerama user, I'm not sure if rotView should consider only
 hidden workspaces or also visible but not focused workspaces. I thought hidden
 workspaces only would be more logical.
] 
[bug fix in DwmPromote. whoops.
Miikka Koskinen <arcatan at kapsi.fi>**20070522062118] 
[make FindEmptyWorkspace compile
Miikka Koskinen <arcatan at kapsi.fi>**20070521123239] 
[make DwmPromote compile
Miikka Koskinen <arcatan at kapsi.fi>**20070521123140] 
[updated Dmenu.hs to work with zipper StackSet
Jason Creighton <jcreigh at gmail.com>**20070521233947] 
[Add GreedyView
Spencer Janssen <sjanssen at cse.unl.edu>**20070521220048] 
[Rescreen: collects new screen information
Spencer Janssen <sjanssen at cse.unl.edu>**20070521164808] 
[Fixes for windowset -> workspace rename
Spencer Janssen <sjanssen at cse.unl.edu>**20070521042118] 
[TwoPane: hide windows that aren't in view
Spencer Janssen <sjanssen at cse.unl.edu>**20070518224240] 
[make Mosaic even less picky by default.
David Roundy <droundy at darcs.net>**20070516175554] 
[add clear window message in Mosaic.
David Roundy <droundy at darcs.net>**20070516175518] 
[Comment only
Spencer Janssen <sjanssen at cse.unl.edu>**20070517211003] 
[Add instructions for TwoPane
Spencer Janssen <sjanssen at cse.unl.edu>**20070517210206] 
[Add TwoPane
Spencer Janssen <sjanssen at cse.unl.edu>**20070517195618] 
[throttle the exponential expense when many windows are present.
David Roundy <droundy at darcs.net>**20070516022123] 
[make mosaic configure windows by name rather than by Window.
David Roundy <droundy at darcs.net>**20070512215644
 Note that this is still pretty flawed.  Often window names change, and the
 layout then stagnates a bit.  Gimp, for example, opens most its windows
 with the same name before renaming them, so you have to hit mod-return or
 something to force a doLayout.  Also, gimp still overrides xmonad regarding
 the size of its main window.  :(
] 
[XMonadContrib.FindEmptyWorkspace
Miikka Koskinen <arcatan at kapsi.fi>**20070513184338
 
 With this module you can find empty workspaces, view them and tag windows to
 them.
] 
[make DwmPromote compile
Miikka Koskinen <arcatan at kapsi.fi>**20070513184254] 
[make DwmPromote compile again
Miikka Koskinen <arcatan at kapsi.fi>**20070510154158] 
[make DwmPromote compile
Miikka Koskinen <arcatan at kapsi.fi>**20070503105236] 
[add SwapFocus.
David Roundy <droundy at darcs.net>**20070512191315] 
[make rotView only consider non-visible workspaces (Xinerama)
Jason Creighton <jcreigh at gmail.com>**20070510012059] 
[fix commend in RotView.
David Roundy <droundy at darcs.net>**20070505185654] 
[switch to Message type for layout messages
Don Stewart <dons at cse.unsw.edu.au>**20070505014332] 
[Fix instructions in Mosaic.
Chris Mears <chris at cmears.id.au>**20070503222345] 
[add Mosaic layout.
David Roundy <droundy at darcs.net>**20070503151024] 
[-Wall police
Spencer Janssen <sjanssen at cse.unl.edu>**20070503211700] 
[Make RotView build, and add a brief description.
Chris Mears <chris at cmears.id.au>**20070503104234] 
[comment: Gave URL to xinerama-enabled dmenu patch
Jason Creighton <jcreigh at gmail.com>**20070503053133] 
[Put dmenu in X too
Spencer Janssen <sjanssen at cse.unl.edu>**20070503053727] 
[Add dmenu (thanks jcreigh)
Spencer Janssen <sjanssen at cse.unl.edu>**20070503052225] 
[add RotView module.
David Roundy <droundy at darcs.net>**20070421233838] 
[XMonadContrib.DwmPromote: dwm-like promote
Miikka Koskinen <arcatan at kapsi.fi>**20070501082031
 I like the way dwm's equivalent to xmonad's promote works, so I
 implemented dwmpromote.
] 
[add simple date example
Don Stewart <dons at cse.unsw.edu.au>**20070429064013] 
[more details
Don Stewart <dons at cse.unsw.edu.au>**20070429061426] 
[add readme
Don Stewart <dons at cse.unsw.edu.au>**20070429061329] 
[Initial import of xmonad contributions
Don Stewart <dons at cse.unsw.edu.au>**20070429061150] 
Patch bundle hash:
0b92e0a7dc33e1ca7203833a68206b4c8e7feb78


More information about the xmonad mailing list