aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorNorbert Zeh <nzeh@cs.dal.ca>2011-04-06 16:02:13 +0200
committerNorbert Zeh <nzeh@cs.dal.ca>2011-04-06 16:02:13 +0200
commit7ebe017965626cf2c476826363023aa3d6b5d293 (patch)
tree79b7b3ac170633239b8c881f341649a5b0a03683
parent7d74e99e143a2a6ead7cb754e02273c10c848757 (diff)
downloadXMonadContrib-7ebe017965626cf2c476826363023aa3d6b5d293.tar.gz
XMonadContrib-7ebe017965626cf2c476826363023aa3d6b5d293.tar.xz
XMonadContrib-7ebe017965626cf2c476826363023aa3d6b5d293.zip
Support for scratchpad applications with multiple windows
Ignore-this: 4c7d5f2ff95292438464e0b1060ab324 I recently found that I use xpad to add sticky notes to my desktop. I wanted to be able to show/hide these in the same fashion as regular scratchpads. This patch adds a function that allows to do this while reusing most of the existing NamedScratchpad code. darcs-hash:20110406140213-18a2b-402b9e2fdd26d4bb06bc50b094079b74e76c0208.gz
-rw-r--r--XMonad/Util/NamedScratchpad.hs47
1 files changed, 27 insertions, 20 deletions
diff --git a/XMonad/Util/NamedScratchpad.hs b/XMonad/Util/NamedScratchpad.hs
index 7269103..6fc226d 100644
--- a/XMonad/Util/NamedScratchpad.hs
+++ b/XMonad/Util/NamedScratchpad.hs
@@ -22,6 +22,7 @@ module XMonad.Util.NamedScratchpad (
customFloating,
NamedScratchpads,
namedScratchpadAction,
+ allNamedScratchpadAction,
namedScratchpadManageHook,
namedScratchpadFilterOutWorkspace
) where
@@ -116,29 +117,35 @@ runApplication = spawn . cmd
namedScratchpadAction :: NamedScratchpads -- ^ Named scratchpads configuration
-> String -- ^ Scratchpad name
-> X ()
-namedScratchpadAction confs n
+namedScratchpadAction = someNamedScratchpadAction (\f ws -> f $ head ws)
+
+allNamedScratchpadAction :: NamedScratchpads
+ -> String
+ -> X ()
+allNamedScratchpadAction = someNamedScratchpadAction mapM_
+
+someNamedScratchpadAction :: ((Window -> X ()) -> [Window] -> X ())
+ -> NamedScratchpads
+ -> String
+ -> X ()
+someNamedScratchpadAction f confs n
| Just conf <- findByName confs n = withWindowSet $ \s -> do
- -- try to find it on the current workspace
- filterCurrent <- filterM (runQuery (query conf))
- ( (maybe [] W.integrate . W.stack .
- W.workspace . W.current) s)
- case filterCurrent of
- (x:_) -> do
- -- create hidden workspace if it doesn't exist
- if null (filter ((== scratchpadWorkspaceTag) . W.tag) (W.workspaces s))
- then addHiddenWorkspace scratchpadWorkspaceTag
- else return ()
- -- push window there
- windows $ W.shiftWin scratchpadWorkspaceTag x
- [] -> do
- -- try to find it on all workspaces
- filterAll <- filterM (runQuery (query conf)) (W.allWindows s)
- case filterAll of
- (x:_) -> windows $ W.shiftWin (W.currentTag s) x
- [] -> runApplication conf
-
+ filterCurrent <- filterM (runQuery (query conf))
+ ((maybe [] W.integrate . W.stack . W.workspace . W.current) s)
+ filterAll <- filterM (runQuery (query conf)) (W.allWindows s)
+ case filterCurrent of
+ [] -> do
+ case filterAll of
+ [] -> runApplication conf
+ _ -> f (windows . W.shiftWin (W.currentTag s)) filterAll
+ _ -> do
+ if null (filter ((== scratchpadWorkspaceTag) . W.tag) (W.workspaces s))
+ then addHiddenWorkspace scratchpadWorkspaceTag
+ else return ()
+ f (windows . W.shiftWin scratchpadWorkspaceTag) filterAll
| otherwise = return ()
+
-- tag of the scratchpad workspace
scratchpadWorkspaceTag :: String
scratchpadWorkspaceTag = "NSP"