darcs patch: New module: XMonad.Actions.TopicSpace

Sun Apr 19 10:52:39 CEST 2009 Nicolas Pouillard

Applied! nicolas.pouillard:
Sun Apr 19 10:52:39 CEST 2009 Nicolas Pouillard
* New module: XMonad.Actions.TopicSpace
Content-Description: A darcs patch for your repository!
New patches:
[New module: XMonad.Actions.TopicSpace Nicolas Pouillard
**20090419085239 Ignore-this: 4c20592ea6ca74f38545c5a1a002ef91 ] { addfile ./XMonad/Actions/TopicSpace.hs hunk ./XMonad/Actions/TopicSpace.hs 1 +----------------------------------------------------------------------------- +-- | +-- Module : XMonad.Actions.TopicSpace +-- Copyright : (c) Nicolas Pouillard +-- License : BSD-style (see LICENSE) +-- +-- Maintainer : Nicolas Pouillard +-- Stability : unstable +-- Portability : unportable +-- +-- Turns your workspaces into a more topic oriented system. +-- +-- This module allow to organize your workspaces on a precise topic basis. So +-- instead of having a workspace called `work' you can setup one workspace per +-- task. Here we will call these workspaces, topics. The great thing with +-- topics is that one can attach a directory that makes sense to each +-- particular topic. One can also attach an action that will be triggered +-- when switching to a topic that does not have any windows in it. So one can +-- attach our mail client to the mail topic, some terminals in the right +-- directory for the xmonad topic... This package also provides a nice way to +-- display your topics in a historical way using a custom `pprWindowSet' +-- function. You can also easily switch to recents topics using this history +-- of last focused topics. +-- +-- Here is an example of configuration using TopicSpace: +-- +-- @ +-- myTopicConfig :: TopicConfig +-- myTopicConfig = TopicConfig +-- { allTopics = +-- [ \"dashboard\" -- the first one +-- , \"admin\", \"build\", \"cleaning\", \"conf\", \"darcs\", \"haskell\", \"irc\" +-- , \"mail\", \"movie\", \"music\", \"talk\", \"text\", \"tools\", \"web\", \"xmonad\" +-- , \"yi\", \"documents\", \"twitter\", \"pdf\" +-- ] +-- , topicDirs = M.fromList $ +-- [ (\"conf\", \"w\/conf\") +-- , (\"dashboard\", \"Desktop\") +-- , (\"yi\", \"w\/dev-haskell\/yi\") +-- , (\"darcs\", \"w\/dev-haskell\/darcs\") +-- , (\"haskell\", \"w\/dev-haskell\") +-- , (\"xmonad\", \"w\/dev-haskell\/xmonad\") +-- , (\"tools\", \"w\/tools\") +-- , (\"movie\", \"Movies\") +-- , (\"talk\", \"w\/talks\") +-- , (\"music\", \"Music\") +-- , (\"documents\", \"w\/documents\") +-- , (\"pdf\", \"w\/documents\") +-- ] +-- , defaultTopicAction = const $ spawnShell >*> 3 +-- , defaultTopic = \"dashboard\" +-- , maxTopicHistory = 10 +-- , topicActions = M.fromList $ +-- [ (\"conf\", spawnShell >> spawnShellIn \"wd\/ertai\/private\") +-- , (\"darcs\", spawnShell >*> 3) +-- , (\"yi\", spawnShell >*> 3) +-- , (\"haskell\", spawnShell >*> 2 >> +-- spawnShellIn \"wd\/dev-haskell\/ghc\") +-- , (\"xmonad\", spawnShellIn \"wd\/x11-wm\/xmonad\" >> +-- spawnShellIn \"wd\/x11-wm\/xmonad\/contrib\" >> +-- spawnShellIn \"wd\/x11-wm\/xmonad\/utils\" >> +-- spawnShellIn \".xmonad\" >> +-- spawnShellIn \".xmonad\") +-- , (\"mail\", mailAction) +-- , (\"irc\", ssh somewhere) +-- , (\"admin\", ssh somewhere >> +-- ssh nowhere) +-- , (\"dashboard\", spawnShell) +-- , (\"twitter\", spawnShell) +-- , (\"web\", spawn browserCmd) +-- , (\"movie\", spawnShell) +-- , (\"documents\", spawnShell >*> 2 >> +-- spawnShellIn \"Documents\" >*> 2) +-- , (\"pdf\", spawn pdfViewerCmd) +-- ] +-- } +-- @ +-- +-- @ +-- -- extend your keybindings +-- myKeys = +-- [ ((modMask , xK_n ), spawnShell) -- %! Launch terminal +-- , ((modMask , xK_a ), currentTopicAction myTopicConfig) +-- , ((modMask , xK_g ), promptedGoto) +-- , ((modMask .|. shiftMask, xK_g ), promptedShift) +-- ... +-- ] +-- ++ +-- [ ((modMask, k), switchNthLastFocused defaultTopic i) +-- | (i, k) <- zip [1..] workspaceKeys] +-- @ +-- +-- @ +-- spawnShell :: X () +-- spawnShell = currentTopicDir myTopicConfig >>= spawnShellIn +-- @ +-- +-- @ +-- spawnShellIn :: Dir -> X () +-- spawnShellIn dir = spawn $ \"urxvt '(cd ''\" ++ dir ++ \"'' && \" ++ myShell ++ \" )'\" +-- @ +-- +-- @ +-- goto :: Topic -> X () +-- goto = switchTopic myTopicConfig +-- @ +-- +-- @ +-- promptedGoto :: X () +-- promptedGoto = workspacePrompt myXPConfig goto +-- @ +-- +-- @ +-- promptedShift :: X () +-- promptedShift = workspacePrompt myXPConfig $ windows . W.shift +-- @ +-- +-- @ +-- myConfig = do +-- checkTopicConfig myTopicConfig +-- myLogHook <- makeMyLogHook +-- return $ defaultConfig +-- { borderWidth = 1 -- Width of the window border in pixels. +-- , workspaces = allTopics myTopicConfig +-- , layoutHook = myModifiers myLayouts +-- , manageHook = myManageHook +-- , logHook = myLogHook +-- , handleEventHook = myHandleEventHook +-- , terminal = myTerminal -- The preferred terminal program. +-- , normalBorderColor = \"#3f3c6d\" +-- , focusedBorderColor = \"#4f66ff\" +-- , XMonad.modMask = mod1Mask +-- , keys = myKeys +-- , mouseBindings = myMouseBindings +-- } +-- @ +-- +-- @ +-- main :: IO () +-- main = xmonad =<< myConfig +-- @ +module XMonad.Actions.TopicSpace + ( Topic + , Dir + , TopicConfig(..) + , getLastFocusedTopics + , setLastFocusedTopic + , pprWindowSet + , topicActionWithPrompt + , topicAction + , currentTopicAction + , switchTopic + , switchNthLastFocused + , currentTopicDir + , checkTopicConfig + , (>*>) + ) +where + +import XMonad + +import Data.List +import Data.Maybe (fromMaybe, isNothing) +import Data.Ord +import qualified Data.Map as M +import Graphics.X11.Xlib +import Control.Monad ((=<<),liftM2,when,unless,replicateM_) +import System.IO +import Foreign.C.String (castCCharToChar,castCharToCChar) + +import XMonad.Operations +import Control.Applicative ((<$>)) +import qualified XMonad.StackSet as W + +import XMonad.Prompt +import XMonad.Prompt.Workspace + +import XMonad.Hooks.UrgencyHook +import XMonad.Hooks.DynamicLog (PP(..)) +import qualified XMonad.Hooks.DynamicLog as DL + +import XMonad.Util.Run (spawnPipe) + +-- | An alias for @flip replicateM_@ +(>*>) :: Monad m => m a -> Int -> m () +(>*>) = flip replicateM_ +infix >*> + +-- | 'Topic' is just an alias for 'WorkspaceId' +type Topic = WorkspaceId + +-- | 'Dir' is just an alias for 'FilePath' but should points to a directory. +type Dir = FilePath + +-- | Here is the topic space configuration area. +data TopicConfig = TopicConfig { allTopics :: [Topic] + -- ^ You have to give a list of topics, + -- this must the be same list than the workspaces field of + -- your xmonad configuration. + -- The order is important, new topics must be inserted + -- at the end of the list if you want hot-restarting + -- to work. + , topicDirs :: M.Map Topic Dir + -- ^ This mapping associate a directory to each topic. + , topicActions :: M.Map Topic (X ()) + -- ^ This mapping associate an action to trigger when + -- switching to a given topic which workspace is empty. + , defaultTopicAction :: Topic -> X () + -- ^ This is the default topic action. + , defaultTopic :: Topic + -- ^ This is the default topic. + , maxTopicHistory :: Int + -- ^ This setups the maximum depth of topic history, usually + -- 10 is a good default since we can bind all of them using + -- numeric keypad. + } + +-- | Returns the list of last focused workspaces the empty list otherwise. +-- This function rely on a reserved property namely _XMONAD_LAST_FOCUSED_WORKSPACES. +getLastFocusedTopics :: X [String] +getLastFocusedTopics = getStringListProp "_XMONAD_LAST_FOCUSED_WORKSPACES" + +-- | Given a 'TopicConfig', the last focused topic, and a predicate that will +-- select topics that one want to keep, this function will set the property +-- of last focused topics. +setLastFocusedTopic :: TopicConfig -> Topic -> (Topic -> Bool) -> X () +setLastFocusedTopic tg w predicate = + getLastFocusedTopics >>= + setStringListProp "_XMONAD_LAST_FOCUSED_WORKSPACES" + . take (maxTopicHistory tg) . nub . (w:) . filter predicate + +-- | This function is a variant of 'DL.pprWindowSet' which takes a topic configuration +-- and a pretty-printing record 'PP'. It will show the list of topics sorted historically +-- and highlighting topics with urgent windows. +pprWindowSet :: TopicConfig -> PP -> X String +pprWindowSet tg pp = do + winset <- gets windowset + urgents <- readUrgents + let empty_workspaces = map W.tag $ filter (isNothing . W.stack) $ W.workspaces winset + maxDepth = maxTopicHistory tg + setLastFocusedTopic tg (W.tag . W.workspace . W.current $ winset) + (`notElem` empty_workspaces) + lastWs <- getLastFocusedTopics + let depth topic = elemIndex topic lastWs + add_depth proj topic = proj pp $ maybe topic (((topic++":")++) . show) $ depth topic + pp' = pp { ppHidden = add_depth ppHidden, ppVisible = add_depth ppVisible } + sortWindows = take (maxDepth - 1) . sortBy (comparing $ fromMaybe maxDepth . depth . W.tag) + return $ DL.pprWindowSet sortWindows urgents pp' winset + +-- | Given a prompt configuration and a topic configuration, triggers the action associated with +-- the topic given in prompt. +topicActionWithPrompt :: XPConfig -> TopicConfig -> X () +topicActionWithPrompt xp tg = workspacePrompt xp (liftM2 (>>) (switchTopic tg) (topicAction tg)) + +-- | Given a configuration and a topic, triggers the action associated with the given topic. +topicAction :: TopicConfig -> Topic -> X () +topicAction tg topic = fromMaybe (defaultTopicAction tg topic) $ M.lookup topic $ topicActions tg + +-- | Trigger the action associated with the current topic. +currentTopicAction :: TopicConfig -> X () +currentTopicAction tg = topicAction tg =<< gets (W.tag . W.workspace . W.current . windowset) + +-- | Switch to the given topic. +switchTopic :: TopicConfig -> Topic -> X () +switchTopic tg topic = do + windows $ W.greedyView topic + wins <- gets (W.integrate' . W.stack . W.workspace . W.current . windowset) + when (null wins) $ topicAction tg topic + +-- | Switch to the Nth last focused topic or failback to the 'defaultTopic'. +switchNthLastFocused ::TopicConfig -> Int -> X () +switchNthLastFocused tg depth = do + lastWs <- getLastFocusedTopics + switchTopic tg $ (lastWs ++ repeat (defaultTopic tg)) !! depth + +-- | Returns the directory associated with current topic returns the empty string otherwise. +currentTopicDir :: TopicConfig -> X String +currentTopicDir tg = do + topic <- gets (W.tag . W.workspace . W.current . windowset) + return . fromMaybe "" . M.lookup topic $ topicDirs tg + +-- | Check the given topic configuration for duplicates topics or undefined topics. +checkTopicConfig :: TopicConfig -> IO () +checkTopicConfig tg = do + unless (null diffTopic) $ xmessage $ "Seen but missing workspaces (tags): " ++ show diffTopic + unless (null dups) $ xmessage $ "Duplicate workspaces (tags): " ++ show dups + where + seenTopics = nub $ sort $ M.keys (topicDirs tg) ++ M.keys (topicActions tg) + dups = tags \\ nub tags + diffTopic = seenTopics \\ sort tags + tags = allTopics tg + +type StringProp = String + +withStringProp :: StringProp -> (Display -> Window -> Atom -> X a) -> X a +withStringProp prop f = + withDisplay $ \dpy -> do + rootw <- asks theRoot + a <- io $ internAtom dpy prop False + f dpy rootw a + +-- | Get the name of a string property and returns it as a 'Maybe'. +getStringProp :: StringProp -> X (Maybe String) +getStringProp prop = + withStringProp prop $ \dpy rootw a -> do + p <- io $ getWindowProperty8 dpy a rootw + return $ map castCCharToChar <$> p + +-- | Set the value of a string property. +setStringProp :: StringProp -> String -> X () +setStringProp prop string = + withStringProp prop $ \dpy rootw a -> + io $ changeProperty8 dpy rootw a a propModeReplace $ map castCharToCChar string + +-- | Given a property name, returns its contents as a list. It uses the empty +-- list as default value. +getStringListProp :: StringProp -> X [String] +getStringListProp prop = return . maybe [] words =<< getStringProp prop + +-- | Given a property name and a list, sets the value of this property with +-- the list given as argument. +setStringListProp :: StringProp -> [String] -> X () +setStringListProp prop = setStringProp prop . unwords + +-- | Display the given message using the @xmessage@ program. +xmessage :: String -> IO () +xmessage s = do + h <- spawnPipe "xmessage -file -" + hPutStr h s + hClose h + hunk ./xmonad-contrib.cabal 105 XMonad.Actions.Submap XMonad.Actions.SwapWorkspaces XMonad.Actions.TagWindows + XMonad.Actions.TopicSpace XMonad.Actions.UpdatePointer XMonad.Actions.Warp XMonad.Actions.WindowNavigation } Context:
[NamedScratchpad konstantin.sobolev@gmail.com**20090419045542 Ignore-this: b442cb08123d2413e0bb144a73bf3f57 ] [More configurability for Layout.NoBorders (typeclass method) Adam Vogt
**20090325050206 Ignore-this: 91fe0bc6217b910b7348ff497b922e11 This method uses a typeclass to pass a function to the layoutmodifier. It is flexible, but a bit indirect and perhaps the flexibility is not required. ] [Add XMonad.Actions.PhysicalScreens nelhage@mit.edu**20090321001320
Add an XMonad.Actions.PhysicalScreens contrib module that allows addressing of screens by physical ordering, rather than the arbitrary ScreenID. ] [pointWithin has moved to the core Joachim Breitner
**20081008154245] [UpdatePointer even to empty workspaces Joachim Breitner **20081007080041 This makes UpdatePointer more Xinerama-compatible: If the user switches to a screen with an empty workspace, the pointer is moved to that workspace, which I think is expected behavoiur. ] [More predictable aspect ratio in GridVariants.Grid Norbert Zeh **20090311013617 The old version fairly arbitrarily decided to prefer windows that are too high over those that are too wide. The new version chooses the number of columns so that all windows on the screen are as close as possible to the desired aspect ratio. As a side effect, the layout changes much more predictably under addition and removal of clients. ] [X.L.Master: fix number of windows Ismael Carnales
**20090301051509 Ignore-this: 2af132159450d4fb72eb52024eda71b5 ] [U.EZConfig: add xK_Print <Print> to special keys wirtwolff@gmail.com**20090302230741 Ignore-this: 9560b7c7c4424edb5cea6eec45e2b41d Many setups are expecting xK_Print rather than xK_Sys_Req, so make it available in additionalKeysP. ] [More flexibility for H.FadeInactive Daniel Schoepe **20090309160020 Ignore-this: ebfa2eadb439763276b372107cdf8d6c ] [Prompt.Shell: escape ampersand Valery V. Vorotyntsev **20090312091314 Ignore-this: 7200b76af8109bab794157da46cb0030 Ampersand (&) is a special character and should be escaped. ] [Cleanup X.L.Mosaic, without breaking it Adam Vogt
**20090219022417 Ignore-this: d49ed55fe8dc2204256dff9252384745 ] [X.L.Mosaic: prevent users from causing non-termination with negative elements Adam Vogt **20090210022727 Ignore-this: 370a7d6249906f1743c6692758ce5aeb ] [better Layout.NoBorders.smartBorders behavior on xinerama Adam Vogt **20090314170058 Ignore-this: 36737ce2fa2087c4a16ddf226d3b0f0a Now smartBorders shows borders when you have multiple screens with one window each. In the case where only one window is visible, no borders are drawn. ] [H.DynamicLog: revised dzenStrip and xmobarStrip functions wirtwolff@gmail.com**20090314041517 Ignore-this: 9897c60b8dfc59344939b7aebc370953 Reconcile darcswatch patch with pushed version of dzenStrip. ] [X.H.DynamicLog: Add dzenStrip to remove formatting, for use in dzenPP's ppUrgent. Braden Shepherdson
**20090314032818 Ignore-this: fd96a1a4b112d0f71589b639b83ec3e This function was written by Wirt Wolff. This change should allow UrgencyHook to work out of the box with dzen and dzenPP, rather than the colours being overridden so even though UrgencyHook is working, it doesn't change colours. ] [X.H.ManageHelpers: export isInProperty Roman Cheplyaka **20090308201112] [L.Cross: clarify documentation wirtwolff@gmail.com**20090222042220 Ignore-this: 4a5dcf71e63d045f27e2340e1def5cc8 Amend-record earlier patch to work with byorgey's fix, this one is just the documentation typo fixes and clarifications. ] [documentation for IndependentScreens daniel@wagner-home.com**20090221235959] [eliminate a haddock warning in BoringWindows daniel@wagner-home.com**20090221235836] [merge IndependentScreens daniel@wagner-home.com**20090221232142] [add IndependentScreens to xmonad-contrib.cabal daniel@wagner-home.com**20090221231632] [add type information for IndependentScreens daniel@wagner-home.com**20090221231525] [add some boilerplate comments at the top of IndependentScreens Brent Yorgey **20090221230850] [IndependentScreens, v0.0 daniel@wagner-home.com**20090221225229] [U.Run: remove waitForProcess to close Issue 268 wirtwolff@gmail.com**20090220214153 Ignore-this: a6780565fde40a4aac9023cc55fc2273 http://code.google.com/p/xmonad/issues/detail?id=268 Submitting with some trepidation, since I've nearly no understanding of process handling. Should be ok, no warnings by sjanssen when asking about it in hpaste or earlier email, and tested locally by spawning excessive numbers of dzens: did not leave zombies or raise exceptions. ] [change Cross data declaration into a record so that Haddock will parse the per-argument comments Brent Yorgey **20090221224742] [X.L.Master: turn it to a Layout modifier and update the code Ismael Carnales **20090213020453 Ignore-this: 69513ad2b60dc4aeb49d64ca30e6f9f8 ] [Use doShift in my config Spencer Janssen **20090219042040 Ignore-this: 1f103d21bbceec8d48384f975f18eaec ] [SpawnOn: use doShift. This resolves problems where SpawnOn would shift the wrong window Spencer Janssen **20090219041856 Ignore-this: 6ae639a638db8eff77203f3f2e481a4e ] [SpawnOn: delete seen pids Spencer Janssen **20090213013011 Ignore-this: 8b15a60bba1edf1bab5fb77ac54eb12f ] [X.U.Loggers: handle possible EOF (reported by dyfrgi) Roman Cheplyaka **20090216213842] [U.Scratchpad: add general spawn action to close issue 249 wirtwolff@gmail.com**20090214003642 Ignore-this: 925ad9db4ecc934dcd86320f383ed44a Adds scratchpadSpawnActionCustom where user specifies how to set resource to "scratchpad". This allows use of gnome-terminal, etc. Add detail to RationalRectangle documentation; strip trailing spaces. ] [SpawnOn: add 'exec' to shell strings where possible Spencer Janssen **20090212234608 Ignore-this: c7de4e05803d60b10f38004dcbda4732 ] [Add Cross Layout 'Luis Cabellos '**20090209174802] [Fix an undefined in EwmhDesktops Daniel Schoepe **20090209152308 Ignore-this: f60a43d7ba90164ebcf700090dfb2480 ] [X.U.WindowProperties: docs (description and sections) Roman Cheplyaka **20090208231422] [X.U.WindowProperties: Add getProp32 and getProp32s, helpers to get properties from windows Ismael Carnales **20090205013031 Ignore-this: c5481fd5d97b15ca049e2da2605f65c1 ] [cleanup and make X.L.Mosaic behavior more intuitive wrt. areas Adam Vogt **20090208221629 Ignore-this: 3c3c6faa203cbb1c1db909e5bf018b6f ] [minor typo in XMonad/Util/EZConfig.hs Joachim Breitner **20090208192224 Ignore-this: 7ffee60858785c3e31fdd5383c9bb784 ] [Multimedia keys support for EZConfig Khudyakov Alexey **20090207173330 Ignore-this: 21183dd7c192682daa18e3768828f88d ] [+A.CycleWindows: bindings to cycle windows in new ways wirtwolff@gmail.com**20090207170622 Ignore-this: 51634299addf224cbbc421adb4b048f5 Provides binding actions and customizable pure stack operations to cycle through a list of permutations of the stack (recent), cycle nth into focus, cycle through focus excluding a neighbor, cycle unfocused, shift a window halfway around the stack. Esp. for Full, two or three pane layouts, but useful for any layout with many windows. ] [XMonad.Actions.CopyWindow: fmt & qualify stackset import gwern0@gmail.com**20090206171833 Ignore-this: 4d08f5a7627020b188f59fc637b53ae8 ] [XMonad.Actions.CopyWindow runOrCopy lan3ny@gmail.com**20080602205742] [ManageHelpers: reduce duplicated code in predicates Ismael Carnales **20090204021847 Ignore-this: e28a912d4f897eba68ab3edfddf9f26b ] [Remove X.U.SpawnOnWorkspace (superseded by X.A.SpawnOn) Roman Cheplyaka **20090204103635] [X.A.SpawnOn: add docs Roman Cheplyaka **20090204102424 Add more documentation, including documentation from X.U.SpawnOnWorkspace by Daniel Schoepe. ] [Remove silliness from XMonad.Doc.Configuring Spencer Janssen **20090204055626] [Adjustments to use the new event hook feature instead of Hooks.EventHook Daniel Schoepe **20090203160046 Ignore-this: f8c239bc8e301cbd6fa509ef748af542 ] [Easier Colorizers for X.A.GridSelect quentin.moser@unifr.ch**20090128001702 Ignore-this: df3e0423824e40537ffdb4bc7363655d ] [X.A.SpawOn: fix usage doc Roman Cheplyaka **20090202102042] [Added GridVariants.SplitGrid Norbert Zeh **20090129152146 GridVariants.TallGrid behaved weird when transformed using Mirror or Reflect. The new layout SplitGrid does away with the need for such transformations by taking a parameter to specify horizontal or vertical splits. ] [FixedColumn: added missing nmaster to the usage doc Ismael Carnales
**20090130195239 Ignore-this: 642aa0bc9e68e7518acc8af30324b97a ] [XMonad.Actions.Search: fix whitespace & tabs gwern0@gmail.com**20090129025246 Ignore-this: 894e479ccc46160848c4d70c2361c929 ] [xmonad-action-search-intelligent-searchengines Michal Trybus **20090128101938 Changed the XMonad.Action.Search to use a function instead of String to prepare the search URL.Added a few useful functions used to connect many search engines together and do intelligent prefixed searches (more doc in haddock)The API has not changed with the only exception of search function, which now accepts a function instead of String. ] [XMonad.Prompt autocompletion fix quentin.moser@unifr.ch**20090127184145 Ignore-this: 635cbf6420722a4edef1ae9c40b36e1b ] [X.A.SinkAll: re-add accidentally deleted usage documentation Brent Yorgey **20090127222533] [move XMonad.Actions.SinkAll functionality to more general XMonad.Actions.WithAll, and re-export sinkAll from X.A.SinkAll for backwards compatibility Brent Yorgey **20090127222355] [adds generic 'all windows on current workspace' functionality loupgaroublond@gmail.com**20081221224850] [placement patch to XMonad.Layout.LayoutHints quentin.moser@unifr.ch**20090126195950 Ignore-this: 87a5efa9c841d378a808b1a4309f18 ] [XMonad.Actions.MessageFeedback module quentin.moser@unifr.ch**20090126181059 Ignore-this: 82e58357a44f98c35ccf6ad0ef98b552 ] [submapDefault Anders Engstrom **20090118152933 Ignore-this: c8958d47eb584a7de04a81eb087f05d1 Add support for a default action to take when the entered key does not match any entry. ] [X.A.CycleWS: convert tabs to spaces (closes #266) Roman Cheplyaka **20090127185604] [Mosaic picks the middle aspect layout, unless overriden Adam Vogt **20090126032421 Ignore-this: aaa31da14720bffd478db0029563aea5 ] [Mosaic: stop preventing access to the widest layouts Adam Vogt **20090125045256 Ignore-this: c792060fe2eaf532f433cfa8eb1e8fe3 ] [X.L.Mosaic add documentation, update interface and aspect ratio behavior Adam Vogt **20090125041229 Ignore-this: e78027707fc844b3307ea87f28efed73 ] [Use currentTag, thanks asgaroth Spencer Janssen **20090125213331 Ignore-this: dd1a3d96038de6479eca3b9798d38437 ] [Support for spawning most applications on a specific workspace Daniel Schoepe **20090125191045 Ignore-this: 26076d54b131e037b42c87e4fde63200 ] [X.L.Mosaic: haddock fix Roman Cheplyaka **20090124235908] [A mosaic layout based on MosaicAlt Adam Vogt **20090124022058 Ignore-this: 92bad7498f1ac402012e3eba6cbb2693 The position of a window in the stack determines its position and layout. And the overall tendency to make wide or tall windows can be changed, though not all of the options presented by MosaicAlt can be reached, the layout changes with each aspect ratio message.
] [uninstallSignalHandlers in spawnPipe Spencer Janssen
**20090122002745 Ignore-this: e8cfe0f18f278c95d492628da8326fd7 ] [Create a new session for spawnPiped processes Spencer Janssen **20090122000441 Ignore-this: 37529c5fe8b4bf1b97fffb043bb3dfb0 ] [TAG 0.8.1 Spencer Janssen **20090118220647] [Use spawnOn in my config Spencer Janssen **20090117041026 Ignore-this: 3f92e4bbe4f2874b86a6c7ad66a31bbb ] [Add XMonad.Actions.SpawnOn Spencer Janssen **20090117040432 Ignore-this: 63869d1ab11f2ed5aab1690763065800 ] [Bump version to 0.8.1 Spencer Janssen **20090116223607 Ignore-this: 1c201e87080e4404f51cadc108b228a1 ] [Compile without optimizations on x86_64 and GHC 6.10 Spencer Janssen **20090108231650 Ignore-this: a803235b8022793f648e8953d9f05e0c This is a workaround for http://xmonad.org/bugs/226 ] [Update all uses of doubleFork/waitForProcess Spencer Janssen **20090116210315 Ignore-this: 4e15b7f3fd6af3b7317449608f5246b0 ] [Update to my config Spencer Janssen **20090116204553 Ignore-this: 81017fa5b99855fc8ed1fe8892929f53 ] [Adjustments to new userCode function Daniel Schoepe **20090110221310] [X.U.EZConfig: expand documentation Brent Yorgey **20090116153143] [add a bit of documentation to HintedTile Brent Yorgey **20090114065126] [ManageHelpers: add isDialog johanngiwer@web.de**20090108232505] [CenteredMaster portnov84@rambler.ru**20090111134513 centerMaster layout modifier places master window at top of other, at center of screen. Other windows are managed by base layout. topRightMaster is similar, but places master window at top right corner. ] [XMonad.Util.XSelection: update maintainer information gwern0@gmail.com**20090110213000 Ignore-this: 1592ba07f2ed5d2258c215c2d175190a ] [X.U.XSelection: get rid of warning about missing newline, add Haddock link Brent Yorgey
**20090102194357] [adds haddock documentation for transformPromptSelection loupgaroublond@gmail.com**20090102190954 also renames the function per mailing list recommendation ] [adds a weird function to XSelection loupgaroublond@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@c-otto.de**20090102091019] [fix-fromJust-errors rupa@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
**20081218001601] [X.L.Monitor: changes in message passing Roman Cheplyaka **20081226220851 - transform mbName (Maybe String) to name (String) - slghtly change semantics of messages, document it ] [X.L.Monitor: change interface Roman Cheplyaka **20081226213118 - remove add*Monitor - add manageMonitor, monitor template ] [X.U.WindowProperties: propertyToQuery+docs Roman Cheplyaka **20081225080702] [X.L.Monitor: docs Roman Cheplyaka **20081225073904] [hlintify XUtils, XSelection, Search, WindowGo gwern0@gmail.com**20081220153302 Ignore-this: 7e877484e3cd8954b74232ea83180fa9 ] [fix focus issue for XMonad.Actions.Warp.banishScreen Norbert Zeh **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
**20081212192621 This works on top of warpToScreen and, thus, suffers from the same issue: focus change. ] [fixed documentation for banish Norbert Zeh
**20081212191819 banish actually warps to the specified corner of the current window, not the screen. ] [addition of combined TallGrid layout Norbert Zeh
**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
**20081213073054] [XMonad.Actions.WindowGo: fix a floating-related focus bug gwern0@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@gmail.com**20081119213122 Ignore-this: 95ac7dbe9c8fe3618135966f251f4fc6 ] [Prompt.hs: increase font size to 12 from niggardly 10 gwern0@gmail.com**20081119212523 Ignore-this: 74a6e1ac5e1774da4ffc7c6667c034c ] [Prompt.hs: replace magic numbers with understandable names gwern0@gmail.com**20081119212502 Ignore-this: 8401c0213be9a32c925e1bd0ba5e01f1 ] [X.L.Monitor: recommend doHideIgnore (docs) Roman Cheplyaka **20081215190710] [X.L.Monitor: docs Roman Cheplyaka **20081215184423] [X.L.Monitor: export Monitor datatype Roman Cheplyaka **20081215184318] [X.H.ManageHelpers: add doHideIgnore Roman Cheplyaka **20081215182758] [Add KDE 4 config, thanks to Shirakawasuna on IRC Spencer Janssen **20081211071141 Ignore-this: 51698961ab5b6e569c294d174f2804a9 ] [I use the deleteConsecutive history filter Spencer Janssen **20081025070438] [Remove XMonad.Config.PlainConfig, it has been turned into the separate xmonad-light project. Braden Shepherdson **20081203161534] [XMonad.Prompt: swap up and down per bug #243 gwern0@gmail.com**20081203013323 Ignore-this: 8ab0481a0da7a983f501ac2fec4a68e8 ] [Fix boolean operator precedence in GridSelect keybindings Aleksandar Dimitrov **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@gmail.com**20081122084725] [Export setOpacity from FadeInactive. Document how to make monitor transparent (X.L.Monitor) Roman Cheplyaka **20081117153027] [Monitor: use broadcastMessage instead of sendMessage; this solves several issues Roman Cheplyaka **20081117133957] [FadeInactive: fade all inactive windows (including focused windows on visible screens) Roman Cheplyaka **20081117130115] [Monitor: documented one more issue Roman Cheplyaka **20081117113807] [Monitor: improved the docs Roman Cheplyaka **20081117073709] [added XMonad.Layout.Monitor Roman Cheplyaka **20081115104735] [WindowProperties: added allWithProperty Roman Cheplyaka **20081115104525] [ManageHelpers: added doSideFloat (generalization of doCenterFloat) Roman Cheplyaka **20081114113015] [GridSelect: Export default_colorizer Dominik Bruhn **20081112140005] [Simplify code for restriction-calculation and remove compiletime warnings Dominik Bruhn **20081112134630] [Simplify handle/eventLoop, introduce findInWindowMap, partial updates for key movements (less flickering) Clemens Fruhwirth **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
**20081111063348] [GridSelect: fix infiniteness problem with diamondRestrict Roman Cheplyaka **20081111055350] [GridSelect: remove tabs Roman Cheplyaka **20081111053647] [Exported shrinkWhile from Decoration to use in GridSelect Roman Cheplyaka **20081110191534] [GridSelect: added link to a screenshot Roman Cheplyaka **20081110190617] [GridSelect: various improvements Roman Cheplyaka **20081110184644 Added documentation Restricted export list for the sake of haddock Added functions: withSelectedWindow bringSelected (by Clemens Fruhwirth) goToSelected (by Dominik Bruhn) ] [windowPromptBringCopy deadguysfrom@gmail.com**20081023173019] [generic menu and window bringer Travis B. Hartwell **20081027005523] [Initial version of GridSelect.hs with a lot room for improvement/cleanups Clemens Fruhwirth **20081107115114] [documentation: XMonad.Util.Search.hs, add EZConfig keybindings example sean.escriva@gmail.com**20081106171707] [typo Don Stewart **20081104043044 Ignore-this: bdac0ff3316c821bce321b51c62f6e89 ] [place an upper bound on the version of base we support Don Stewart **20081104035857 Ignore-this: 29139cc4f0ecb299b56ae99f7d20b854 ] [explicit import list for things in the process library Don Stewart **20081104035319 Ignore-this: 91b7f96421828788760e8bcff7dec317 ] [Work around ghc 6.10 bug #2738 Don Stewart **20081104034819 Ignore-this: c75da9693fa642025eac0d074869423d ] [Search.hs: +hackage search, courtesy of byorgey gwern0@gmail.com**20081031214937 Ignore-this: 24db0ceed49f8bd37ce98ccf8f8ca2ab ] [Prompt.hs rename deleteConsecutiveDuplicates gwern0@gmail.com**20081008205131 That name is really unwieldy and long. ] [Prompt.hs: have historyCompletion filter dupes gwern0@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@gmail.com**20081008204649] [Prompt.hs: mv uniqSort to next to its confreres, and mention the trade-off gwern0@gmail.com**20081008192645] [Do not consider XMONAD_TIMER unknown Joachim Breitner **20081008195643] [Kill window without focusing it first Joachim Breitner **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@wagner-home.com**20081015153911] [Actions.Search: add a few search engines intrigeri@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
**20081006211027 (Just to reduce code duplication) ] [Add straightforward HiddenWS to WSType Joachim Breitner **20081006210548 With NonEmptyWS and HiddenNonEmptyWS present, HiddenWS is obviously missing. ] [Merge emptyLayoutMod into redoLayout Joachim Breitner **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 **20081005184426 Fixes: http://code.google.com/p/xmonad/issues/detail?id=223 ] [Paste.hs: improve haddocks gwern0@gmail.com**20080927150158] [Paste.hs: fix haddock gwern0@gmail.com**20080927145238] [minor explanatory comment daniel@wagner-home.com**20081003015919] [XMonad.Layout.HintedGrid: add GridRatio (--no-test because of haddock breakage) Lukas Mai **20080930141715] [XMonad.Util.Font: UTF8 -> USE_UTF8 Lukas Mai **20080930140056] [Paste.hs: implement noModMask suggestion gwern0@gmail.com**20080926232056] [fix a divide by zero error in Grid daniel@wagner-home.com**20080926204148] [-DUTF8 flag with -DUSE_UTF8 gwern0@gmail.com**20080921154014] [XSelection.hs: use CPP to compile against utf8-string gwern0@gmail.com**20080920151615] [add XMonad.Config.Azerty Devin Mullins **20080924044946] [flip GridRatio to match convention (x/y) Devin Mullins **20080922033354] [let Grid have a configurable aspect ratio goal daniel@wagner-home.com**20080922010950] [Paste.hs: +warning about ASCII limitations gwern0@gmail.com**20080921155038] [Paste.hs: shorten comment lines to under 80 columns per sjanssen gwern0@gmail.com**20080921154950] [Forgot to enable historyFilter :( Spencer Janssen **20080921094254] [Prompt: add configurable history filters Spencer Janssen **20080921093453] [Update my config to use 'statusBar' Spencer Janssen **20080921063513] [Rename pasteKey functions to sendKey Spencer Janssen **20080921062016] [DynamicLog: doc fixes Spencer Janssen **20080921061314] [Move XMonad.Util.XPaste to XMonad.Util.Paste Spencer Janssen **20080921060947] [Depend on X11 >= 1.4.3 Spencer Janssen **20080921055456] [statusBar now supplies the action to toggle struts Spencer Janssen **20080918013858] [cleanup - use currentTag Devin Mullins **20080921011159] [XPaste.hs: improve author info gwern0@gmail.com**20080920152342] [+XMonad.Util.XPaste: a module for pasting strings to windows gwern0@gmail.com**20080920152106] [UrgencyHook bug fix: cleanupUrgents should clean up reminders, too Devin Mullins **20080920062117] [Sketch of XMonad.Config.Monad Spencer Janssen **20080917081838] [raiseMaster seanmce33@gmail.com**20080912184830] [Add missing space between dzen command and flags Daniel Neri **20080915131009] [Big DynamicLog refactor. Added statusBar, improved compositionality for dzen and xmobar Spencer Janssen **20080913205931 Compatibility notes: - dzen type change - xmobar type change - dynamicLogDzen removed - dynamicLogXmobar removed ] [Take maintainership of XMonad.Prompt Spencer Janssen **20080911230442] [Overhaul Prompt to use a zipper for history navigation. Fixes issue #216 Spencer Janssen **20080911225940] [Use the new completion on tab setting Spencer Janssen **20080911085940] [Only start to show the completion window with more than one match Joachim Breitner **20080908110129] [XPrompt: Add showCompletionOnTab option Joachim Breitner **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 **20080714153601] [XMonad.Actions.Plane: removed unneeded hiding Marco Túlio Gontijo e Silva **20080714152631] [Improvements in documentation Marco Túlio Gontijo e Silva **20080709002425] [Fix haddock typos in XMonad.Config.{Desktop,Gnome,Kde} Spencer Janssen **20080911040808] [add clearUrgents for your keys Devin Mullins **20080909055425] [add reminder functionality to UrgencyHook Devin Mullins **20080824200548 I'm considering rewriting remindWhen and suppressWhen as UrgencyHookModifiers, so to speak. Bleh. ] [TAG 0.8 Spencer Janssen **20080905195420] [Bump version to 0.8 Spencer Janssen **20080905194415] [Take maintainership of X.L.WindowNavigation Devin Mullins **20080902070247 Since I've been working on a rewrite, it seems only fair that I be forced to better understand the existing code / issues. ] [Take maintainership of NoBorders Spencer Janssen **20080829201325] [Only move pointers over managed windows Joachim Breitner **20080610195916] [Fix window region checking in UpdatePointer robreim@bobturf.org**20080511094056] [remove myself as maintainer from modules I don't maintain or use. David Roundy **20080828151830] [change withUrgencyHookC api Devin Mullins **20080821052046 Now it takes an UrgencyConfig record type. ] [Accept a range of xmonad versions Spencer Janssen **20080820214056] [StackTile_fix acura@allyourbase.se**20080820061918] [X.H.UrgencyHook: haddock fixes Devin Mullins **20080816195220] [Improve documentation for XMonad.Hooks.EwmhDesktops Spencer Janssen **20080813191857] [simplify WindowBringer code, and change greedyView to focusWindow Devin Mullins **20080811033137] [Updates to my config Spencer Janssen **20080812050124] [Added XMonad.Hooks.DynamicHooks Braden Shepherdson **20080724222054 Allows runtime creation and modification of ManageHooks. Also allows one-shot ManageHooks that are removed after the fire. Note that if several transient hooks fire at once, only the most recently defined is executed, and all are removed. ] [XMonad.Hooks.UrgencyHook: +FocusHook gwern0@gmail.com**20080716224745 This is a hook for simply traveling to whatever window has just set an urgent flag, instead of doing something more involved like printing to a status bar and letting the user do something manually. ] [Grid/HintedGrid: prefer wider windows Lukas Mai **20080717205138] [I prefer the spencerjanssen@gmail.com address Spencer Janssen **20080714204005] [callUrgencyHook after adjustUrgents Devin Mullins **20080714043020 So folks can readUrgents inside their urgencyHook, should they so desire. ] [XMonad/Doc/Developing.hs: update haddock ln, cpedit gwern0@gmail.com**20080708205058] [XMonad/Doc.hs: why link to a specific version instead of the latest? gwern0@gmail.com**20080708202236] [XMonad.Actions.Plane.Linear leoserra@minaslivre.org**20080706175303] [XMonad.Actions.Plane: Improvements in code quality Marco Túlio Gontijo e Silva **20080706172829] [XMonad.Actions.Plane: Treat error in read Marco Túlio Gontijo e Silva **20080710135342] [XMonad.Actions.Plane: GConf support Marco Túlio Gontijo e Silva **20080709001900 Thanks to Johan Dahlin. ] [X.A.WindowNavigation: comments Devin Mullins **20080710041028] [add autoComplete option to XMonad.Prompt Devin Mullins **20080704073415 Maybe this will get Gwern one step closer to a complete Ratpoison binding. ] [XMonad.Actions.Plane: Copyright update Marco Túlio Gontijo e Silva **20080709001548] [XMonad.Actions.Plane: removed missing haddock chunck Marco Túlio Gontijo e Silva **20080709010530] [Added function to filter out scratchpad workspace for use with ewmhLogHookCustom. Braden Shepherdson **20080706161027] [Added ewmhLogHookCustom, which allows arbitrary transformation of the workspace list. Braden Shepherdson **20080706160847] [adding thesaurus.reference.com and Google Labs Code Search searches brian@lorf.org**20080701090142] [fillout banish example in Warp.hs gwern0@gmail.com**20080629202047 We also include a nice little type to avoid specifying 0 0 stuff. ] [fix Actions.Wap doc gwern0@gmail.com**20080629115504 warp 1 1 has a comment claiming that this moves the cursor to the lower *left*, but if you look at the warpToWindow haddock, it says that 1 1 is actually lower *right* - as indeed it proved to do. This was annoying as it led me astray for a minute or so. ] [allow function keys up to F24 brian@lorf.org**20080626040516] [Now using -name instead of -title as the term app argument, and correspondingly resource for the ManageHook. Braden Shepherdson **20080608180748] [Actions/Search.hs: export SearchEngine constructor Brent Yorgey **20080620212016] [Export PerWorkspace to allow type signatures Malebria **20080620015046] [XMonad.Util.EZConfig: add keypad bindings Lukas Mai **20080615143702] [XMonad.Util.EZConfig: minor cleanups Lukas Mai **20080528165450] [make default highlighting a bit dimmer for neighbors in WindowNavigation. David Roundy **20080610174200] [keep drag panes on the bottom of the window stack. David Roundy **20080610174044] [add support to Magnifier for vertical zooming. David Roundy **20080610173747] [XMonad.Hooks.EwmhDesktops export EwmHDesktopsHook Malebria **20080610130614 Any function that a user may write in his configuration file that is related to ewmhDesktopsLayout cannot have it's type signature if this type is not exported. ] [XMonad.Config.Desktop type problem (monomorphism?) Malebria **20080610182856 With main = xmonad defaultConfig {layoutHook = desktopLayoutModifiers Full} I got a type error, that's not present with the patch. ] [Make prompt keybindings work when numLock or capsLock are active Justin Bogner **20080608172057] [Replaced old "spawn on mod+s" semantics with "spawn/summon or banish on mod+s". Braden Shepherdson **20080608045457 Originally the key binding just spawned a new floating terminal on every keypress. Now it spawns if it doesn't exist, summons from another workspace if it does but isn't visible, or banishes it to a dynamically created workspace if it is on the current workspace. ] [Exporting addHiddenWorkspace, it's needed by the new Scratchpad Braden Shepherdson **20080608045318] [Added scratchpadSpawnActionTerminal to specify the terminal program directly as a String. Braden Shepherdson **20080608032619] [Removed odd scratchpadSpawnDefault, improved documentation. Braden Shepherdson **20080608032439] [Actions.Search.hs: switch inappropriate use of getShellCompl for a historyCompletion gwern0@gmail.com**20080607071331 It's inappropriate because if I am searching Wikipedia, say, why on earth do I want completion of files and executables on my PC? A previous search query is much more likely to be what I want. ] [Prompt.hs: +a historyCompletion function for use in XPrompts gwern0@gmail.com**20080607071225] [Add C-w to XMonad.Prompt Trevor Elliott **20080605220656 * Bind C-w to kill the previous word
] [Add missing xfce module to .cabal Don Stewart
**20080602174219] [Use lines instead of columns in configuration (similar to GNOME and KDE) Malebria **20080526225337] [Bug correction when areasColumn > 1 Malebria **20080526223220] [more documentation for WindowNavigation and UrgencyHook Devin Mullins **20080525050231] [X.A.WindowNavigation: add logHook for better state tracking Devin Mullins **20080525032325] [doco tweaks Devin Mullins **20080524211849] [made fadeInactiveLogHook take an argument amount to fade Justin Bogner **20080523213937] [add FadeInactive to fade out inactive windows using xcompmgr Justin Bogner **20080523205838] [Don't move the pointer if the user is moving the mouse Klaus Weidner **20080417022234 This patch depends on the following xmonad core patch:
Remember if focus changes were caused by mouse actions or by key commands
If the user was moving the mouse, it's not appropriate to move the pointer around in resonse to focus changes. Do that only in response to keyboard commands. ] [add close window functionality to EwmhDesktops Justin Bogner
**20080523185908] [Add XMonad.Actions.Plane Malebria **20080523004357] [Default Xfce config, this time with me holding the copyright, maintainership, etc. Ivan.Miljenovic@gmail.com**20080522105316] [StackTile: minor documentation fix Joachim Fasting **20080521182637 That '[]' in the example seems incorrect ] [StackTile acura@allyourbase.se**20080520195559 A simple patch to get a dishes like stacking, but with the ability to resize master pane. ] [revamp Search.hs to export a replacement for simpleEngine gwern0@gmail.com**20080519190912 It's called searchEngine now, and is a wrapper around the SearchEngine type. Different type as well ] [sp ShowWName.hs gwern0@gmail.com**20080519190520] [remove ScratchWorkspace. David Roundy
**20080516185729 It's ugly code, and I'd be surprised if anyone actually uses it. I see no reason to continue to maintain it. ] [Fixed location of xmonad.conf Roman Cheplyaka **20080518204602] [add site name in search prompt dialog zhen.sydow@gmail.com**20080518101357] [add youtube to search engines zhen.sydow@gmail.com**20080513212508] [SwapWorkspaces: swapTo Next|Prev Devin Mullins **20080518024121] [UrgencyHook: removeVisiblesFromUrgents -> cleanupUrgents Devin Mullins **20080515164436 Now only removes windows based on SuppressWhen setting. ] [Added XMonad.Config.PlainConfig: proof-of-concept GHC-less plain text configuration file parser Braden Shepherdson **20080517222916 An example of the config file format can be found in the Haddock. Notably missing features are docks and more layouts than just the standard three. ] [XMonad.Hooks.SetWMName: Update documentation to reflect the addition of startupHook. lithis
**20080516221011] [I no longer use ScratchWorkspace. David Roundy **20080516185715] [fix bug in smartBorders when combined with decorated windows. David Roundy **20080516184855] [decent documentation for UrgencyHook Devin Mullins **20080515082222 Blame it on lack of sleep. Or perhaps the causation is the reverse. ] [X.A.WindowNavigation: currentPosition and setPosition share the same `inside` logic, now Devin Mullins **20080515062211 Aside from documentation, this is pretty much usable, now. ] [X.A.WindowNavigation: have currentPosition handle axes independently Devin Mullins **20080515053330 This improves some subtle interactions between mod-j/k and mod-w/a/s/d, though that might not become very apparent until I fix setPosition. ] [fix compile warnings in BoringWindows Devin Mullins **20080515051728] [add BoringWindows module to make certain windows skipped when rotating focus. David Roundy **20080514162846] [UrgencyHook: some documentation (more is needed) Devin Mullins **20080514080104] [UrgencyHook: got rid of the need for instances to know about suppressWhen Devin Mullins **20080514072217 This changes the API a little bit, but that's what you get for using a day-old feature from darcs. ] [move AppLauncher from Actions module to Prompt module zhen.sydow@gmail.com**20080513201252] [X.A.WindowNavigation: comment cleanup Devin Mullins **20080513091313] [windowRect now compensates for border width Devin Mullins **20080513090151 Odd that I have to do (Rectangle x y (w + 2 * bw) (h + 2 * bw)) -- you'd think the window would be centered within the bordered area. ] [X.A.WindowNavigation: update TODO Devin Mullins **20080513044229] [X.A.WindowNavigation: minor cleanup Devin Mullins **20080512170410] [X.A.WindowNavigation: simplify inr somewhat Devin Mullins **20080512090647] [X.A.WindowNavigation: clarity Devin Mullins **20080512085338] [X.A.WindowNavigation: ugh, typo Devin Mullins **20080512082228] [X.A.WindowNavigation: implement swap, extract withTargetWindow commonality Devin Mullins **20080512064715 Why doesn't mapWindows exist already? ] [add more flexible withWindowNavigationKeys Devin Mullins **20080512050637 Names aren't permanent yet, so don't cry if they change. ] [X.A.WindowNavigation: TODO Devin Mullins **20080511222116] [X.A.WindowNavigation: add withWindowNavigation, for easy setup Devin Mullins **20080511220458 This should be more flexible than it is -- I've got an idea, but am interested to hear others. ] [X.A.WindowNavigation: fix currentPosition Devin Mullins **20080511212128 Now properly deals with an unitialized state (e.g. from a restart) or an inconsistent state (e.g. from using mod-j/k). Deserves cleanup. ] [X.A.WindowNavigation: add TODOs Devin Mullins **20080511211326] [X.A.WindowNavigation state is now workspace-specific Devin Mullins **20080511071656 racking up some code debt, here... ] [X.A.WindowNavigation: minor doco changes Devin Mullins **20080506074235] [add draft XMonad.Actions.WindowNavigation Devin Mullins **20080504050022 This is an experiment with replacing the WindowNavigation LayoutModifier with one that simply adds keybindings and stores state in an IORef. Credit to droundy for the original code -- hopefully I'm not butchering it. The end intent is to add Xinerama support, but it'll be a little while before I get there. ] [new contrib module to launch apps with command line parameters zhen.sydow@gmail.com**20080513134754] [pull suppressWhen logic into main WithUrgencyHook handler Devin Mullins **20080513075247 In order for this to work, I added a new UrgencyHook method to communicate the SuppressWhen value. I'm not sure if this is actually better than just providing a convenience function, but it's an easy switch. ] [add suppressWhen option to dzenUrgencyHook Devin Mullins **20080513054615] [WindowNavigation: extract navigable function Devin Mullins **20080422045248] [UrgencyHook: doc typo Devin Mullins **20080512052137] [UrgencyHook: extract whenNotVisible Devin Mullins **20080512041852] [SpawnUrgencyHook, FWIW Devin Mullins **20080512040449] [make UrgencyHook an EventHook Devin Mullins **20080512024822 This gets rid of the stupid bug that led to a need for the clearBit hack, and allowed me to simplify the types (since EventHooks aren't required to parameterize on the window type). Config files need not change, unless they declare instances of UrgencyHook, in which case, they should remove "Window" as is seen in this patch. ] ['xmobar' function added to DynamicLog for running xmobar with some defaults Ivan N. Veselov
**20080508194918] [HintedTile: Fix mistake in documentation. lithis **20080508003552] [Use gnome-session-save for the mod-shift-q binding Spencer Janssen **20080507082205] [Use the named constant 'none' rather than 0 Spencer Janssen **20080507081854] [HintedTile: Improve documentation. lithis **20080508000245] [Whitespace only Spencer Janssen **20080507031306] [Add a binding for Gnome's "Run Application" dialog Spencer Janssen **20080507031127] [Add some keybindings to the Kde config Spencer Janssen **20080507022658] [Indentation Spencer Janssen **20080507022553] [Add ToggleStruts to the desktop config Spencer Janssen **20080507022516] [Refactor my config Spencer Janssen **20080507021504] [Add XMonad.Config.Kde Spencer Janssen **20080507020833] [Missing pragmas Don Stewart **20080506053402] [Add full documentation Don Stewart **20080505210546] [minor cleanup on getName Devin Mullins **20080504054923] [bug doco for UrgencyHook Devin Mullins **20080426203638] [NamedWindows: when converting the text property, handle the empty list. Spencer Janssen **20080502104249 This fixes a "Prelude.head" exception observed with windows that have no title. Reproduce by placing several windows in the tabbed layout, then starting 'xterm -name ""'. Thanks to Andrea for pointing out the issue. ] [Fix issue #179 by handling events correctly Andrea Rossato **20080501062357] [My monitor is larger now :) Spencer Janssen **20080430083026] [manageHooks for my config Spencer Janssen **20080430082536] [Remove redundant type signature Spencer Janssen **20080430082447] [Add XMonad.Config.Desktop and XMonad.Config.Gnome Spencer Janssen **20080430082253] [Alphabetize exposed-modules Spencer Janssen **20080430035453] [new contrib layout: XMonad.Layout.SimplestFloat - A floating layout like SimpleFloat, but without decoration joamaki@gmail.com**20080424220957] [stricitfy some gap fields Don Stewart **20080427191247] [XMonad.Hooks.ManageHelpers: quick&dirty support for _NET_WM_STATE_FULLSCREEN Lukas Mai **20080426132745] [XMonad.Hooks.Script: haddock fixes Lukas Mai **20080426132629] [Error fix for Tabbed when tabbar always shown Ivan.Miljenovic@gmail.com**20080424063135] [remove my config file -- the wiki is where its at. Don Stewart **20080419195650] [tweaks to docs for SimpleDecoration Don Stewart **20080418215155] [Allow tabbar to always be shown. Ivan.Miljenovic@gmail.com**20080415043728 Patch take 4, hopefully the final version. Includes droundy's suggestions. ] [polish Don Stewart **20080418033133] [Script-based hooks Trevor Elliott **20080416213024] [Don't strictify the Display component, this triggers a bug in GHC 6.6 Spencer Janssen **20080416185733] [Fix to IM modifier. Roman Cheplyaka **20080414232437 Avoid differentiating integrated stack by using StackSet.filter. ] [IM layout converted to LayoutModifier, which can be applied to any layout Ivan N. Veselov **20080413205824] [stictify some fields Don Stewart **20080413070117] [strictify some fields Don Stewart **20080413065958] [Fix window order in EWMH Joachim Breitner **20080411134411 For pagers to draw the stacking order correctly, the focused window has to be the last in the list. Thus put an appropriate implementation of allWindows into the Module. This does not work perfectly with floating windows. ] [update contrib for applySizeHints changes Lukas Mai **20080404220558] [TAG 0.7 Spencer Janssen **20080329202416] [XMonad.Layout.HintedTile: make alignment of shrunk windows configurable Lukas Mai **20080325202958] [remove myself as maintainer of CopyWindow. David Roundy **20080409144333 I'm not sure who's maintaining this, but it's not me. ] [XMonad.Util.WindowProperties: add WM_WINDOW_ROLE as Role Roman Cheplyaka **20080409174935] [Generalize copyWindow, minor style change Spencer Janssen **20080408210050] [XMonad.Actions.CopyWindow: added copyToAll and killAllOtherCopies functions Ivan N. Veselov **20080408195111] [XMonad.Actions.UpdatePointer: doc fix Lukas Mai **20080407152741] [XMonad.Util.Font: minor reformatting Lukas Mai **20080406020935] [DynamicLog: resolve merge conflict Lukas Mai **20080406020527] [Encode the entire DynamicLog output, instead of just window title. lithis **20080329031537] [DynamicLog: add support for UTF-8 locales when compiled with XFT or UFT-8 support Andrea Rossato **20080313102643] [XMonad.Util.Font: don't call setlocale; core does it for us Lukas Mai **20080406013123] [XMonad.Util.NamedWindows: fix imports Lukas Mai **20080326172745] [Changed getName to use locale-aware functions Mats Jansborg **20070819132104 Rewrote getName using getTextProperty and wcTextPropertyToTextList. ] [Added next-window versions of the raise* functions. Ian Zerny **20080405182900] [XMonad.Layout.Master: initial import Lukas Mai **20080404220734] [XMonad.Hooks.ManageDocks: haddock fix Lukas Mai **20080404220532] [MultiToggle/Instances: ghc 6.6 can't parse LANGUAGE pragma Brent Yorgey **20080404200157] [Document _NET_ACTIVE_WINDOW behaviour more exactly Joachim Breitner **20080404072944] [_NET_ACTIVE_WINDOW moves windows if necessary Joachim Breitner *-20080402143811 This makes EWMH behave a bit more like metacity: If _NET_ACTIVE_WINDOW is received and the window is not on the current worspace, it is brought here (instead of the workspace switched to the other one). So for example, if you click on the pidgin icon in the panel and the buddy list is already open some where it is moved here. ] [onstart=lower, solves floating dzen issue Don Stewart **20080403203425] [some bang patterns Don Stewart **20080403172246] [have 'dzen' use autoStruts to detect the gaps Don Stewart **20080403003130] [Actions/Search.hs: add dictionary.com search Brent Yorgey **20080402150521] [_NET_ACTIVE_WINDOW moves windows if necessary Joachim Breitner **20080402143811 This makes EWMH behave a bit more like metacity: If _NET_ACTIVE_WINDOW is received and the window is not on the current worspace, it is brought here (instead of the workspace switched to the other one). So for example, if you click on the pidgin icon in the panel and the buddy list is already open some where it is moved here. ] [HintedGrid: guesstimate window flexibility and layout rigid windows first Lukas Mai **20080402042846] [HintedGrid: try both bottom-up/top-down window placement to minimize unused space Lukas Mai **20080402012538] [Grid/HintedGrid: use an ncolumns formula inspired by dwm's "optimal" mode Lukas Mai **20080402012126] [XMonad.Layout.Gaps: new contrib module for manual gap support, in the few cases where ManageDocks is not appropriate (dock apps that don't set STRUTS properly, adjusting for a display that is cut off on one edge, etc.) Brent Yorgey **20080402003742] [improve WindowGo.hs Haddock formatting gwern0@gmail.com**20080401023130] [forgot a haddock for getEditor in Shell.hs gwern0@gmail.com**20080401022012] [WindowGo.hs: +raiseBrowser, raiseEditor gwern0@gmail.com**20080401021740 Specialize runOrRaise in the same way as with Actions.Search, for one's browser and one's editors. ] [RunOrRaise.hs: FF 3 doesn't use the "Firefox-bin" classname gwern0@gmail.com**20080401015049] [Search.hs: remove an argument from selectSearch and promptSearch gwern0@gmail.com**20080401013947 The new getBrowser function allows us to mv the old selectSearch and promptSearch aside as too-general functions, and replace them with new versions, which employ getBrowser to supply one more argument. This allows us to replace the tedious 'selectSearch google "firefox"; selectSearch yahoo "firefox"...' with shorter 'selectSearch google' and so on. One less argument. Also, update the docs. ] [Shell.hs: +getBrowser, getEditor, helper function gwern0@gmail.com**20080401013447 The helper function asks the shell for the value of a variable, else returns the second argument. getBrowser and getEditor obviously specialize it for two particular possibly queries ] [XMonad.Layout.HintedGrid: initial import Lukas Mai
**20080401231722] [Documentation improvement. Roman Cheplyaka **20080401134305] [Remove broken link to screenshot. Roman Cheplyaka **20080331210854] [MultiToggle: add new XMonad.Layout.MultiToggle.Instances module for common instances of Transformer, update MultiToggle docs accordingly Brent Yorgey **20080331201739] [XMonad.Actions.CycleRecentWS: initial import Michal Janeczek **20080331111906] [XMonad.Hooks.ManageDocks: export checkDoc Lukas Mai **20080331012911] [XMonad.Layout.Grid: fix indentation Lukas Mai **20080330004859] [move Direction type from WindowNavigation to ManageDocks (ManageDocks will move into the core, taking Direction with it) Brent Yorgey **20080331010127] [ManageDocks: clean up + add more documentation Brent Yorgey **20080331002929] [Util.Run, Hooks.DynamicLog: re-export hPutStrLn and hPutStr from Util.Run for convenience, and update DynamicLog documentation to show proper imports Brent Yorgey **20080328205446] [ManageDocks: add avoidStrutsOn, for covering some docks and not others by default. Brent Yorgey **20080327203940] [ManageDocks: add ability to toggle individual gaps independently Brent Yorgey **20080327111722] [PerWorkspace: add modWorkspace(s) combinators, for selectively applying layout modifiers to certain workspaces but not others Brent Yorgey **20080326214351] [Haddock fix Roman Cheplyaka **20080330134435] [Remove stale status gaps code Spencer Janssen **20080329230737] [Bump version to 0.7 Spencer Janssen **20080329192400] [Fix haddock error Spencer Janssen **20080329191752] [XMonad.Layout.MultiToggle: let runLayout modify the base layout if no transformer is active Lukas Mai **20080328190903] [Spiral: add documentation Brent Yorgey **20080328192231] [corrected version of make workspaceDir work even in workspaces with no windows. David Roundy **20080327142257] [cleanup in Tabbed (make 'loc' be actual location). David Roundy **20080326151004] [make workspaceDir work even in workspaces with no windows. David Roundy *-20080326152708 This also fixes a (minor) bug when the focussed window is present on multiple visible workspaces. ] [clean up Config.Droundy. David Roundy **20080327002159] [make workspaceDir work even in workspaces with no windows. David Roundy **20080326152708 This also fixes a (minor) bug when the focussed window is present on multiple visible workspaces. ] [ManageDocks: add warning about making sure gaps are set to zero before switching to avoidStruts, since ToggleStruts won't work otherwise Brent Yorgey **20080326231928] [update documentation in XMonad/Doc in preparation for 0.7 release Brent Yorgey **20080326195741] [XMonad.Hooks.ManageHelpers: reformatting Lukas Mai **20080326182707] [XMonad.Layout.NoBorders: fix floating fullscreen logic Lukas Mai **20080326172844] [UpdatePointer: Make pointer position configurable. xmonad@selg.hethrael.org**20080326075759] [Fix bugs in Tabbed and TabBarDecoration -- please remember multi-head! Spencer Janssen **20080326034541] [my current config Don Stewart **20080326023303] [I don't use DwmStyle Spencer Janssen **20080325213818] [fix bug in TabBarDecoration leading to gaps in corner. David Roundy **20080325210327] [fix bug leading to gaps in tabs at the corner of the screen. David Roundy **20080325210211 Besides being ugly, this had the effect of making me fail to click on the tab I aimed for, if it was in the corner. ] [XMonad.Layout.LayoutModifier: add a metric crapload of documentation Brent Yorgey **20080325205006] [XMonad.Layout.Reflect: update documentation to reflect (haha) recent updates to MultiToggle Brent Yorgey **20080325185630] [XMonad.Actions.Commands: documentation fix Brent Yorgey **20080325165707] [focusedHasProperty redbeard0531@gmail.com**20080325040412] [XMonad.Util.Themes: improve documentation to make it clear that themes only apply to decorated layouts Brent Yorgey **20080324185946] [Doc/Extending: remove references to "XMonad.Layouts" -- it's now called "XMonad.Layout", and in any case, importing it explicitly is not needed anyway. Brent Yorgey **20080324143503] [XMonad.Actions.Search: add Google Maps search Brent Yorgey **20080324143348] [XMonad.Layout.Magnifier: add documentation Brent Yorgey **20080324143214] [wfarrTheme wcfarrington@gmail.com**20080324011625 Add a new color theme using blue and black. ] [added RunOrRaisePrompt, exported getCommands from Shell Justin Bogner **20080323222632] [XMonad.Actions.MouseGestures: reexport Direction from WindowNavigation, avoid type duplication Lukas Mai **20080322193457] [use ewmhDesktopsLayout in Droundy. David Roundy **20080322153610] [cut Anneal and Mosaic. David Roundy **20080322153546] [fix WorkspaceDir to work when there are multiple screens. David Roundy **20080311221201 In particlar, ScratchWorkspace broke this. ] [fix various compilation errors Lukas Mai **20080322074113] [XMonad.Layout.NoBorders: first attempt at documenting smartBorders Lukas Mai **20080321221315] [allow magnifier to toggle whether it's active daniel@wagner-home.com**20080321104605] [a magnifier that defaults to not magnifying any windows daniel@wagner-home.com**20080321104441] [XMonad.Layout.Magnifier: remove references to Data.Ratio.% from documentation Lukas Mai **20080320223816] [mark Mosaic as broken. use MosaicAlt Don Stewart **20080320223717] [add ewmhDesktopsLayout for EWMH interaction Joachim Breitner **20080319195736 This is based on Andreaâs EventHook thingy. Note that I could not merge this with some of my earlier EWHM interaction patches (darcs was failing on me), so I copied some code. Do not try to merge it with those patches either.
Note that the docs are saying what should work. There are still some bugs to be resolved, but it works sometimes and should work similar to what we have. ] [Export HandleEvent type to be able to use it in type annotations Joachim Breitner
**20080319195603] [I now use ServerMode Andrea Rossato **20080226115347] [EventHook: handle events after the underlying layout and more Andrea Rossato **20080224230854 - check the first time the Bool is True - coding and naming style ] [Add Hooks.ServerMode: an event hook to execute commands sent by an external client Andrea Rossato **20080224133706] [Add EventHook: a layout modifier to handle X events Andrea Rossato **20080224112432] [tabs Don Stewart **20080317224758] [WindowProperties: fix documentation Brent Yorgey **20080318204540] [Move window properties to a separate Util module Roman Cheplyaka **20080318165658 Add XMonad.Util.WindowProperties Modify XMonad.Layout.IM.hs to use WindowProperties. ] [XMonad.Layout.NoBorders: always unborder fullscreen floating windows, even when there are multiple screens Lukas Mai **20080317183043] [MagicFocus: reimplement as a LayoutModifier, fix bug (MagicFocus didn't pass on messages to underlying layouts) Brent Yorgey **20080317193008] [WindowGo.hs: improve description gwern0@gmail.com**20080316223946 I'm still not sure whether the description makes sense if you don't already understand the idea. ] [Run.hs: improve haddock gwern0@gmail.com**20080316223219 This module too was causing horizontal scrolling because of the shell command. I managed to discover that you only need to specify 'png:' *or* "foo.png", not both, which trimmed off enough characters. Also, I improved the docs for my functions. ] [XSelection.hs: improved haddockf formatting, more links, & cpedit gwern0@gmail.com**20080316222050] [Search.hs: try to add a more descriptive type gwern0@gmail.com**20080316215728] [improve the formatting for WindowGo.hs gwern0@gmail.com**20080316215642] [Search.hs: haddock fmt gwern0@gmail.com**20080316213914 This removes whitespace in source code snippets. Because Haddock renders quoted source code as monospaced unwrappable text, the excess whitespace meant you would have to scroll horizontally, unpleasantly. ] [Add XMonad.Actions.Promote xmonad@s001.hethrael.com**20080316205722] [LayoutCombinators: improve documentation (closes ticket #136) Brent Yorgey **20080316195826] [Xmonad.Layout.NoBorders: make smartBorders unborder fullscreen floating windows (bug 157) Lukas Mai **20080316042941] [Xmonad.Prompt.DirExec: fix haddock error Lukas Mai **20080316042840] [EwmhDesktops: advertise support for _NET_CLIENT_LIST_STACKING Alec Berryman **20080315212631] [ScratchWorkspace: update to work with runLayout changes Brent Yorgey **20080311212908] [Scratchpad: update to work with runLayout changes Brent Yorgey **20080311181715] [MagicFocus: update to work with runLayout changes Brent Yorgey **20080311181625] [LayoutScreens: update to work with runLayout changes Brent Yorgey **20080311181537] [Combo: update to work with runLayout changes Brent Yorgey **20080311181400] [MultiToggle: fix to work with runLayout changes to core Brent Yorgey **20080311172046] [PerWorksapce: use a safer False as default Andrea Rossato **20080223075531] [PerWorkspace: reimplemented using runLayout Andrea Rossato **20080222175954 This way we have a Xinerama safe PerWorkspace and the emptyLayout method for free. ] [ToggleLayouts: reimplemented with runLayout Andrea Rossato **20080223081553] [LayoutCombinators: NewSelect reimplemented with runLayout Andrea Rossato **20080223080958] [LayoutModifier: reimplement ModifiedLayout using runLayout and more Andrea Rossato **20080223075610 - change modifyLayout type to get the Workspace - updated ResizeScreen and ManageDocks accordingly. ] [Combo: updated to latest runLayout changes Andrea Rossato **20080222175924] [EZConfig: add documentation and a warning, so no one repeats my silly hard-to-track-down mistake. Brent Yorgey **20080311172610] [Fix to work with "floats always use current screen" patch robreim@bobturf.org**20080308024928] [make smartBorders ignore screens with no dimensions. David Roundy **20080308224244] [rewrite ScratchWorkspace to make scratch always visible, but not always on screen. David Roundy **20080308223830] [add HiddenNonEmptyWS to CycleWS to avoid workspaces already visible. David Roundy **20080308223717] [Fix ThreeColumns doc. Roman Cheplyaka **20080307203022] [Shell: add support for UTF-8 locales Andrea Rossato **20080302095924] [Font and XUtils: add UTF-8 support and various fixes related to XFT Andrea Rossato **20080302095712 - printStringXMF: use the background color for XFT fonts too - textWidthXMF now returns the text width even with xft fonts - textExtentsXMF will now return only the ascend and the descent of a string. - stringPosition now takes the display too - add support for UTF-8 locales: if the contrib library is compiled with the 'with_xft' or the 'with_utf8' option the prompt and the decoration system will support UTF-8 locales - this requires utf8-strings. ] [Ssh: coding style Andrea Rossato **20080229100346] [Ssh: complete known hosts with non standard ports too Andrea Rossato **20080229095014] [Fix xmonadPromptC and use it. nicolas.pouillard@gmail.com**20080306163928] [Documentation typo about UpdatePointer. nicolas.pouillard@gmail.com**20080306163516] [Fix ToggleOff: It was adding 0.1 to the magnification. Braden Shepherdson **20080305222302] [Removed WmiiActions module. Juraj Hercek **20080305082336] [Adjusted signature of DirExec module functions. Juraj Hercek **20080301171905 - added parameter for function which executes the selected program - renamed dirExecPromptWithName to dirExecPromptNamed ] [Import of new DirExec module. Juraj Hercek **20080229212257 - allows execution of executable files from specific directory ] [Hooks.DynamicLog: export xmobarPP Dmitry Kurochkin **20080303215637] [Magnifier: fix behavior for windows on the bottom + right of the screen. Now all magnified windows will be the same size, possibly shifted in order to fit completely on the screen. Brent Yorgey **20080303204619] [Changed semantics of UpdatePointer to move to nearest point robreim@bobturf.org**20080301143126] [UpdatePointer XMonadContrib module robreim@bobturf.org**20080301134401] [Util.Run: minor clarification in comment gwern0@gmail.com**20080303051513] [Add XMonad.Actions.PerWorkspaceKeys Roman Cheplyaka **20080302202346] [Haddock fix: Changed URL-Markup Dominik Bruhn **20080302185435] [switch Droundy to smartBorders (which works better with ScratchWorkspace). David Roundy **20080301191103] [XMonad.Layout.Simplest: add FlexibleInstances pragma Lukas Mai **20080301061714] [XMonad.Layout.ScratchWorkspace: avoid warnings, make tests compile again Lukas Mai **20080301061625] [implement ScratchWorkspace. David Roundy **20080229224316] [in Prompt.Workspace sort by official workspace order. David Roundy **20080229223047] [simplify Simplest--allow it to apply to non-Windows. David Roundy **20080229221326] [XMonad.Actions.MouseGestures.mkCollect: generalize type Lukas Mai **20080229211732] [Add bottom-tabbed layout. Roman Cheplyaka **20080229155120] [XMonad.Actions.MouseGestures: refactoring, code simplification Lukas Mai **20080229002136 It is now possible to get "live" status updates while the gesture handler is running. I use this in my xmonad.hs to print the current gesture to my status bar. Because collecting movements is now the callback's job, the implementation of mouseGestureH got quite a bit simpler. The interface is incompatible with the previous mouseGestureH but the old mouseGesture function works as before.
] [EZConfig: additional documentation Brent Yorgey
**20080227164602] [XMonad.Util.Scratchpad: change 'XConfig Layout' to 'XConfig l', to avoid type mismatches; the exact layout type doesn't actually matter Brent Yorgey **20080227014201] [EZConfig: add an emacs-style keybinding parser! Brent Yorgey **20080226222723 Now, instead of writing out incredibly dull things like ((modMask conf .|. controlMask .|. shiftMask, xK_F2), ...)
you can just write
("M-C-S-<F2>", ...)
Hooray! ] [Xmonad.Actions.MouseGestures: generalize interface, allow hooks Lukas Mai
**20080226202639] [update inactive debugging code in MouseGestures; no visible changes Lukas Mai **20071109020755] [Scratchpad terminal Braden Shepherdson **20080225183633 Key binding and ManageHook to pop up a small, floating terminal window for a few quick commands.
Combined with a utility like detach[1], makes a great X application launcher.
Requires my two new ManageHooks (doRectFloat, specifically).
[1] http://detach.sourceforge.net ] [Two new floating window ManageHooks. Braden Shepherdson
**20080225183337 Adds doRectFloat, which floats the new window in the given rectangle; and doCenterFloat, which floats the new window with its original size, but centered. ] [Fix usage doc. Roman Cheplyaka
**20080225062330] [Fix haddock hyperlink. Roman Cheplyaka **20080224205416] [Add XMonad.Layout.IM Roman Cheplyaka **20080221085752] [Export XMonad.Layout.Grid.arrange (for use in XMonad.Layout.IM) Roman Cheplyaka **20080221062204] [Decoration: some haddock updates Andrea Rossato **20080220214934] [Small refactoring. Nils Anders Danielsson **20080210224756] [Fixed off-by-one error which broke strut handling for some panels. Nils Anders Danielsson **20080210222600] [Decoration: fix an issue with decoration window creation and more Andrea Rossato **20080220204355 - fix a bug reported by Roman Cheplyaka: when decorate returned Nothing the window was never going to be created, even if decorate was reporting a Just Rectangle in the next run. Quite a deep issue, still visible only with TabbedDecoration at the present time. - remove decorateFirst (decorate has enough information to decide whether a window is the first one or not, am I right, David?) - some point free. ] [DynamicLog.hs: haddock fix Andrea Rossato **20080220204033 Someone forgot to check if her patch was going to break haddock docs generation or not. So, while I was recording a patch with quite a long description I had to manually write - sound strange? -, I found out that my patch did not pass the tests, because of this haddock problem left behind.
And so I fixed it, recorded this patch, with the hope the my next description of the next patch I'm going to record will survive the test suite we created to avoid this kind of problems for. ] [improvements to XMonad.Hooks.DynamicLog, and new contrib module XMonad.Util.Loggers Brent Yorgey
**20080219210128 Improvements to DynamicLog include: * Greatly expanded and improved documentation and examples * remove seemingly useless makeSimpleDzenConfig function * factor out xmobarPP * add new ppExtras field to PP record, for specifying 'extra' loggers which can supply information other than window title, layout, and workspace status to a status bar (for example, time and date, battery status, mail status, etc.) The new XMonad.Util.Loggers module provides some example loggers that can be used in the new ppExtras field of the PP record. Create your own, add them to this module, go crazy! =)
] [LayoutHints: fix a wrong fix Andrea Rossato
**20080219165127 The case analisys of my fix should be the other way around... this is the real fix. ] [Arossato: updated to latest changes Andrea Rossato **20080219163058] [Decoration: comment only Andrea Rossato **20080219161339 This is a detailed commentary of all the code. ] [Decoratione: generate rectangles first, and create windows accordingly Andrea Rossato **20080219122115 With this patch Decoration will first generate a rectangle and only if there is a rectangle available a window will be created. This makes the Decoration state a bit more difficult to process, but should reduce resource consumption. ] [Fix doc for Tabbed Roman Cheplyaka
**20080219055650] [Tabbed and TabBarDecoration: no need to implement decorateFirst (the default is used) Andrea Rossato **20080218184950] [TabBarDecoration: simpleTabBar automatically applies resizeVertical Andrea Rossato **20080218180922 Added some comments too. ] [DwmStyle: comment fix only Andrea Rossato **20080218180727] [ResizeScreen: add resizeHorizontalRight and resizeVerticalBottom Andrea Rossato **20080218180504] [Add TabBarDecoration, a layout modifier to add a bar of tabs to any layout Andrea Rossato **20080218161121 ... and port DecorationMadness to the new system. ] [add Eq superclass to DecorationStyle and change styles in order not to decorate non managed windows Andrea Rossato **20080218131320] [Refactor MouseResize, remove isDecoration and introduce isInStack, isVisible, isInvisible Andrea Rossato **20080218105726 This patch includes several changes, which are strictly related and cannot be recorded separately: - remove Decoraion.isDecoartion and introduce Decoration.isInStack (with the related change to LayoutHints) - in Decoration introduce useful utilities: isVisible, isInvisible, isWithin and lookFor' - MouseResize: - invisible inputOnly windows will not be created; - fix a bug in the read instance which caused a failure in the state deserialization. ] [Prompt: regenerate completion list if there's just one completion Andrea Rossato **20080217132734] [Prompt.Theme: use mkComplFunFromList' to generate completions Andrea Rossato **20080217124453] [some code formatting Andrea Rossato **20080217124434] [Prompt: comment only (clafiry completionToCommand uses) Andrea Rossato **20080216181620] [Prompt: comment only (remove confusing remarks about commandToComplete) Andrea Rossato **20080216180412] [Prompt: haddock fixes only Andrea Rossato **20080216172331] [Prompt.XMonad: use mkComplFunFromList' to get all the completions with an empty command line Andrea Rossato **20080216133949] [Prompt.Window: remove unneeded and ugly escaping/unescaping Andrea Rossato **20080216133842] [Theme: move theme's nextCompletion implementation to Prompt.getNextCompletion Andrea Rossato **20080216133738] [Shell: escape the string in the command line only Andrea Rossato **20080216133651] [Prompt: add some methods to make completions more flexible Andrea Rossato **20080216133454 - now it is possible to decide if the prompt will complete the last word of the command line or the whole line (default is the last word); - completing the last word can be fine tuned by implementing 'commandToComplete' and 'completionToCommand': see comments for details; - move mkComplFunFromList' from TagWindows to Prompt. ] [Prompt.Theme: display all theme information and handle completion accordingly Andrea Rossato **20080216114159] [Prompt.Shell: if there's just one completion and it is a directory add a trailing slash Andrea Rossato **20080216114005] [Prompt: added nextCompletion and commandToComplete methods to fine tune prompts' completion functions Andrea Rossato **20080216113723] [Util.Themes: add ppThemeInfor to render the theme info Andrea Rossato **20080216113635] [DecorationMadness: resizable layouts now use MouseResize too Andrea Rossato **20080212173645] [SimpleFloat now uses MouseResize Andrea Rossato **20080212173615] [Add Actions.MouseResize: a layout modifier to resize windows with the mouse Andrea Rossato **20080212173455] [Decoration: remove mouse resize and more Andrea Rossato **20080212165306 - since mouse resize is not related to decoration, I removed the code from here. Mouse resize will be handled by a separated layout modifier (in a separated module) - now also stacked decoration will be removed (I separated insert_dwr from remove_stacked) ] [Decoration.hs: variable names consistency only Andrea Rossato **20080211123056] [Tabbed and SimpleTabbed (in DecorationMadness) define their own decorationMouseDragHook method Andrea Rossato **20080211114043 ... to disable mouse drag in tabbed layouts ] [Decoration: DecorationStyle class cleanup and focus/drag unification Andrea Rossato **20080211113650 - moved decoEventHook to decorationEventHook - added decorationMouseFocusHook, decorationMouseDragHook, decorationMouseResizeHook methods - added a handleMouseFocusDrag to focus and drag a window (which makes it possible to focus *and* drag unfocused windows too ] [Refactor XMonad.Hooks.DynamicLog Roman Cheplyaka **20080210222406 This allows using DynamicLog not only for statusbar. ] [DecorationMadness: comment only Andrea Rossato **20080210131427] [DecorationMadness: added a few floating layouts Andrea Rossato **20080210122523] [SimpleFloat: export SimpleFloat and add documentation Andrea Rossato **20080210113159] [Move DefaultDecoration from DecorationMadness to Decoration Andrea Rossato **20080210104304] [Themes: added robertTheme and donaldTheme Andrea Rossato **20080210083016] [DecorationMadness: make tunable tabbed layouts respect the Theme decoHeight field Andrea Rossato **20080210075322] [ScreenResize: vertical and horizontal now respond to SetTheme Andrea Rossato **20080210074544 And so they will change the screen dimension accordingly. ] [WindowGo.hs: fix syntax in example Brent Yorgey **20080209225135] [+doc for WindowGo.hs: I've discovered a common usecase for me for raiseMaybe gwern0@gmail.com**20080205032155] [Run.hs: add an option to runinterms gwern0@gmail.com**20080205031824 It turns out that for urxvt, and most terminal, apparently, once you give a '-e' option, that's it. They will not interpret anything after that as anything but input for /bin/sh, so if you wanted to go 'runInTerm "'screen -r session' -title IRC"', you were SOL - the -title would not be seen by urxvt. This, needless to say, is bad, since then you can't do stuff like set the title which means various hooks and extensions are helpless. This patch adds an extra options argument which is inserted *before* the -e. If you want the old behaivour, you can just go 'runInTerm "" "executable"', but now if you need to do something extra, 'runInTerm "-title mutt" "mutt"' works fine. This patch also updates callers. ] [Add DecorationMadness: a repository of weirdnesses Andrea Rossato
**20080209182515] [Decoration: change mouseEventHook to decoEventHook and more Andrea Rossato **20080209165101 Fix also the problem with window's movement when the grabbing starts ] [Tabbed: add simpleTabbed and fx documentation Andrea Rossato **20080209163917 simpleTabbed is just a version of tabbed with default theme and default srhinker. ] [Arossato: update to latest changes Andrea Rossato **20080208140604] [Decoration: enable mouse dragging of windows Andrea Rossato **20080208083602] [WindowArranger: add a SetGeometry message - needed to enable mouseDrag Andrea Rossato **20080208083413] [Decoration: add a mouseEventHook methohd and move mouse button event there Andrea Rossato **20080208073514] [Util.Thems: some more typos in comments Andrea Rossato **20080207233341] [Util.Themes: documentation and export list (added themes that have been left out) Andrea Rossato **20080207232251] [Prompt.Theme: comments and some point-free Andrea Rossato **20080207232155] [oxymor00nTheme **20080207213100] [add swapScreen to CycleWS **20080206191032 * add support for swapping the workspaces on screens to CycleWS ] [Decoration: consistency of variable names Andrea Rossato **20080207191442 Since the configuration is now called Theme, the variable 'c' is now a 't' ] [Add Prompt.Theme: a prompt for dynamically applying a theme to the current workspace Andrea Rossato **20080207184321] [Decoration: add a SetTheme message and releaseResources Andrea Rossato **20080207184048 ...which should make it harder to forget to release the font structure. ] [cabal file: respect alphabetic order for modules Andrea Rossato **20080207183153] [Add Util.Themes to collect user contributed themes Andrea Rossato **20080207182843] [SimpleFloat: comment only Andrea Rossato **20080207182438] [Update to safer initColor api Don Stewart **20080206192232] [use Util.WorkspaceCompare in Prompt.Workspace. David Roundy **20080206004057] [roll back to previous version of Droundy.hs. David Roundy **20080205204043 A cleaner WindowNavigation fix made the separation of tabbed and addTabs not strictly necessary (but still a desireable possibility in my opinion, as it allows pretty decoration of non-composite layouts that might want to have some of their windows tabbed. ] [make WindowNavigation ignore decorations. David Roundy
**20080205203556] [make tabbed work nicely with LayoutCombinators and WindowNavigation. David Roundy **20080205202343 The problem is that WindowNavigation assumes all windows are navigable, and it was getting confused by decorations. With a bit of work, we can decorate windows *after* combining layouts just fine. ] [make WindowNavigation work when windows are stacked. David Roundy **20080205202027] [ XMonad.Actions.WindowGo: add a runOrRaise module for Joseph Garvin with the help of Spencer Janssen gwern0@gmail.com**20080204173402] [enable proper handling of panels in droundy config. David Roundy **20080204030843] [enable button click for focus in tabbed. David Roundy **20080204010536 Note that this patch doesn't work with Thu Dec 27 03:03:56 EST 2007 Spencer Janssen
* Broadcast button events to all layouts, fix for issue #111 but this isn't a regression, since button events have never worked with tabbed and this change. ] [in Decoration, remove windows that are precisely hidden underneath other windows. David Roundy
**20080204005413 This is needed for WindowNavigation to work properly with the new Decorations framework. ] [switch tabbed back to using Simplest (so tabs will be shown). David Roundy **20080204005350] [Remove LayoutCombinator class and revert PerWorkspace to its Maybe Bool state Andrea Rossato **20080131063929 As I said in order to have a CombinedLayout type instace of LayoutClass and a class for easily writing pure and impure combinators to be feeded to the CombinedLayout together with the layouts to be conbined, there's seems to be the need to change the type of the LayoutClass.description method from l a -> String to l a -> X String. Without that "ugly" change - loosing the purity of the description (please note the *every* methods of that class unless description operates in the X monad) - I'm plainly unable to write something really useful and maintainable. If someone can point me in the right direction I would really really appreciate.
Since, in the meantime, PerWorkspace, which has its users, is broken and I broke it, I'm reverting it to it supposedly more beautiful PerWorkspac [WorkspaceId] (Maybe Bool) (l1 a) (l2 a) type. ] [LayoutCombinator class: code clean up Andrea Rossato
**20080129224952 - ComboType becomes CombboChooser - removed the stupid doFirst - better comboDescription default implemenation ] [Add a LayoutCombinator class and a CombinedLayout and port PerWorkspace to the new system Andrea Rossato **20080129192903] [CycleWS: change example binding for toggleWS from mod-t to mod-z. example bindings shouldn't conflict with default key bindings. Brent Yorgey **20080201202126] [REMOVE RotView: use CycleWS instead. Brent Yorgey **20080201180618 See CycleWS docs for info on switching, or just look at the changes to XMonad.Config.Droundy. ] [CycleWS: add more general functionality that now subsumes the functionality of RotView. Now with parameterized workspace sorting and predicates! Brent Yorgey **20080201121524] [WorkspaceCompare: some refactoring. Brent Yorgey **20080201120430 * Export WorkspaceCompare and WorkspaceSort types. * Extract commonality in sort methods into mkWsSort, which creates a workspace sort from a workspace comparison function. * Rename getSortByTag to getSortByIndex, since it did not actually sort by tag at all; it sorts by index of workspace tags in the user's config. * Create a new getSortByTag function which actually does sort lexicographically by tag. * Enhance documentation. ] [Search.hs: haddock cleanup Brent Yorgey **20080131161948] [Added a handy tip to the documentation of XMonad.Actions.Search v.dijk.bas@gmail.com**20080131122620 The tip explains how to use the submap action to create a handy submap of keybindings for searching. ] [Make LayoutHints a decoration aware layout modifier Andrea Rossato **20080131082314] [Extending.hs: documentation update Brent Yorgey **20080131012728] [DynamicLog: lots of additional documentation; add byorgeyPP as an example dzen config Brent Yorgey **20080130205219] [Extended PP with sorting algorithm specification and added xinerama sorting Juraj Hercek **20080109154923 algorithm - idea is to specify sorting algorithm from user's xmonad.hs - xinerama sorting algorithm produces same ordering as pprWindowSetXinerama - default ppSort is set to getSortByTag, so the default functionality is the same as it was before ] [SimpleDecoration: export defaultTheme Andrea Rossato **20080130124609] [Various decorations related updates Spencer Janssen **20080130064624 * remove deprecated TConf stuff * Remove 'style' from DeConf * Change DeConf to Theme * share defaultTheme across all decorations ] [TwoPane: add description string Joachim Fasting **20080126141332] [add XMonad.Actions.CycleSelectedLayouts Roman Cheplyaka **20080116205020] [Search.hs: add documentation and two more search engines (MathWorld and Google Scholar) Brent Yorgey **20080128190443] [xmonad-contrib.cabal: add build-type field to get rid of Cabal warning Brent Yorgey **20080128190137] [Named: reimplemented as a LayoutModifier and updated Config.Droundy accordingly Andrea Rossato **20080128161343] [LayoutModifier: add modifyDescription for completely override the modified layout description Andrea Rossato **20080128160614] [Make ToggleLayouts and Named implement emptyLayout Andrea Rossato **20080128151535] [Decoration: the fontset must be released even when we don't decorate the first window Andrea Rossato **20080128004411 This is quite an old bug! It affected Tabbed since the very beginning..;) ] [Decoration: I forgot we need to release the fontset too! Andrea Rossato **20080127233521] [Decoration: after deleting the windows we must update the layout modifier Andrea Rossato **20080127231815 Thanks to Feuerbach for reporting this. ] [Reflect: reimplemented as a layout modifier (which makes it compatible with windowArranger and decoration) Andrea Rossato **20080127165854] [SimpleFLoat: change the description to Float (Simple is the decoration description) Andrea Rossato **20080127144556] [ManageDocks: implement AvoidStruts as a layout modifier Andrea Rossato **20080127144301] [ResizeScreen has been rewritten as a layout modifier Andrea Rossato **20080127140837] [LayoutModifier add a modifyLayout Andrea Rossato **20080127140219 Many layouts are written as layout modifiers because they need to change the stack of the rectangle before executing doLayout. This is a major source of bugs. all layout modifiers should be using the LayoutModifier class. This method (modifyLayout) can be used to manipulate the rectangle and the stack before running doLayout by the layout modifier. ] [Make LayoutCombinators deal with emptyLayout Andrea Rossato
**20080127092415] [Add ResizeScreen, a layout modifier for modifing the screen geometry Andrea Rossato **20080127010755] [WindowArranger can now arrange all windows Andrea Rossato **20080126233053 This is useful for SimpleFloat, whose state can now persists across layout switches. ] [Arossato: updated my config to recent changes Andrea Rossato **20080126205638] [Add SimpleFloat a very basic floating layout that will place windows according to their size hints Andrea Rossato **20080126205410] [WindoWrranger: export the WindowArranger type (see the upcoming SimpleFloat) Andrea Rossato **20080126204605] [ShowWName: show the name of empty layouts too Andrea Rossato **20080126190214] [ManageDocks: add emptyLayout definition for supporting the new decoration framework Andrea Rossato **20080126185936] [Decoration: code formatting only Andrea Rossato **20080126101354] [export DeConfig to avoid importing Decoration Andrea Rossato **20080126101049] [Prompt: code formatting only Andrea Rossato **20080126093234] [Don't export TConf anymore and export DeConfig instead Andrea Rossato **20080126092141 WARNING: this patch may be breaking your configuration. While it is still possible to use: tabbed shrinkText defaultTConf
updating the fields of the defaultTConf record is not possible anymore, since the type TConf is now hidden.
WARNING: "tabSize" has been substituted by "decoHeight"
You can change your configuration this way: myTConf :: TConf myTConf = defaultTConf { tabSize = 15 , etc....
becomes: myTConf :: DeConfig TabbedDecoration Window myTConf = defaultTabbedConfig { decoHeight = 15 , etc....
and tabbed shrinkText myTConf
becomes: tabDeco shrinkText myTConf
] [Tabbed now uses Decoration Andrea Rossato
**20080125152311] [Add DwmStyle, a layout modifier to add dwm-style decorations to windows in any layout Andrea Rossato **20080125152152] [Adde SimpleDecoration, a layout modifier to add simple decorations to windows in any layout Andrea Rossato **20080125152106] [Add Layout.Simplest, the simplest layout Andrea Rossato **20080125152015] [Add Decoration, a layout modifier and a class for easily writing decorated layouts Andrea Rossato **20080125151726] [Add WindowArranger, a layout modifier to move and resize windows with the keyboard Andrea Rossato **20080125151633] [ShowWName: moved fi to XUtils Andrea Rossato **20080124134725] [XUtils: add functions for operating on lists of windows and export fi Andrea Rossato **20080124134638] [LayoutModifier: add emptyLayoutMod for dealing with empty workspaces Andrea Rossato **20080124015605] [LayoutModifier: add pureMess and pureModifier to the LayoutModifier class Andrea Rossato **20080122111319] [Layout.ShowWName: generalize the instance Andrea Rossato **20080115045139] [add emptyLayout to MultiToggle Lukas Mai **20080128175313] [grammar fix Lukas Mai **20080128175059] [TAG 0.6 Spencer Janssen **20080127222114] Patch bundle hash: d4cd98fb7451473a544cedd2e4f3d6aa8e5df31a
_______________________________________________ xmonad mailing list xmonad@haskell.org http://www.haskell.org/mailman/listinfo/xmonad
participants (2)
-
Don Stewart
-
Nicolas Pouillard