aboutsummaryrefslogtreecommitdiffstats
path: root/Commands.hs
diff options
context:
space:
mode:
authorglasser <glasser@mit.edu>2007-06-01 06:38:49 +0200
committerglasser <glasser@mit.edu>2007-06-01 06:38:49 +0200
commit08f32fb84c270635de6d532a432fa9e54d5897c5 (patch)
tree6052186128be4ea654d288caceaa2b7a8f820653 /Commands.hs
parent6581f4ababa122394de0b6b897fbc63beeacd406 (diff)
downloadXMonadContrib-08f32fb84c270635de6d532a432fa9e54d5897c5.tar.gz
XMonadContrib-08f32fb84c270635de6d532a432fa9e54d5897c5.tar.xz
XMonadContrib-08f32fb84c270635de6d532a432fa9e54d5897c5.zip
New contrib module: run internal xmonad commands via dmenu
darcs-hash:20070601043849-64353-0c9bdd026d3040dd1bb1fcd3551d941d170fb76f.gz
Diffstat (limited to '')
-rw-r--r--Commands.hs88
1 files changed, 88 insertions, 0 deletions
diff --git a/Commands.hs b/Commands.hs
new file mode 100644
index 0000000..0e56e86
--- /dev/null
+++ b/Commands.hs
@@ -0,0 +1,88 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonadContrib.Commands
+-- Copyright : (c) David Glasser 2007
+--
+-- Maintainer : glasser@mit.edu
+-- Stability : stable
+-- Portability : portable
+--
+-----------------------------------------------------------------------------
+--
+-- Allows you to run internal xmonad commands (X () actions) using
+-- a dmenu menu in addition to key bindings. Requires dmenu and
+-- the Dmenu XMonadContrib module.
+--
+-- To use, modify your Config.hs to:
+--
+-- import XMonadContrib.Commands
+--
+-- and add a keybinding to the runCommand action:
+--
+-- , ((modMask .|. controlMask, xK_y), runCommand)
+--
+-- and define the list commands:
+--
+-- commands = defaultCommands
+--
+-- Finally, add the following lines to Config.hs-boot:
+--
+-- import XMonad (X)
+-- workspaces :: Int
+-- commands :: [(String, X ())]
+--
+-- A popup menu of internal xmonad commands will appear. You can
+-- change the commands by changing the contents of the list
+-- 'commands'. (If you like it enough, you may even want to get rid
+-- of many of your other key bindings!)
+
+module XMonadContrib.Commands where
+
+import XMonad
+import Operations
+import {-# SOURCE #-} Config (workspaces, commands)
+import XMonadContrib.Dmenu (dmenu)
+
+import qualified Data.Map as M
+import System.Exit
+import Data.Maybe
+
+commandMap :: M.Map String (X ())
+commandMap = M.fromList commands
+
+workspaceCommands :: [(String, X ())]
+workspaceCommands = [((m ++ show i), f i)
+ | i <- [0 .. fromIntegral workspaces - 1]
+ , (f, m) <- [(view, "view"), (shift, "shift")]
+ ]
+
+screenCommands :: [(String, X ())]
+screenCommands = [((m ++ show sc), screenWorkspace sc >>= f)
+ | sc <- [0, 1] -- TODO: adapt to screen changes
+ , (f, m) <- [(view, "screen"), (shift, "screen-to-")]
+ ]
+
+defaultCommands :: [(String, X ())]
+defaultCommands = workspaceCommands ++ screenCommands
+ ++ [ ("shrink", sendMessage Shrink)
+ , ("expand", sendMessage Expand)
+ , ("restart-wm", restart Nothing True)
+ , ("restart-wm-no-resume", restart Nothing False)
+ , ("layout", switchLayout)
+ , ("xterm", spawn "xterm")
+ , ("run", spawn "exe=`dmenu_path | dmenu -b` && exec $exe")
+ , ("kill", kill)
+ , ("refresh", refresh)
+ , ("focus-up", focusUp)
+ , ("focus-down", focusDown)
+ , ("swap-up", swapUp)
+ , ("swap-down", swapDown)
+ , ("swap-master", swapMaster)
+ , ("sink", withFocused sink)
+ , ("quit-wm", io $ exitWith ExitSuccess)
+ ]
+
+runCommand :: X ()
+runCommand = do
+ choice <- dmenu (M.keys commandMap)
+ fromMaybe (return ()) (M.lookup choice commandMap)