New patches: [XSelection.hs: Implementing Spencer's efficiency suggestion gwern0@gmail.com**20071011220730] < > { hunk ./XSelection.hs 39 module XMonadContrib.XSelection (getSelection, promptSelection, putSelection) where -- getSelection, putSelection's imports: -import Graphics.X11.Xlib (allocaXEvent, createSimpleWindow, defaultScreen, destroyWindow, internAtom, nextEvent, openDisplay, rootWindow, selectionNotify, Display(), Atom(), XEventPtr(), selectionRequest, sendEvent, noEventMask, sync) +import Graphics.X11.Xlib (allocaXEvent, createSimpleWindow, defaultScreen, destroyWindow, internAtom, nextEvent, rootWindow, selectionNotify, Display(), Atom(), XEventPtr(), selectionRequest, sendEvent, noEventMask, sync) import Graphics.X11.Xlib.Extras (currentTime, ev_event_type, getEvent, getWindowProperty8, xConvertSelection, xSetSelectionOwner, xGetSelectionOwner, changeProperty8, propModeReplace, setSelectionNotify, ev_requestor, ev_selection, ev_target, ev_property, ev_time, ev_event_display) import Data.Maybe (fromMaybe) import Control.Concurrent (forkIO) hunk ./XSelection.hs 47 import Control.Exception as E (catch) -- promptSelection's imports: -import XMonad (io, spawn, X ()) +import XMonad (io, spawn, withDisplay, X ()) -- decode's imports import Foreign (Word8(), (.&.), shiftL, (.|.)) hunk ./XSelection.hs 54 -- | Returns a String corresponding to the current mouse selection in X; if there is none, an empty string is returned.. Note that this is -- only reliable for ASCII text and currently mangles/escapes more complex UTF-8 characters. -getSelection :: IO String -getSelection = do - dpy <- openDisplay "" +getSelection :: X String +getSelection = withDisplay $ \dpy -> io $ do let dflt = defaultScreen dpy rootw <- rootWindow dpy dflt win <- createSimpleWindow dpy rootw 0 0 200 100 0 0 0 hunk ./XSelection.hs 76 else destroyWindow dpy win >> return "" -- | Set the current X Selection to a given String. -putSelection :: String -> IO () -putSelection text = do - dpy <- openDisplay "" +putSelection :: String -> X () +putSelection text = withDisplay $ \dpy -> io $ do let dflt = defaultScreen dpy rootw <- rootWindow dpy dflt win <- createSimpleWindow dpy rootw 0 0 200 100 0 0 0 hunk ./XSelection.hs 117 -- for handling URLs, in particular. For example, in your Config.hs you could bind a key to 'promptSelection "firefox"'; this would allow you to -- highlight a URL string and then immediately open it up in Firefox. promptSelection :: String -> X () -promptSelection app = spawn . ((app ++ " ") ++) =<< io getSelection +promptSelection app = spawn . ((app ++ " ") ++) =<< getSelection {- UTF-8 decoding for internal use in getSelection. This code is copied from Eric Mertens's utf-string library (version 0.1), which is BSD-3 licensed, as is this module. } Context: [Added wmii like actions extension. Juraj Hercek **20071010201452] [Remove spurious output from ShellPrompt Spencer Janssen **20071011182816] [add/reformat (commented out) tracing code to SwitchTrans l.mai@web.de**20071011022139] [NoBorders bugfix (I hope) l.mai@web.de**20071011021756 David Roundy should probably have a look at this, but this change makes sense to me. Plus it makes NoBorders work in combination with SwitchTrans. :-) ] [Add XSelection to MetaModule Spencer Janssen **20071010160340] [Add WindowPrompt: the XPrompt equivalent of WindowBringer Andrea Rossato **20071009164047] [WindowBringer: export windowMapWith used by WindowPrompt Andrea Rossato **20071009163505] [MetaModule: added WindowPrompt Andrea Rossato **20071009163445] [XSelection.hs: Implement Andrea's idea for handling non-UTF-8 string cases gwern0@gmail.com**20071010020616] [XSelection.hs: a new module for XMonadContrib dealing with copy-and-paste gwern0@gmail.com**20071008222706 This is based on Andrea Rossato's standalone tools and is meant for integration straight into a Config.hs. It offers two main functions, 'getSelection' and 'putSelection', whose names should be self-explanatory. ] [LayoutScreens: update docs Spencer Janssen **20071008161441] [TwoPane: update docs Spencer Janssen **20071008161345] [DragPane: no need to deal with expose events in this simplified version Andrea Rossato **20071008143801] [make createNewWindow set background and foreground to a given color. David Roundy **20071008125206 This means we don't need to draw colors that are this color. Also speeds up redrawing, since the X server can do all the drawing on its own, without talking with xmonad. ] [Fix more LANGUAGE pragmas Shachaf Ben-Kiki **20071008115229 This patch should go after my other one -- I'd missed some files that used -fglasgow-exts. ] [Add LANGUAGE pragams Shachaf Ben-Kiki **20071008022141 It seems that GHC 6.6 just enables -fglasgow-exts when it sees any LANGUAGE pragma, so not all of them were added; this patch adds the rest of them, which is necessary for xmonad to compile in GHC >=6.7. ] [fix SwitchTrans some more l.mai@web.de**20071007224116] [update doco Devin Mullins **20071007215906] [add bringMenu, and extract duplication Devin Mullins **20071007215532] [DragPane must handle ExposeEvent too Andrea Rossato **20071008074702] [Tabbed and XPrompt updated to lates Extras changes Andrea Rossato **20071007163825] [ShellPrompt.hs: add getShellCompl to export list gwern0@gmail.com**20071007220236 getShellCompl is useful for writing prompts in Config.hs or even full standalone prompts; and personally, if a small utility function like 'split' can be exported, how much more so something useful like getShellCompl? ] [doc fixes for ManageDocks Devin Mullins **20071007204016] [fix(?) SwitchTrans (makes noBorders work again) l.mai@web.de**20071007193055] [avoid compiler warning in FlexibleManipulate l.mai@web.de**20071007163509] [d'oh, add WindowBringer to MetaModule Devin Mullins **20071007185138] [Maybe? What Maybe? (rollback earlier dmenu change) Devin Mullins **20071007185915] [Enter WindowBringer, Bringer of Windows. Devin Mullins **20071007173633] [add dmenuMap function Devin Mullins **20071007172543] [update NoBorders.hs configuration documentation gwern0@gmail.com**20071007190621 It seems 'noBorder full' no longer hacks it. ] [ShellPrompt: check for executables and better error handling Andrea Rossato **20071007110133 Code contributed by Spencer (basically I just removed FilePath depenency). ] [Move my NextWorkspace functionality into CycleWS mail@joachim-breitner.de**20071007103933 Hi, This patch merges the additional functionality of my NextWorkspace into CycleWS, using a compatible interface for what was there before. Greetings, Joachim ] [ManageDocks now handles STRUT windows as well mail@joachim-breitner.de**20071007103116 It now also detects window with STRUT set and modifies the gap accordingly. Cheveats: * Only acts on STRUT apps on creation, not if you move or close them * To reset the gap, press Mod-b twice and restart xmonad (Mod-q) ] [NextWorkspace haddock improvement mail@joachim-breitner.de**20071007083216 I just added to the docs how to move a window to the next workspace _and_ switch to that (by >>’ing the two actions). Some users (like me, it seems) probably prefer that behaviour. Greetings, Joachim ] [NextWorkspace: Go forward or backward mail@joachim-breitner.de**20071006233010 Hi, inspired by RotView, I implemented an Extension that allows the user to go forward or backward in the list of workspaces, or to move the current window to the next or previous workspace. Haddock included. Works here, but hardly tested (and while tired). Cu torrow @ HacII, if you are there. Greetings, Joachim ] [Better EWMH support mail@joachim-breitner.de**20071007091648 Yay, SetWMName contains just what I need! Thanks Ivan, that saved me quite some work. Now the panel switch should work even when you start with xmonad right away, and don’t run it after metacity has run before :-] Greetings, Joachim ] [Add ShellPrompt to MetaModule Andrea Rossato **20071007075937] [Tabbed: updated to the last (unannounced) API changes Andrea Rossato **20071007072018] [ShellPrompt: fromMaybe requires importing Data.Maybe Andrea Rossato **20071007070148] [add MouseGestures to MetaModule l.mai@web.de**20071006230735] [re-add SwitchTrans to MetaModule l.mai@web.de**20071006230711] [add MouseGestures.hs to darcs l.mai@web.de**20071006230425] [document noBorders breakage l.mai@web.de**20071006230316] [Replace -fglasgow-exts with LANGUAGE pragma in WindowNavigation.hs nornagon@gmail.com**20071006224156] [Replace -fglasgow-exts with LANGUAGE pragma in ResizableTile.hs nornagon@gmail.com**20071006223156] [Replace -fglasgow-exts with LANGUAGE pragma in MosaicAlt.hs nornagon@gmail.com**20071006223025] [Replace -fglasgow-exts with LANGUAGE pragma in Grid.hs nornagon@gmail.com**20071006222320] [Replace -fglasgow-exts with LANGUAGE pragma in Dishes.hs nornagon@gmail.com**20071006222155] [update SwitchTrans for the new layout system l.mai@web.de**20071006212008] [Two new dynamic log functions that display the title of the currently focused window Christian Thiemann **20071006173113 I liked the window-title-in-statusbar feature of dwm very much and wanted to have that in XMonad as well. Somewhere on the net I found some code to put into Config.hs (and sorry, that was last week and I already forgot where I got it from) which I modified and put into the DynamicLog extension. One can now set the logHook in Config.hs either to dynamicLogWithTitle to get the usual layout description and workspace list plus window title enclosed in angle brackets, or dynamicLogWithTitleColored "white" (or "red" etc.) to have xmonad print out some ^fg() markers for dzen to display the window title in the given color. Some windows (like terminals or browsers) change their window title from time to time but xmonad does not recognize this. So I started learning Haskell to provide patches for X11-extras and xmonad so that PropertyNotify events are captured and, if the event notifies about a WM_NAME property change, call the logHook to update the status bar. Hope you find this useful, Christian ] [change Dmenu functions to return IO/X (Maybe String) Devin Mullins **20071006070959 dmenu exits with code 1 when you hit Escape, and I wanna create a contrib that takes advantage of that. This required changes in four contribs (Commands, DirectoryPrompt, ShellPrompt, and WorkspaceDir), and might require changes in users' Configs. Also, I'm not sure some of the changes I made to the client code are very Haskelly. Would appreciate input there. ] [fix problem found by Heffalump in CopyWindow. David Roundy **20071005143746] [(un)Manage Docks based on WINDOW_TYPE mail@joachim-breitner.de**20071006132802 Hi, this is a replacement for the example code in Config.hs that should detect and unamange, for example, the gnome-panel. The problem with that code is that it also unamangs dialog boxes from gnome-panel which then are not usable (no keyboard intput, at least here). Greetings, Joachim ] [MetaModule.hs: add Dishes. Joachim Fasting **20071006123900] [Dishes.hs: needs -fglasgow-exts. Joachim Fasting **20071006123851] [ResizableTile.hs: needs -fglasgow-exts. Joachim Fasting **20071006123550] [MetaModule.hs: whitespace. Joachim Fasting **20071006123540] [MetaModule.hs: add some missing imports. Joachim Fasting **20071006123525] [MetaModule.hs: typo. Joachim Fasting **20071006123214] [NoBorders.hs: unused bindings. Joachim Fasting **20071006102316] [NoBorders.smartBorders: add type signature. Joachim Fasting **20071006102210] [Grid.hs: needs -fglasgow-exts. Joachim Fasting **20071006102204] [EwmhWindows wrap up for inclusion mail@joachim-breitner.de**20071006110529 Now with haddock documentation, a proper header and nicer, warningfree code, ready for a first release and inclusion in XMonadConrib. It works for me, but needs more testing. If you run xmonad with gnome-panel or something similar, please try it. Thanks, Joachim ] [EwmhDesktops initial patch mail@joachim-breitner.de**20071005222540 What works so far, quit hackerish: * Number of Workspaces * Active current workspace * Names of workspaces More to come.. ] [get rid of obviated comment Devin Mullins **20071006055652] [get rid of duplicate mapWorkspaces function Devin Mullins **20071006055404] [add Grid to MetaModule l.mai@web.de**20071005230032] [basic docs for Grid l.mai@web.de**20071005225934] [import Grid.hs into repository l.mai@web.de**20071005013412] [Dishes layout. Stacks windows underneath masters. nornagon@gmail.com**20071005230038] [ShellPrompt: removed readline dependency and added escape character support Andrea Rossato **20071005112250] [XPrompt: added ^A and ^E and more Andrea Rossato **20071005112122 - added ^A (start of line) and ^E (end of line) - added support for escaping spaces (see an example of it's use in the new ShellPrompt) - some code cleanup: I'm now tracking changes to XPrompt also in modified version that supports i18n. This is the reason of some name changes. ] [Tabbed: check if we really have a window to focus Andrea Rossato **20071005111733] [add QC tests for SwapWorkspaces Devin Mullins **20071004081534 run with -i..:../tests ] [add man page doco Devin Mullins **20071004081504] [Maximize layout modifier Jamie Webb**20071004061202] [Add ^K and ^U support to XPrompt Eric Mertens **20071002210814] [Rename ResizableTile.Tall to ResizableTall Jamie Webb**20071003023000 Having two layouts named Tall was upsetting the deserialization code. ] [MosaicAlt take 2 Jamie Webb**20071003162533] [Mark modules that haven't been ported to the new API yet. Spencer Janssen **20071003164516 These need to be ported or removed before the 0.4 release. ] [More LANGUAGE pragmas Spencer Janssen **20071003164257] [Add XPropManage to MetaModule Spencer Janssen **20071003164236] [add swapping capability in WindowNavigation. David Roundy **20071003151755 This allows you to reorder your windows geometrically, by swapping the currently focussed window with ones that are up/down/right/left of it. The idea is that we should be able to manipulate windows based on the visual layout of the screen rather than some (possibly obscure) logical ordering. ] [export constructor to make ThreeColumns layout usable again Daniel Neri **20071003093103] [WindowNavigation: add configurable colors and the possibility to turn them off Andrea Rossato **20071003090017] [Add SwapWorkspaces to MetaModule Spencer Janssen **20071003163405] [add SwapWorkspaces (to reorder them on your number keys) Devin Mullins **20071002212407] [Layout -> LayoutClass for ResizableTile and MosaicAlt Jamie Webb**20071003010849] [NoBorders: reduce flicker Spencer Janssen **20071002213053] [TagWindows Karsten Schoelzel **20071002190526 Functions to work with window tags, including a XPrompt interface. These are stored in the window property "_XMONAD_TAGS" Adding also functions shiftHere and shiftToScreen (move to another module?). ] [Add XPropManage, a manageHook using XProperties Karsten Schoelzel **20071002190231] [make Spiral work with new layout class. David Roundy **20071002164735] [some renaming of classes and data types. David Roundy **20070929191238] [SimpleStacking is deprecated Spencer Janssen **20071002185604] [Make Tabbed use XUtils.releaseFont Andrea Rossato **20071002062709] [XUtils: added releaseFont Andrea Rossato **20071002062640] [An alternative mosaic layout implementation Jamie Webb**20071002011716] [Fix infinite loop in ResizableTile serialization Jamie Webb**20071002001254] [Use newtype deriving for Invisible Spencer Janssen **20071001151555] [Tabbed: updated usage information Andrea Rossato **20071001082219] [XMonadContrib.ResizableTile in darcs patch. matsuyama3@ariel-networks.com**20071001091411 I have fixed error "" to return Nothing. Thanks Andrea. ] [Commands: added recent layout commands Andrea Rossato **20070930213225] [Removed fromIMaybe from Tabbed ad added it to Invisible Andrea Rossato **20070930181912] [Tabbed: reintroduced shrinker configuration option and removed the unneeded Read instance Andrea Rossato **20070930131936] [Tabbed: moved string positioning to XUtils Andrea Rossato **20070930095441] [refactor paintAndWrite to take the alignment and hide string positioning Andrea Rossato **20070930095215] [make DraPane use XUtils Andrea Rossato **20070929172849] [make Tabbed use XUtils Andrea Rossato **20070929172823] [Added XUtils: a library for drawing Andrea Rossato **20070929172754] [enable color setting in WindowNavigation. David Roundy **20070929114531 This is still somewhat experimental, comments welcome. ] [Add smartBorders Spencer Janssen **20070929010946] [Give Invisible a definition for fail. Spencer Janssen **20070929051527 The default definition of fail calls error. This is very bad, as we rely on a non-bottom result. We should consider moving to MonadZero, to be on the safe side. ] [Tabbed: fixed a bug: when only one window is in the stack doLayout must still return a Tabbed (I Nothing) TConf Andrea Rossato **20070928223136] [Added Invisible to store layout state Andrea Rossato **20070928190107 Invisible is a data type to store information that will be lost when restarting XMonad (the idea came from David Roundy) ] [WindowNavigation now uses Invisible (plus some vertical alignement) Andrea Rossato **20070928185907] [DragPane now uses Invisible Andrea Rossato **20070928185832] [Tabbed now uses Invisible Andrea Rossato **20070928185808] [add new WindowNavigation module. David Roundy **20070928131906] [Tabbed: removed two little bugs due to the mess during the transition (my fault, sorry ;) Andrea Rossato **20070928085513] [DeManage.hs: doesn't need -fglasgow-exts. Joachim Fasting **20070928083639] [Use LANGUAGE pragmas over -fglasgow-exts Spencer Janssen **20070928181614] [remove SetLayout. David Roundy **20070928015855] [Various fixes to NoBorders. Hopefully fixes bug #42 Spencer Janssen **20070928174615] [Use LANGUAGE pragmas Spencer Janssen **20070928174602] [LayoutModifier: call unhook after releaseResources Spencer Janssen **20070928174510] [DynamicLog: sort first by index in the workspaces list, then by tag name Spencer Janssen **20070928144900] [Make modifier descriptions prettier Spencer Janssen **20070928053257] [Give Hinted a nice description Spencer Janssen **20070928053121] [LayoutModifier should have descriptions too Spencer Janssen **20070928053106] [Tabbed: give a nice description Spencer Janssen **20070928052608] [DynamicLog: print a description of the current layout Spencer Janssen **20070928051606] [Update docs Spencer Janssen **20070928034350] [Add simpler layoutHints Spencer Janssen **20070928034008] [NewTabbed: after a ReleaseResources we should return Tabbed Nothing... Andrea Rossato **20070928011645] [Move NewTabbed to Tabbed Spencer Janssen **20070927231840] [Remove Tabbed.hs Spencer Janssen **20070927231002] [Remove Decoration.hs Spencer Janssen **20070927230947] [DragPane:just code formatting Andrea Rossato **20070927083814] [NewTabbed: fixes a (reintroduced) bug and some code formatting Andrea Rossato **20070927083551 - The InvisibleMaybe patch reintroduced the rectangle bug. - Some code formatting - Corrected usage information ] [make NewTabbed use InvisibleMaybe to hide its cache. David Roundy **20070926202330] [make DragPane code a bit more compact. David Roundy **20070926191656] [hide implementation of DragPane from users. David Roundy **20070926191630] [make DragPane a bit more succinct. David Roundy **20070926190900] [make DragPane work with the new Layout class Andrea Rossato **20070926190439] [make MagicFocus work with the new Layout class Andrea Rossato **20070926114307] [NewTabbed: we must check if the sceen rectangle changed Andrea Rossato **20070926114056 - Check if rectangle changed - removed orphan instances warnings - some code formatting ] [fix DynamicWorkspaces. David Roundy **20070925220659] [Remove LayoutChoice, this functionality is in the core Spencer Janssen **20070925214912] [new SetLayout module. David Roundy **20070925205333] [make Accordian use pureLayout. David Roundy **20070925192117] [modifyLayout -> handleMessage. David Roundy **20070925182930] [Make Square work with class. David Roundy **20070925174446] [make Combo work with class David Roundy **20070925174417] [NewTabbed: fixed a bug and some code formatting Andrea Rossato **20070925133749 - Since now Operations.windows doesn't call sendMessage UnDoLayout anymore, doLayout must take care of destroying all tabs when only one window ( or none) is left on the workspace. - Some code formatting. ] [make Roledex work with Layout class Andrea Rossato **20070925153237] [make Accordion work with Layout class Andrea Rossato **20070925152307] [fix embarrassing bugs in LayoutModifier. David Roundy **20070924195726] [Added a NewTabbed module with a new tabbed layout to test Andrea Rossato **20070924193419] [LayoutModifier updated to use LayoutMessages Andrea Rossato **20070924193345] [move ThreeCol over to new class. David Roundy **20070924191632] [Use the new modifiers in LayoutHints Spencer Janssen **20070924062000] [Use the new layout switcher in Commands Spencer Janssen **20070924060541] [Follow kind changes in FindEmptyWorkspace Spencer Janssen **20070924055928] [update WorkspaceDir. David Roundy **20070923221456] [rename LayoutHelpers to LayoutModifier. David Roundy **20070923215956] [convert LayoutScreens to class. David Roundy **20070923215942] [Update NoBorders and LayoutHelpers. David Roundy **20070923192640] [add a hook to LayoutHelpers. David Roundy **20070923121723] [use default modifyLayout in Circle. David Roundy **20070923115257] [update LayoutHelpers to work with new Layout class. David Roundy **20070923114929] [make TwoPane work with Layout class Andrea Rossato **20070922124210] [Circle: must export type constructor Andrea Rossato **20070922124126] [make Circle work with Layout class. David Roundy **20070921215525] [Cope with StackSet export changes Spencer Janssen **20070924091031] [Rolodex.hs: add missing type signature. Joachim Fasting **20070919215436 div' is only used with Dimension, used Integral to keep it general. ] [Warp.hs: remove seemingly unused code. Joachim Fasting **20070919214634] [CopyWindow.hs: -Wall police. Joachim Fasting **20070919214556] [CopyWindow.copy: remove seemingly unnecessary parameter from helper func. Joachim Fasting **20070919214526] [DirectoryPrompt.hs: add missing type signature. Joachim Fasting **20070919213736] [LayoutChoice.hs: update module header. Joachim Fasting **20070919213101] [LayoutChoice.hs: add LANGUAGE pragma. Joachim Fasting **20070919212815] [SinkAll.hs: -Wall police. Joachim Fasting **20070919212359] [XPrompt.hs: replace 'borderWidth' with 'borderPixel' gwern0@gmail.com**20070918162950 borderWidth is already defined in Config.hs. Thus, if one attempted to use a prompt configuration different than defaultXPConfig, and one defined it in one's Config.hs where it should be, then the borderWidth field would cause a warning by -Wall, since borderWidth is already a name being used by XMonad at large. ] [Operations.sink is gone Spencer Janssen **20070917214113] [Match 'Remove Operations functions which have StackSet equivalents' from the core Spencer Janssen **20070917213329] [SshPrompt.hs: fix some copy/paste errors, rebind sshPrompt to not conflict with xmonadPrompt Brandon S Allbery KF8NH **20070916182520 Just a minor patch to the comments/documentation, which was clearly copied unchanged from ShellPrompt.hs. ] [make fixedLayout accept a list of Rectangles. David Roundy **20070911134845 This works nicely for describing a fixed xinerama-like layout. (e.g. when using two distinct VNC clients to log into a single VNC server and attain multiheadedness). ] [Fixing some typos and grammar in documentation. Michael Fellinger **20070911023158] [Typo in Tabbed.hs documentation Michael Fellinger **20070911021815] [ssh-global-known-hosts Brandon S Allbery KF8NH **20070909222432 Add support for global ssh known hosts file, which is checked for via $SSH_KNOWN_HOSTS or a standard list of locations. This is stripped of comments and hashed hosts, combined with the local hosts file (which is trated the same way), and duplicates eliminated. ] [add LayoutChoice module. David Roundy **20070906154955] [FloatKeys.hs: needs -fglasgow-exts to compile. Joachim Fasting **20070909144215] [DragPane.hs: needs -fglasgow-exts to compile. Joachim Fasting **20070909144205] [Unify Drag(UpDown)Pane Karsten Schoelzel **20070904210312] [add function and comment assisting use in resizing the screen. David Roundy **20070906125543] [Add FloatKeys for moving and resizing of floating windows with the keyboard Karsten Schoelzel **20070905212531] [Fix FlexibleResize for change in applySizeHints Karsten Schoelzel **20070905193926] [make dragPane handle thinner. David Roundy **20070905124139] [cleanup in WorkspaceDir. David Roundy **20070827185833] [new SetWMName module, useful for working around problems running Java GUI applications. Ivan Tarasov **20070826004411] [remove LayoutHooks module (which is unused). David Roundy **20070823154520] [cleanup in DwmPromote. David Roundy **20070823155437] [cleanup in ViewPrev. David Roundy **20070823155405] [clean up CopyWindow. David Roundy **20070823155912] [Add CycleWS to MetaModule Spencer Janssen **20070905203137] [CycleWS: a couple of simple functions to cycle between workspaces Andrea Rossato **20070821061132] [make Contrib use WorkspaceId = type String. David Roundy **20070820113813] [Add HintedTile docstring Spencer Janssen **20070905200310] [Docstring parser for generating xmonad build configs with default settings for extensions Alex Tarkovsky **20070905200128] [docs not generated in DragPane.hs Don Stewart **20070904232447] [TAG 0.3 Spencer Janssen **20070905022947] Patch bundle hash: d99913b9e66b8f2df0f4446ab0da24880a3432e3