[xmonad] Visual hints for XMonad actions

Mario Pastorelli pastorelli.mario at gmail.com
Tue Dec 25 21:51:54 CET 2012


I wrote a patch for xmonad-contrib 0.10.1 to include an action to show 
some text in the centre of the screen. The patch is based on 
XMonad.Layout.ShowWName (thank you again Brandon Allbery) but it is an 
action and not a layout modifier. In this way it could be used to show 
some text when a key is pressed, for example. It includes an event 
handler to destroy the window after the timeout.
-------------- next part --------------
1 patch for repository http://code.haskell.org/XMonadContrib:

Tue Dec 25 21:26:35 CET 2012  pastorelli.mario at gmail.com
  * Add XMonad.Actions.ShowText


New patches:

[Add XMonad.Actions.ShowText
pastorelli.mario at gmail.com**20121225202635
 Ignore-this: 5f4818f7ec9ad37df58e73d4bb8b5590
] {
addfile ./XMonad/Actions/ShowText.hs
hunk ./XMonad/Actions/ShowText.hs 1
+{-# LANGUAGE DeriveDataTypeable #-}
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  XMonad.Actions.ShowText
+-- Copyright   :  (c) Mario Pastorelli (2012)
+-- License     :  BSD-style (see xmonad/LICENSE)
+--
+-- Maintainer  :  pastorelli.mario at gmail.com
+-- Stability   :  unstable
+-- Portability :  unportable
+--
+-- ShowText displays text for sometime on the screen
+-----------------------------------------------------------------------------
+
+module XMonad.Actions.ShowText
+    ( -- * Usage
+      -- $usage
+      defaultSTConfig
+    , handleTimerEvent
+    , flashText
+    , ShowTextConfig(..)
+    ) where
+
+import Control.Monad (when)
+import Data.Map (Map,empty,insert,lookup)
+import Prelude hiding (lookup)
+import XMonad
+import XMonad.StackSet (current,screen)
+import XMonad.Util.Font (Align(AlignCenter)
+                       , initXMF
+                       , releaseXMF
+                       , textExtentsXMF
+                       , textWidthXMF)
+import XMonad.Util.Timer (startTimer)
+import XMonad.Util.XUtils (createNewWindow
+                         , deleteWindow
+                         , fi
+                         , showWindow
+                         , paintAndWrite)
+import qualified XMonad.Util.ExtensibleState as ES
+
+-- $usage
+-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
+--
+-- > import XMonad.Actions.ShowText
+--
+-- Then add the event hook handler:
+--
+-- > xmonad { handleEventHook = myHandleEventHooks <+> handleTimerEvent }
+--
+-- You can then use flashText in your keybindings:
+--
+-- > ((modMask, xK_Right), flashText defaultSTConfig 1 "->" >> nextWS)
+--
+
+-- ShowText contains the map with timers as keys and created windows as values
+newtype ShowText = ShowText (Map Atom Window)
+    deriving (Read,Show,Typeable)
+
+instance ExtensionClass ShowText where
+    initialValue = ShowText empty
+
+-- | Utility to modify a ShowText
+modShowText :: (Map Atom Window -> Map Atom Window) -> ShowText -> ShowText
+modShowText f (ShowText m) = ShowText $ f m
+
+data ShowTextConfig =
+    STC { st_font :: String -- ^ Font name
+        , st_bg   :: String -- ^ Background color
+        , st_fg   :: String -- ^ Foreground color
+    }
+
+defaultSTConfig :: ShowTextConfig
+defaultSTConfig =
+    STC { st_font = "-misc-fixed-*-*-*-*-20-*-*-*-*-*-*-*"
+        , st_bg   = "black"
+        , st_fg   = "white"
+    }
+
+-- | Handles timer events that notify when a window should be removed
+handleTimerEvent :: Event -> X ()
+handleTimerEvent (ClientMessageEvent _ _ _ dis _ mtyp d) = do
+    (ShowText m) <- ES.get :: X ShowText
+    a <- io $ internAtom dis "XMONAD_TIMER" False
+    when (mtyp == a && length d >= 1)
+         (whenJust (lookup (fromIntegral $ d !! 0) m) deleteWindow)
+handleTimerEvent _ = return ()
+
+-- | Shows a window in the center of the screen with the given text
+flashText :: ShowTextConfig -> Rational -> String -> X ()
+flashText c i s = do
+  f <- initXMF (st_font c)
+  d <- asks display
+  sc <- gets $ fi . screen . current . windowset
+  width <- textWidthXMF d f s
+  (as,ds) <- textExtentsXMF f s
+  let hight = as + ds
+      ht    = displayHeight d sc
+      wh    = displayWidth d sc
+      y     = (fi ht - hight + 2) `div` 2
+      x     = (fi wh - width + 2) `div` 2
+  w <- createNewWindow (Rectangle (fi x) (fi y) (fi width) (fi hight))
+                      Nothing "" True
+  showWindow w
+  paintAndWrite w f (fi width) (fi hight) 0 (st_bg c) ""
+                (st_fg c) (st_bg c) [AlignCenter] [s]
+  releaseXMF f
+  io $ sync d False
+  t <- startTimer i
+  ES.modify $ modShowText (insert (fromIntegral t) w)
hunk ./xmonad-contrib.cabal 120
                         XMonad.Actions.KeyRemap
                         XMonad.Actions.RotSlaves
                         XMonad.Actions.Search
+                        XMonad.Actions.ShowText
                         XMonad.Actions.SimpleDate
                         XMonad.Actions.SinkAll
                         XMonad.Actions.SpawnOn
}

Context:

[Removes unused function spawnWithActions and redundant imports in XMonad.Actions.Launcher
c.lopez at kmels.net**20121215223714
 Ignore-this: 76d7ac195e186b491968a548a13889c
] 
[A.Launcher markup identifiers for haddock links
Adam Vogt <vogt.adam at gmail.com>**20121215165914
 Ignore-this: 2fd3fa1dd4e00d573dd359a4b6a7291b
] 
[Address warnings from Debug modules
Adam Vogt <vogt.adam at gmail.com>**20121215165525
 Ignore-this: f97416ae4feffe4e5f9916d14d9e1524
 
 The warnings were related to ghc-7.6 removing Prelude.catch
 (triggering warnings regarding the import hiding it), as well
 as defaulting of some numeric types.
] 
[Removes LocateMode and LocateRegexMode from XMonad.Actions.Launcher
c.lopez at kmels.net**20121214211230
 Ignore-this: b8ad32f23f15368a94202f9ad73995f2
] 
[debug-hooks
allbery.b at gmail.com**20120813223821
 Ignore-this: 7f41c93fdd6643c687598d2fe07aad5d
 Hooks to print diagnostic information to stderr (usually .xsession-errors)
 to help debug complex issues involving the StackSet and received events.
] 
[Remove trailing whitespace.
Adam Vogt <vogt.adam at gmail.com>**20121109014156
 Ignore-this: 72e3afb6e6df47c51262006601765365
] 
[Use Control.Exception.catch explitly to avoid warnings
Adam Vogt <vogt.adam at gmail.com>**20121109013506
 Ignore-this: 2cebdfe604c581f2b4a644e9aed726c7
 
 The base that comes with ghc-7.6.1 no longer includes Prelude.catch;
 so these modules were changed so that there is no warning for
 
 import Prelude hiding (catch)
 
 At the same time these changes should be compatible with older GHCs,
 since the catch being has never been the one in the Prelude.
] 
[Add missing type signatures.
Adam Vogt <vogt.adam at gmail.com>**20121109012752
 Ignore-this: f54f5d9907ae48d58c98de7f8eb1f8a
 
 For whatever reason, some patches applied were missing these signatures.
 While haddock has been able to include inferred signatures for a while,
 including type signatures makes it easier to see if and when types have
 been changed.
] 
[Rename variables "state" to avoid warnings about shadowing
Adam Vogt <vogt.adam at gmail.com>**20121109012316
 Ignore-this: cd063d632412f758ca9fed6393521c8f
 
 XMonad core re-exports Control.Monad.State, which includes
 a function "state" if you happen to use mtl-2. Since there's
 a chance xmonad still works with mtl-1 avoid imports like:
 
 import XMonad hiding (state)
] 
[Rename variable in L.Minimize to avoid shadowing.
Adam Vogt <vogt.adam at gmail.com>**20121109003410
 Ignore-this: b46d3e8e0d4106cea6966116be386677
 
 This "state" is new with a newer mtl.
] 
[Gut H.ICCCMFocus: issue 177 has been merged in core.
Adam Vogt <vogt.adam at gmail.com>**20121108225716
 Ignore-this: 937fe7f514ea6e36ee529e055e100e7f
 
 Keep the module for now: the LG3D bit might still be useful
 and there's no need to break configs unnecessarily.
] 
[ewmh-eventhook-custom
pastorelli.mario at gmail.com**20120816153032
 Ignore-this: 95176f6d955d74321c28caafda63faa0
 
 Add ewmhDesktopsEventHookCustom, a generalized version of ewmhDesktopsEventHook that takes a sort function as argument. This sort function should be the same used by the LogHook.
] 
[Added smart spacing to the spacing module
daedalusinfinity at gmail.com**20120923034527
 Ignore-this: 9104bc8feb832f63f2f18998c0f7ba92
 Added smart spacing to the spacing module, which adds spacing to all windows,
 except to windows on singleton workspaces.
] 
[Improves haddock documentation
c.lopez at kmels.net**20120826091716
 Ignore-this: a0ce4838652acfff7922c111e4d879bb
] 
[Improve comments, add an error throw that shouldn't happen
c.lopez at kmels.net**20120826085426
 Ignore-this: 7675070826b3c53499e4352e692d6036
] 
[fix a bug when ncompletions = nrows
c.lopez at kmels.net**20120826083137
 Ignore-this: 5f573028318473c333809217c271a81d
] 
[Fixes typos in Actions.Launcher haddock documentation
c.lopez at kmels.net**20120811112502
 Ignore-this: f8152c0ad59d2b0cc9a6c9061e83aaf0
] 
[Correctly get the autocompletion item when alwaysHighlight in XMonad.Prompt is True
c.lopez at kmels.net**20120811104805
 Ignore-this: fa2600df210c7d3472a797f19fb31a7
] 
[Removes warnings, adds a browser value for LauncherConfig in haddock comments
c.lopez at kmels.net**20120628114533
 Ignore-this: 2610cf63594db3df61bac52f3d8f5836
 
] 
[Changes on XPrompt:
c.lopez at kmels.net**20120628101749
 Ignore-this: 2384f5c1b886716b3d9785877c2e32f9
   
     * Adds mkPromptWithModes, creates a prompt given a list of modes (list of XPType).
 
     * Adds Setting `alwaysHighlight` to defaultXPConfig. When set to true, autocompletion always highlight the first result if it is not highlighted.
     
 Adds module XMonad.Actions.Launcher. This module allows to combine and switch between instances of XPrompt. It includes a default set of modes which require the programs `hoogle`, `locate` and `calc` to be installed to work properly.
 
] 
[accept more windows as docks
Daniel Wagner <daniel at wagner-home.com>**20120823124153
 Ignore-this: 21d9b406c7e39cca2cc60331aab04873
] 
[strip newlines from dmenu's returns to be compatible with the newest version of dmenu
longpoke at gmail.com**20120723212807
 Ignore-this: 3b11a35125d0bc23b33e0b926562f85a
] 
[A workscreen permits to display a set of workspaces on several
kedals0 at gmail.com**20120706093308
 Ignore-this: 572ed3c3305205bfbcc17bb3fe2600a3
 screens. In xinerama mode, when a workscreen is viewed, workspaces
 associated to all screens are visible.
 
 The first workspace of a workscreen is displayed on first screen,
 second on second screen, etc. Workspace position can be easily
 changed. If the current workscreen is called again, workspaces are
 shifted.
 
 This also permits to see all workspaces of a workscreen even if just
 one screen is present, and to move windows from workspace to workscreen.
] 
[refer to the new name 'handleEventHook' instead of the old name 'eventHook' in X.L.Fullscreen documentation
Daniel Wagner <daniel at wagner-home.com>**20120618181003
 Ignore-this: bd3b26c758cf3993d5a93957bb6f3663
] 
[UrgencyHooks made available as Window -> X () functions
gopsychonauts at gmail.com**20120504062339
 Ignore-this: 6a57cae1d693109b7e27c6471d04f50f
 Adds an UrgencyHook instance for the type Window -> X (), allowing any such
 functions to be used directly as UrgencyHooks. The Show and Read constraints
 were removed from the UrgencyHook class in order to permit this; these
 constraints were required only in a historical implementation of the module,
 which used a layout modifier.
 
 All existing configurations using UrgencyHooks should remain fully functional.
 New configs may make use of this modification by declaring their UrgencyHook as
 a simple Window -> X () function.
 
] 
[updates to XMonad.Prompt re: word-oriented commands
Brent Yorgey <byorgey at cis.upenn.edu>**20120510174317
 Ignore-this: 138b5e8942fe4b55ad7e6ab24f17703f
 
   + change killWord and moveWord to have emacs-like behavior: first move
     past/kill consecutive whitespace, then move past/kill consecutive
     non-whitespace.
 
   + create variants killWord' and moveWord' which take a predicate
     specifying non-word characters.
 
   + create variants defaultXPKeymap' and emacsLikeXPKeymap' which take
     the same sort of predicate, which is applied to all keybindings with
     word-oriented commands.
] 
[Added isUnfocusedOnCurrentWS and fadeInactiveCurrentWSLogHook for better support of fading/opacity on multi monitor setups
Jesper Reenberg <jesper.reenberg at gmail.com>**20120329141818
 Ignore-this: d001a8aafbcdedae21ccd1d18f019185
] 
[Fixed X.A.GridSelect to be consistent in the way it (now) sorts the shown
Jesper Reenberg <jesper.reenberg at gmail.com>**20120501180415
 Ignore-this: 1d0991f9fb44e42f5d1c5a4f427ea661
 elements when modifying the searchString.
 
 The implemented ordering sorts based on how "deep the needle is in the
 haystack", meaning that searching for "st" in the elements "Install" and "Study"
 will order them as "Study" and "Install". Previously there was no ordering and
 when using GridSelect to select workspaces, the ordering was not consistent, as
 the list of workspaces (if not modified manually) is ordered by last used. In
 this case either "Study" or "Install" would come first depending on which
 workspace was last visited.
] 
[Use getXMonadDir to get the default xmonad directory.
Julia Jomantaite <julia.jomantaite at gmail.com>**20120501121427
 Ignore-this: a075433761488b76a58a193aeb4e4a25
] 
[Minor haddock formatting for X.L.OnHost and X.A.DynamicWorkspaceOrder
Adam Vogt <vogt.adam at gmail.com>**20120428194552
 Ignore-this: 843ec567e249cc96d51ca931f1e36514
] 
[Remove trailing whitespace.
Adam Vogt <vogt.adam at gmail.com>**20120428194048
 Ignore-this: d61584110954e84d3611ef3497a29725
] 
[Add emacs-like keys to browse history in XMonad.Prompt
Carlos Lopez-Camey <c.lopez at kmels.net>**20120421110737
 Ignore-this: b90345f72007d09a6b732b974c0faf79
] 
[Adds an emacs-like Keymap in XMonad.Prompt
Carlos Lopez-Camey <c.lopez at kmels.net>**20120421012335
 Ignore-this: f281b8ad01f3d21055e2d6de79af2d79
] 
[add 'withNthWorkspace' to DynamicWorkspaceOrder.
jakob at pipefour.org**20120407184640
 Ignore-this: f5f87ffe9ddf1a12fab775e6fb8e856f
 Note this is very similar to the function of the same name exported by
 DynamicWorkspaces.  Ultimately it would probably be cleaner to
 generalize the one in DynamicWorkspaces to accept an arbitrary
 workspace sort as a parameter; this is left as an exercise for future
 hackers.
] 
[XMonad.Layout.OnHost allows host-specific modifications to a layout, which
allbery.b at gmail.com**20120320030912
 Ignore-this: 4c0d5580e805ff9f40918308914f3bf9
 is otherwise very difficult to do.  Similarly to X.L.PerWorkspace, it provides
 onHost, onHosts, modHost, and modHosts layout modifiers.  It attempts to do
 smart hostname comparison, such that short names will be matched with short
 names and FQDNs with FQDNs.
 
 This module currently requires that $HOST be set in the environment.
 You can use System.Posix.Env.setEnv to do so in xmonad.hs if need be.
 (Properly, this should be done via the network library, but I'm trying to
 avoid adding that dependency.)  An alternative would be to shell out to
 get the name, but that has considerable portability hurdles.
] 
[Bump version to 0.10.1
Adam Vogt <vogt.adam at gmail.com>**20120320005311
 Ignore-this: f0608ffaa877f605eaa86c45a107a14d
 
 Raising the X11 dependency while keeping the xmonad version the same leads to
 problems where cabal install uses the dependency versions following hackage,
 not what is installed.
] 
[narrower BorderResize rectangles placed within border edges
Jens Petersen <juhp at community.haskell.org>**20120314064703
 Ignore-this: 3a43bbdb7f2317d702edafb231f58802
 
   Change the border resize rectangles to be narrower and only extend
   inside the window not outside.  Most window managers just seem to use
   the border decoration area for starting resizes which is often just 1 pixel
   wide but as a compromise the width is now 2 pixels (before it was 10!).
   The rectangles are now placed symmetrically within the border and window.
   This seems to work ok with PositionStoreFloat for the Bluetile config.
] 
[add-dynamic-bars-module
Ben Boeckel <mathstuf at gmail.com>**20120316002204
 Ignore-this: 41347c8f894d8d0b5095dfad86784cf4
 
 This adds the X.H.DynamicBars module. It allows per-screen status bars to be
 easily managed and dynamically handles the number of screens changing.
] 
[bump X11 dependency so that noModMask is available
Daniel Wagner <daniel at wagner-home.com>**20120316000302
 Ignore-this: 971a75dcad25f66848eef4174cd4ddd1
] 
[Paste.hs: rm noModMask, shifted definition to X11 binding (see previous email)
gwern0 at gmail.com**20111203203038
 Ignore-this: dcd164ff8f8f135c8fdef08f42f9244d
] 
[GroupNavigation: fix import typo in usage
Jens Petersen <juhp at community.haskell.org>**20120312103349
 Ignore-this: 65367218ca50a33a37813469b4616f34
] 
[add sendToEmptyWorkspace to FindEmptyWorkspace
Jens Petersen <juhp at community.haskell.org>**20120312102331
 Ignore-this: 50e7992d80d2db43e4d0adf5c95e964f
 
 sendToEmptyWorkspace is like tagToEmptyWorkspace except
 it does not change workspace after moving the window.
] 
[xmonad-contrib.cabal: simplify xmonad dependency to >=0.10 && < 0.11
Jens Petersen <juhp at community.haskell.org>**20120312101800
 Ignore-this: 1ff5a0caa2a1e3487e9a0831e385b3d2
 
 Unless there is a particular reason for listing the lower and upper bounds
 separately then this seems simpler and cleaner.
] 
[ShowWName: Increase horizontal padding for flash
crodjer at gmail.com**20120305164517
 Ignore-this: de5fd30fad2630875c5c78091f07c324
 
 Currently the flash window width leaves a very small amount of padding. This
 patch adds some extra horizontal width, governed by text width and length.
] 
[persist-togglehook-options
Ben Boeckel <mathstuf at gmail.com>**20120311050143
 Ignore-this: 580bacb35b617c1198f01c5a7c0d3fef
 
 Save the state of ToggleHook options over a restart.
] 
[ShowWName flash window background color
Rohan Jain <crodjer at gmail.com>**20120306065224
 Ignore-this: 9cd8fcfc13cc326b9dcc79ef3cc21b26
 
 While calling paintAndWrite for flash window, the background color from config
 should also be passed on as window background in addition to as text background
 color. Otherwise the window color gets set to the default black which shows up
 when text cannot span whole of the window.
 
 This issue becomes visible when the font size is considerably large or even in
 small size with truetype fonts.
] 
[ShowWName: Fix flash location by screen rectangle
crodjer at gmail.com**20120305161240
 Ignore-this: 83ec4cce2297efc6736a1fe55f44ee73
 
 In case of using this hook with multiple monitors, the Tag flash was not
 following the screen's coordinates. This patch shifts the new window created for
 flash according to the Rectangle defined by the screen.
] 
[Fix typo in tabbed layout link for font utils docs
crodjer at gmail.com**20120229070022
 Ignore-this: 2f7e90269e08ce08264d7b1d05bb16f9
] 
[L.WorkspaceDir: cleanup redundant {definitions,imports}
Steffen Schuldenzucker <sschuldenzucker at uni-bonn.de>**20120229112124
 Ignore-this: 7a796b18a64e693e071e9ea3a6a01aa3
] 
[fix L.WorkspaceDir special char handling: remove "echo -n" processing
Steffen Schuldenzucker <sschuldenzucker at uni-bonn.de>**20120227122004
 Ignore-this: ab48687eb4c9018312089a13fd25ecd8
] 
[Add BorderUrgencyHook to XMonad.Hooks.UrgencyHook
allbery.b at gmail.com**20120225082616
 Ignore-this: 9fac77914ff28a6e9eb830e8c9c7e21e
 BorderUrgencyHook is a new UrgencyHook usable with withUrgencyHook or
 withUrgencyHookC; it allows an urgent window to be given a different
 border color.  This may not always work as intended, since UrgencyHook
 likes to assume that a window being visible is sufficient to disable
 urgency notification; but with suppressWhen = Never it may work well
 enough.
 
 There is a report that if a new window is created at the wrong time,
 the wrong window may be marked urgent somehow.  I seem to once again
 be revealing bugs in underlying packages, although a quick examination
 of X.H.UrgencyHook doesn't seem to show any way for the wrong window
 to be selected.
] 
[Adding use case for namedScratchpad.
nicolas.dudebout at gatech.edu**20120122235843
 Ignore-this: 44201e82bcd708cd7098f060345400f1
] 
[Actions.WindowGo: typo fix - trim 's' per cub.uanic https://code.google.com/p/xmonad/issues/detail?id=491
gwern0 at gmail.com**20120116224244
 Ignore-this: fb1d55c1b4609069c55f13523c091260
] 
[XMonad.Actions.PhysicalScreens: fix typo spotted by Chris Pick <haskell at chrispick.com>
gwern0 at gmail.com**20120115223013
 Ignore-this: eb73b33b07dc58a36d3aa00bc8ac31c2
] 
[roll back previous incorrect fix
Daniel Wagner <daniel at wagner-home.com>**20120111214133
 Ignore-this: 91496faef411e6ae3442498b528d119b
] 
[Extending: fix http://code.google.com/p/xmonad/issues/detail?id=490
gwern0 at gmail.com**20120111211907
 Ignore-this: 515afbed507c070d60ab547e98682f12
] 
[another documentation patch: XMonadContrib.UpdatePointer -> XMonad.Actions.UpdatePointer
Daniel Wagner <daniel at wagner-home.com>**20120111211226
 Ignore-this: 1444e4a3f20ba442602ef1811d0b32c7
] 
[documentation patch, fixes issue 490
Daniel Wagner <daniel at wagner-home.com>**20120111210832
 Ignore-this: 8d899e15f9d1a657e9fc687e2f649f45
] 
[X.H.EwmhDesktops note that fullscreenEventHook is not included in ewmh
Adam Vogt <vogt.adam at gmail.com>**20120102211404
 Ignore-this: 92f15fa93877c165158c8fbd24aa2360
 
 Just a documentation fix (nomeata's suggestion at issue 339).
] 
[X.H.EwmhDesktops haddock formatting.
Adam Vogt <vogt.adam at gmail.com>**20120102211203
 Ignore-this: cfff985e4034e06a0fe27c52c9971901
] 
[X.A.Navigation2D
Norbert Zeh <nzeh at cs.dal.ca>**20111208205842
 Ignore-this: 3860cc71bfc08d99bd8279c2e0945186
 
 This is a new module to support directional navigation across multiple screens.
 As such it is related to X.A.WindowNavigation and X.L.WindowNavigation, but it
 is more general.  For a detailed discussion of the differences, see
 http://www.cs.dal.ca/~nzeh/xmonad/Navigation2D.pdf.
] 
[documentation patch: mention PostfixOperators
Daniel Wagner <daniel at wagner-home.com>**20111210234820
 Ignore-this: 20a05b1f396f18a742346d6e3daea9a8
] 
[P.Shell documentation and add missing unsafePrompt export
Adam Vogt <vogt.adam at gmail.com>**20111207163951
 Ignore-this: a03992ffdc9c1a0f5bfa6dafc453b587
 
 Haddock (version 2.9.2 at least) does not attach documentation to any of a b or
 c when given:
 
     -- | documentation
     a,b,c :: X
 
] 
[Paste: 3 more escaped characters from alistra
gwern0 at gmail.com**20111129160335
 Ignore-this: 46f5b86a25bcd2b26d2e07ed33ffad68
] 
[unfuck X.U.Paste
Daniel Wagner <daniel at wagner-home.com>**20111129032331
 Ignore-this: d450e23ca026143bb6ca9d744dcdd906
] 
[XMonad.Util.Paste: +alistra's patch for fixing his pasting of things like email address (@)
gwern0 at gmail.com**20111128215648
 Ignore-this: 4af1af27637fe056792aa4f3bb0403eb
] 
[XMonad.Util.Paste: rm myself from maintainer field; I don't know how to fix any of it even if I wanted
gwern0 at gmail.com**20111128213001
 Ignore-this: 87a4996aaa5241428ccb13851c5eb455
] 
[XMonad.Prompt.Shell: improve 'env' documentation to cover goodgrue's problem
gwern0 at gmail.com**20111127231507
 Ignore-this: 7b652a280960cbdf99c236496ca091b0
] 
[Fix spelling 'prefered' -> 'preferred'.
Erik de Castro Lopo <erikd at mega-nerd.com>**20111125010229
 Ignore-this: f2eac1728b5e023399188becf867a14d
] 
[Restore TrackFloating behavior to an earlier version.
Adam Vogt <vogt.adam at gmail.com>**20111120045538
 Ignore-this: 1a1367b4171c3ad23b0553766021629f
 
 Thanks for liskni_si for pressing the matter: without this change it is very
 broken, with the patch it is still not perfect but still useful.
] 
[Explicitly list test files in .cabal
Adam Vogt <vogt.adam at gmail.com>**20111118232511
 Ignore-this: ac48a0d388293cc6c771d676aaf142e3
 
 In the future, require Cabal >= 1.6 to be able to just write tests/*.hs
] 
[TAG 0.10
Adam Vogt <vogt.adam at gmail.com>**20111118225640
 Ignore-this: 8f81b175b902e985d584160fc41ab7d1
] 
Patch bundle hash:
dfa067cfe53383919e91f7bce00696b6ec520cdd


More information about the xmonad mailing list