aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Util/Dmenu.hs
diff options
context:
space:
mode:
Diffstat (limited to 'XMonad/Util/Dmenu.hs')
-rw-r--r--XMonad/Util/Dmenu.hs49
1 files changed, 49 insertions, 0 deletions
diff --git a/XMonad/Util/Dmenu.hs b/XMonad/Util/Dmenu.hs
new file mode 100644
index 0000000..8eeb0d9
--- /dev/null
+++ b/XMonad/Util/Dmenu.hs
@@ -0,0 +1,49 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Util.Dmenu
+-- Copyright : (c) Spencer Janssen <sjanssen@cse.unl.edu>
+-- License : BSD-style (see LICENSE)
+--
+-- Maintainer : Spencer Janssen <sjanssen@cse.unl.edu>
+-- Stability : unstable
+-- Portability : unportable
+--
+-- A convenient binding to dmenu.
+--
+-- Requires the process-1.0 package
+--
+-----------------------------------------------------------------------------
+
+module XMonad.Util.Dmenu (
+ -- * Usage
+ -- $usage
+ dmenu, dmenuXinerama, dmenuMap
+ ) where
+
+import XMonad
+import qualified XMonad.StackSet as W
+import qualified Data.Map as M
+import Control.Monad.State
+import XMonad.Util.Run
+
+-- $usage
+-- You can use this module with the following in your Config.hs file:
+--
+-- > import XMonad.Util.Dmenu
+
+-- %import XMonad.Util.Dmenu
+
+-- | Starts dmenu on the current screen. Requires this patch to dmenu:
+-- <http://www.jcreigh.com/dmenu/dmenu-3.2-xinerama.patch>
+dmenuXinerama :: [String] -> X String
+dmenuXinerama opts = do
+ curscreen <- (fromIntegral . W.screen . W.current) `liftM` gets windowset :: X Int
+ io $ runProcessWithInput "dmenu" ["-xs", show (curscreen+1)] (unlines opts)
+
+dmenu :: [String] -> X String
+dmenu opts = io $ runProcessWithInput "dmenu" [] (unlines opts)
+
+dmenuMap :: M.Map String a -> X (Maybe a)
+dmenuMap selectionMap = do
+ selection <- dmenu (M.keys selectionMap)
+ return $ M.lookup selection selectionMap