aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad
diff options
context:
space:
mode:
authorTravis B. Hartwell <nafai@travishartwell.net>2008-10-27 01:55:23 +0100
committerTravis B. Hartwell <nafai@travishartwell.net>2008-10-27 01:55:23 +0100
commit623a6320e20b53ef302dbb827e6045756f236b52 (patch)
tree603fcddb6e1089ee8925e43825dcad038259ffbf /XMonad
parent5256f6f0aa92b0c2c9a1cd5a45ef25014510eaa1 (diff)
downloadXMonadContrib-623a6320e20b53ef302dbb827e6045756f236b52.tar.gz
XMonadContrib-623a6320e20b53ef302dbb827e6045756f236b52.tar.xz
XMonadContrib-623a6320e20b53ef302dbb827e6045756f236b52.zip
generic menu and window bringer
darcs-hash:20081027005523-c78c1-4de3783ba078b1acd99f70f675c37341030b3d7c.gz
Diffstat (limited to 'XMonad')
-rw-r--r--XMonad/Actions/WindowBringer.hs23
-rw-r--r--XMonad/Util/Dmenu.hs24
2 files changed, 32 insertions, 15 deletions
diff --git a/XMonad/Actions/WindowBringer.hs b/XMonad/Actions/WindowBringer.hs
index 102c15b..91bc0d1 100644
--- a/XMonad/Actions/WindowBringer.hs
+++ b/XMonad/Actions/WindowBringer.hs
@@ -15,11 +15,11 @@
-----------------------------------------------------------------------------
module XMonad.Actions.WindowBringer (
- -- * Usage
- -- $usage
- gotoMenu, bringMenu, windowMap,
- bringWindow
- ) where
+ -- * Usage
+ -- $usage
+ gotoMenu, gotoMenu', bringMenu, windowMap,
+ bringWindow
+ ) where
import Data.Char (toLower)
import qualified Data.Map as M
@@ -27,7 +27,7 @@ import qualified Data.Map as M
import qualified XMonad.StackSet as W
import XMonad
import qualified XMonad as X
-import XMonad.Util.Dmenu (dmenuMap)
+import XMonad.Util.Dmenu (menuMap)
import XMonad.Util.NamedWindows (getName)
-- $usage
@@ -50,6 +50,9 @@ import XMonad.Util.NamedWindows (getName)
gotoMenu :: X ()
gotoMenu = actionMenu W.focusWindow
+gotoMenu' :: String -> X ()
+gotoMenu' menuCmd = actionMenu' menuCmd W.focusWindow
+
-- | Pops open a dmenu with window titles. Choose one, and it will be
-- dragged, kicking and screaming, into your current workspace.
bringMenu :: X ()
@@ -62,7 +65,13 @@ bringWindow w ws = W.shiftWin (W.currentTag ws) w ws
-- | Calls dmenuMap to grab the appropriate Window, and hands it off to action
-- if found.
actionMenu :: (Window -> X.WindowSet -> X.WindowSet) -> X()
-actionMenu action = windowMap >>= dmenuMap >>= flip X.whenJust (windows . action)
+actionMenu action = actionMenu' "dmenu" action
+
+actionMenu' :: String -> (Window -> X.WindowSet -> X.WindowSet) -> X()
+actionMenu' menuCmd action = windowMap >>= menuMapFunction >>= flip X.whenJust (windows . action)
+ where
+ menuMapFunction :: M.Map String a -> X (Maybe a)
+ menuMapFunction selectionMap = menuMap menuCmd selectionMap
-- | A map from window names to Windows.
windowMap :: X (M.Map String Window)
diff --git a/XMonad/Util/Dmenu.hs b/XMonad/Util/Dmenu.hs
index ad0ccfc..8a8dc08 100644
--- a/XMonad/Util/Dmenu.hs
+++ b/XMonad/Util/Dmenu.hs
@@ -15,10 +15,10 @@
-----------------------------------------------------------------------------
module XMonad.Util.Dmenu (
- -- * Usage
- -- $usage
- dmenu, dmenuXinerama, dmenuMap
- ) where
+ -- * Usage
+ -- $usage
+ dmenu, dmenuXinerama, dmenuMap, menu, menuMap
+ ) where
import XMonad
import qualified XMonad.StackSet as W
@@ -40,9 +40,17 @@ dmenuXinerama opts = do
io $ runProcessWithInput "dmenu" ["-xs", show (curscreen+1)] (unlines opts)
dmenu :: [String] -> X String
-dmenu opts = io $ runProcessWithInput "dmenu" [] (unlines opts)
+dmenu opts = menu "dmenu" opts
-dmenuMap :: M.Map String a -> X (Maybe a)
-dmenuMap selectionMap = do
- selection <- dmenu (M.keys selectionMap)
+menu :: String -> [String] -> X String
+menu menuCmd opts = io $ runProcessWithInput menuCmd [] (unlines opts)
+
+menuMap :: String -> M.Map String a -> X (Maybe a)
+menuMap menuCmd selectionMap = do
+ selection <- menuFunction (M.keys selectionMap)
return $ M.lookup selection selectionMap
+ where
+ menuFunction = menu menuCmd
+
+dmenuMap :: M.Map String a -> X (Maybe a)
+dmenuMap selectionMap = menuMap "dmenu" selectionMap \ No newline at end of file