[xmonad] that's it

Andrea Rossato mailing_list at istitutocolli.org
Fri Jan 25 10:46:41 EST 2008


Hi,

we have been waiting this new 0.6 release for quite sometime now, and,
instead of branching the code to be released so not to block
developers from pushing new features and having users try them out,
providing useful feedback, ideas, bugs reports, and so on, we have a
freezed repository, which is quite a useless thing, as far as I
understand. The last patch is 11 days old.

I hoped I could use this quiet period of time, the one between the end
of the first semester and the start of the second, to code a new
decoration framework, something I wanted since we moved to the class
approach, in order to replace the old David's Decorations.

That would require some testing, some discussion, some ideas, but
probably, when this code will be pushed, I'll be back to work, I won't
have the code fresh in my mind, so I will have to spend more time to
fix it, or to improve it, or to add new features.

I already have something in mind (a mouse interface), but I'm not
going to write a single line of code as long as a decision on the code
I've already produced have been taken.

So, this is the code: a small patch to the core (to add the
emptyLayout to the LayoutClass class), and the new decoration
framework.

I hope you understand I'm not complaining. I share the lack of time
problem. On the other hand I hope you understand that such a project
management is discouraging people from writing new code. Or at least
it discourage me.

So, that's it. I'll see you *after* 0.6 is out.
Cheers,
Andrea

a minimum working example:

import XMonad
import XMonad.Layout.Tabbed
import XMonad.Layout.DwmStyle
import XMonad.Layout.SimpleDecoration

myL = tabDeco shrinkText defaultTabbedConfig |||
      simpleDeco shrinkText defaultSimpleConfig (layoutHook defaultConfig) |||
      dwmStyle shrinkText defaultDwmStyleConfig (layoutHook defaultConfig)

main = xmonad defaultConfig { layoutHook = myL }

-------------- next part --------------

New patches:

[Add emptyLayout to LayoutClass, a method to be called when a workspace is empty
Andrea Rossato <andrea.rossato at unibz.it>**20080124013207] 
<
> {
hunk ./XMonad/Core.hs 221
     pureLayout  :: layout a -> Rectangle -> Stack a -> [(a, Rectangle)]
     pureLayout _ r s = [(focus s, r)]
 
+    -- | 'emptyLayout' is called when there is no window.
+    emptyLayout :: layout a -> Rectangle -> X ([(a, Rectangle)], Maybe (layout a))
+    emptyLayout _ _ = return ([], Nothing)
+
     -- | 'handleMessage' performs message handling for that layout.  If
     -- 'handleMessage' returns Nothing, then the layout did not respond to
     -- that message and the screen is not refreshed.  Otherwise, 'handleMessage'
hunk ./XMonad/Core.hs 245
 
 instance LayoutClass Layout Window where
     doLayout (Layout l) r s  = fmap (fmap Layout) `fmap` doLayout l r s
+    emptyLayout (Layout l) r = fmap (fmap Layout) `fmap` emptyLayout l r
     handleMessage (Layout l) = fmap (fmap Layout) . handleMessage l
     description (Layout l)   = description l
 
hunk ./XMonad/Core.hs 253
 
 -- | This calls doLayout if there are any windows to be laid out.
 runLayout :: LayoutClass l a => l a -> Rectangle -> Maybe (Stack a) -> X ([(a, Rectangle)], Maybe (l a))
-runLayout l r = maybe (return ([], Nothing)) (doLayout l r)
+runLayout l r = maybe (emptyLayout l r) (doLayout l r)
 
 -- | Based on ideas in /An Extensible Dynamically-Typed Hierarchy of Exceptions/,
 -- Simon Marlow, 2006. Use extensible messages to the handleMessage handler.
hunk ./XMonad/Layout.hs 56
 instance (LayoutClass l a, LayoutClass r a) => LayoutClass (Choose l r) a where
     doLayout (SLeft  r l) = (fmap (second . fmap $ SLeft r) .) . doLayout l
     doLayout (SRight l r) = (fmap (second . fmap $ SRight l) .) . doLayout r
+
+    emptyLayout (SLeft  r l) = (fmap (second . fmap $ SLeft r) .) $ emptyLayout l
+    emptyLayout (SRight l r) = (fmap (second . fmap $ SRight l) .) $ emptyLayout r
 
     description (SLeft _ l)  = description l
     description (SRight _ r) = description r
}

Context:

[Updated ./man/xmonad.1.in to contain new command line parameters
Austin Seipp <mad.one at gmail.com>**20080122070153] 
[Depend on QuickCheck < 2 when building tests
Spencer Janssen <sjanssen at cse.unl.edu>**20080122070225] 
[Roll testing into the main executable, use Cabal to build the tests
Spencer Janssen <sjanssen at cse.unl.edu>**20080119091215] 
[Simplify duplicate/cloned screen logic
Spencer Janssen <sjanssen at cse.unl.edu>**20080118032228] 
[Put the screen removing stuff in getCleanedScreenInfo
Joachim Breitner <mail at joachim-breitner.de>**20071231181556] 
[Ignore cloned screens
Joachim Breitner <mail at joachim-breitner.de>**20071231180628
 This patch ignores screens that are just clones of existing ones,
 or are completely contained in another. Currently only for rescreen, not yet for
 xmonad start.
] 
[-Werror when flag(testing) only
Spencer Janssen <sjanssen at cse.unl.edu>**20080118014827] 
[Export doubleFork
nicolas.pouillard at gmail.com**20080114202612] 
[reword comment (previous version didn't make sense to me)
Lukas Mai <l.mai at web.de>**20071122165925] 
[The recompile function now returns a boolean status instead of ().
nicolas.pouillard at gmail.com**20080105225500] 
[Make focus-follows-mouse configurable
Spencer Janssen <sjanssen at cse.unl.edu>**20071229023301] 
[Strictify all XConfig fields, gives nice error messages when a field is forgotten on construction
Spencer Janssen <sjanssen at cse.unl.edu>**20071229021923] 
[Spelling
Spencer Janssen <sjanssen at cse.unl.edu>**20071229021628] 
[Wibble
Spencer Janssen <sjanssen at cse.unl.edu>**20071229021519] 
[Broadcast button events to all layouts, fix for issue #111
Spencer Janssen <sjanssen at cse.unl.edu>**20071227080356] 
[Config.hs: too many users seem to be ignoring/missing the polite warning not to modify this file; change it to something a bit less polite/more obvious.
Brent Yorgey <byorgey at gmail.com>**20071220201549] 
[Remove desktop manageHook rules in favor of ManageDocks
Spencer Janssen <sjanssen at cse.unl.edu>**20071222113735] 
[Wibble
Spencer Janssen <sjanssen at cse.unl.edu>**20071222041151] 
[Add support for several flags:
Spencer Janssen <sjanssen at cse.unl.edu>**20071222020520
  --version: print xmonad's version
  --recompile: recompile xmonad.hs if it is out of date
  --force-recompile: recompile xmonad.hs unconditionally
] 
[Remove getProgName capability from restart, we don't use it anymore
Spencer Janssen <sjanssen at cse.unl.edu>**20071219215011] 
[Flush pending X calls before restarting
Spencer Janssen <sjanssen at cse.unl.edu>**20071219162029] 
[Allow for sharing of home directory across architectures.
tim.thelion at gmail.com**20071218065146] 
[Call 'broadcastMessage ReleaseResources' in restart
Spencer Janssen <sjanssen at cse.unl.edu>**20071219065710] 
[Manpage now describes config in ~/.xmonad/xmonad.hs
Adam Vogt <vogt.adam at gmail.com>**20071219023918] 
[Update manpage to describe greedyView
Adam Vogt <vogt.adam at gmail.com>**20071219023726] 
[Depend on X11-1.4.1, it has crucial bugfixes
Spencer Janssen <sjanssen at cse.unl.edu>**20071215022100] 
[1.4.1 X11 dep
Don Stewart <dons at galois.com>**20071214160558] 
[Set withdrawnState after calling hide
Spencer Janssen <sjanssen at cse.unl.edu>**20071212060250] 
[Remove stale comment
Spencer Janssen <sjanssen at cse.unl.edu>**20071211084236] 
[Make windows responsible for setting withdrawn state
Spencer Janssen <sjanssen at cse.unl.edu>**20071211080117] 
[Remove stale comment
Spencer Janssen <sjanssen at cse.unl.edu>**20071211075641] 
[Clean up stale mapped/waitingUnmap state in handle rather than unmanage.
Spencer Janssen <sjanssen at cse.unl.edu>**20071211074810
 This is an attempt to fix issue #96.  Thanks to jcreigh for the insights
 necessary to fix the bug.
] 
[Delete windows from waitingUnmap that aren't waitng for any unmaps
Spencer Janssen <sjanssen at cse.unl.edu>**20071211074506] 
[man/xmonad.hs: add some documentation explaining that 'title' can be used in the manageHook just like 'resource' and 'className'.
Brent Yorgey <byorgey at gmail.com>**20071210173357] 
[normalize Module headers
Lukas Mai <l.mai at web.de>**20071210085327] 
[Add 'testing' mode, this should reduce 'darcs check' time significantly
Spencer Janssen <sjanssen at cse.unl.edu>**20071210004704] 
[Use XMonad meta-module in Main.hs
Spencer Janssen <sjanssen at cse.unl.edu>**20071210004456] 
[TAG 0.5
Spencer Janssen <sjanssen at cse.unl.edu>**20071209233044] 
Patch bundle hash:
37e8b91590e3ffda2d8c4fc231013669a4c29558
-------------- next part --------------

New patches:

[Layout.ShowWName: generalize the instance
Andrea Rossato <andrea.rossato at unibz.it>**20080115045139] 
<
> {
hunk ./XMonad/Layout/ShowWName.hs 1
-{-# LANGUAGE PatternGuards, TypeSynonymInstances, MultiParamTypeClasses #-}
+{-# LANGUAGE PatternGuards, FlexibleInstances, MultiParamTypeClasses #-}
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  XMonad.Layout.ShowWName
hunk ./XMonad/Layout/ShowWName.hs 70
          , swn_fade    = 1
          }
 
-instance LayoutModifier ShowWName Window where
+instance LayoutModifier ShowWName a where
     redoLayout (SWN True  c (Just (_,w))) r _ wrs = deleteWindow w >> flashName c r wrs
     redoLayout (SWN True  c  Nothing    ) r _ wrs = flashName c r wrs
     redoLayout (SWN False _  _          ) _ _ wrs = return (wrs, Nothing)
}
[LayoutModifier: add pureMess and pureModifier to the LayoutModifier class
Andrea Rossato <andrea.rossato at unibz.it>**20080122111319] 
<
> {
hunk ./XMonad/Layout/LayoutModifier.hs 39
     handleMess :: m a -> SomeMessage -> X (Maybe (m a))
     handleMess m mess | Just Hide <- fromMessage mess             = doUnhook
                       | Just ReleaseResources <- fromMessage mess = doUnhook
-                      | otherwise = return Nothing
+                      | otherwise = return $ pureMess m mess
      where doUnhook = do unhook m; return Nothing
     handleMessOrMaybeModifyIt :: m a -> SomeMessage -> X (Maybe (Either (m a) SomeMessage))
     handleMessOrMaybeModifyIt m mess = do mm' <- handleMess m mess
hunk ./XMonad/Layout/LayoutModifier.hs 44
                                           return (Left `fmap` mm')
+    pureMess :: m a -> SomeMessage -> Maybe (m a)
+    pureMess _ _ = Nothing
     redoLayout :: m a -> Rectangle -> Stack a -> [(a, Rectangle)]
                -> X ([(a, Rectangle)], Maybe (m a))
hunk ./XMonad/Layout/LayoutModifier.hs 48
-    redoLayout m _ _ wrs = do hook m; return (wrs, Nothing)
+    redoLayout m r s wrs = do hook m; return $ pureModifier m r s wrs
+    pureModifier :: m a -> Rectangle -> Stack a -> [(a, Rectangle)]
+                 -> ([(a, Rectangle)], Maybe (m a))
+    pureModifier _ _ _ wrs = (wrs, Nothing)
     hook :: m a -> X ()
     hook _ = return ()
     unhook :: m a -> X ()
}
[LayoutModifier: add emptyLayoutMod for dealing with empty workspaces
Andrea Rossato <andrea.rossato at unibz.it>**20080124015605] 
<
> {
hunk ./XMonad/Layout/LayoutModifier.hs 52
     pureModifier :: m a -> Rectangle -> Stack a -> [(a, Rectangle)]
                  -> ([(a, Rectangle)], Maybe (m a))
     pureModifier _ _ _ wrs = (wrs, Nothing)
+    emptyLayoutMod :: m a -> Rectangle -> [(a, Rectangle)]
+                   -> X ([(a, Rectangle)], Maybe (m a))
+    emptyLayoutMod _ _ _ = return ([], Nothing)
     hook :: m a -> X ()
     hook _ = return ()
     unhook :: m a -> X ()
hunk ./XMonad/Layout/LayoutModifier.hs 67
         do (ws, ml') <- doLayout l r s
            (ws', mm') <- redoLayout m r s ws
            let ml'' = case mm' of
+                      Just m' -> Just $ (ModifiedLayout m') $ maybe l id ml'
+                      Nothing -> ModifiedLayout m `fmap` ml'
+           return (ws', ml'')
+    emptyLayout (ModifiedLayout m l) r =
+        do (ws, ml') <- emptyLayout l r
+           (ws',mm') <- emptyLayoutMod m r ws
+           let ml'' = case mm' of
                       Just m' -> Just $ (ModifiedLayout m') $ maybe l id ml'
                       Nothing -> ModifiedLayout m `fmap` ml'
            return (ws', ml'')
}
[XUtils: add functions for operating on lists of windows and export fi
Andrea Rossato <andrea.rossato at unibz.it>**20080124134638] 
<
> {
hunk ./XMonad/Util/XUtils.hs 15
 --
 -----------------------------------------------------------------------------
 
-module XMonad.Util.XUtils  (
-                             -- * Usage:
-                             -- $usage
-                               averagePixels
-                             , createNewWindow
-                             , showWindow
-                             , hideWindow
-                             , deleteWindow
-                             , paintWindow
-                             , paintAndWrite
-                             , stringToPixel
-                            ) where
-
+module XMonad.Util.XUtils
+    ( -- * Usage:
+      -- $usage
+      averagePixels
+    , createNewWindow
+    , showWindow
+    , showWindows
+    , hideWindow
+    , hideWindows
+    , deleteWindow
+    , deleteWindows
+    , paintWindow
+    , paintAndWrite
+    , stringToPixel
+    , fi
+    ) where
 
 import Data.Maybe
 import XMonad
hunk ./XMonad/Util/XUtils.hs 71
   d <- asks display
   io $ mapWindow d w
 
+-- | the list version
+showWindows :: [Window] -> X ()
+showWindows = mapM_ showWindow
+
 -- | unmap a window
 hideWindow :: Window -> X ()
 hideWindow w = do
hunk ./XMonad/Util/XUtils.hs 81
   d <- asks display
   io $ unmapWindow d w
 
+-- | the list version
+hideWindows :: [Window] -> X ()
+hideWindows = mapM_ hideWindow
+
 -- | destroy a window
 deleteWindow :: Window -> X ()
 deleteWindow w = do
hunk ./XMonad/Util/XUtils.hs 91
   d <- asks display
   io $ destroyWindow d w
 
+-- | the list version
+deleteWindows :: [Window] -> X ()
+deleteWindows = mapM_ deleteWindow
+
 -- | Fill a window with a rectangle and a border
 paintWindow :: Window     -- ^ The window where to draw
             -> Dimension  -- ^ Window width
}
[ShowWName: moved fi to XUtils
Andrea Rossato <andrea.rossato at unibz.it>**20080124134725] 
<
> {
hunk ./XMonad/Layout/ShowWName.hs 102
   i <- startTimer (swn_fade c)
   return (wrs, Just $ SWN False c $ Just (i,w))
 
--- | Short-hand for 'fromIntegral'
-fi :: (Integral a, Num b) => a -> b
-fi = fromIntegral
-
}
[Add WindowArranger, a layout modifier to move and resize windows with the keyboard
Andrea Rossato <andrea.rossato at unibz.it>**20080125151633] 
<
> {
addfile ./XMonad/Layout/WindowArranger.hs
hunk ./XMonad/Layout/WindowArranger.hs 1
+{-# OPTIONS_GHC -fglasgow-exts #-} -- for deriving Typeable
+{-# LANGUAGE PatternGuards, FlexibleInstances, MultiParamTypeClasses, TypeSynonymInstances #-}
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  XMonad.Layout.WindowArranger
+-- Copyright   :  (c) Andrea Rossato 2007
+-- License     :  BSD-style (see xmonad/LICENSE)
+--
+-- Maintainer  :  andrea.rossato at unibz.it
+-- Stability   :  unstable
+-- Portability :  unportable
+--
+-- This is a pure layout modifier that will let you move and resize
+-- windows with the keyboard in any layout.
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.WindowArranger
+    ( -- * Usage
+      -- $usage
+      windowArranger
+    , WindowArrangerMsg (..)
+    , memberFromList
+    , listFromList
+    , diff
+    ) where
+
+import XMonad
+import qualified XMonad.StackSet as S
+import XMonad.Layout.LayoutModifier
+import XMonad.Util.XUtils (fi)
+
+import Control.Arrow
+import Data.List
+import Data.Maybe
+
+-- $usage
+-- You can use this module with the following in your
+-- @~\/.xmonad\/xmonad.hs@:
+--
+-- > import XMonad.Layout.WindowArranger
+-- > myLayout = layoutHook defaultConfig
+-- > main = xmonad defaultConfig { layoutHook = windowArranger myLayout }
+--
+-- For more detailed instructions on editing the layoutHook see:
+--
+-- "XMonad.Doc.Extending#Editing_the_layout_hook"
+--
+-- You may also want to define some key binding to move or resize
+-- windows. These are good defaults:
+--
+-- >        , ((modMask x .|. controlMask              , xK_s    ), sendMessage  Arrange         )
+-- >        , ((modMask x .|. controlMask .|. shiftMask, xK_s    ), sendMessage  DeArrange       )
+-- >        , ((modMask x .|. controlMask              , xK_Left ), sendMessage (MoveLeft      1))
+-- >        , ((modMask x .|. controlMask              , xK_Right), sendMessage (MoveRight     1))
+-- >        , ((modMask x .|. controlMask              , xK_Down ), sendMessage (MoveDown      1))
+-- >        , ((modMask x .|. controlMask              , xK_Up   ), sendMessage (MoveUp        1))
+-- >        , ((modMask x                 .|. shiftMask, xK_Left ), sendMessage (IncreaseLeft  1))
+-- >        , ((modMask x                 .|. shiftMask, xK_Right), sendMessage (IncreaseRight 1))
+-- >        , ((modMask x                 .|. shiftMask, xK_Down ), sendMessage (IncreaseDown  1))
+-- >        , ((modMask x                 .|. shiftMask, xK_Up   ), sendMessage (IncreaseUp    1))
+-- >        , ((modMask x .|. controlMask .|. shiftMask, xK_Left ), sendMessage (DecreaseLeft  1))
+-- >        , ((modMask x .|. controlMask .|. shiftMask, xK_Right), sendMessage (DecreaseRight 1))
+-- >        , ((modMask x .|. controlMask .|. shiftMask, xK_Down ), sendMessage (DecreaseDown  1))
+-- >        , ((modMask x .|. controlMask .|. shiftMask, xK_Up   ), sendMessage (DecreaseUp    1))
+--
+-- For detailed instructions on editing your key bindings, see
+-- "XMonad.Doc.Extending#Editing_key_bindings".
+
+-- | A layout modifier to float the windows in a workspace
+windowArranger :: l a -> ModifiedLayout WindowArranger l a
+windowArranger = ModifiedLayout (WA True [])
+
+data WindowArrangerMsg = DeArrange
+                       | Arrange
+                       | IncreaseLeft  Int
+                       | IncreaseRight Int
+                       | IncreaseUp    Int
+                       | IncreaseDown  Int
+                       | DecreaseLeft  Int
+                       | DecreaseRight Int
+                       | DecreaseUp    Int
+                       | DecreaseDown  Int
+                       | MoveLeft      Int
+                       | MoveRight     Int
+                       | MoveUp        Int
+                       | MoveDown      Int
+                         deriving ( Typeable )
+instance Message WindowArrangerMsg
+
+data ArrangedWindow a = WR   (a, Rectangle)
+                      | AWR  (a, Rectangle)
+                        deriving (Read, Show)
+
+data WindowArranger a = WA Bool [ArrangedWindow a] deriving (Read, Show)
+
+instance (Show a, Read a, Eq a) => LayoutModifier WindowArranger a where
+    pureModifier (WA True []  ) _  _              wrs = arrangeWindows wrs
+
+    pureModifier (WA True awrs) _ (S.Stack w _ _) wrs = curry process  wrs awrs
+        where
+          wins         = map fst     *** map awrWin
+          update (a,r) = mkNewAWRs a *** removeAWRs r >>> uncurry (++)
+          process      = wins &&&  id  >>> first diff >>> uncurry update >>>
+                         replaceWR wrs >>> putOnTop w >>> map fromAWR &&& Just . WA True
+
+    pureModifier _ _ _ wrs = (wrs, Nothing)
+
+    pureMess (WA True (wr:wrs)) m
+        -- increase the window's size
+        | Just (IncreaseRight i) <- fm, (win, Rectangle x y w h) <- fa = res win  x         y        (w + fi i) h
+        | Just (IncreaseLeft  i) <- fm, (win, Rectangle x y w h) <- fa = res win (x - fi i) y        (w + fi i) h
+        | Just (IncreaseUp    i) <- fm, (win, Rectangle x y w h) <- fa = res win  x        (y - fi i) w        (h + fi i)
+        | Just (IncreaseDown  i) <- fm, (win, Rectangle x y w h) <- fa = res win  x         y         w        (h + fi i)
+        -- decrease the window's size
+        | Just (DecreaseRight i) <- fm, (win, Rectangle x y w h) <- fa = res win (x + fi i) y        (chk  w i) h
+        | Just (DecreaseLeft  i) <- fm, (win, Rectangle x y w h) <- fa = res win  x         y        (chk  w i) h
+        | Just (DecreaseUp    i) <- fm, (win, Rectangle x y w h) <- fa = res win  x         y         w        (chk h i)
+        | Just (DecreaseDown  i) <- fm, (win, Rectangle x y w h) <- fa = res win  x        (y + fi i) w        (chk h i)
+        --move the window around
+        | Just (MoveRight     i) <- fm, (win, Rectangle x y w h) <- fa = res win (x + fi i) y         w         h
+        | Just (MoveLeft      i) <- fm, (win, Rectangle x y w h) <- fa = res win (x - fi i) y         w         h
+        | Just (MoveUp        i) <- fm, (win, Rectangle x y w h) <- fa = res win  x        (y - fi i) w         h
+        | Just (MoveDown      i) <- fm, (win, Rectangle x y w h) <- fa = res win  x        (y + fi i) w         h
+
+        where res wi x y w h = Just . WA True $ AWR (wi,Rectangle x y w h):wrs
+              fm             = fromMessage m
+              fa             = fromAWR     wr
+              chk        x y = fi $ max 1 (fi x - y)
+
+    pureMess (WA _ l) m
+        | Just DeArrange <- fromMessage m = Just $ WA False l
+        | Just Arrange   <- fromMessage m = Just $ WA True  l
+        | otherwise                       = Nothing
+
+arrangeWindows :: [(a,Rectangle)] -> ([(a, Rectangle)], Maybe (WindowArranger a))
+arrangeWindows wrs = (wrs, Just $ WA True (map WR wrs))
+
+fromAWR :: ArrangedWindow a -> (a, Rectangle)
+fromAWR (WR   x) = x
+fromAWR (AWR  x) = x
+
+awrWin :: ArrangedWindow a -> a
+awrWin = fst . fromAWR
+
+getAWR :: Eq a => a -> [ArrangedWindow a] -> [ArrangedWindow a]
+getAWR = memberFromList awrWin (==)
+
+getWR ::  Eq a => a -> [(a,Rectangle)] -> [(a,Rectangle)]
+getWR = memberFromList fst (==)
+
+mkNewAWRs :: Eq a => [a] -> [(a,Rectangle)] -> [ArrangedWindow a]
+mkNewAWRs w wrs = map WR . concatMap (flip getWR wrs) $ w
+
+removeAWRs :: Eq a => [a] -> [ArrangedWindow a] -> [ArrangedWindow a]
+removeAWRs = listFromList awrWin notElem
+
+putOnTop :: Eq a => a -> [ArrangedWindow a] -> [ArrangedWindow a]
+putOnTop w awrs = awr ++ nawrs
+    where awr   = getAWR w awrs
+          nawrs = filter ((/=w) . awrWin) awrs
+
+replaceWR :: Eq a => [(a, Rectangle)] -> [ArrangedWindow a] -> [ArrangedWindow a]
+replaceWR wrs = foldr r []
+    where r x xs
+              | WR wr <- x = case fst wr `elemIndex` map fst wrs of
+                               Just i  -> (WR $ wrs !! i):xs
+                               Nothing -> x:xs
+              | otherwise  = x:xs
+
+-- | Given a function to be applied to each member of a list, and a
+-- function to check a condition by processing this transformed member
+-- with the members of a list, you get the list of members that
+-- satisfy the condition.
+listFromList :: (b -> c) -> (c -> [a] -> Bool) -> [a] -> [b] -> [b]
+listFromList f g l = foldr (h l) []
+    where h x y ys = if g (f y) x then y:ys else ys
+
+-- | Given a function to be applied to each member of ta list, and a
+-- function to check a condition by processing this transformed member
+-- with something, you get the first member that satisfy the condition,
+-- or an empty list.
+memberFromList :: (b -> c) -> (c -> a -> Bool) -> a -> [b] -> [b]
+memberFromList f g l = foldr (h l) []
+    where h x y ys = if g (f y) x then [y] else ys
+
+-- | Get the list of elements to be deleted and the list ef elements to
+-- be added to the first list in order to get the second list.
+diff :: Eq a => ([a],[a]) -> ([a],[a])
+diff (x,y) = (x \\ y, y \\ x)
hunk ./xmonad-contrib.cabal 126
                         XMonad.Layout.ThreeColumns
                         XMonad.Layout.ToggleLayouts
                         XMonad.Layout.TwoPane
+                        XMonad.Layout.WindowArranger
                         XMonad.Layout.WindowNavigation
                         XMonad.Layout.WorkspaceDir
                         XMonad.Prompt.Directory
}
[Add Decoration, a layout modifier and a class for easily writing decorated layouts
Andrea Rossato <andrea.rossato at unibz.it>**20080125151726] 
<
> {
addfile ./XMonad/Layout/Decoration.hs
hunk ./XMonad/Layout/Decoration.hs 1
+{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, PatternGuards, TypeSynonymInstances #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  XMonad.Layout.Decoration
+-- Copyright   :  (c) 2007 Andrea Rossato
+-- License     :  BSD-style (see xmonad/LICENSE)
+--
+-- Maintainer  :  andrea.rossato at unibz.it
+-- Stability   :  unstable
+-- Portability :  unportable
+--
+-- A layout modifier and a class for easily creating decorated
+-- layouts.
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.Decoration
+    ( -- * Usage:
+      -- $usage
+      decoration
+    , Decoration
+    , DecorationStyle (..)
+    , shrinkText, CustomShrink(CustomShrink)
+    , mkDefaultDeConfig
+    , DeConfig (..), defaultDeConfig
+    , Shrinker(..)
+    , module XMonad.Layout.LayoutModifier
+    , fi
+    ) where
+
+import Data.Maybe
+import Data.List
+
+import XMonad
+import qualified XMonad.StackSet as W
+
+import XMonad.Layout.LayoutModifier
+import XMonad.Layout.WindowArranger
+
+import XMonad.Util.NamedWindows
+import XMonad.Util.Invisible
+import XMonad.Util.XUtils
+import XMonad.Util.Font
+
+import XMonad.Hooks.UrgencyHook
+
+-- $usage
+-- For usage examples you can see "XMonad.Layout.SimpleDecoration",
+-- "XMonad.Layout.Tabbed", "XMonad.Layout.DwmStyle",
+
+decoration :: (DecorationStyle ds a, Shrinker s) => s -> DeConfig ds a
+           -> l a -> ModifiedLayout (Decoration ds s) l a
+decoration s c = ModifiedLayout (Decoration (I Nothing) s c)
+
+data DeConfig ds a =
+    DeConfig { activeColor         :: String
+             , inactiveColor       :: String
+             , urgentColor         :: String
+             , activeBorderColor   :: String
+             , inactiveBorderColor :: String
+             , urgentBorderColor   :: String
+             , activeTextColor     :: String
+             , inactiveTextColor   :: String
+             , urgentTextColor     :: String
+             , fontName            :: String
+             , decoWidth           :: Dimension
+             , decoHeight          :: Dimension
+             , style               :: ds a
+             } deriving (Show, Read)
+
+mkDefaultDeConfig :: DecorationStyle ds a => ds a -> DeConfig ds a
+mkDefaultDeConfig ds =
+    DeConfig { activeColor         = "#999999"
+             , inactiveColor       = "#666666"
+             , urgentColor         = "#FFFF00"
+             , activeBorderColor   = "#FFFFFF"
+             , inactiveBorderColor = "#BBBBBB"
+             , urgentBorderColor   = "##00FF00"
+             , activeTextColor     = "#FFFFFF"
+             , inactiveTextColor   = "#BFBFBF"
+             , urgentTextColor     = "#FF0000"
+             , fontName            = "-misc-fixed-*-*-*-*-10-*-*-*-*-*-*-*"
+             , decoWidth           = 200
+             , decoHeight          = 20
+             , style               = ds
+             }
+
+type DecoWin = (Window,Maybe Rectangle)
+type OrigWin = (Window,Rectangle)
+data DecorationState =
+    DS { decos  :: [(OrigWin,DecoWin)]
+       , font   :: XMonadFont
+       }
+
+data Decoration ds s a =
+    Decoration (Invisible Maybe DecorationState) s (DeConfig ds a)
+    deriving (Show, Read)
+
+class (Read (ds a), Show (ds a)) => DecorationStyle ds a where
+    describeDeco :: ds a -> String
+    describeDeco ds = show ds
+
+    decorateFirst :: ds a -> Bool
+    decorateFirst _ = True
+
+    shrink :: ds a -> Rectangle -> Rectangle -> Rectangle
+    shrink _ (Rectangle _ _ _ dh) (Rectangle x y w h) = Rectangle x (y + fi dh) w (h - dh)
+
+    pureDecoration :: ds a -> Dimension -> Dimension -> Rectangle
+                   -> W.Stack a -> [(a,Rectangle)] -> (a,Rectangle) -> Maybe Rectangle
+    pureDecoration _ _ h _ _ _ (_,Rectangle x y w _) = Just $ Rectangle x y w h
+
+    decorate :: ds a -> Dimension -> Dimension -> Rectangle
+             -> W.Stack a -> [(a,Rectangle)] -> (a,Rectangle) -> X (Maybe Rectangle)
+    decorate ds w h r s ars ar = return $ pureDecoration ds w h r s ars ar
+
+data DefaultStyle a = DefaultStyle deriving (Read, Show)
+instance DecorationStyle DefaultStyle a
+
+defaultDeConfig :: DeConfig DefaultStyle a
+defaultDeConfig = mkDefaultDeConfig DefaultStyle
+
+instance (DecorationStyle ds Window, Shrinker s) => LayoutModifier (Decoration ds s) Window where
+    redoLayout (Decoration st sh c) sc stack wrs
+        | decorate_first   = do whenIJust st $ \s -> deleteWindows (getDWs $ decos s)
+                                return (wrs, Just $ Decoration (I Nothing) sh c)
+        | I Nothing  <- st = initState c wrs >>= processState
+        | I (Just s) <- st = do let dwrs  = decos s
+                                    (d,a) = curry diff (get_ws dwrs) ws
+                                    toDel = todel d dwrs
+                                    toAdd = toadd a wrs
+                                deleteWindows (getDWs toDel)
+                                ndwrs <- createDecos c toAdd
+                                processState (s {decos = ndwrs ++ del_dwrs d dwrs })
+        | otherwise        = return (wrs, Nothing)
+
+        where
+          ws        = map fst wrs
+          del_dwrs  = listFromList get_w notElem
+          get_ws    = map get_w
+          get_w     = fst . fst
+          find_dw i = fst . snd . flip (!!) i
+          todel   d = filter (flip elem d . get_w)
+          toadd   a = filter (flip elem a . fst  )
+
+          insert_dwr ((w,r),(dw,Just dr)) xs = (dw,dr):(w, shrink (style c) dr r):xs
+          insert_dwr (x    ,(_ ,Nothing)) xs = x:xs
+
+          resync _         [] = return []
+          resync d ((w,r):xs) = case  w `elemIndex` get_ws d of
+                                  Just i  -> do dr   <- decorate (style c) (decoWidth c) (decoHeight c) sc stack wrs (w,r)
+                                                dwrs <- resync d xs
+                                                return $ ((w,r),(find_dw i d, dr)) : dwrs
+                                  Nothing -> resync d xs
+
+          decorate_first = length wrs == 1 && (not . decorateFirst . style $ c)
+          processState s = do ndwrs <- resync (decos s) wrs
+                              showWindows (getDWs ndwrs)
+                              updateDecos sh c (font s) ndwrs
+                              return (foldr insert_dwr [] ndwrs, Just (Decoration (I (Just (s {decos = ndwrs}))) sh c))
+
+
+    handleMess (Decoration (I (Just s@(DS {decos = dwrs}))) sh c) m
+        | Just e <- fromMessage m :: Maybe Event = handleEvent sh c s e >> return Nothing
+        | Just Hide             <- fromMessage m = hideWindows      dws >> return Nothing
+        | Just ReleaseResources <- fromMessage m = do deleteWindows dws
+                                                      releaseXMF (font s)
+                                                      return $ Just $ Decoration (I Nothing) sh c
+        where dws = getDWs dwrs
+
+    handleMess _ _ = return Nothing
+
+    emptyLayoutMod (Decoration (I (Just (DS dwrs _))) _ _) _ _ = deleteWindows (getDWs dwrs) >> return ([], Nothing)
+    emptyLayoutMod _ _ _  = return ([], Nothing)
+
+    modifierDescription (Decoration _ _ c) = describeDeco $ style c
+
+handleEvent :: (DecorationStyle ds a, Shrinker s) => s -> DeConfig ds a -> DecorationState-> Event -> X ()
+handleEvent sh c (DS dwrs fs) e
+    | PropertyEvent {ev_window = w} <- e, w `elem` (map (fst . fst) dwrs) = updateDecos sh c fs dwrs
+    | ExposeEvent   {ev_window = w} <- e, w `elem` (map (fst . snd) dwrs) = updateDecos sh c fs dwrs
+handleEvent _ _ _ _ = return ()
+
+
+getDWs :: [(OrigWin,DecoWin)] -> [Window]
+getDWs = map (fst . snd)
+
+initState ::  DecorationStyle ds a => DeConfig ds a -> [(Window,Rectangle)] -> X DecorationState
+initState conf wrs = do
+  fs   <- initXMF (fontName conf)
+  dwrs <- createDecos conf wrs
+  return $ DS dwrs fs
+
+createDecos :: DecorationStyle ds a => DeConfig ds a -> [(Window,Rectangle)] -> X [(OrigWin,DecoWin)]
+createDecos _ [] = return []
+createDecos c (wr:wrs) = do
+  let rect = Rectangle 0 0 1 1
+      mask = Just (exposureMask .|. buttonPressMask)
+  dw  <- createNewWindow rect mask (inactiveColor c) True
+  dwrs <- createDecos c wrs
+  return ((wr,(dw,Nothing)):dwrs)
+
+updateDecos :: (DecorationStyle ds a, Shrinker s) => s -> DeConfig ds a -> XMonadFont -> [(OrigWin, DecoWin)] -> X ()
+updateDecos s c f = mapM_ $ updateDeco s c f
+
+updateDeco :: (DecorationStyle ds a, Shrinker s) => s -> DeConfig ds a -> XMonadFont -> (OrigWin, DecoWin) -> X ()
+updateDeco sh c fs ((w,_),(dw,Just (Rectangle _ _ wh ht))) = do
+  nw  <- getName w
+  ur  <- readUrgents
+  dpy <- asks display
+  let focusColor win ic ac uc = (maybe ic (\focusw -> case () of
+                                                       _ | focusw == win -> ac
+                                                         | win `elem` ur -> uc
+                                                         | otherwise     -> ic) . W.peek)
+                                `fmap` gets windowset
+  (bc',borderc',tc') <- focusColor w
+                           (inactiveColor c, inactiveBorderColor c, inactiveTextColor c)
+                           (activeColor   c, activeBorderColor   c, activeTextColor   c)
+                           (urgentColor   c, urgentBorderColor   c, urgentTextColor   c)
+  let s  = shrinkIt sh
+  name <- shrinkWhile s (\n -> do
+                                size <- io $ textWidthXMF dpy fs n
+                                return $ size > fromIntegral wh - fromIntegral (ht `div` 2)) (show nw)
+  paintAndWrite dw fs wh ht 1 bc' borderc' tc' bc' AlignCenter name
+updateDeco _ _ _ (_,(w,Nothing)) = hideWindow w
+
+shrinkWhile :: (String -> [String]) -> (String -> X Bool) -> String -> X String
+shrinkWhile sh p x = sw $ sh x
+    where sw [n] = return n
+          sw [] = return ""
+          sw (n:ns) = do
+                        cond <- p n
+                        if cond
+                          then sw ns
+                          else return n
+
+data CustomShrink = CustomShrink
+instance Show CustomShrink where show _ = ""
+instance Read CustomShrink where readsPrec _ s = [(CustomShrink,s)]
+
+class (Read s, Show s) => Shrinker s where
+    shrinkIt :: s -> String -> [String]
+
+data DefaultShrinker = DefaultShrinker
+instance Show DefaultShrinker where show _ = ""
+instance Read DefaultShrinker where readsPrec _ s = [(DefaultShrinker,s)]
+instance Shrinker DefaultShrinker where
+    shrinkIt _ "" = [""]
+    shrinkIt s cs = cs : shrinkIt s (init cs)
+
+shrinkText :: DefaultShrinker
+shrinkText = DefaultShrinker
hunk ./xmonad-contrib.cabal 99
                         XMonad.Layout.Accordion
                         XMonad.Layout.Circle
                         XMonad.Layout.Combo
+                        XMonad.Layout.Decoration
                         XMonad.Layout.Dishes
                         XMonad.Layout.DragPane
                         XMonad.Layout.Grid
}
[Add Layout.ResizeScreen, a layout transformer to have a layout respect a given screen geometry
Andrea Rossato <andrea.rossato at unibz.it>**20080125151905] 
<
> {
addfile ./XMonad/Layout/ResizeScreen.hs
hunk ./XMonad/Layout/ResizeScreen.hs 1
+{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, PatternGuards #-}
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  XMonad.Layout.ResizeScreen
+-- Copyright   :  (c) 2007 Andrea Rossato
+-- License     :  BSD-style (see xmonad/LICENSE)
+--
+-- Maintainer  :  andrea.rossato at unibz.it
+-- Stability   :  unstable
+-- Portability :  unportable
+--
+-- A layout transformer to have a layout respect a given screen
+-- geometry
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.ResizeScreen
+    ( -- * Usage:
+      -- $usage
+      resizeHorizontal
+    , resizeVertical
+    , withNewRectangle
+    , ResizeScreen (..)
+    ) where
+
+import Control.Arrow (second)
+import Control.Applicative ((<$>))
+
+import XMonad
+import XMonad.Util.XUtils (fi)
+
+-- $usage
+-- You can use this module by importing it into your
+-- @~\/.xmonad\/xmonad.hs@ file:
+--
+-- > import XMonad.Layout.ResizeScreen
+--
+-- and modifying your layoutHook as follows (for example):
+--
+-- > layoutHook = resizeHorizontal 40 Full
+--
+-- For more detailed instructions on editing the layoutHook see:
+--
+-- "XMonad.Doc.Extending#Editing_the_layout_hook"
+
+resizeHorizontal :: Int -> l a -> ResizeScreen l a
+resizeHorizontal = ResizeScreen H 
+
+resizeVertical :: Int -> l a -> ResizeScreen l a
+resizeVertical = ResizeScreen V
+
+withNewRectangle  :: Rectangle -> l a -> ResizeScreen l a
+withNewRectangle = WithNewScreen
+
+data ResizeScreen l a = ResizeScreen ResizeMode Int (l a)
+                      | WithNewScreen Rectangle (l a)
+                        deriving (Read, Show)
+data ResizeMode = H | V deriving (Read, Show)
+
+instance (LayoutClass l a) => LayoutClass (ResizeScreen l) a where
+    doLayout m rec@(Rectangle x y w h ) s
+        | ResizeScreen H i l <- m = resize (ResizeScreen V i) l (Rectangle (x + fi i) y (w - fi i) h)
+        | ResizeScreen V i l <- m = resize (ResizeScreen H i) l (Rectangle x (y + fi i) w (h - fi i))
+        | WithNewScreen  r l <- m = resize (WithNewScreen  r) l r
+        | otherwise               = doLayout m rec s
+       where resize t l' nr = second (fmap t) <$> doLayout l' nr s 
+
+    description _ = []
hunk ./xmonad-contrib.cabal 119
                         XMonad.Layout.PerWorkspace
                         XMonad.Layout.Reflect
                         XMonad.Layout.ResizableTile
+                        XMonad.Layout.ResizeScreen
                         XMonad.Layout.Roledex
                         XMonad.Layout.Spiral
                         XMonad.Layout.Square
}
[Add Layout.Simplest, the simplest layout
Andrea Rossato <andrea.rossato at unibz.it>**20080125152015] 
<
> {
addfile ./XMonad/Layout/Simplest.hs
hunk ./XMonad/Layout/Simplest.hs 1
+{-# LANGUAGE TypeSynonymInstances, MultiParamTypeClasses #-}
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  XMonad.Layout.Simplest
+-- Copyright   :  (c) 2007 Andrea Rossato
+-- License     :  BSD-style (see xmonad/LICENSE)
+--
+-- Maintainer  :  andrea.rossato at unibz.it
+-- Stability   :  unstable
+-- Portability :  unportable
+--
+-- A very simple layout. The simplest, afaik.
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.Simplest
+    ( -- * Usage:
+      -- $usage
+      Simplest (..)
+    ) where
+
+import XMonad
+import qualified XMonad.StackSet as S
+
+-- $usage
+-- You can use this module with the following in your
+-- @~\/.xmonad\/xmonad.hs@:
+--
+-- > import XMonad.Layout.Simplest
+--
+-- Then edit your @layoutHook@ by adding the Simplest layout:
+--
+-- > myLayouts = Simplest ||| Full ||| etc..
+-- > main = xmonad defaultConfig { layoutHook = myLayouts }
+--
+-- For more detailed instructions on editing the layoutHook see:
+--
+-- "XMonad.Doc.Extending#Editing_the_layout_hook"
+
+data Simplest a = Simplest deriving (Show, Read)
+instance LayoutClass Simplest Window where
+    pureLayout Simplest rec (S.Stack w l r) = zip (w : reverse l ++ r) (repeat rec)
hunk ./xmonad-contrib.cabal 121
                         XMonad.Layout.ResizableTile
                         XMonad.Layout.ResizeScreen
                         XMonad.Layout.Roledex
+                        XMonad.Layout.Simplest
                         XMonad.Layout.Spiral
                         XMonad.Layout.Square
                         XMonad.Layout.ShowWName
}
[Adde SimpleDecoration, a layout modifier to add simple decorations to windows in any layout
Andrea Rossato <andrea.rossato at unibz.it>**20080125152106] 
<
> {
addfile ./XMonad/Layout/SimpleDecoration.hs
hunk ./XMonad/Layout/SimpleDecoration.hs 1
-
+{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  XMonad.Layout.SimpleDecoration
+-- Copyright   :  (c) 2007 Andrea Rossato
+-- License     :  BSD-style (see xmonad/LICENSE)
+--
+-- Maintainer  :  andrea.rossato at unibz.it
+-- Stability   :  unstable
+-- Portability :  unportable
+--
+-- A layout modifier for adding simple decorations to the windows of a
+-- given layout.
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.SimpleDecoration
+    ( -- * Usage:
+      -- $usage
+      simpleDeco
+    , SimpleDecoration (..), defaultSimpleConfig
+    , shrinkText, CustomShrink(CustomShrink)
+    , Shrinker(..)
+    ) where
+
+import XMonad
+import XMonad.Layout.Decoration
+
+-- $usage
+-- You can use this module with the following in your
+-- @~\/.xmonad\/xmonad.hs@:
+--
+-- > import XMonad.Layout.SimpleDecoration
+--
+-- Then edit your @layoutHook@ by adding the SimpleDecoration decoration to
+-- your layout:
+--
+-- > myL = simpleDeco shrinkText defaultSimpleConfig (layoutHook defaultConfig)
+-- > main = xmonad defaultConfig { layoutHook = myL }
+--
+-- For more detailed instructions on editing the layoutHook see:
+--
+-- "XMonad.Doc.Extending#Editing_the_layout_hook"
+--
+-- You can also edit the default configuration options.
+--
+-- > mySDConfig = defaultSimpleConfig { inactiveBorderColor = "red"
+-- >                                  , inactiveTextColor   = "red"}
+--
+-- and
+--
+-- > myL = dwmStyle shrinkText mySDConfig (layoutHook defaultConfig)
+
+-- | Add simple decorations to windows of a layout.
+simpleDeco :: Shrinker s => s -> DeConfig SimpleDecoration a
+           -> l a -> ModifiedLayout (Decoration SimpleDecoration s) l a
+simpleDeco s c = decoration s c
+
+defaultSimpleConfig :: DeConfig SimpleDecoration a
+defaultSimpleConfig = mkDefaultDeConfig $ Simple True
+
+data SimpleDecoration a = Simple Bool deriving (Show, Read)
+
+instance DecorationStyle SimpleDecoration a where
+    describeDeco _ = "Simple"
+    shrink (Simple b) (Rectangle _ _ _ dh) r@(Rectangle x y w h) =
+        if b then Rectangle x (y + fi dh) w (h - dh) else r
+    pureDecoration (Simple b) wh ht _ _ _ (_,Rectangle x y wid _) =
+        if b then Just $ Rectangle x y nwh ht else Just $ Rectangle x (y - fi ht) nwh ht
+            where nwh = min wid wh
hunk ./xmonad-contrib.cabal 122
                         XMonad.Layout.ResizeScreen
                         XMonad.Layout.Roledex
                         XMonad.Layout.Simplest
+                        XMonad.Layout.SimpleDecoration
                         XMonad.Layout.Spiral
                         XMonad.Layout.Square
                         XMonad.Layout.ShowWName
}
[Add DwmStyle, a layout modifier to add dwm-style decorations to windows in any layout
Andrea Rossato <andrea.rossato at unibz.it>**20080125152152] 
<
> {
addfile ./XMonad/Layout/DwmStyle.hs
hunk ./XMonad/Layout/DwmStyle.hs 1
+{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  XMonad.Layout.DwmStyle
+-- Copyright   :  (c) 2007 Andrea Rossato
+-- License     :  BSD-style (see xmonad/LICENSE)
+--
+-- Maintainer  :  andrea.rossato at unibz.it
+-- Stability   :  unstable
+-- Portability :  unportable
+--
+-- A layout modifier for decorating windows in a dwm like style.
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.DwmStyle
+    ( -- * Usage:
+      -- $usage
+      dwmStyle
+    , DwmStyle (..), defaultDwmStyleConfig
+    , shrinkText, CustomShrink(CustomShrink)
+    , Shrinker(..)
+    ) where
+
+import XMonad
+import XMonad.StackSet ( Stack (..) )
+import XMonad.Layout.Decoration
+
+-- $usage
+-- You can use this module with the following in your
+-- @~\/.xmonad\/xmonad.hs@:
+--
+-- > import XMonad.Layout.DwmStyle
+--
+-- Then edit your @layoutHook@ by adding the DwmStyle decoration to
+-- your layout:
+--
+-- > myL = dwmStyle shrinkText defaultDwmStyleConfig (layoutHook defaultConfig)
+-- > main = xmonad defaultConfig { layoutHook = myL }
+--
+-- For more detailed instructions on editing the layoutHook see:
+--
+-- "XMonad.Doc.Extending#Editing_the_layout_hook"
+--
+-- You can also edit the default configuration options.
+--
+-- > myDWConfig = defaultDwmStyleConfig { inactiveBorderColor = "red"
+-- >                                    , inactiveTextColor   = "red"}
+--
+-- and
+--
+-- > myL = dwmStyle shrinkText myDWConfig (layoutHook defaultConfig)
+
+-- | Add simple old dwm-style decorations to windows of a layout.
+dwmStyle :: (Eq a, Shrinker s) => s -> DeConfig DwmStyle a
+         -> l a -> ModifiedLayout (Decoration DwmStyle s) l a
+dwmStyle s c = decoration s c
+
+defaultDwmStyleConfig :: Eq a => DeConfig DwmStyle a
+defaultDwmStyleConfig= mkDefaultDeConfig Dwm
+
+data DwmStyle a = Dwm deriving (Show, Read)
+
+instance Eq a => DecorationStyle DwmStyle a where
+    describeDeco _ = "DwmStyle"
+    shrink  _ _  r = r
+    pureDecoration _ wh ht _ (Stack fw _ _) _ (win,Rectangle x y wid _) =
+        if win == fw then Nothing else Just $ Rectangle (fi nx) y nwh (fi ht)
+            where nwh = min wid $ fi wh
+                  nx  = fi x + wid - nwh
hunk ./xmonad-contrib.cabal 102
                         XMonad.Layout.Decoration
                         XMonad.Layout.Dishes
                         XMonad.Layout.DragPane
+                        XMonad.Layout.DwmStyle
                         XMonad.Layout.Grid
                         XMonad.Layout.HintedTile
                         XMonad.Layout.LayoutCombinators
}
[Tabbed now uses Decoration
Andrea Rossato <andrea.rossato at unibz.it>**20080125152311] 
<
> {
hunk ./XMonad/Layout/Tabbed.hs 2
 {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, PatternGuards, TypeSynonymInstances #-}
+
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  XMonad.Layout.Tabbed
hunk ./XMonad/Layout/Tabbed.hs 15
 --
 -- A tabbed layout for the Xmonad Window Manager
 --
+-- This module has functions and types that conflict with those used
+-- in Decoration.hs. These functions and types are deprecated and will
+-- be removed.
+--
+-- PLEASE: do not use 'tabbed'. Use 'tabDeco' instead.
+--
 -----------------------------------------------------------------------------
 
hunk ./XMonad/Layout/Tabbed.hs 23
-module XMonad.Layout.Tabbed (
-                             -- * Usage:
-                             -- $usage
-                             tabbed
-                            , shrinkText, CustomShrink(CustomShrink)
-                            , TConf (..), defaultTConf
-                            , Shrinker(..)
-                            ) where
+module XMonad.Layout.Tabbed
+    ( -- * Usage:
+      -- $usage
+      tabbed
+    , tabDeco
+    , TConf (..), defaultTConf
+    , TabbedDecoration (..), defaultTabbedConfig
+    , shrinkText, CustomShrink(CustomShrink)
+    , Shrinker(..)
+    ) where
 
 import Data.Maybe
 import Data.List
hunk ./XMonad/Layout/Tabbed.hs 38
 
 import XMonad
-import qualified XMonad.StackSet as W
-
-import XMonad.Util.NamedWindows
-import XMonad.Util.Invisible
-import XMonad.Util.XUtils
-import XMonad.Util.Font
-
-import XMonad.Hooks.UrgencyHook
+import qualified XMonad.StackSet as S
+import XMonad.Layout.Decoration
+import XMonad.Layout.Simplest
 
 -- $usage
 -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
hunk ./XMonad/Layout/Tabbed.hs 49
 --
 -- Then edit your @layoutHook@ by adding the Tabbed layout:
 --
--- > myLayouts = tabbed shrinkText defaultTConf ||| Full ||| etc..
+-- > myLayouts = tabDeco shrinkText defaultTabbedConfig ||| Full ||| etc..
 -- > main = xmonad defaultConfig { layoutHook = myLayouts }
 --
 -- For more detailed instructions on editing the layoutHook see:
hunk ./XMonad/Layout/Tabbed.hs 58
 --
 -- You can also edit the default configuration options.
 --
--- > myTabConfig = defaultTConf { inactiveBorderColor = "#FF0000"
--- >                            , activeTextColor = "#00FF00"}
+-- > myTabConfig = defaultTabbedConfig { inactiveBorderColor = "#FF0000"
+-- >                                   , activeTextColor = "#00FF00"}
 --
 -- and
 --
hunk ./XMonad/Layout/Tabbed.hs 63
--- > mylayout = tabbed shrinkText myTabConfig ||| Full ||| etc..
+-- > mylayout = tabDeco shrinkText myTabConfig ||| Full ||| etc..
+
+-- | Create a tabbed layout with a shrinker and a tabbed configuration.
+tabDeco :: (Eq a, Shrinker s) => s -> DeConfig TabbedDecoration a
+        -> ModifiedLayout (Decoration TabbedDecoration s) Simplest  a
+tabDeco s c = decoration s c Simplest
+
+-- | This function is deprecated and will be removed before 0.7!!
+tabbed :: (Eq a, Shrinker s) => s -> TConf
+       -> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
+tabbed s c = decoration s (toNewConf c) Simplest
 
hunk ./XMonad/Layout/Tabbed.hs 75
-tabbed :: Shrinker s => s -> TConf -> Tabbed s a
-tabbed s t = Tabbed (I Nothing) s t
+defaultTabbedConfig :: Eq a => DeConfig TabbedDecoration a
+defaultTabbedConfig = mkDefaultDeConfig $ Tabbed
 
hunk ./XMonad/Layout/Tabbed.hs 78
+data TabbedDecoration a = Tabbed deriving (Read, Show)
+
+instance Eq a => DecorationStyle TabbedDecoration a where
+    describeDeco  _ = "Tabbed"
+    decorateFirst _ = False
+    pureDecoration _ _ ht (Rectangle x y wh _) s wrs (w,_) = Just $ Rectangle nx y nwh (fi ht)
+        where nwh = wh `div` max 1 (fi $ length wrs)
+              nx  = case w `elemIndex` (S.integrate s) of
+                      Just i  -> x + (fi nwh * fi i)
+                      Nothing -> x
+
+-- Backward compatibility stuff
+-- DEPRECATED!!
+toNewConf :: Eq a => TConf -> DeConfig TabbedDecoration a
+toNewConf oc =
+    nc { XMonad.Layout.Decoration.activeColor         = XMonad.Layout.Tabbed.activeColor         oc
+       , XMonad.Layout.Decoration.inactiveColor       = XMonad.Layout.Tabbed.inactiveColor       oc
+       , XMonad.Layout.Decoration.urgentColor         = XMonad.Layout.Tabbed.urgentColor         oc
+       , XMonad.Layout.Decoration.activeBorderColor   = XMonad.Layout.Tabbed.activeBorderColor   oc
+       , XMonad.Layout.Decoration.inactiveBorderColor = XMonad.Layout.Tabbed.inactiveBorderColor oc
+       , XMonad.Layout.Decoration.urgentBorderColor   = XMonad.Layout.Tabbed.urgentBorderColor   oc
+       , XMonad.Layout.Decoration.activeTextColor     = XMonad.Layout.Tabbed.activeTextColor     oc
+       , XMonad.Layout.Decoration.inactiveTextColor   = XMonad.Layout.Tabbed.inactiveTextColor   oc
+       , XMonad.Layout.Decoration.urgentTextColor     = XMonad.Layout.Tabbed.urgentTextColor     oc
+       , XMonad.Layout.Decoration.fontName            = XMonad.Layout.Tabbed.fontName            oc
+       , XMonad.Layout.Decoration.decoHeight     = fi $ XMonad.Layout.Tabbed.tabSize             oc
+       }
+    where nc = mkDefaultDeConfig $ Tabbed
+
+-- | This datatype is deprecated and will be removed before 0.7!!
 data TConf =
     TConf { activeColor         :: String
           , inactiveColor       :: String
hunk ./XMonad/Layout/Tabbed.hs 122
           , tabSize             :: Int
           } deriving (Show, Read)
 
+-- | This function is deprecated and will be removed before 0.7!!
 defaultTConf :: TConf
 defaultTConf =
hunk ./XMonad/Layout/Tabbed.hs 125
-    TConf { activeColor         = "#999999"
-          , inactiveColor       = "#666666"
-          , urgentColor         = "#FFFF00"
-          , activeBorderColor   = "#FFFFFF"
-          , inactiveBorderColor = "#BBBBBB"
-          , urgentBorderColor   = "##00FF00"
-          , activeTextColor     = "#FFFFFF"
-          , inactiveTextColor   = "#BFBFBF"
-          , urgentTextColor     = "#FF0000"
-          , fontName            = "-misc-fixed-*-*-*-*-10-*-*-*-*-*-*-*"
-          , tabSize             = 20
+    TConf { XMonad.Layout.Tabbed.activeColor         = "#999999"
+          , XMonad.Layout.Tabbed.inactiveColor       = "#666666"
+          , XMonad.Layout.Tabbed.urgentColor         = "#FFFF00"
+          , XMonad.Layout.Tabbed.activeBorderColor   = "#FFFFFF"
+          , XMonad.Layout.Tabbed.inactiveBorderColor = "#BBBBBB"
+          , XMonad.Layout.Tabbed.urgentBorderColor   = "##00FF00"
+          , XMonad.Layout.Tabbed.activeTextColor     = "#FFFFFF"
+          , XMonad.Layout.Tabbed.inactiveTextColor   = "#BFBFBF"
+          , XMonad.Layout.Tabbed.urgentTextColor     = "#FF0000"
+          , XMonad.Layout.Tabbed.fontName            = "-misc-fixed-*-*-*-*-10-*-*-*-*-*-*-*"
+          , XMonad.Layout.Tabbed.tabSize             = 20
           }
 
hunk ./XMonad/Layout/Tabbed.hs 138
-data TabState =
-    TabState { tabsWindows :: [(Window,Window)]
-             , scr         :: Rectangle
-             , font        :: XMonadFont
-             }
-
-data Tabbed s a =
-    Tabbed (Invisible Maybe TabState) s TConf
-    deriving (Show, Read)
-
-instance Shrinker s => LayoutClass (Tabbed s) Window where
-    doLayout (Tabbed ist ishr conf) = doLay ist ishr conf
-    handleMessage                   = handleMess
-    description _                   = "Tabbed"
-
-doLay :: Shrinker s => Invisible Maybe TabState -> s -> TConf
-      -> Rectangle -> W.Stack Window -> X ([(Window, Rectangle)], Maybe (Tabbed s Window))
-doLay ist ishr c sc (W.Stack w [] []) = do
-  whenIJust ist $ \st -> mapM_ deleteWindow (map fst $ tabsWindows st)
-  return ([(w,sc)], Just $ Tabbed (I Nothing) ishr c)
-doLay ist ishr c sc@(Rectangle _ _ wid _) s@(W.Stack w _ _) = do
-  let ws = W.integrate s
-      width = wid `div` fromIntegral (length ws)
-  -- initialize state
-  st <- case ist of
-          (I Nothing  ) -> initState c sc ws
-          (I (Just ts)) -> if map snd (tabsWindows ts) == ws && scr ts == sc
-                           then return ts
-                           else do mapM_ deleteWindow (map fst $ tabsWindows ts)
-                                   tws <- createTabs c sc ws
-                                   return (ts {scr = sc, tabsWindows = zip tws ws})
-  mapM_ showWindow $ map fst $ tabsWindows st
-  mapM_ (updateTab ishr c (font st) width) $ tabsWindows st
-  return ([(w,shrink c sc)], Just (Tabbed (I (Just st)) ishr c))
-
-handleMess :: Shrinker s => Tabbed s Window -> SomeMessage -> X (Maybe (Tabbed s Window))
-handleMess (Tabbed (I (Just st@(TabState {tabsWindows = tws}))) ishr conf) m
-    | Just e <- fromMessage m :: Maybe Event = handleEvent ishr conf st e     >> return Nothing
-    | Just Hide             == fromMessage m = mapM_ hideWindow (map fst tws) >> return Nothing
-    | Just ReleaseResources == fromMessage m = do mapM_ deleteWindow $ map fst tws
-                                                  releaseXMF (font st)
-                                                  return $ Just $ Tabbed (I Nothing) ishr conf
-handleMess _ _  = return Nothing
-
-handleEvent :: Shrinker s => s -> TConf -> TabState -> Event -> X ()
--- button press
-handleEvent ishr conf (TabState    {tabsWindows = tws,   scr          = screen, font          = fs})
-                      (ButtonEvent {ev_window   = thisw, ev_subwindow = thisbw, ev_event_type = t })
-    | t == buttonPress, tl <- map fst tws, thisw `elem` tl || thisbw `elem` tl  = do
-  case lookup thisw tws of
-    Just x  -> do focus x
-                  updateTab ishr conf fs width (thisw, x)
-    Nothing -> return ()
-    where
-      width = rect_width screen`div` fromIntegral (length tws)
-
-handleEvent ishr conf (TabState {tabsWindows = tws,   scr           = screen, font = fs})
-                      (AnyEvent {ev_window   = thisw, ev_event_type = t                })
--- expose
-    | thisw `elem` (map fst tws) && t == expose         = do
-  updateTab ishr conf fs width (thisw, fromJust $ lookup thisw tws)
-    where
-      width = rect_width screen`div` fromIntegral (length tws)
-
--- propertyNotify
-handleEvent ishr conf (TabState      {tabsWindows = tws, scr = screen, font = fs})
-                      (PropertyEvent {ev_window   = thisw})
-    | thisw `elem` (map snd tws) = do
-  let tabwin = (fst $ fromJust $ find ((== thisw) . snd) tws, thisw)
-  updateTab ishr conf fs width tabwin
-    where width = rect_width screen `div` fromIntegral (length tws)
--- expose
-handleEvent ishr conf (TabState {tabsWindows = tws, scr = screen, font = fs})
-                      (ExposeEvent {ev_window   = thisw})
-    | thisw `elem` (map fst tws) = do
-  updateTab ishr conf fs width (thisw, fromJust $ lookup thisw tws)
-    where width = rect_width screen `div` fromIntegral (length tws)
-handleEvent _ _ _ _ =  return ()
-
-initState :: TConf -> Rectangle -> [Window] -> X TabState
-initState conf sc ws = do
-  fs  <- initXMF (fontName conf)
-  tws <- createTabs conf sc ws
-  return $ TabState (zip tws ws) sc fs
-
-createTabs :: TConf -> Rectangle -> [Window] -> X [Window]
-createTabs _ _ [] = return []
-createTabs c (Rectangle x y wh ht) owl@(ow:ows) = do
-  let wid    = wh `div` (fromIntegral $ length owl)
-      height = fromIntegral $ tabSize c
-      mask   = Just (exposureMask .|. buttonPressMask)
-  d  <- asks display
-  w  <- createNewWindow (Rectangle x y wid height) mask (inactiveColor c) True
-  io $ restackWindows d $ w : [ow]
-  ws <- createTabs c (Rectangle (x + fromIntegral wid) y (wh - wid) ht) ows
-  return (w:ws)
-
-updateTab :: Shrinker s => s -> TConf -> XMonadFont -> Dimension -> (Window,Window) -> X ()
-updateTab ishr c fs wh (tabw,ow) = do
-  nw <- getName ow
-  ur <- readUrgents
-  let ht                   = fromIntegral $ tabSize c :: Dimension
-      focusColor win ic ac uc = (maybe ic (\focusw -> case () of
-                                                       _ | focusw == win -> ac
-                                                         | win `elem` ur -> uc
-                                                         | otherwise     -> ic) . W.peek)
-                                `fmap` gets windowset
-  (bc',borderc',tc') <- focusColor ow
-                           (inactiveColor c, inactiveBorderColor c, inactiveTextColor c)
-                           (activeColor   c, activeBorderColor   c, activeTextColor   c)
-                           (urgentColor   c, urgentBorderColor   c, urgentTextColor   c)
-  dpy <- asks display
-  let s = shrinkIt ishr
-  name <- shrinkWhile s (\n -> do
-                                size <- io $ textWidthXMF dpy fs n
-                                return $ size > fromIntegral wh - fromIntegral (ht `div` 2)) (show nw)
-  paintAndWrite tabw fs wh ht 1 bc' borderc' tc' bc' AlignCenter name
-
-shrink :: TConf -> Rectangle -> Rectangle
-shrink c (Rectangle x y w h) =
-    Rectangle x (y + fromIntegral (tabSize c)) w (h - fromIntegral (tabSize c))
-
-shrinkWhile :: (String -> [String]) -> (String -> X Bool) -> String -> X String
-shrinkWhile sh p x = sw $ sh x
-    where sw [n] = return n
-          sw [] = return ""
-          sw (n:ns) = do
-                        cond <- p n
-                        if cond
-                          then sw ns
-                          else return n
-
-data CustomShrink = CustomShrink
-instance Show CustomShrink where show _ = ""
-instance Read CustomShrink where readsPrec _ s = [(CustomShrink,s)]
-
-class (Read s, Show s) => Shrinker s where
-    shrinkIt :: s -> String -> [String]
-
-data DefaultShrinker = DefaultShrinker
-instance Show DefaultShrinker where show _ = ""
-instance Read DefaultShrinker where readsPrec _ s = [(DefaultShrinker,s)]
-instance Shrinker DefaultShrinker where
-    shrinkIt _ "" = [""]
-    shrinkIt s cs = cs : shrinkIt s (init cs)
-
-shrinkText :: DefaultShrinker
-shrinkText = DefaultShrinker
}

Context:

[cleared up transience to better highlight how to use ManageHooks properly
xmonad-contrib at hexago.nl**20080102074810
 
 The initial patch that extended the EDSL for writing ManageHook rules did not come with a good example on how to use it.  This patch ammends that. 'move' is an example of how to write a rule to resolve a Query (Maybe a) into something tangible.  'move'' is an example of how to write a rule isolating window managing code from the rest ofthe mess the EDSL creates.
] 
[expands the EDSL for performing actions on windows
xmonad-contrib at hexago.nl**20080101174446
 
 This patch adds a few types of relationships and operators for managing windows with rules.  It provides grouping operators so the X action can access the quantifier that was matched or not matched.  It provides a formalism for predicates that work in both grouping and non grouping rules.  It could do with some classes, so that there are fewer operators that always do the Right Thing (TM), but the Haskell Type system currently has some problems resolving types.  Since I don't know enough about these high level things, it would be hard to create a GHC patch just to make it all work.
] 
[-Werror when flag(testing) only
Spencer Janssen <sjanssen at cse.unl.edu>**20080118015207] 
[Reflect.hs: minor haddock fix
Brent Yorgey <byorgey at gmail.com>**20080116203546] 
[Reflect.hs: use -fglasgow-exts for now instead of LANGUAGE pragmas, for compatibility with ghc 6.6
Brent Yorgey <byorgey at gmail.com>**20080115194811] 
[Reflect.hs: add MultiToggle support
Brent Yorgey <byorgey at gmail.com>**20080115193519] 
[MultiToggle.hs: improve 'description' implementation in LayoutClass instance to display the current transformed layout rather than just 'MultiToggle'
Brent Yorgey <byorgey at gmail.com>**20080115193311] 
[Layout.Reflect: new contrib module for reflecting layouts horizontally/vertically
Brent Yorgey <byorgey at gmail.com>**20080115030947] 
[Timer: some code cleanup
Andrea Rossato <andrea.rossato at unibz.it>**20080114211114] 
[Use doubleFork instead of manual double fork, or buggy single fork.
nicolas.pouillard at gmail.com**20080114202833
 
 This fixes showWName because Timer was leaking zombie processes.
 You should update xmonad, since doubleFork was not exported.
] 
[ShowWName.hs: switch color/bgcolor in call to paintAndWrite
Brent Yorgey <byorgey at gmail.com>**20080114153821] 
[Prompt: clean up and optimize moveWord a bit
Andrea Rossato <andrea.rossato at unibz.it>**20080113164745] 
[Prompt: added moveWord to move the cursor to the word boundaries
Andrea Rossato <andrea.rossato at unibz.it>**20080113123529
 The actions have been bound to ctrl+Left and Right
] 
[Doc.Extending: added links and description of recent module addition
Andrea Rossato <andrea.rossato at unibz.it>**20080113093211] 
[Action.Search: small haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20080113092646] 
[ShowWName now uses Timer and XUtils to display the workspace name
Andrea Rossato <andrea.rossato at unibz.it>**20080113091107] 
[Add XMonad.Util.Timer, a module to set up timers and to handle them
Andrea Rossato <andrea.rossato at unibz.it>**20080113090140] 
[de-obfuscate the initState and set the init offset to the length of the default text
Andrea Rossato <andrea.rossato at unibz.it>**20080110140951] 
[prompt: Allow to provide a default text in the prompt config.
nicolas.pouillard at gmail.com**20080109213916] 
[Correct caps in module header.
Joachim Fasting <joachim.fasting at gmail.com>**20071230061920] 
[Use LANGUAGE pragma.
Joachim Fasting <joachim.fasting at gmail.com>**20071230061817] 
[shiftPrevScreen and shiftNextScreen, to make CycleWS consistent
mail at joachim-breitner.de**20071231171609] 
[formatting
Don Stewart <dons at galois.com>**20071204174920] 
[PerWorkspace.hs: add an explanatory note
Brent Yorgey <byorgey at gmail.com>**20071231135806] 
[Add ShowWName a layout modifier to show the workspace name
Andrea Rossato <andrea.rossato at unibz.it>**20071231130441
 This module requires dzen
] 
[ManageDocks: some documentation fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071231101820] 
[-Wall police (again)
Spencer Janssen <sjanssen at cse.unl.edu>**20071228061841] 
[-Wall police
Spencer Janssen <sjanssen at cse.unl.edu>**20071228061822] 
[Fulfill the EWMH specification by listing the supported ATOMs, doesnt really make a differene AFAIK
mail at joachim-breitner.de**20071227215607] 
[display all visible windows on the current desktop in the pager
mail at joachim-breitner.de**20071227204349
 This is my best shot at modeling xmonad’s WM behaviour in a way that
 the Extended Window Manager Hints specification allows.
 
 Unfortunately, we can not tell the panel what size and position it should
 think the apps are.
] 
[Although I do not need the curr variable after all, this is nicer
mail at joachim-breitner.de**20071227190113] 
[Add support for cycling through screens to CycleWS
mail at joachim-breitner.de**20071227182635] 
[Clear _NET_ACTIVE_WINDOW when nothing is focused
mail at joachim-breitner.de**20071228154222] 
[textExtentsXMF doesn't require the display
Andrea Rossato <andrea.rossato at unibz.it>**20071228125913] 
[Don't bother checking executable bits of items in $PATH, yields a significant speed-up
Spencer Janssen <sjanssen at cse.unl.edu>**20071226032412] 
[ResizableTile.hs: fix resizing to work in the presence of floating windows (resolves issue #100)
Brent Yorgey <byorgey at gmail.com>**20071225135839] 
[LayoutScreens: haddock fixes
Andrea Rossato <andrea.rossato at unibz.it>**20071225105316] 
[XMonad.Actions.Search: haddock fix
Andrea Rossato <andrea.rossato at unibz.it>**20071224171115] 
[Fix isssue 105
Andrea Rossato <andrea.rossato at unibz.it>**20071224171020
 issue 105 was due to the fact that tab windows created when
 bootstrapping the windowset after a restart where managed. Setting the
 override_redirect attributes to True fixes the issue.
 
 Added the possibility to set the override_redirect attribute with
 XMonad.Util.XUtils.creationNewWindow
] 
[Prompt.hs: mv .xmonad_history into .xmonad/
gwern0 at gmail.com**20071224054610
 See my email to mailing list. This will slightly break anyone who upgrades while running and expects to see their prompt history, and leave a stray file, I think, but nothing else, and it'll permanently improve tab-completion, and is tidier.
] 
[Search.hs: +docs, and export simpleEngine so users can define their own
gwern0 at gmail.com**20071224043828] 
[Search.hs: mv into Actions/ per IRC suggestion
gwern0 at gmail.com**20071224043735] 
[add XMonad.Actions.NoBorders
Lukas Mai <l.mai at web.de>**20071220203953] 
[AvoidStruts: add support for partial struts
Spencer Janssen <sjanssen at cse.unl.edu>**20071222133425] 
[Search.hs: add hoogle
Brent Yorgey <byorgey at gmail.com>**20071222184912] 
[ManageDocks: ignore desktop windows also
Spencer Janssen <sjanssen at cse.unl.edu>**20071222113808] 
[Wibble
Spencer Janssen <sjanssen at cse.unl.edu>**20071222110641] 
[EwmhDesktops: add _NET_ACTIVE_WINDOW support
Spencer Janssen <sjanssen at cse.unl.edu>**20071222110552] 
[A few short comments for WorkspaceCompare
Spencer Janssen <sjanssen at cse.unl.edu>**20071222105045] 
[EwmhDesktops: drop 'Workspace' from displayed workspace names
Spencer Janssen <sjanssen at cse.unl.edu>**20071222104559] 
[Factor workspace sorting into a separate module
Spencer Janssen <sjanssen at cse.unl.edu>**20071222104114] 
[No more tabs
Spencer Janssen <sjanssen at cse.unl.edu>**20071222050439] 
[Refactor Search.hs
Spencer Janssen <sjanssen at cse.unl.edu>**20071222044714] 
[Generalize XSelection functions to MonadIO
Spencer Janssen <sjanssen at cse.unl.edu>**20071222044514] 
[Search.hs: +imdb & amazon engines for unk_red
gwern0 at gmail.com**20071222035837] 
[Search.hs: cleanup and refactor
gwern0 at gmail.com**20071220174001] 
[Update various restart bindings
Spencer Janssen <sjanssen at cse.unl.edu>**20071219220634] 
[Fix typo.
Roman Cheplyaka <roma at ro-che.info>**20071219073857] 
[Doc/Developing.hs: add some information about Haddock documentation.
Brent Yorgey <byorgey at gmail.com>**20071219215300] 
[require haddock documentation to build successfully in order to record a patch.
Brent Yorgey <byorgey at gmail.com>**20071219215217] 
[Remove inaccurate comment about 'banish'
Spencer Janssen <sjanssen at cse.unl.edu>**20071217231540] 
[Warp.hs: haddock fixes
Brent Yorgey <byorgey at gmail.com>**20071217224712] 
[Warp.hs: +doc
gwern0 at gmail.com**20071216030015
 Describe how to emulate Ratpoison's 'banish' functionality on one's config
] 
[Util/Search.hs: a few updates/fixes
Brent Yorgey <byorgey at gmail.com>**20071217222930
   * fix shadowing warning (ghc 6.8.2 complains)
   * export a few more of the functions
   * re-de-obfuscate generated URLs by not escaping alphanumerics or punct.
] 
[Util.Search: import escapeURIString, and fall back on the ugly const false hack to avoid copy-pasting even more
gwern0 at gmail.com**20071215211638] 
[update Config.Droundy to use a few nice hooks.
David Roundy <droundy at darcs.net>**20071216185653] 
[Add UrgencyHook support to Tabbed
Shachaf Ben-Kiki <shachaf at gmail.com>**20071215171617] 
[DynamicLog.hs: some documentation updates.
Brent Yorgey <byorgey at gmail.com>**20071215143727] 
[DynamicLog.hs: fix shadowing warning
Brent Yorgey <byorgey at gmail.com>**20071215143227] 
[Add UrgencyHook support to DynamicLog
Shachaf Ben-Kiki <shachaf at gmail.com>**20071214043528
 Someone with Xinerama should look at this -- I don't know exactly how that
 should behave.
] 
[Depend on X11-1.4.1, it has crucial bugfixes
Spencer Janssen <sjanssen at cse.unl.edu>**20071215022151] 
[Remove network dependency, potentially breaking XMonad.Util.Search
Spencer Janssen <sjanssen at cse.unl.edu>**20071214231859] 
[Search.hs: fix shadowing warning and haddock errors
Brent Yorgey <byorgey at gmail.com>**20071214163119] 
[+cabal support for XMonad.Util.Search
gwern0 at gmail.com**20071213205654] 
[+XMonad.Util.Search: new module
gwern0 at gmail.com**20071213205159
 This module is intended to provide helpful functions for easily running web searchs; just hit a bound key, enter your query, and up opens a new tab/browser/window with the search results. In theory anyway; the Wikipedia and Google ones work fine for me, but the Internet Archive's docs on how to do don't necessarily seem to be correct. If you were, like me, previously running shell commands to call Surfraw or similar shell scripts to do the same thing, you can now scrap them and replace them.
 
 There aren't too many search engines defined here; new ones would be good, and they're easy to add!
] 
[Add support for _NET_WM_STRUT_PARTIAL
Spencer Janssen <sjanssen at cse.unl.edu>**20071213021704] 
[ManageDocks: when there are struts on opposing edges, the right/bottom strut
Spencer Janssen <sjanssen at cse.unl.edu>**20071210021030
 was ignored.  TODO: quickchecks
] 
[Run.hs: fix documentation, cleanup whitespace
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071212091516] 
[Man.hs: input speedup
"Valery V. Vorotyntsev" <valery.vv at gmail.com>**20071212090256
 
 Descend manpage directories once -- when `manPrompt' is called.
 (Previous version used to search directories upon each character
 arrival.)
] 
[new XMonad.Hooks.ManageHelpers module
Lukas Mai <l.mai at web.de>**20071211183040] 
[Magnifier: custom zoom ratio for magnifier' too
intrigeri at boum.org**20071211015554] 
[Magnifier.hs: minor haddock fixes
Brent Yorgey <byorgey at gmail.com>**20071211011154] 
[fix haddock on Magnifier
tim.thelion at gmail.com**20071210231942] 
[Custom zoom levels for magnifier
tim.thelion at gmail.com**20071208230844] 
[TAG 0.5
Spencer Janssen <sjanssen at cse.unl.edu>**20071209233056] 
Patch bundle hash:
15b3002199217a5c1e1fcc13b6d633bf6abd079a


More information about the xmonad mailing list