[xmonad] darcs patch: X actions in DynamicLog

asgaroth asgaroth_ at gmx.de
Fri Jan 2 16:43:09 EST 2009


The attached patch makes it possible to use arbitrary X actions in the 
functions in DynamicLog, e.g. to display the window count for each 
workspace or display other more dynamic information. I supplied an 
additional PPX data type and functions that use it in order to maintain 
compatability with current configs.
(This is my first contribution to a Haskell project and I'm not very 
skilled in writing Haskell code, so the patch probably contains style 
errors).
-------------- next part --------------
Fri Jan  2 22:16:26 CET 2009  asgaroth <asgaroth_ at gmx.de>
  * Support for X actions in logHook

New patches:

[Support for X actions in logHook
asgaroth <asgaroth_ at gmx.de>**20090102211626] {
hunk ./XMonad/Hooks/DynamicLog.hs 36
     dynamicLogWithPP,
     dynamicLogString,
     PP(..), defaultPP,
+    dynamicLogWithPPX,
+    dynamicLogStringX,
+    ppToPPX, PPX(..),
 
     -- * Example formatters
     dzenPP, xmobarPP, sjanssenPP, byorgeyPP,
hunk ./XMonad/Hooks/DynamicLog.hs 225
 
 -- | Format the current status using the supplied pretty-printing format,
 --   and write it to stdout.
+dynamicLogWithPPX :: PPX -> X ()
+dynamicLogWithPPX ppx = dynamicLogStringX ppx >>= io . ppxOutput ppx
+
+-- | The same as dynamicLogWithPPX for PP
 dynamicLogWithPP :: PP -> X ()
hunk ./XMonad/Hooks/DynamicLog.hs 230
-dynamicLogWithPP pp = dynamicLogString pp >>= io . ppOutput pp
+dynamicLogWithPP = dynamicLogWithPPX . ppToPPX
 
hunk ./XMonad/Hooks/DynamicLog.hs 232
--- | The same as 'dynamicLogWithPP', except it simply returns the status
+-- | The same as 'dynamicLogWithPPX', except it simply returns the status
 --   as a formatted string without actually printing it to stdout, to
 --   allow for further processing, or use in some application other than
 --   a status bar.
hunk ./XMonad/Hooks/DynamicLog.hs 236
-dynamicLogString :: PP -> X String
-dynamicLogString pp = do
+dynamicLogStringX :: PPX -> X String
+dynamicLogStringX ppx = do
 
     winset <- gets windowset
     urgents <- readUrgents
hunk ./XMonad/Hooks/DynamicLog.hs 241
-    sort' <- ppSort pp
+    sort' <- ppxSort ppx
 
     -- layout description
     let ld = description . S.layout . S.workspace . S.current $ winset
hunk ./XMonad/Hooks/DynamicLog.hs 247
 
     -- workspace list
-    let ws = pprWindowSet sort' urgents pp winset
+    ws <- pprWindowSet sort' urgents ppx winset
 
     -- window title
hunk ./XMonad/Hooks/DynamicLog.hs 250
-    wt <- maybe (return "") (fmap show . getName) . S.peek $ winset
+    wt <- (maybe (return "") (fmap show . getName) . S.peek $ winset)
 
     -- run extra loggers, ignoring any that generate errors.
hunk ./XMonad/Hooks/DynamicLog.hs 253
-    extras <- sequence $ map (flip catchX (return Nothing)) $ ppExtras pp
+    extras <- sequence $ map (flip catchX (return Nothing)) $ ppxExtras ppx
+
+    -- format layout
+    layout <- ppxLayout ppx ld
 
hunk ./XMonad/Hooks/DynamicLog.hs 258
-    return $ encodeOutput . sepBy (ppSep pp) . ppOrder pp $
+    -- format window title
+    tl <- ppxTitle ppx wt
+
+    return $ encodeOutput . sepBy (ppxSep ppx) . ppxOrder ppx $
                         [ ws
hunk ./XMonad/Hooks/DynamicLog.hs 263
-                        , ppLayout pp ld
-                        , ppTitle  pp wt
+                        , layout
+                        , tl
                         ]
                         ++ catMaybes extras
 
hunk ./XMonad/Hooks/DynamicLog.hs 268
+-- | The same as dynamicLogStringX for PP
+dynamicLogString :: PP -> X String
+dynamicLogString = dynamicLogStringX . ppToPPX
+
 -- | Format the workspace information, given a workspace sorting function,
 --   a list of urgent windows, a pretty-printer format, and the current
 --   WindowSet.
hunk ./XMonad/Hooks/DynamicLog.hs 275
-pprWindowSet :: WorkspaceSort -> [Window] -> PP -> WindowSet -> String
-pprWindowSet sort' urgents pp s = sepBy (ppWsSep pp) . map fmt . sort' $
-            map S.workspace (S.current s : S.visible s) ++ S.hidden s
+pprWindowSet :: WorkspaceSort -> [Window] -> PPX -> WindowSet -> X String
+pprWindowSet sort' urgents ppx s = return . sepBy (ppxWsSep ppx) =<< (mapM fmt . sort' $
+            map S.workspace (S.current s : S.visible s) ++ S.hidden s)
    where this     = S.currentTag s
          visibles = map (S.tag . S.workspace) (S.visible s)
 
hunk ./XMonad/Hooks/DynamicLog.hs 281
-         fmt w = printer pp (S.tag w)
-          where printer | S.tag w == this                                               = ppCurrent
-                        | S.tag w `elem` visibles                                       = ppVisible
-                        | any (\x -> maybe False (== S.tag w) (S.findTag x s)) urgents  = \ppC -> ppUrgent ppC . ppHidden ppC
-                        | isJust (S.stack w)                                            = ppHidden
-                        | otherwise                                                     = ppHiddenNoWindows
+         fmt w = printer ppx (S.tag w)
+          where printer | S.tag w == this                                               = ppxCurrent
+                        | S.tag w `elem` visibles                                       = ppxVisible
+                        | any (\x -> maybe False (== S.tag w) (S.findTag x s)) urgents  = \ppC str -> ppxUrgent ppC =<< ppxHidden ppC str
+                        | isJust (S.stack w)                                            = ppxHidden
+                        | otherwise                                                     = ppxHiddenNoWindows
 
 -- |
 -- Workspace logger with a format designed for Xinerama:
hunk ./XMonad/Hooks/DynamicLog.hs 418
                -- formatting.
              }
 
+-- | The 'PPX' is almost identical to PP, but differs from PP in that it 
+--   allows for X actions in its functions
+data PPX = PPX { ppxCurrent :: WorkspaceId -> X String
+               -- ^ how to print the tag of the currently focused
+               -- workspace
+               , ppxVisible :: WorkspaceId -> X String
+               -- ^ how to print tags of visible but not focused
+               -- workspaces (xinerama only)
+               , ppxHidden  :: WorkspaceId -> X String
+               -- ^ how to print tags of hidden workspaces which
+               -- contain windows
+               , ppxHiddenNoWindows :: WorkspaceId -> X String
+               -- ^ how to print tags of empty hidden workspaces
+               , ppxUrgent :: WorkspaceId -> X String
+               -- ^ format to be applied to tags of urgent workspaces.
+               -- NOTE that 'ppUrgent' is applied /in addition to/
+               -- 'ppHidden'!
+               , ppxSep :: String
+               -- ^ separator to use between different log sections
+               -- (window name, layout, workspaces)
+               , ppxWsSep :: String
+               -- ^ separator to use between workspace tags
+               , ppxTitle :: String -> X String
+               -- ^ window title format
+               , ppxLayout :: String -> X String
+               -- ^ layout name format
+               , ppxOrder :: [String] -> [String]
+               -- ^ how to order the different log sections. By
+               --   default, this function receives a list with three
+               --   formatted strings, representing the workspaces,
+               --   the layout, and the current window title,
+               --   respectively. If you have specified any extra
+               --   loggers in 'ppExtras', their output will also be
+               --   appended to the list.  To get them in the reverse
+               --   order, you can just use @ppOrder = reverse at .  If
+               --   you don't want to display the current layout, you
+               --   could use something like @ppOrder = \\(ws:_:t:_) ->
+               --   [ws,t]@, and so on.
+               , ppxSort :: X ([WindowSpace] -> [WindowSpace])
+               -- ^ how to sort the workspaces.  See
+               -- "XMonad.Util.WorkspaceCompare" for some useful
+               -- sorts.
+               , ppxExtras :: [X (Maybe String)]
+               -- ^ loggers for generating extra information such as
+               -- time and date, system load, battery status, and so
+               -- on.  See "XMonad.Util.Loggers" for examples, or create
+               -- your own!
+               , ppxOutput :: String -> IO ()
+               -- ^ applied to the entire formatted string in order to
+               -- output it.  Can be used to specify an alternative
+               -- output method (e.g. write to a pipe instead of
+               -- stdout), and\/or to perform some last-minute
+               -- formatting.
+             }
+-- | Converts a PP to a PPX.
+ppToPPX :: PP -> PPX
+ppToPPX pp = PPX {
+               ppxCurrent = return . ppCurrent pp,
+               ppxVisible = return . ppVisible pp,
+               ppxHidden = return . ppHidden pp,
+               ppxHiddenNoWindows = return . ppHiddenNoWindows pp,
+               ppxUrgent = return . ppUrgent pp,
+               ppxSep = ppSep pp,
+               ppxWsSep = ppWsSep pp,
+               ppxTitle = return . ppTitle pp,
+               ppxLayout = return . ppLayout pp,
+               ppxOrder = ppOrder pp,
+               ppxSort = ppSort pp,
+               ppxExtras = ppExtras pp,
+               ppxOutput = ppOutput pp
+             }
+               
+
 -- | The default pretty printing options, as seen in 'dynamicLog'.
 defaultPP :: PP
 defaultPP = PP { ppCurrent         = wrap "[" "]"
}

Context:

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


More information about the xmonad mailing list