aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--Commands.hs34
-rw-r--r--MetaModule.hs2
2 files changed, 20 insertions, 16 deletions
diff --git a/Commands.hs b/Commands.hs
index 921cb1b..0472a45 100644
--- a/Commands.hs
+++ b/Commands.hs
@@ -17,14 +17,18 @@
module XMonadContrib.Commands (
-- * Usage
-- $usage
+ commandMap,
runCommand,
+ runCommand',
+ workspaceCommands,
+ screenCommands,
defaultCommands
) where
-
+
import XMonad
import Operations
-import {-# SOURCE #-} Config (workspaces, commands)
import XMonadContrib.Dmenu (dmenu)
+import {-# SOURCE #-} Config (workspaces)
import qualified Data.Map as M
import System.Exit
@@ -42,22 +46,16 @@ import Data.Maybe
--
-- and define the list commands:
--
+-- > commands :: [(String, X ())]
-- > 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!)
-
-commandMap :: M.Map String (X ())
-commandMap = M.fromList commands
+commandMap :: [(String, X ())] -> M.Map String (X ())
+commandMap c = M.fromList c
workspaceCommands :: [(String, X ())]
workspaceCommands = [((m ++ show i), f (fromIntegral i))
@@ -91,7 +89,13 @@ defaultCommands = workspaceCommands ++ screenCommands
, ("quit-wm", io $ exitWith ExitSuccess)
]
-runCommand :: X ()
-runCommand = do
- choice <- dmenu (M.keys commandMap)
- fromMaybe (return ()) (M.lookup choice commandMap)
+runCommand :: [(String, X ())] -> X ()
+runCommand cl = do
+ let m = commandMap cl
+ choice <- dmenu (M.keys m)
+ fromMaybe (return ()) (M.lookup choice m)
+
+runCommand' :: String -> X ()
+runCommand' c = do
+ let m = commandMap defaultCommands
+ fromMaybe (return ()) (M.lookup c m)
diff --git a/MetaModule.hs b/MetaModule.hs
index 226a1b0..db8d505 100644
--- a/MetaModule.hs
+++ b/MetaModule.hs
@@ -23,7 +23,7 @@ import XMonadContrib.Accordion ()
import XMonadContrib.Anneal ()
-- commented because of conflicts with 6.6's instances import XMonadContrib.BackCompat ()
import XMonadContrib.Circle ()
--- TODO commented because it requires hs-boot modifications import XMonadContrib.Commands ()
+import XMonadContrib.Commands ()
import XMonadContrib.Combo ()
import XMonadContrib.CopyWindow ()
import XMonadContrib.Decoration ()