aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorAdam Vogt <vogt.adam@gmail.com>2013-01-14 02:46:42 +0100
committerAdam Vogt <vogt.adam@gmail.com>2013-01-14 02:46:42 +0100
commit68858069a8b1b0c00867520b40ce5d266cd8293c (patch)
tree4f999c6d5c1fab04f6821c3706fe6881ddf81d04
parent9d66b337524a7e7992b1a9a6d56746cd996babc2 (diff)
downloadXMonadContrib-68858069a8b1b0c00867520b40ce5d266cd8293c.tar.gz
XMonadContrib-68858069a8b1b0c00867520b40ce5d266cd8293c.tar.xz
XMonadContrib-68858069a8b1b0c00867520b40ce5d266cd8293c.zip
SpawnOn modification for issue 523
Ignore-this: 703f7dc0f800366b752f0ec1cecb52e5 This moves the function to help clean up the `Spawner' to the ManageHook rather than in functions like spawnOn. Probably it makes no difference, the reason is because there's one manageSpawn function but many different so this way there are less functions to write. darcs-hash:20130114014642-1499c-5d00aa9a169d200f22b278b541ae0f9efe2d0358.gz
-rw-r--r--XMonad/Actions/SpawnOn.hs17
1 files changed, 11 insertions, 6 deletions
diff --git a/XMonad/Actions/SpawnOn.hs b/XMonad/Actions/SpawnOn.hs
index d7500b2..1154ce5 100644
--- a/XMonad/Actions/SpawnOn.hs
+++ b/XMonad/Actions/SpawnOn.hs
@@ -20,6 +20,7 @@ module XMonad.Actions.SpawnOn (
-- $usage
Spawner,
manageSpawn,
+ manageSpawnWithGC,
spawnHere,
spawnOn,
spawnAndDo,
@@ -66,8 +67,6 @@ newtype Spawner = Spawner {pidsRef :: [(ProcessID, ManageHook)]} deriving Typeab
instance ExtensionClass Spawner where
initialValue = Spawner []
-maxPids :: Int
-maxPids = 5
-- | Get the current Spawner or create one if it doesn't exist.
modifySpawner :: ([(ProcessID, ManageHook)] -> [(ProcessID, ManageHook)]) -> X ()
@@ -76,14 +75,20 @@ modifySpawner f = XS.modify (Spawner . f . pidsRef)
-- | Provides a manage hook to react on process spawned with
-- 'spawnOn', 'spawnHere' etc.
manageSpawn :: ManageHook
-manageSpawn = do
+manageSpawn = manageSpawnWithGC (return . take 20)
+
+manageSpawnWithGC :: ([(ProcessID, ManageHook)] -> X [(ProcessID, ManageHook)])
+ -- ^ function to stop accumulation of entries for windows that never set @_NET_WM_PID@
+ -> ManageHook
+manageSpawnWithGC garbageCollect = do
Spawner pids <- liftX XS.get
mp <- pid
case flip lookup pids =<< mp of
Nothing -> idHook
Just mh -> do
- whenJust mp $ \p ->
- liftX . modifySpawner $ filter ((/= p) . fst)
+ whenJust mp $ \p -> liftX $ do
+ ps <- XS.gets pidsRef
+ XS.put . Spawner =<< garbageCollect (filter ((/= p) . fst) ps)
mh
mkPrompt :: (String -> X ()) -> XPConfig -> X ()
@@ -115,7 +120,7 @@ spawnOn ws cmd = spawnAndDo (doShift ws) cmd
spawnAndDo :: ManageHook -> String -> X ()
spawnAndDo mh cmd = do
p <- spawnPID $ mangle cmd
- modifySpawner $ (take maxPids . ((p,mh) :))
+ modifySpawner $ ((p,mh) :)
where
-- TODO this is silly, search for a better solution
mangle xs | any (`elem` metaChars) xs || "exec" `isInfixOf` xs = xs