aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad
diff options
context:
space:
mode:
authorBrent Yorgey <byorgey@gmail.com>2007-11-23 18:16:19 +0100
committerBrent Yorgey <byorgey@gmail.com>2007-11-23 18:16:19 +0100
commitf0bce453588aeef69e86961211922cbdde518181 (patch)
treef5c7f995dc6d98534aaab18947143be162c6948c /XMonad
parent7392520331a58d103244efc8ce33aa071880fbe6 (diff)
downloadXMonadContrib-f0bce453588aeef69e86961211922cbdde518181.tar.gz
XMonadContrib-f0bce453588aeef69e86961211922cbdde518181.tar.xz
XMonadContrib-f0bce453588aeef69e86961211922cbdde518181.zip
Commands.hs: haddock updates
darcs-hash:20071123171619-bd4d7-d34578e28eec4b2dda7325a6f61b7ce1d07720ae.gz
Diffstat (limited to 'XMonad')
-rw-r--r--XMonad/Actions/Commands.hs35
1 files changed, 22 insertions, 13 deletions
diff --git a/XMonad/Actions/Commands.hs b/XMonad/Actions/Commands.hs
index eaf6624..807a19c 100644
--- a/XMonad/Actions/Commands.hs
+++ b/XMonad/Actions/Commands.hs
@@ -3,7 +3,7 @@
-- Module : XMonad.Actions.Commands
-- Copyright : (c) David Glasser 2007
-- License : BSD3
---
+--
-- Maintainer : glasser@mit.edu
-- Stability : stable
-- Portability : portable
@@ -38,44 +38,48 @@ import Data.Maybe
-- $usage
--
--- To use, modify your Config.hs to:
+-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Actions.Commands
--
--- and add a keybinding to the runCommand action:
+-- Then add a keybinding to the runCommand action:
--
-- > , ((modMask .|. controlMask, xK_y), runCommand commands)
--
--- and define the list commands:
+-- and define the list of commands you want to use:
--
-- > commands :: [(String, X ())]
-- > commands = defaultCommands
--
--- 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!)
-
--- %def commands :: [(String, X ())]
--- %def commands = defaultCommands
--- %import XMonad.Actions.Commands
--- %keybind , ((modMask .|. controlMask, xK_y), runCommand commands)
+-- Whatever key you bound to will now cause a popup menu of internal
+-- xmonad commands to 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!)
+--
+-- For detailed instructions on editing your key bindings, see
+-- "XMonad.Doc.Extending#Editing_key_bindings".
+-- | Create a 'Data.Map.Map' from @String@s to xmonad actions from a
+-- list of pairs.
commandMap :: [(String, X ())] -> M.Map String (X ())
commandMap c = M.fromList c
+-- | Generate a list of commands to switch to\/send windows to workspaces.
workspaceCommands :: X [(String, X ())]
workspaceCommands = asks (workspaces . config) >>= \spaces -> return
[((m ++ show i), windows $ f i)
| i <- spaces
, (f, m) <- [(view, "view"), (shift, "shift")] ]
+-- | Generate a list of commands dealing with multiple screens.
screenCommands :: [(String, X ())]
screenCommands = [((m ++ show sc), screenWorkspace (fromIntegral sc) >>= flip whenJust (windows . f))
| sc <- [0, 1]::[Int] -- TODO: adapt to screen changes
, (f, m) <- [(view, "screen"), (shift, "screen-to-")]
]
+-- | A nice pre-defined list of commands.
defaultCommands :: X [(String, X ())]
defaultCommands = do
wscmds <- workspaceCommands
@@ -102,12 +106,17 @@ defaultCommands = do
, ("quit-wm" , io $ exitWith ExitSuccess )
]
+-- | Given a list of command\/action pairs, prompt the user to choose a
+-- command and return the corresponding action.
runCommand :: [(String, X ())] -> X ()
runCommand cl = do
let m = commandMap cl
choice <- dmenu (M.keys m)
fromMaybe (return ()) (M.lookup choice m)
+-- | Given the name of a command from 'defaultCommands', return the
+-- corresponding action (or the null action if the command is not
+-- found).
runCommand' :: String -> X ()
runCommand' c = do
m <- fmap commandMap defaultCommands