
26 Oct
2009
26 Oct
'09
2:09 p.m.
This has been a long time coming. I think we first discussed this in April 2007. Can you characterize what changes to the core (if any) were required to support this? daniel.schoepe: > These patches add support for extensible state in contrib modules to > remove the need for having the user create IORefs for that. > This somewhat simplifies the interface of A.SpawnOn and H.DynamicHooks > and removes the use of unsafePerformIO in H.UrgencyHooks. > > This will break configs, since one no longer has to pass around > IORefs, but since this makes those modules somewhat easier to use, I > think that's tolerable. > > Those patches also fix issue 78. > Mon Oct 26 16:15:06 CET 2009 Daniel Schoepe> * Add X.U.ExtensibleState > > Mon Oct 26 17:15:00 CET 2009 Daniel Schoepe > * Use X.U.ExtensibleState instead of IORefs > > This patch changes SpawnOn, DynamicHooks and UrgencyHooks to > use X.U.ExtensibleState instead of IORefs. This simplifies the > usage of those modules thus also breaking current configs. > > New patches: > > [Add X.U.ExtensibleState > Daniel Schoepe **20091026151506 > Ignore-this: a7cf226fc7f4c4c76512bd441cf9a448 > ] { > addfile ./XMonad/Util/ExtensibleState.hs > hunk ./XMonad/Util/ExtensibleState.hs 1 > +----------------------------------------------------------------------------- > +-- | > +-- Module : XMonad.Util.ExtensibleState > +-- Copyright : (c) Daniel Schoepe 2009 > +-- License : BSD3-style (see LICENSE) > +-- > +-- Maintainer : daniel.schoepe@gmail.com > +-- Stability : unstable > +-- Portability : not portable > +-- > +-- Module for storing custom mutable state in xmonad. > +-- > +----------------------------------------------------------------------------- > + > +module XMonad.Util.ExtensibleState ( > + -- * Usage > + -- $usage > + putState > + , modifyState > + , removeState > + , getState > + ) where > + > +import Control.Applicative > +import Data.Typeable (typeOf,Typeable,cast) > +import qualified Data.Map as M > +import XMonad.Core > +import Control.Monad.State > + > +-- --------------------------------------------------------------------- > +-- $usage > +-- > +-- To utilize this feature in a contrib module create a data type, > +-- and make it an instance of ExtensionClass. You can then use > +-- the functions from this module for storing your data: > +-- > +-- > {-# LANGUAGE DeriveDataTypeable #-} > +-- > > +-- > data ListStorage = ListStorage [Integer] deriving Typeable > +-- > instance ExtensionClass ListStorage where > +-- > initialValue = ListStorage [] > +-- > > +-- > .. putState (ListStorage [23,42]) > +-- > +-- To retrieve the stored data call: > +-- > +-- > .. getState > +-- > +-- If the type can't be infered from the usage of the retrieved data, you > +-- might need to add an explicit type signature: > +-- > +-- > .. getState :: X ListStorage > +-- > +-- To make your data persistent between restarts, the data type needs to be > +-- an instance of Read and Show and the instance declaration has to be changed: > +-- > +-- > data ListStorage = ListStorage [Integer] deriving (Typeable,Read,Show) > +-- > > +-- > instance ExtensionClass ListStorage where > +-- > initialValue = ListStorage [] > +-- > extensionType = PersistentExtension > +-- > +-- Additionally, you have to instruct the user to add a type witness to > +-- the stateExtensions field of his config. To provide such a value you > +-- can use undefined, since it is only used as a type witness: > +-- > +-- > myModuleExtension = PersistentState (initialValue :: ListStorage) > +-- > -- the user has to add: > +-- > .. stateExtensions = [otherExtensions, myModuleExtension] > +-- > +-- One should take care that the string representation of the chosen type > +-- is unique among the stored values, otherwise it will be overwritten. > +-- Normally these values contain fully qualified module names when deriving Typeable, so > +-- name collisions should not be a problem in most cases. > +-- A module should not try to store common datatypes(e.g. a list of Integers) > +-- without a custom data type as a wrapper to avoid those collisions. > +-- > + > +-- | Modify the map of state extensions by applying the given function. > +modifyStateExts :: (M.Map String StateExtension -> M.Map String StateExtension) -> X () > +modifyStateExts f = modify $ \st -> st { extensibleState = f (extensibleState st) } > + > +-- | Apply a function to a stored value of the matching type or the initial value if there > +-- is none. > +modifyState :: ExtensionClass a => (a -> a) -> X () > +modifyState f = putState =<< f <$> getState > + > +-- | Add a value to the extensible state field. A previously stored value with the same > +-- type will be overwritten. (More precisely: A value whose string representation of its type > +-- is equal to the new one's) > +putState :: ExtensionClass a => a -> X () > +putState v = modifyStateExts . M.insert (show . typeOf $ v) . extensionType $ v > + > +-- | Try to retrieve a value of the requested type, return an initial value if there is no such value. > +getState :: ExtensionClass a => X a > +getState = getState' undefined -- `trick' to avoid needing -XScopedTypeVariables > + where toValue val = maybe initialValue id $ cast val > + getState' :: ExtensionClass a => a -> X a > + getState' k = do > + v <- gets $ M.lookup (show . typeOf $ k) . extensibleState > + return $ case v of > + Just (StateExtension val) -> toValue val > + Just (PersistentExtension val) -> toValue val > + Nothing -> initialValue > + > +-- | Remove the value from the extensible state field that has the same type as the supplied argument > +removeState :: ExtensionClass a => a -> X () > +removeState wit = modifyStateExts $ M.delete (show . typeOf $ wit) > hunk ./xmonad-contrib.cabal 223 > XMonad.Util.CustomKeys > XMonad.Util.Dmenu > XMonad.Util.Dzen > + XMonad.Util.ExtensibleState > XMonad.Util.EZConfig > XMonad.Util.Font > XMonad.Util.Invisible > } > [Use X.U.ExtensibleState instead of IORefs > Daniel Schoepe **20091026161500 > Ignore-this: 444ed40abab50fc8d5b80a8def5ddde > > This patch changes SpawnOn, DynamicHooks and UrgencyHooks to > use X.U.ExtensibleState instead of IORefs. This simplifies the > usage of those modules thus also breaking current configs. > ] { > hunk ./XMonad/Actions/SpawnOn.hs 1 > +{-# LANGUAGE DeriveDataTypeable #-} > ----------------------------------------------------------------------------- > -- | > -- Module : XMonad.Actions.SpawnOn > hunk ./XMonad/Actions/SpawnOn.hs 22 > -- * Usage > -- $usage > Spawner, > - mkSpawner, > manageSpawn, > spawnHere, > spawnOn, > hunk ./XMonad/Actions/SpawnOn.hs 31 > ) where > > import Data.List (isInfixOf) > -import Data.IORef > import System.Posix.Types (ProcessID) > > import XMonad > hunk ./XMonad/Actions/SpawnOn.hs 39 > import XMonad.Hooks.ManageHelpers > import XMonad.Prompt > import XMonad.Prompt.Shell > +import XMonad.Util.ExtensibleState > > -- $usage > -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@: > hunk ./XMonad/Actions/SpawnOn.hs 47 > -- > import XMonad.Actions.SpawnOn > -- > -- > main = do > --- > sp <- mkSpawner > -- > xmonad defaultConfig { > -- > ... > hunk ./XMonad/Actions/SpawnOn.hs 49 > --- > manageHook = manageSpawn sp <+> manageHook defaultConfig > +-- > manageHook = manageSpawn <+> manageHook defaultConfig > -- > ... > -- > } > -- > hunk ./XMonad/Actions/SpawnOn.hs 55 > -- To ensure that application appears on a workspace it was launched at, add keybindings like: > -- > --- > , ((mod1Mask,xK_o), spawnHere sp "urxvt") > --- > , ((mod1Mask,xK_s), shellPromptHere sp defaultXPConfig) > +-- > , ((mod1Mask,xK_o), spawnHere "urxvt") > +-- > , ((mod1Mask,xK_s), shellPromptHere defaultXPConfig) > -- > -- The module can also be used to apply other manage hooks to the window of > -- the spawned application(e.g. float or resize it). > hunk ./XMonad/Actions/SpawnOn.hs 64 > -- For detailed instructions on editing your key bindings, see > -- "XMonad.Doc.Extending#Editing_key_bindings". > > -newtype Spawner = Spawner {pidsRef :: IORef [(ProcessID, ManageHook)]} > +newtype Spawner = Spawner {pidsRef :: [(ProcessID, ManageHook)]} deriving Typeable > + > +instance ExtensionClass Spawner where > + initialValue = Spawner [] > > maxPids :: Int > maxPids = 5 > hunk ./XMonad/Actions/SpawnOn.hs 72 > > --- | Create 'Spawner' which then has to be passed to other functions. > -mkSpawner :: (Functor m, MonadIO m) => m Spawner > -mkSpawner = io . fmap Spawner $ newIORef [] > +-- | Get the current Spawner or create one if it doesn't exist. > +modifySpawner :: ([(ProcessID, ManageHook)] -> [(ProcessID, ManageHook)]) -> X () > +modifySpawner f = putState . Spawner . f . pidsRef =<< getState > > -- | Provides a manage hook to react on process spawned with > -- 'spawnOn', 'spawnHere' etc. > hunk ./XMonad/Actions/SpawnOn.hs 78 > -manageSpawn :: Spawner -> ManageHook > -manageSpawn sp = do > - pids <- io . readIORef $ pidsRef sp > +manageSpawn :: ManageHook > +manageSpawn = do > + Spawner pids <- liftX getState > mp <- pid > case flip lookup pids =<< mp of > hunk ./XMonad/Actions/SpawnOn.hs 83 > - Nothing -> doF id > + Nothing -> idHook > Just mh -> do > whenJust mp $ \p -> > hunk ./XMonad/Actions/SpawnOn.hs 86 > - io . modifyIORef (pidsRef sp) $ filter ((/= p) . fst) > + liftX . modifySpawner $ filter ((/= p) . fst) > mh > > mkPrompt :: (String -> X ()) -> XPConfig -> X () > hunk ./XMonad/Actions/SpawnOn.hs 96 > > -- | Replacement for Shell prompt ("XMonad.Prompt.Shell") which launches > -- application on current workspace. > -shellPromptHere :: Spawner -> XPConfig -> X () > -shellPromptHere sp = mkPrompt (spawnHere sp) > +shellPromptHere :: XPConfig -> X () > +shellPromptHere = mkPrompt spawnHere > > -- | Replacement for Shell prompt ("XMonad.Prompt.Shell") which launches > -- application on given workspace. > hunk ./XMonad/Actions/SpawnOn.hs 101 > -shellPromptOn :: Spawner -> WorkspaceId -> XPConfig -> X () > -shellPromptOn sp ws = mkPrompt (spawnOn sp ws) > +shellPromptOn :: WorkspaceId -> XPConfig -> X () > +shellPromptOn ws = mkPrompt (spawnOn ws) > > -- | Replacement for 'spawn' which launches > -- application on current workspace. > hunk ./XMonad/Actions/SpawnOn.hs 106 > -spawnHere :: Spawner -> String -> X () > -spawnHere sp cmd = withWindowSet $ \ws -> spawnOn sp (W.currentTag ws) cmd > +spawnHere :: String -> X () > +spawnHere cmd = withWindowSet $ \ws -> spawnOn (W.currentTag ws) cmd > > -- | Replacement for 'spawn' which launches > -- application on given workspace. > hunk ./XMonad/Actions/SpawnOn.hs 111 > -spawnOn :: Spawner -> WorkspaceId -> String -> X () > -spawnOn sp ws cmd = spawnAndDo sp (doShift ws) cmd > +spawnOn :: WorkspaceId -> String -> X () > +spawnOn ws cmd = spawnAndDo (doShift ws) cmd > > -- | Spawn an application and apply the manage hook when it opens. > hunk ./XMonad/Actions/SpawnOn.hs 115 > -spawnAndDo :: Spawner -> ManageHook -> String -> X () > -spawnAndDo sp mh cmd = do > +spawnAndDo :: ManageHook -> String -> X () > +spawnAndDo mh cmd = do > p <- spawnPID $ mangle cmd > hunk ./XMonad/Actions/SpawnOn.hs 118 > - io $ modifyIORef (pidsRef sp) (take maxPids . ((p,mh) :)) > + modifySpawner $ (take maxPids . ((p,mh) :)) > where > -- TODO this is silly, search for a better solution > mangle xs | any (`elem` metaChars) xs || "exec" `isInfixOf` xs = xs > hunk ./XMonad/Actions/SpawnOn.hs 124 > | otherwise = "exec " ++ xs > metaChars = "&|;" > - > hunk ./XMonad/Config/Sjanssen.hs 28 > strutkey (XConfig {modMask = modm}) = (modm, xK_b) > > sjanssenConfig = do > - sp <- mkSpawner > return . ewmh $ defaultConfig > { terminal = "exec urxvt" > , workspaces = ["irc", "web"] ++ map show [3 .. 9 :: Int] > hunk ./XMonad/Config/Sjanssen.hs 35 > [ ((modm, button1), (\w -> focus w >> mouseMoveWindow w)) > , ((modm, button2), (\w -> focus w >> windows W.swapMaster)) > , ((modm.|. shiftMask, button1), (\w -> focus w >> mouseResizeWindow w)) ] > - , keys = \c -> mykeys sp c `M.union` keys defaultConfig c > + , keys = \c -> mykeys c `M.union` keys defaultConfig c > , layoutHook = modifiers layouts > , manageHook = composeAll [className =? x --> doShift w > | (x, w) <- [ ("Firefox", "web") > hunk ./XMonad/Config/Sjanssen.hs 41 > , ("Ktorrent", "7") > , ("Amarokapp", "7")]] > - <+> manageHook defaultConfig <+> manageDocks <+> manageSpawn sp > + <+> manageHook defaultConfig <+> manageDocks <+> manageSpawn > <+> (isFullscreen --> doFullFloat) > } > where > hunk ./XMonad/Config/Sjanssen.hs 49 > layouts = (tiled Tall ||| (tiled Wide ||| Full)) ||| tabbed shrinkText myTheme > modifiers = smartBorders > > - mykeys sp (XConfig {modMask = modm}) = M.fromList $ > - [((modm, xK_p ), shellPromptHere sp myPromptConfig) > - ,((modm .|. shiftMask, xK_Return), spawnHere sp =<< asks (terminal . config)) > + mykeys (XConfig {modMask = modm}) = M.fromList $ > + [((modm, xK_p ), shellPromptHere myPromptConfig) > + ,((modm .|. shiftMask, xK_Return), spawnHere =<< asks (terminal . config)) > ,((modm .|. shiftMask, xK_c ), kill1) > ,((modm .|. shiftMask .|. controlMask, xK_c ), kill) > ,((modm .|. shiftMask, xK_0 ), windows $ copyToAll) > hunk ./XMonad/Hooks/DynamicHooks.hs 1 > +{-# LANGUAGE DeriveDataTypeable #-} > ----------------------------------------------------------------------------- > -- | > -- Module : XMonad.Hooks.DynamicHooks > hunk ./XMonad/Hooks/DynamicHooks.hs 19 > module XMonad.Hooks.DynamicHooks ( > -- * Usage > -- $usage > - initDynamicHooks > - ,dynamicMasterHook > + dynamicMasterHook > ,addDynamicHook > ,updateDynamicHook > ,oneShotHook > hunk ./XMonad/Hooks/DynamicHooks.hs 26 > ) where > > import XMonad > -import System.IO > +import XMonad.Util.ExtensibleState > > import Data.List > import Data.Maybe (listToMaybe) > hunk ./XMonad/Hooks/DynamicHooks.hs 31 > import Data.Monoid > -import Data.IORef > > -- $usage > -- Provides two new kinds of 'ManageHooks' that can be defined at runtime. > hunk ./XMonad/Hooks/DynamicHooks.hs 42 > -- Note that you will lose all dynamically defined 'ManageHook's when you @mod+q@! > -- If you want them to last, you should create them as normal in your @xmonad.hs@. > -- > --- First, you must execute 'initDynamicHooks' from 'main' in your @xmonad.hs@: > +-- To use this module, add 'dynamicMasterHook' to your 'manageHook': > -- > hunk ./XMonad/Hooks/DynamicHooks.hs 44 > --- > dynHooksRef <- initDynamicHooks > --- > --- and then pass this value to the other functions in this module. > --- > --- You also need to add the base 'ManageHook': > --- > --- > xmonad { manageHook = myManageHook <+> dynamicMasterHook dynHooksRef } > --- > --- You must include this @dynHooksRef@ value when using the functions in this > --- module: > --- > --- > xmonad { keys = myKeys `Data.Map.union` Data.Map.fromList > --- > [((modm, xK_i), oneShotHook dynHooksRef > --- > "FFlaunchHook" (className =? "firefox") (doShift "3") > --- > >> spawn "firefox") > --- > ,((modm, xK_u), addDynamicHook dynHooksRef > --- > (className =? "example" --> doFloat)) > --- > ,((modm, xK_y), updatePermanentHook dynHooksRef > --- > (const idHook))) ] -- resets the permanent hook. > +-- > xmonad { manageHook = myManageHook <+> dynamicMasterHook } > -- > hunk ./XMonad/Hooks/DynamicHooks.hs 46 > +-- You can then use the supplied functions in your keybindings: > +-- > +-- > ((modMask,xK_a), oneShotHook (className =? "example") doFloat) > +-- > > data DynamicHooks = DynamicHooks > { transients :: [(Query Bool, ManageHook)] > hunk ./XMonad/Hooks/DynamicHooks.hs 54 > , permanent :: ManageHook } > + deriving Typeable > > hunk ./XMonad/Hooks/DynamicHooks.hs 56 > +instance ExtensionClass DynamicHooks where > + initialValue = DynamicHooks [] idHook > > hunk ./XMonad/Hooks/DynamicHooks.hs 59 > --- | Creates the 'IORef' that stores the dynamically created 'ManageHook's. > -initDynamicHooks :: IO (IORef DynamicHooks) > -initDynamicHooks = newIORef (DynamicHooks { transients = [], > - permanent = idHook }) > - > - > --- this hook is always executed, and the IORef's contents checked. > +-- this hook is always executed, and the contents of the stored hooks checked. > -- note that transient hooks are run second, therefore taking precedence > -- over permanent ones on matters such as which workspace to shift to. > -- doFloat and doIgnore are idempotent. > hunk ./XMonad/Hooks/DynamicHooks.hs 64 > -- | Master 'ManageHook' that must be in your @xmonad.hs@ 'ManageHook'. > -dynamicMasterHook :: IORef DynamicHooks -> ManageHook > -dynamicMasterHook ref = return True --> > - (ask >>= \w -> liftX (do > - dh <- io $ readIORef ref > +dynamicMasterHook :: ManageHook > +dynamicMasterHook = (ask >>= \w -> liftX (do > + dh <- getState > (Endo f) <- runQuery (permanent dh) w > ts <- mapM (\(q,a) -> runQuery q w >>= \x -> return (x,(q, a))) (transients dh) > let (ts',nts) = partition fst ts > hunk ./XMonad/Hooks/DynamicHooks.hs 72 > gs <- mapM (flip runQuery w . snd . snd) ts' > let (Endo g) = maybe (Endo id) id $ listToMaybe gs > - io $ writeIORef ref $ dh { transients = map snd nts } > + putState $ dh { transients = map snd nts } > return $ Endo $ f . g > )) > hunk ./XMonad/Hooks/DynamicHooks.hs 75 > - > -- | Appends the given 'ManageHook' to the permanent dynamic 'ManageHook'. > hunk ./XMonad/Hooks/DynamicHooks.hs 76 > -addDynamicHook :: IORef DynamicHooks -> ManageHook -> X () > -addDynamicHook ref m = updateDynamicHook ref (<+> m) > - > +addDynamicHook :: ManageHook -> X () > +addDynamicHook m = updateDynamicHook (<+> m) > > -- | Modifies the permanent 'ManageHook' with an arbitrary function. > hunk ./XMonad/Hooks/DynamicHooks.hs 80 > -updateDynamicHook :: IORef DynamicHooks -> (ManageHook -> ManageHook) -> X () > -updateDynamicHook ref f = > - io $ modifyIORef ref $ \dh -> dh { permanent = f (permanent dh) } > - > +updateDynamicHook :: (ManageHook -> ManageHook) -> X () > +updateDynamicHook f = modifyState $ \dh -> dh { permanent = f (permanent dh) } > > -- | Creates a one-shot 'ManageHook'. Note that you have to specify the two > -- parts of the 'ManageHook' separately. Where you would usually write: > hunk ./XMonad/Hooks/DynamicHooks.hs 92 > -- > -- > oneShotHook dynHooksRef (className =? "example) doFloat > -- > -oneShotHook :: IORef DynamicHooks -> Query Bool -> ManageHook -> X () > -oneShotHook ref q a = > - io $ modifyIORef ref > - $ \dh -> dh { transients = (q,a):(transients dh) } > - > - > - > - > +oneShotHook :: Query Bool -> ManageHook -> X () > +oneShotHook q a = modifyState $ \dh -> dh { transients = (q,a):(transients dh) } > hunk ./XMonad/Hooks/UrgencyHook.hs 1 > -{-# LANGUAGE FlexibleContexts, MultiParamTypeClasses, TypeSynonymInstances, PatternGuards #-} > +{-# LANGUAGE FlexibleContexts, MultiParamTypeClasses, TypeSynonymInstances, PatternGuards, DeriveDataTypeable, > + FlexibleInstances #-} > > ----------------------------------------------------------------------------- > -- | > hunk ./XMonad/Hooks/UrgencyHook.hs 75 > import qualified XMonad.StackSet as W > > import XMonad.Util.Dzen (dzenWithArgs, seconds) > +import XMonad.Util.ExtensibleState > import XMonad.Util.NamedWindows (getName) > import XMonad.Util.Timer (TimerId, startTimer, handleTimer) > > hunk ./XMonad/Hooks/UrgencyHook.hs 82 > import Control.Applicative ((<$>)) > import Control.Monad (when) > import Data.Bits (testBit) > -import Data.IORef > import Data.List (delete) > import Data.Maybe (listToMaybe, maybeToList) > import qualified Data.Set as S > hunk ./XMonad/Hooks/UrgencyHook.hs 85 > -import Foreign (unsafePerformIO) > > -- $usage > -- > hunk ./XMonad/Hooks/UrgencyHook.hs 216 > logHook = cleanupUrgents (suppressWhen urgConf) >> logHook conf > } > > +data Urgents = Urgents { fromUrgents :: [Window] } deriving (Read,Show,Typeable) > + > +onUrgents :: ([Window] -> [Window]) -> Urgents -> Urgents > +onUrgents f = Urgents . f . fromUrgents > + > +instance ExtensionClass Urgents where > + initialValue = Urgents [] > + > -- | Global configuration, applied to all types of 'UrgencyHook'. See > -- 'urgencyConfig' for the defaults. > data UrgencyConfig = UrgencyConfig > hunk ./XMonad/Hooks/UrgencyHook.hs 273 > clearUrgents :: X () > clearUrgents = adjustUrgents (const []) >> adjustReminders (const []) > > --- | Stores the global set of all urgent windows, across workspaces. Not exported -- use > --- 'readUrgents' or 'withUrgents' instead. > -{-# NOINLINE urgents #-} > -urgents :: IORef [Window] > -urgents = unsafePerformIO (newIORef []) > --- (Hey, I don't like it any more than you do.) > - > -- | X action that returns a list of currently urgent windows. You might use > -- it, or 'withUrgents', in your custom logHook, to display the workspaces that > -- contain urgent windows. > hunk ./XMonad/Hooks/UrgencyHook.hs 277 > readUrgents :: X [Window] > -readUrgents = io $ readIORef urgents > +readUrgents = fromUrgents <$> getState > > -- | An HOF version of 'readUrgents', for those who prefer that sort of thing. > withUrgents :: ([Window] -> X a) -> X a > hunk ./XMonad/Hooks/UrgencyHook.hs 284 > withUrgents f = readUrgents >>= f > > adjustUrgents :: ([Window] -> [Window]) -> X () > -adjustUrgents f = io $ modifyIORef urgents f > +adjustUrgents f = modifyState $ onUrgents f > > type Interval = Rational > > hunk ./XMonad/Hooks/UrgencyHook.hs 294 > , window :: Window > , interval :: Interval > , remaining :: Maybe Int > - } deriving Eq > + } deriving (Show,Read,Eq,Typeable) > + > +instance ExtensionClass [Reminder] where > + initialValue = [] > > -- | Stores the list of urgency reminders. > hunk ./XMonad/Hooks/UrgencyHook.hs 300 > -{-# NOINLINE reminders #-} > -reminders :: IORef [Reminder] > -reminders = unsafePerformIO (newIORef []) > > readReminders :: X [Reminder] > hunk ./XMonad/Hooks/UrgencyHook.hs 302 > -readReminders = io $ readIORef reminders > +readReminders = getState > > adjustReminders :: ([Reminder] -> [Reminder]) -> X () > hunk ./XMonad/Hooks/UrgencyHook.hs 305 > -adjustReminders f = io $ modifyIORef reminders f > +adjustReminders f = modifyState f > > clearUrgency :: Window -> X () > clearUrgency w = adjustUrgents (delete w) >> adjustReminders (filter $ (w /=) . window) > hunk ./XMonad/Hooks/UrgencyHook.hs 336 > callUrgencyHook wuh w > else > clearUrgency w > - userCodeDef () =<< asks (logHook . config) -- call *after* IORef has been modified > + userCodeDef () =<< asks (logHook . config) > DestroyWindowEvent {ev_window = w} -> > clearUrgency w > _ -> > } > > Context: > > [Changing behaviour of ppUrgent with X.H.DynamicLog > mail@n-sch.de**20090910010411 > Ignore-this: 3882f36d5c49e53628485c1570bf136a > > Currently, the ppUrgent method is an addition to the ppHidden method. > This doesn't make any sense since it is in fact possible to get urgent > windows on the current and visible screens. So I've raised the ppUrgent > printer to be above ppCurrent/ppVisible and dropped its dependency on > ppHidden. > > In addition to that this makes it a lot more easier to define a more > custom ppUrgent printer, since you don't have to "undo" the ppHidden > printer anymore. This also basicly removes the need for dzenStrip, > although I just changed the description. > > -- McManiaC / Nils > > ] > [fix X.U.Run.spawnPipe fd leak > Tomas Janousek **20091025210246 > Ignore-this: 24375912d505963fafc917a63d0e79a0 > ] > [TAG 0.9 > Spencer Janssen **20091026013449 > Ignore-this: 542b6105d6deed65e12d1f91c666b0b2 > ] > [Bump version to 0.9 > Spencer Janssen **20091026004850 > Ignore-this: e9d2eee4ec5df8f52bf8f593ff0d2605 > ] > [README Update to point to wiki changelog, prettify > Wirt Wolff **20091024203550 > Ignore-this: 8a0a1824e67c5b2dbbb23e5061d01ece > ] > [Doc namespace minor updates > Wirt Wolff **20091023184905 > Ignore-this: b3fd7de477f0a9ba6af1d8c78eb47754 > Most signifigant changes are use unversioned links to external html, > fix a couple of key binding examples, and double quotes that should > have been single. > ] > [Docs: use myLayout like template rather than plural > Wirt Wolff **20091023042651 > Ignore-this: 8f1814c42e90e18af636a14751ae2f58 > Despite myLayouts currently being more popular in examples, make > them all myLayout as in man/xmonad.hs to avoid mixing them in the > same module as was done a few places, leading to confusion for some users. > ] > [Use 'ewmh' in relevant configs > Spencer Janssen **20091023035043 > Ignore-this: 7cac9c6c3795a3fb60899db29cc65d08 > ] > [Add ewmh function to set all EWMH settings in one step > Spencer Janssen **20091023034630 > Ignore-this: 4d79c1e156f56882036ce43e70cce6f2 > ] > [Refer to modm as the current modMask > Adam Vogt **20091022041126 > Ignore-this: d097c7dc1746c55e1d4078a7148f9d5a > > This makes the config suggestions consistent with the current template. > ] > [Resolve conflicts between Justin Bogner's C.Desktop patch and latest head. > Daniel Schoepe **20091022115849 > Ignore-this: ba805e9889d6bda5ea873e3537b0111f > ] > [Move EWMH support initialization to a startupHook > Justin Bogner **20091011053538 > Ignore-this: bd35654d0afb0a2fec73b16ab7ac38b1 > > Set EWMH support atoms and the window manager name in a startup hook, > rather than in the log hook: the log hook occurs far too frequently > for it to make sense to set constants with it. > ] > [C.Desktop fix bad escaping and typo > Wirt Wolff **20091022100156 > Ignore-this: 70b51a2d8b4443fa364414630ed074c0 > ] > [C.Desktop doc explaining common desktop config customizations > Wirt Wolff **20091022042748 > Ignore-this: 83d1f026ae4f4b7f5796269b51e98349 > To close http://code.google.com/p/xmonad/issues/detail?id=174 > ] > [Clean keymask in GridSelect(solves issue 318) > Daniel Schoepe **20091021223404 > Ignore-this: 2c315539bf1ae8c427b7856b5fdb2e49 > ] > [Share one StdGen between RGB channels in A.RandomBackground > Adam Vogt **20091020165924 > Ignore-this: 15eef05c9a73d578f5513550757bb8bb > ] > [Document A.RandomBackground > Adam Vogt **20091020165205 > Ignore-this: cb6fb4567abde474fd975a25dca5adc2 > ] > [Bump X11 dependency to 1.4.6.1, to access cursor definitions. > Adam Vogt **20091020161914 > Ignore-this: 60728999fe041302379326494df30921 > ] > [C.Gnome combine with instead of replace Desktop startupHook > Wirt Wolff **20091020092010 > Ignore-this: 99af07c4d36a575570935a0421a0e241 > Now that C.Desktop sets startupHook do both rather than only > gnomeRegister. > ] > [Remove H.SetCursor: U.Cursor is preferred > Adam Vogt **20091019235722 > Ignore-this: 5796fe86879c2ce02ef12150e0a8603a > ] > [Add some haddock formatting in U.Cursor > Adam Vogt **20091019233036 > Ignore-this: 744c36a128b403980e3bc62c9e99d432 > ] > [XMonadContrib: set the default cursor to left_ptr for the Desktop config > Andres Salomon **20090915165753 > Ignore-this: a4f7417c8a4190a0cabdadbd359e217 > ] > [XMonadContrib: add a utility module to set the default cursor > Andres Salomon **20090915165604 > Ignore-this: b0559b7b2617db90506492aa1479cde > > This adds XMonad.Util.Cursor, which defines a function that allows setting > the default mouse cursor. This can be useful for (for example) gnomeConfig, > to ensure that the root cursor is changed from X_cursor to left_ptr. > > ] > [More docs formatting in A.GridSelect > Adam Vogt **20091016203132 > Ignore-this: a0a489c2b65fa2d755b4aca544c3d73a > ] > [In A.GridSelect correct haddocks > Adam Vogt **20091016171159 > Ignore-this: f7f714c42544d9230eb9c9bec86cd36a > ] > [Describe parameters to subLayouts more > Adam Vogt **20091016164937 > Ignore-this: d09f236cb17adf7a9092f1b0e646def3 > ] > [Refer to modMask as modm in L.SubLayouts sample keybinds > Adam Vogt **20091016164737 > Ignore-this: 3a8366f7d8f337be750b4db61a454991 > ] > [Format L.SubLayout TODO > Adam Vogt **20091016155837 > Ignore-this: 4dfa10aa2f7087658b6a93299f75310 > ] > [Add more links in L.SubLayout documentation > Adam Vogt **20091016155518 > Ignore-this: 70347cc0bcf4966e6c07f45740882087 > ] > [Link a screenshot in L.SubLayouts from the haskellwiki > Adam Vogt **20091016150539 > Ignore-this: c58b64c5c5f28f4d71c9e8498965ca9e > ] > [Added focusMaster to BoringWindows > Jan Vornberger **20091015233518 > Ignore-this: 7f99337fc63cdc7c861fdc3c2ab2d3d1 > ] > [Remove NamedFieldPuns from L.LimitWindows > Adam Vogt **20091015010123 > Ignore-this: 228ca5b5ac067876c3b2809fc03b6016 > > This is more ugly, but otherwise we have lots of trouble for ghc-6.8 > compatibility (due to the recomended flag having changed) > ] > [added prop_select_two_consec to test_Selective.hs > Max Rabkin **20091001155853 > Ignore-this: 80e2b5d8658dc053c66993be970e6247 > ] > [Note L.Minimize in L.LimitWindows haddocks. > Adam Vogt **20091014205326 > Ignore-this: 83a809d2467a286e0c1a133be947add9 > ] > [Move limitSelect into L.LimitWindows > Max Rabkin **20091014202213 > Ignore-this: 51d6e9da4a6a4f683cd145371e90be17 > ] > [added haddocks for L.Selective > Max Rabkin **20091002112720 > Ignore-this: d29016f1261d0176634bb040fcc1836a > ] > [Support IncMasterN in Selective > Max Rabkin **20090929173346 > Ignore-this: 3fd288d0062905177c06006ea4066f6d > ] > [removed commented-out code > Max Rabkin **20090929163509 > Ignore-this: 776b1566626660b639f8933980f5a3a1 > ] > [Test that update preserves invariants of Selection > Max Rabkin **20090929163139 > Ignore-this: 340b2a1465b9fc98cdc386b511ce26bb > ] > [move updateSel from test_Selective into Selective > Max Rabkin **20090929160420 > Ignore-this: 6636f2f2d5aa15a6d0ef6d45ee38aa42 > ] > [Add "Selective" layout modifier > Max Rabkin **20090929160207 > Ignore-this: ded23208563ca8c8d411916d01351132 > ] > [Filter extra modifier bits some layouts set in XMonad.Prompt > Daniel Schoepe **20091012132814 > Ignore-this: c0898809766061700c11f6da84c74bed > ] > [Cleanup L.BorderResize > Adam Vogt **20091012055532 > Ignore-this: 7d369ed3050543a5c30a64991b7bf6f5 > ] > [Layout modifier to resize windows by dragging their borders with the mouse > Jan Vornberger **20091011222214 > Ignore-this: 5cf197ea14b7c502fa13a16773215762 > ] > [Add U.Replace which implements a --replace behavior. > Adam Vogt **20091012052306 > Ignore-this: bd519abe3250a01507f225a29c08048a > ] > [Update D.Extending module lists with help of a script (also added) > Adam Vogt **20091012044918 > Ignore-this: c280d3047355be962e8ef706d598aa43 > ] > [Correct erroneous haddock link in U.XSelection > Adam Vogt **20091012043133 > Ignore-this: e5c905104741d14dbb411272c37e0e29 > ] > [Make L.Mosaic explicit imports compatible with haskell-src-exts > Adam Vogt **20091012042859 > Ignore-this: 85ca9ff7fc924e6291edb05f4a1de77c > ] > [Put screenshots inline for L.ThreeColumns and L.Roledex > Adam Vogt **20091012042651 > Ignore-this: df314db757ad09bb7185c16cca8649d3 > ] > [Use LANGUAGE pragma instead of -fglasgow-exts in L.Minimize > Adam Vogt **20091012042457 > Ignore-this: cbb454ab573b1e1f931d79c322fa1303 > ] > [Add a description to L.LayoutScreens > Adam Vogt **20091012042231 > Ignore-this: beceb2f65206079fae6421c5df0fb439 > ] > [Add Portability and Stability boilerplate for a couple modules. > Adam Vogt **20091012041055 > Ignore-this: 7d875c5e47535a11e26f9a604a01fe88 > > Needed for automating the generation of the Doc.Extending module summaries. > ] > [Correct hyperlink in A.DeManage > Adam Vogt **20091012040340 > Ignore-this: db08eba0253f94e5ce9cbcf3632b387a > ] > [NoFrillsDecoration - most basic version of decoration for windows > Jan Vornberger **20091011220512 > Ignore-this: accda53da08f37d6b4091d1c6e17e2c1 > ] > [Split A.TopicSpace documentation into sections > Adam Vogt **20091012004730 > Ignore-this: 312066f68e7051a8ee89cbbec40ce2a0 > ] > [Use hyperlinks in WorkspaceCursors documentation. > Adam Vogt **20091008032047 > Ignore-this: d698d86d01d9a69652fa3aa732873299 > ] > [Minor haddock formatting correction in L.Tabbed > Adam Vogt **20091008024839 > Ignore-this: 8084aebbae198eda3d455ab541e94169 > ] > [Hyperlink the reference to ResizableTile in MouseResizableTile > Adam Vogt **20091005175303 > Ignore-this: 8d98176fd0b78ef3565a6f9556e220b8 > ] > [Finish a sentence in H.ManageDocks haddocks. > Adam Vogt **20091005165312 > Ignore-this: 43f4ffc627b3db204d74ed361ef939cf > ] > [Add a SetStruts message to H.ManageDocks. > Adam Vogt **20091005164221 > Ignore-this: 98a76bb48b8a569b459cadc4e6412c06 > > This patch also uses Data.Set instead of [] for the AvoidStruts > constructor to simplify the SetStruts implementation. > ] > [Derive Enum for U.Types.Direction2D > Adam Vogt **20091005163132 > Ignore-this: 258e35a6f23f46039b9a8ee45187cdff > ] > [Rearrange the GSCONFIG class in A.Gridselect > Adam Vogt **20091005023227 > Ignore-this: 875080c8beabb81e19de44f7e60ca19d > ] > [Add a GSCONFIG class to overload defaultGSConfig. > Adam Vogt **20091003193804 > Ignore-this: 220a13bf1ee145b18f28c66e32c79266 > > This uses -XOverlappingInstances to provide a fallback instance which uses the > focusedBorderColor and normalBorderColor, but that part is optional. > > User's configs should use -XNoMonomorphismRestriction if they want to avoid > writing a type signature for myGSConfig. > > Also, type variables become ambiguous in expressions like: > > > myGSConfig = defaultGSConfig { gs_navigate = neiu `M.union` gs_navigate defaultGSConfig } > > where neiu = M.map (\(x,y) (a,b) -> (x+a,y+b)) $ M.fromList > > [((0,xK_n),(-1,0)) ,((0,xK_e),(0,1)) ,((0,xK_i),(1,0)) ,((0,xK_u),(0,-1))] > > But that can be resolved with the appropriate (`asTypeOf`myGSConfig) applied to > the second defaultGSConfig, or the use of some other method for modifying > existing fields. > ] > [Add a screenshots section in the A.GridSelect haddocks > Adam Vogt **20091004160816 > Ignore-this: be358c0173df3d02b45526c134604f4e > ] > [Fixed guard in WorkspaceByPos - condition got switched during transformation > Jan Vornberger **20091004085232 > Ignore-this: 6685ef8ddff55c7758c2b77cfc65cbba > ] > [A.CycleWindows update docs, use lib fn second instead of custom lambda > Wirt Wolff **20090926154700 > Ignore-this: 7ec0d6a46d4a6255870b1e9c4a25c1bb > ] > [Group functions in GridSelect haddock, add an inline screenshot. > Adam Vogt **20091003181927 > Ignore-this: 3c6f1c5aff4fe197aa965cbda23e1be7 > ] > [minor hlint cleanup of Prompt and XMonad.Prompt.* sub-modules > sean.escriva@gmail.com**20090928204443 > Ignore-this: 25e71f59bdcc5bf94c2d6f476833216b > ] > [New module : X.H.SetCursor > mail@n-sch.de**20090915101327 > Ignore-this: 2f0641155ada05dae955cd6941d52b70 > Idea from Andres Salomon > (http://www.haskell.org/pipermail/xmonad/2009-September/008553.html). > ] > [Hyperlink modules named in WindowMenu, RestoreMinimized, and Minimize > Adam Vogt **20091003151325 > Ignore-this: 5eb1496fd258fa0c43fb0a58136ccfff > ] > [Mention X.L.Maximize and X.L.Minimize in WindowMenu documentation > Jan Vornberger **20091003111330 > Ignore-this: 3a00a896509aa8646ae718005d7a1fc1 > ] > [Small style change in L.SimplestFloat > Adam Vogt **20091002001552 > Ignore-this: d8be5d01d47833c70d220e0f1555c42f > ] > [Use U.XUtils.fi to make WindowMenu clearer > Adam Vogt **20091001225736 > Ignore-this: 63e73cd7c5de22b3e30e63c1e588e403 > ] > [Extended GridSelect > Jan Vornberger **20090930152741 > Ignore-this: 2999d891387e4db9746061b1a42264a4 > 1) Added another convenience wrapper that allows to select an X() action > from a given list. > 2) Implemented the option to change the position of the selection diamond. > (Re-recorded from Bluetile repo, rebased to current darcs) > ] > [WindowMenu based on GridSelect that displays actions for the focused window (re-recorded from Bluetile repo). > Jan Vornberger **20090930155343 > Ignore-this: b12a06c0321f3e9689ab8109a1fac0ac > ] > [Use default handler in XMonad.Prompt.eventLoop > Daniel Schoepe **20091001180402 > Ignore-this: 10c9c856aec515d57f0f0a42bc727f1 > ] > [Remove redundant parentheses from L.MouseResizableTile > Adam Vogt **20090930212110 > Ignore-this: 1853cde69ec03ce5b88726b4de05f2b0 > ] > [Use ErrorT instead of nested case for H.WorkspaceByPos > Adam Vogt **20090930204914 > Ignore-this: c3f96fbbf0ce917c4962b297dea3b174 > ] > [Note that ManageDocks is preferred to A.DeManage > Adam Vogt **20090930204443 > Ignore-this: dcb9e069a65980f83941ca58607a6ce5 > ] > [Factor out redundancy in L.MouseResizableTile.handleResize > Adam Vogt **20090930204151 > Ignore-this: 77d8e635a06237b220f427fa64045a3a > ] > [In a multi-head setup, move windows with a non-zero position upon creation to the right workspace. > Jan Vornberger **20090930123341 > Ignore-this: 4efdb9d64f33d70c48fb3797b635513e > Useful in a dual-head setup: Looks at the requested geometry of > new windows and moves them to the workspace of the non-focused > screen if necessary. > ] > [Use LANGUAGE instead of -fglasgow-exts in L.MouseResizableTile > Adam Vogt **20090930200443 > Ignore-this: 861364005402c2c34a20495dd2bb81f8 > ] > [Remove redundant ($) in A.Commands > Adam Vogt **20090930200311 > Ignore-this: 63084d42007481b0e0ca5fd99d3ba083 > ] > [Fix haddock parse error in MouseResizableTile > Adam Vogt **20090930200143 > Ignore-this: 34d9bbabcf48424121387e87931bf973 > ] > [A ResizableTile-like layout that can be resized using the mouse. > Jan Vornberger **20090930121105 > Ignore-this: 8941ecfb0e5653663db29e9f195e23f2 > All separations between windows can be dragged to modify the layout. > Keyboard commands can also be used to achieve the same effect. > ] > [Replaced more stuff in X.L.Maximize with pure versions > Jan Vornberger **20090516233557 > Ignore-this: ffafa9ce65efb2639a147493fb49c7e1 > ] > [Expanded on X.L.Maximize functionality > Jan Vornberger **20090503001052 > Ignore-this: b0d765b3bf6fc1e72cedebfd564236fc > 1. Move maximized window into the background when it's not focused. > 2. Changed semantics so that maximizing a different window will > automatically restore the currently maximized window and maximize the > new one (previously this had to be done in two seperate steps). > ] > [EventHook to restore minimized windows from taskbar (re-recorded from Bluetile repo) > Jan Vornberger **20090928231549 > Ignore-this: 673b003c4e07b591046ed01e5f27a7ec > ] > [LayoutModifier to minimize windows (re-recorded from Bluetile repo) > Jan Vornberger **20090928231320 > Ignore-this: 45830f2bf3bb8473c569582593844253 > ] > [Correctly check completionKey field in XMonad.Prompt > Daniel Schoepe **20090928093215 > Ignore-this: 99e68a63fe156650cc8e96d31e6d1f5a > ] > [Fix for issue 315 > Daniel Schoepe **20090928091946 > Ignore-this: 7de748d6cbd143b073451ba92ecec659 > ] > [Only use search history for completion in X.A.Search > Daniel Schoepe **20090920221455 > Ignore-this: 807fcd4fa14a25ecc9787940f9950736 > ] > [Fix regression in XMonad.Prompt's completion > Daniel Schoepe **20090920205711 > Ignore-this: 3c0e5a1f843be1981ecc3d40d43530d1 > ] > [Clean keymask before use in XMonad.Prompt > Daniel Schoepe **20090920201229 > Ignore-this: 80903452f15352aef025b9979793fb8a > ] > [Export moveCursor in XMonad.Prompt > Daniel Schoepe **20090920192513 > Ignore-this: 7732b0444b26cd653190bb3a6e69346c > ] > [U.EZConfig: Correct additionalKeysP M2-M5 values > Wirt Wolff **20090906070503 > Ignore-this: 938c9739a8e00c07195890938e7c12fc > Was 8,9,10,11,12 rather than needed 8,16,32,64,128 > ] > [Factor out direction types and put them in X.U.Types > Daniel Schoepe **20090919191717 > Ignore-this: b2255ec2754fcdf797b1ce2c082642ba > > This patch factors out commonly used direction types like > data Direction = Prev | Next > and moves them to X.U.Types. > ] > [Add function to disable focusFollowsMouse conditionally > Daniel Schoepe **20090829212916 > Ignore-this: de73003672f76d955fe4476ca279cded > > This patch adds an event hook to have the focus follow the mouse only > if a given condition is true. > ] > [Make the keymap of XMonad.Prompt customizable > Daniel Schoepe **20090910160828 > Ignore-this: 37c04043518d7e4e06b821b3438cbe03 > > This patch allows the user to change the keymap XMonad.Prompt and > related modules use to be customized using the XPConfig structure. > ] > [Run gnomeRegister from startupHook > Spencer Janssen **20090918023410 > Ignore-this: 419959a33840264674d2c8034882b689 > ] > [Use U.Run.safeSpawn in C.Gnome > Adam Vogt **20090917233953 > Ignore-this: b2476a239089a3fd3fe9001cf48e8f09 > ] > [Add gnomeRegister to C.Gnome. > Adam Vogt **20090917232150 > Ignore-this: 5b2960004418c04bdbb921e3aa777fc2 > > Credit to Joachim Breitner here: > http://www.haskell.org/pipermail/xmonad/2009-May/007984.html > ] > [Remove excess broadcastMessage ReleaseResources from A.Commands > Adam Vogt **20090904010259 > Ignore-this: e55e16750bd1ee116760559680495b46 > > XMonad.Operations.restart tells the layouts to release resources. There's no > sense in duplicating it in contrib code anymore. > ] > [Mark modules last-modified in 2007 as stable > Adam Vogt **20090904005147 > Ignore-this: 53f7fde5684cd9f105cf4e3ce0d849d2 > > http://www.haskell.org/pipermail/xmonad/2009-July/008328.html > ] > [Minor changes to my config > Spencer Janssen **20090901024802 > Ignore-this: 5196fb217e72153fc4fb32fb40ab18f > ] > [Return True in X.H.FadeInactive.isUnfocused if current workspace is empty. (dschoepe) > Adam Vogt **20090828214537 > Ignore-this: 56a3dac874f6430f10ad23870a4be38a > ] > [Actually execute the correct command when giving user-defined commands to ServerMode > Jan Vornberger **20090825233828 > Ignore-this: 571e4d3ec5bcae56987c6e3b85b800b6 > ] > [Preserve backwards compatibility with H.ServerMode > Adam Vogt **20090825220348 > Ignore-this: cd5df0c49e1d0f07ede1994da9c4c865 > ] > [Let the user decide which commands to use in X.H.ServerMode > Daniel Schoepe **20090825101630 > Ignore-this: 3a1b95f85253ce6059f4528e23c5a3d3 > ] > [Improve/correct documentation in X.A.TagWindows > Daniel Schoepe **20090823131229 > Ignore-this: e9adb7bf77eeebff42f564390c6ceedc > ] > [Replace nextEvent with maskEvent to prevent GridSelect from swallowing unrelated events (such as map/unmap) > Clemens Fruhwirth **20090809131055 > Ignore-this: 6c3bc2487e4f011e0febe0935c223f2 > ] > [Better default for ppUrgent in xmobarPP > Daniel Schoepe **20090822183416 > Ignore-this: ffdfad360d8fd5c5bfa38fd0549b8f19 > > Most users would expect workspaces with urgent windows to be highlighted in > xmobar when they set up an UrgencyHook. Hence, doing this by default in xmobarPP > makes sense. (dzenPP does the same) > ] > [Add backwards compatability in X.H.FadeInactive > Daniel Schoepe **20090821225646 > Ignore-this: d2ef91429d80fde5126b2aa8f0de9b1f > ] > [More flexible interface for X.H.FadeInactive > Daniel Schoepe **20090821203936 > Ignore-this: e905086d3fb640cbccf4eec2f11f293 > > This patch allows setting the opacity on a per-window basis and lets the > user specify it as a percentage instead of an Integer between 0 and 2^32-1. > ] > [U.Scratchpad: doc add disable-factory flag to gnome-terminal example > Wirt Wolff **20090818192503 > Ignore-this: 6fd874a236121b5669b0ec5944caf205 > Few systems have --disable-factory on by default, but it's needed to > set custom resource string. > http://code.google.com/p/xmonad/issues/detail?id=308 > ] > [A.CycleWS: add toggleOrView fns, fix doc, prevent head exception > Wirt Wolff **20090817215549 > Ignore-this: 35acc32e696e665aca900721d309d1d3 > ] > [Add -fwarn-tabs to ghc-options for the regular build > Adam Vogt **20090814022108 > Ignore-this: 203ea4e54936f8bb6c3c28446d069f88 > ] > [Don't use tabs in EwmhDesktops > Daniel Schoepe **20090813200119 > Ignore-this: 59b1ade240aa75cf448620cd7a37579b > ] > [Do not warn about unknown ClientMessageEvents > Joachim Breitner **20090812222917 > Ignore-this: d02940888cd54cf209d6e5f4847548ab > Not all client messages are are meant to be handled by the wndow manager, so do > not complain when one is unknown. > ] > [ScratchpadRewrite > konstantin.sobolev@gmail.com**20090428200136 > Ignore-this: 17c946c04dae72f0873f0f5bb56c9f37 > Scratchpad reimplementation in terms of NamedScratchpad. No interface changes. > ] > [NS_Placement > konstantin.sobolev@gmail.com**20090428192731 > Ignore-this: 7cf2d8d956c8e906b41731632db67e2a > Added ability to specify scratchpad manage hooks, mostly for defining window placement in a more flexible manner > ] > [ThreeColMid - Swap slave window positions > Anders Engstrom **20090503195026 > Ignore-this: f2673e83386bc0e5d398d4e875537cc8 > This patch will swap the positions of the two slave windows and this will result in a more intuitive window order. When using focusDown beginning in the master pane we will move in the following graphical order 2->3->1->2->3 instead of 2->1->3->2->1. This is backwards from what is expected. > > The small drawback is that increasing from 2 to 3 windows (and therefore also columns) will behave in a less intuitive way. The window in the right column will jump to the left of the screen. > > I think that it is a good idea to make this change since I rely a lot on the window order but people using WindowNavigation may be of a different opinion. > > An alternative is to add an option to select in what way to behave, but that could be overkill... I leave it up to discussion and devs to decide. > ] > [fix UrgencyHook docs (\a -> \\a in Haddock) > Brent Yorgey **20090809184016 > Ignore-this: a1fcfe2446184a8cea4553fd68565b58 > ] > [XMonad.Actions.Search: removeColonPrefix shouldn't throw an exception if no :! > gwern0@gmail.com**20090808002224 > Ignore-this: db0a25c0d615c3d8cb6ef31489919d91 > ] > [XMonad.Actions.Search: clean up hasPrefix - dupe of Data.List.isPrefixOf > gwern0@gmail.com**20090808002120 > Ignore-this: 3327a19e5aa23af649ce080fc38a7409 > ] > [XMonad.Actions.Search: +wikt > gwern0@gmail.com**20090808000622 > Ignore-this: cee8b1325820ea1f513ae18d840b4c48 > ] > [NoWrap export patch for use with X.L.MessageControl > quentin.moser@unifr.ch**20090128004726 > Ignore-this: 2b76afa0547aaed5fb39454a074ec4c3 > ] > [new XMonad.Layout.MessageControl module > quentin.moser@unifr.ch**20090128013917 > Ignore-this: cc28e0def6c797f6d1da8f23469a4f8 > ] > [U.NamedActions: align the descriptions for each section, refactor its integration with EZConfig > Adam Vogt **20090726032003 > Ignore-this: f7132388b1f1fd2dbf03885ffa534c20 > ] > [U.NamedActions support subtitles bound to (0,0) unreachable normally > Adam Vogt **20090525002915 > Ignore-this: fdb9f0f07663854049cade2f0f7c2ebd > ] > [Add U.NamedActions: present a list of keybindings including submaps > Adam Vogt **20090504024017 > Ignore-this: 181c3ee603c82e0c56406ba8552fd394 > ] > [Revert to old behavior where unmatched keys do not exit the eventloop for A.GridSelect > Adam Vogt **20090727012302 > Ignore-this: 936cfd1e1b6243ced54e356f8067fac > ] > [Share more mkAdjust calls L.LayoutHints in the LayoutHintsToCenter modifier > Adam Vogt **20090726061802 > Ignore-this: baa33d5b38a7811b9f50b7d0f808ee75 > ] > [Make direction keybindings configurable in A.GridSelect > Adam Vogt **20090726020438 > Ignore-this: 9cd675485270ccebec22df72eea40578 > ] > [LayoutBuilder - make an example more sane > Anders Engstrom **20090513155732 > Ignore-this: 772566441df97479c49b6b149b57fc27 > ] > [Clean Xkb masks in X.A.Submap > Khudyakov Alexey **20090623164653 > Ignore-this: 930e2bca230d5f403bf9c06650afc57b > > Xkb adds its own mask and prevent Submap keybindings from normal > functioning when alternate layout is used. This patch cleans > these masks. > > ] > [Fix defaulting warning with A.RandomBackground > Adam Vogt **20090716234955 > Ignore-this: 55dddcc134aa173d2c8e015fc462ff99 > ] > [Addition of Machine window property. > Juraj Hercek **20090715105053 > Ignore-this: d71d82bac7cc59ef462e728adaf5db01 > > This patch adds WM_CLIENT_MACHINE property to window properties. > I can be used to distinguish windows run from different machines. > ] > [remove myself as maintainer from code I don't maintain. > David Roundy **20090716153409 > Ignore-this: 362988aeca1996474942fa29ffcccbce5e543e57 > ] > [X.A.CopyWindow: add wsContainingCopies, doc cleanup > wirtwolff@gmail.com**20090703011524 > Ignore-this: 883899013707737d085476637a44695a > Use wsContainingCopies in a logHook to highlight hidden workspaces > with copies of the focused window. (refactored from original by aavogt) > ] > [Correct license for L.CenteredMaster > Adam Vogt **20090708051616 > Ignore-this: 31136b901a7dc476ea337678cbc8637f > > Context for why I've recorded the patch: > aavogt | portnov: did you get the message about your XMonad.Layout.CenteredMaster licence being not compatible with the licence of contrib? > portnov | aavogt: yep. Could you change that yourself? I allow this to be distributed as bsd3. Making so small patch and sending it will get to much time :) > portnov | *so > aavogt | I can change it, its more about whether you would allow the change to be made > aavogt | but I guess this clears it up > portnov | i allow. > ] > [Remove trailing whitespace from many modules > Adam Vogt **20090705201205 > Ignore-this: 1e28ff0974578d329bd3d593c1a5125e > ] > [Clarify documentation the Migrate message added to L.SubLayouts > Adam Vogt **20090705180014 > Ignore-this: 1d47165904048edfe28414ec5ce7f3e > ] > [Reduce a bit of recently introduced duplication in L.SubLayouts > Adam Vogt **20090705175145 > Ignore-this: e87a5643938183eff156e08646cc71ac > ] > [Add Migrate message to L.SubLayouts, for better support of moving windows between groups > Adam Vogt **20090705174934 > Ignore-this: d76b2f3e5999999a489b843b4dde59f1 > ] > [L.SubLayouts: also run the layout being modified in a restricted environment > Adam Vogt **20090705174156 > Ignore-this: 9defa5b6a59ed84a15f733bd979e1c45 > > This way, correct behavior can be expected if the layout runs ex. 'withWindowset > W.peek', instead of looking at its arguments. > ] > [L.SubLayouts fix bug where previously run layouts would not get messages > Adam Vogt **20090705173504 > Ignore-this: 1d54ddb6596173f2fb6f30a648d7f3ba > ] > [Simplify A.WorkspaceCursors use of layout for state, add documentation > Adam Vogt **20090705050629 > Ignore-this: 5a4cb6f165edd266a55e42ccedc8c0a7 > ] > [Add A.WorkspaceCursors, a generalization of Plane to arbitrary dimensions > Adam Vogt **20090702042609 > Ignore-this: 54225917a34aa0785a97c8153ff32ab9 > > This is implemented as a layoutModifier, since that way the workspace > arrangment is preserved between restarts. > ] > [Add ability to copy the entered string in X.Prompt > Daniel Schoepe **20090709100703 > Ignore-this: 4e8b98f281001d7540617d0ff6a3d4f3 > ] > [Refactor A.OnScreen to use Maybe Monad > Adam Vogt **20090703021507 > Ignore-this: d45331ad77662b356f12b3912ea3eac0 > ] > [Added XMonad.Actions.OnScreen > mail@n-sch.de**20090702101621 > Ignore-this: 605666aeba92e1d53f03a480506ddf2f > ] > [Remove code duplication in X.A.CopyWindow > Daniel Schoepe **20090702104933 > Ignore-this: cbbbe68690dbb4b814cd48fa32d4720 > ] > [Cleanup code duplication in X.P.Layout and X.P.Workspace > sean.escriva@gmail.com**20090701215640 > Ignore-this: 8675be8952f8d100c9042bdcdb962d3a > ] > [X.A.Search: use the new canonical package URL for hackage search > Brent Yorgey **20090629192455] > [X.H.ManageHelpers: add two new helper functions, doFloatDep and doFloatAt > Brent Yorgey **20090605030113] > [Keep track of whether messages should be given to new sublayouts in L.SubLayouts > Adam Vogt **20090628060608 > Ignore-this: 647184c1b7f65c262c8cc15fdd0829d5 > ] > [Run sublayouts in L.Sublayouts in a restricted state > Adam Vogt **20090628060333 > Ignore-this: f2a236d3dc0374bbc1c19b864baa7c86 > ] > [A.RandomBackground: Parameterize randomBg by a RandomColor data > Adam Vogt **20090629004147 > Ignore-this: ba8042aa0f5d3221583aead9dced6cc > ] > [Add A.RandomBackground, actions to start terminals with a random -bg option > Adam Vogt **20090627202755 > Ignore-this: a90c98bb14a2f917d8552cd2563aeb49 > ] > [Replace most -fglasgow-exts with specific LANGUAGE pragmas > Adam Vogt **20090626025457 > Ignore-this: 2274fdd689b0576a76d9f3373e9c7159 > ] > [Column_layout.dpatch > portnov84@rambler.ru**20090605184515 > Ignore-this: ea5ebf0d6e8ac5c044d9291b3c55479d > This module defines layot named Column. It places all windows in one > column. Windows heights are calculated from equation: H1/H2 = H2/H3 = ... = q, > where `q' is given (thus, windows heights forms a geometric progression). With > Shrink/Expand messages one can change the `q' value. > > ] > [X.A.Search: add Google "I'm feeling lucky" search > Brent Yorgey **20090625173751 > Ignore-this: 98bbdd4fbf12d7cd9fad6645653cb84b > ] > [Use -fwarn-tabs for test, remove tabs > Adam Vogt **20090624043831 > Ignore-this: 84dfa0d9d50826527abbe7ff6acf4465 > ] > [Add ifWindow and ifWindows and simplify WindowGo > Daniel Schoepe **20090624231711 > Ignore-this: 4ed6e789034db8804accfe06a47ef4a2 > > This patch adds ifWindow and ifWindows as helper functions to > X.A.WindowGo and removes some boilerplate by rewriting other functions > in terms of those. Also some minor simplifications. > ] > [From A.Topicspace split functions for storing strings with root to U.StringProp > Adam Vogt **20090623052537 > Ignore-this: 543b172fbefa9feded94d792d01921c4 > > These functions will be used to send strings for execution by command line, in > xmonad-eval > ] > [Correct A.TopicSpace sample config > Adam Vogt **20090623003937 > Ignore-this: 68a6fed2943eb9982e32815168b6f297 > ] > [Add shiftNthLastFocused to A.TopicSpace > Adam Vogt **20090623002645 > Ignore-this: 64f4fa63f4cc25f634f8fbc3276ef2a2 > ] > [update callers of safeSpawn > gwern0@gmail.com**20090622201423 > Ignore-this: 484eca17b9877f7d587fc5bce8c5ae8a > ] > [XMonad.Util.Run: improve definition so this can be used with emacs > gwern0@gmail.com**20090622201401 > Ignore-this: 984788359376e3d2bab0d1e86ff1276f > ] > [XMonad.Actions.WindowGo: switch to safeSpawn, since everyone just passes a prog name (no shell scripting) > gwern0@gmail.com**20090622193255 > Ignore-this: 5515c72649471fac1ffcf4b68e1e0cf9 > ] > [XMonad.Util.Run: +convenience function for safeSpawn which drops args to the prog > gwern0@gmail.com**20090622193018 > Ignore-this: fc48265f252e015ffdc1792c6c9eaa12 > ] > [XMonad.Actions.WindowGo: improve haddocks > gwern0@gmail.com**20090622192831 > Ignore-this: 28dc1d5b094d50eaf6148fa9cc2d3755 > ] > [Generalize Actions.SpawnOn > Daniel Schoepe **20090622183825 > Ignore-this: 8cfd0a4664ece5d721f52c59d4759a5f > > Actions.SpawnOn can now be used to execute arbitrary manage hooks on > the windows spawned by a command(e.g. start a terminal of specific size > or floated). > ] > [Fix window ordering bug in L.LimitWindows > Adam Vogt **20090622004309 > Ignore-this: 7bcfffe335b765c081c18b103d9d450a > ] > [L.LimitWindows add usage information, functions to modify the limit > Adam Vogt **20090622000115 > Ignore-this: 813473c5f42540ed0d575bb273f8652 > ] > [Expand Tabbed documentation to describe mouse clicks processing > Dmitry Astapov **20090621211947 > Ignore-this: 185a5dba1c1333aa4a2e778f34417c39 > ] > [Close tabs by middle click on tab decoration > Dmitry Astapov **20090621195225 > Ignore-this: e3fb5d78b766f63a20ab4db064d8285c > > I'd better do it in xmonad.hs, but I can't decide what to expose from > Tabbed.hs to make it happed. Suggestions on how to make mouse click > handling hook a part of the Tabbed creation interface are very welcome > - my attempts turned out to be ugly in extreme. > ] > [Provide means to find original window by its decoration. > Dmitry Astapov **20090621194652 > Ignore-this: fad8cb7fb4c2785b14b97d48f19604cc > > In order to enable user to write custom `decorationMouseFocusHook' and > `decorationMouseDragHook' hooks we need to provide him with means to > lookup original window by its decoration. > > Module Decoration has internal function `lookFor' for exactly the same > purpose. I exported it under a slightly different name and without > exposing internals of DecorationState. > ] > [Remove Hooks.EventHook > Daniel Schoepe **20090618104318 > Ignore-this: 14c32fddc8b7b0561e97eb1d09e27fd7 > > The Hooks.EventHook module is superseded by handleEventHook from core and should no longer be needed. > ] > [Add L.LimitWindows layout modifier > Adam Vogt **20090619052731 > Ignore-this: e91c07885f0ab662f70e0ebd82fb7a5d > ] > [use 'take 1' instead of custom truncHead function in L.WindowNavigation > Adam Vogt **20090618010118 > Ignore-this: ecbb2063337bb87108c12a3c3f8ceeba > ] > [Correct many typos in the documentation, consistent US spellingg > Adam Vogt **20090618003729 > Ignore-this: cf6dcf340fa6cc010f7879f188d376f5 > ] > [minor typo in ./XMonad/Layout/StackTile.hs > Joachim Breitner **20090617210345 > Ignore-this: ddb5dff32e332cf378f2204e23335d43 > ] > [X.L.ResizableTile: make sure windows aren't resized to a height larger than the screen (fixes #298) > Brent Yorgey **20090604123509] > [X.A.PhysicalScreens: fix typo > Roman Cheplyaka **20090602172148] > [X.L.AutoMaster: fix warning > Roman Cheplyaka **20090602171754] > [AutoMaster.dpatch > Ilya Portnov **20090426155401 > Ignore-this: e5cbb04882671d6fcc56f181f7d0d292 > Provides layout modifier AutoMaster. It separates screen in two parts - > master and slave. Size of slave area automatically changes depending on > number of slave windows. > ] > [UpdatePointer - Don't warp while dragging with mouse > Anders Engstrom **20090530185752 > Ignore-this: 4c3769dc96041608660789573b670c23 > ] > [FlexibleResize - Resize from edge, don't move adjust at opposite edge > Anders Engstrom **20090530185437 > Ignore-this: 3c6c0748a4b0d14bd39bcb88f10aade6 > > When resizing other corners than bottom-right, instead of adjusting to even columns/rows on the opposite side to it the same way as if resizing was made from the bottom right. > > Also add the possibility to add an area in the middle of an edge where only that edge is resized, not the closest corner. > > ] > [Remove USE_UTF8 defines. > Khudyakov Alexey **20090419130909 > They are not needed any more since utf8-string is mandatory dependence. > ] > [FloatSnap - calculate gaps instead of snapping against unmanaged windows > Anders Engstrom **20090526222942 > Ignore-this: 4378f4c6c4f383c9a35acb503409d865 > > This patch will remove snapping against unmanaged windows, but instead calculate a new rectangle with all gaps (computed by ManageDocks) removed. This new rectangle is used to snap against. (Both the inside and outside of the rectangle.) > > This will remedy the issue of snapping against multiple layers of the same window, additionally there will be no snap-points between windows on the same side. So if you are running two dzen side by side with half the screen each. You will not automatically have a snap-point in the middle. > > Naturally, this patch will change which function is exported from ManageDocks. > ] > [Fix L.Mosaic bug where stored [Rational] was not extended > Adam Vogt **20090525030734 > Ignore-this: 55bb5b7fabc00f3dcc89e45cc416fc97 > ] > [X.A.Search: add Wolfram|Alpha search > Brent Yorgey **20090525010419] > [Remove L.ThreeColumnsMiddle compatiblity module > Adam Vogt **20090525003245 > Ignore-this: daac5841cf203c0e0df865a6fb0db3a1 > > Signed off here too: > http://www.haskell.org/pipermail/xmonad/2009-May/007883.html > ] > [A.FloatSnap snap to unmanaged docks too > Adam Vogt **20090525001834 > Ignore-this: 46a856cae139d2e224ded985a9866ecf > ] > [LayoutBuilder fix maintainer > Anders Engstrom **20090524205957 > Ignore-this: 380c279320cff67c60a9bbf9a49ec509 > ] > [FloatSnap fix maintainer > Anders Engstrom **20090524205854 > Ignore-this: d3932d211e9dc755be799d863b7d58e3 > ] > [X.A.FloatSnap - More configuration for magic resize, adaption for mouse bindings and some minor fixes > Anders Engstrom **20090524201143 > Ignore-this: d5fd9356e101b019735d54267a120ed > ] > [X.A.FloatSnap - Assisted move/resize of windows > Anders Engstrom **20090523235230 > Ignore-this: 53af93bdf537cf3417cedd313e36bcbd > > TODO: Try to snap against unmanaged windows such as dzen/xmobar. > > ] > [Simplyify L.Mosaic interface, and support resizing specific windows > Adam Vogt **20090524193810 > Ignore-this: acea22bec582ee5eb076ac3bc862a9ea > > The order previously was not as documented, which prevented resizing specific > windows. > > The Mosaic constructor is hidden in favour of mosaic :: Rational -> [Rational] -> Mosaic a > > Expand and Shrink messages are added, requiring another argument. > > Remove useless demonstration of SlopeMod message since resizing the focused > window is better. > ] > [L.ResizableTile document ResizableTall parameters with records > Adam Vogt **20090519024258 > Ignore-this: a29502bc1302f18b9ae0062105a0e109 > ] > [L.LayoutHints, add layoutHintsToCentre > Adam Vogt **20090519013806 > Ignore-this: a49106d5abb683d805e59beb29c727a9 > > layoutHintsToCentre attempts to apply hints in a way that eliminates gaps > between windows. The excess space ends up on all edges. > ] > [Remove excess whitespace from L.LayoutHints > Adam Vogt **20090519013350 > Ignore-this: b4bb5b6aeba95be047a102d07d916c48 > ] > [new layout module X.L.Spacing, put blank space around each window > Brent Yorgey **20090514215552] > [X.L.LayoutBuilder doc fix and cleaning > Anders Engstrom **20090509195254 > Ignore-this: 7cbf72ba48a2222b65615a02125d87ef > ] > [X.L.LayoutBuilder custom layouts > Anders Engstrom **20090509174627 > Ignore-this: 65c251663f02a083c5838ae1d1bd112a > > A layout combinator that sends a specified number of windows to one rectangle and the rest to another. > ] > [submapDefault fix key leakage > Anders Engstrom **20090426171002 > Ignore-this: edb0a2a03b2ed2959cb7068ae601fa28 > ] > [Fix typo in L.Mosaic hints > Adam Vogt **20090508202937 > Ignore-this: 5f2163e64d876f4982b0d6baf13e0614 > ] > [U.Loggers: add maildirNew, other loggers, and logger formatting utilities > wirtwolff@gmail.com**20090412041356 > Ignore-this: 73240ab34348ad895c3d66c2a2e8e40f > Rework of the Logger portions of patches originally from seanmce33@gmail.com > to apply without conflicts, plus several formatting utilities for use with > X (Maybe String) aka Loggers. > ] > [ThreeCol - Update docs to match reality > Anders Engstrom **20090503190755 > Ignore-this: e63f3ee533dd9bcf0f32da2316dde1dd > ] > [Remove some excess whitespace in XMonad.AppLauncher > Adam Vogt **20090503183416 > Ignore-this: b5bfa9625b5b080c20398cf1aa396a08 > ] > [Export ThreeColMid from L.ThreeColumnsMiddle > Adam Vogt **20090425161710 > Ignore-this: f08d23d108ae9aa4ad176fd9dd275409 > > The configs that import it should continue to work with this module, though the > type of the ThreeColMid constructor is now ThreeCol (previously ThreeColMid). > ] > [ThreeColumns support middle column, with more backwards compatiblity > Adam Vogt **20090414061819 > Ignore-this: 5a8991269904986e0e012e955c6d4712 > ] > [X.L.ThreeColumnsMiddle merged into X.L.ThreeColumns with some new features > Anders Engstrom **20090411113636 > Ignore-this: 1d5bb8de98f8ade3780444ed99f5a12f > ] > [nameTail - Remove the first word of a layout description > Anders Engstrom **20090503105950 > Ignore-this: a44c5e38163ed98ffc244cdd206632d1 > ] > [Add H.InsertPosition: add new windows to different positions in a workspace > Adam Vogt **20090503020303 > Ignore-this: 7e7d5fa5b42698799cabe600159a75f7 > ] > [Add changeMaster function to L.Mosaic > Adam Vogt **20090501233136 > Ignore-this: eca2a48fb987bb871ad93e6c6bf1a186 > ] > [Optimizer bug does not affect 6.10.2 (issue 226) > Adam Vogt **20090430034823 > Ignore-this: f43f9bf9502ebb19743c3b417ef02347 > ] > [Remove -XScopedTypeVariables requirement with L.SubLayouts > Adam Vogt **20090428222749 > Ignore-this: dbb08e3c1641796603fdaf7b929cdf6d > > This should keep the code -Wall clean on ghc-6.8 in addition to ghc-6.10 > ] > [Add SubLayouts: a layout combinator for nesting layouts. > Adam Vogt **20090423013135 > Ignore-this: abb21b19bfbc567953419b3035b6a295 > ] > [Document and extend BoringWindows to support multiple sources of boring. > Adam Vogt **20090406041301 > Ignore-this: 7375c8912ede6a6a44db4a4b91ffbc33 > > The Replace and Merge messages are added to support layouts sending a list of > windows that should be skipped over. The sources are tagged by a string key, so > it is possible though unlikely for different sources of boring windows to > interfere with eachother. > ] > [Add Apply message to L.WindowNavigation > Adam Vogt **20090303065701 > Ignore-this: e808729ddd2375778a96775568b8b621 > ] > [X.A.TopicSpace: remove the allTopics lists from the configuration. > Nicolas Pouillard **20090423172939 > Ignore-this: 1ac344b32865b38e53b968cc037b0a01 > ] > [added colour themes > perlkat@katspace.org**20090227065315 > These themes are colour themes only; they use the default font settings. > I thought the existing themes were rather dull, so these give more bright > (but tasteful) colours; shades of peacock feathers, shades of autumn. > ] > [Prompt.hs: setSuccess True also on Keypad Enter > sean.escriva@gmail.com**20090409162609 > Ignore-this: cf04f87c546f89bd32a94de3a2a93b22 > ] > [Update focus on mouse moves within inactive windows > Daniel Schoepe **20090407191819 > Ignore-this: 36c05c60420520dab708401d8a80fc85 > > This patch adds functionality to update the focus on moves in unfocused windows, which would make sense if one wanted the focus to follow the mouse. > Currently this only happens when the mouse enters/leaves a window. > This patch should fix issue #205. > ] > [Add promoteWarp event to L.MagicFocus > Adam Vogt **20090322221456 > Ignore-this: 12ad5fc144a35fb605f53b744d8146ef > > This event enables A.UpdatePointer behavior without causing infinite loops in > combination with magicFocus > ] > [Add TowardsCentre option to UpdatePointer > Adam Vogt **20090322215811 > Ignore-this: d543d8f090b03a6c26b3a0427be3a051 > > This option is like Nearest, but it places the pointer a configurable > percentage towards the centre of the window, instead of right at the edge. > ] > [Remove excess whitespace in A.UpdatePointer > Adam Vogt **20090322215553 > Ignore-this: 6fbc63642b946461e0fafcb44016824 > ] > [Combo fix ReleaseResources when no windows are available, new fix > Anders Engstrom **20090224172018 > Ignore-this: b59603df8e4cfc1fb2cf9070cea615b3 > ] > [OneBig_resize.dpatch > portnov84@rambler.ru**20090221142300 > Ignore-this: c02b25bd370ee449aab28005eb4418cf > Add Shrink/Expand messages handling for OneBig layout. > ] > [OneBig_layout.dpatch > portnov84@rambler.ru**20090220172634 > Ignore-this: 9d4f308d13f003aa4236417307a66c15 > Add the OneBig layout, which places one (master) window at top left corner of > screen (width and height of master window are parameters of layout), and other > (slave) windows at bottom and at right of master, trying to give equal space > for each slave window. > ] > [Properly encode destop names before sending them to X server in XMonad.Hooks.EwmhDesktops > Khudyakov Alexey **20090220184137 > Ignore-this: 6a22ea8bdc49f8484e18f04aaeb545ae > ] > [Make utf8-string regular dependency > Khudyakov Alexey **20090220183318 > Ignore-this: b38936b037c1172ec69905fa345f7afe > > The reason for this is that EWMH specification require > utf8 encoded strings. > ] > [Update haddock description for Actions.GridSelect > Daniel Schoepe **20090422172510 > Ignore-this: db5a2c009f7e88647f168ccb225d6219 > ] > [X.H.DynamicLog: provides trim, inverse of pad > sean.escriva@gmail.com**20090409163513 > Ignore-this: 9d92ff592f2bc4f041b85d1314058fdc > ] > [Mouse support for GridSelect > Daniel Schoepe **20090409223302 > Ignore-this: 38669e39c8676233d71f457c0b697500 > > GridSelect now allows selecting an element by a click with the left mouse button. > ] > [Generalize GridSelect to arbitrary elements > Daniel Schoepe **20090409155704 > Ignore-this: 69fbce85232871482adcce06c1a5fe62 > > This patch generalizes Actions.GridSelect to work for arbitrary (String,a)-lists. The changes break configurations that used `gridSelect' directly, which is now named gridSelectWindow. As an example for uses of the GridSelect-UI, I included a function to spawn an application from a list of commands(`spawnSelected'). > ] > [Improve composability of X.H.Place, drop simple(st)Float support > quentin.moser@unifr.ch**20090415184550 > Ignore-this: 8a0fb64aa0db27b242b7ad4bcba1a3ca > ] > [Fixed X.H.Place.position > quentin.moser@unifr.ch**20090409084946 > Ignore-this: 29e3936800194916a859976ff126dbfe > ] > [Module for automatic placement of floating windows > quentin.moser@unifr.ch**20090408080953 > Ignore-this: 1874df995fc02a0b80051db39d91a2e1 > ] > [X.H.FloatNext: new module, float the next spawned window(s) > quentin.moser@unifr.ch**20090415181907 > Ignore-this: 95e1c9daa3ca43bfb058f6a881a97f3a > ] > [ComboP > konstantin.sobolev@gmail.com**20090415014327 > Ignore-this: 73bb986165a7bba466aae789a5448170 > ] > [New module: XMonad.Actions.TopicSpace > Nicolas Pouillard **20090419085239 > Ignore-this: 4c20592ea6ca74f38545c5a1a002ef91 > ] > [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 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