improve the formatting for WindowGo.hs

This commit is contained in:
gwern0
2008-03-16 21:56:42 +00:00
parent 87bb590217
commit aca42e5ddb

View File

@@ -1,5 +1,4 @@
{- --------------------------------------------------------------------------
|
{- |
Module : XMonad.Actions.WindowGo
License : Public domain
@@ -8,9 +7,7 @@ Stability : unstable
Portability : unportable
Defines a few simple operations for raising windows based on XMonad's Query
Monad, such as runOrRaise.
----------------------------------------------------------------------------- -}
monad, such as 'runOrRaise'. -}
module XMonad.Actions.WindowGo (
-- * Usage
@@ -26,19 +23,21 @@ import Control.Monad (filterM)
import qualified XMonad.StackSet as W (allWindows)
import XMonad.ManageHook
-- $usage
--
-- Import the module into your @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Actions.WindowGo
--
-- and define appropriate key bindings:
--
-- > , ((modMask x .|. shiftMask, xK_g ), raise (className =? "Firefox-bin"))
-- > , ((modMask x .|. shiftMask, xK_b ), runOrRaise "mozilla-firefox" (className =? "Firefox-bin"))
--
-- For detailed instructions on editing your key bindings, see
-- "XMonad.Doc.Extending#Editing_key_bindings".
{- $usage
Import the module into your @~\/.xmonad\/xmonad.hs@:
> import XMonad.Actions.WindowGo
and define appropriate key bindings:
> , ((modMask x .|. shiftMask, xK_g), raise (className =? "Firefox"))
> , ((modMask x .|. shiftMask, xK_b), runOrRaise "firefox" (className =? "Firefox"))
(Note that Firefox v3 and up have a class-name of "Firefox" and "Navigator";
lower versions use other classnames such as "Firefox-bin"
For detailed instructions on editing your key bindings, see
"XMonad.Doc.Extending#Editing_key_bindings". -}
-- | 'action' is an executable to be run via 'spawn' if the Window cannot be found.
-- Presumably this executable is the same one that you were looking for.
@@ -49,13 +48,14 @@ runOrRaise action = raiseMaybe $ spawn action
raise :: Query Bool -> X ()
raise = raiseMaybe $ return ()
{- | raiseMaybe: this queries all Windows based on a boolean provided by the
{- | 'raiseMaybe' queries all Windows based on a boolean provided by the
user. Currently, there are three such useful booleans defined in
XMonad.ManageHook: title, resource, className. Each one tests based pretty
much as you would think. ManageHook also defines several operators, the most
useful of which is (=?). So a useful test might be finding a Window whose
class is Firefox. Firefox declares the class "Firefox-bin", so you'd want to
pass in a boolean like '(className =? "Firefox-bin")'.
class is Firefox. Firefox declares the class "Firefox", so you'd want to
pass in a boolean like '(className =? "Firefox")'.
If the boolean returns True on one or more windows, then XMonad will quickly
make visible the first result. If no Window meets the criteria, then the
first argument comes into play.
@@ -69,14 +69,14 @@ raise = raiseMaybe $ return ()
some cute things with this hook. Suppose you want to do the same thing for
Mutt which you just did for Firefox - but Mutt runs inside a terminal window?
No problem: you search for a terminal window calling itself 'mutt', and if
there isn't you run a terminal with a command to run mutt! Here's an example,
borrowing 'runInTerm' from XMonad.Utils.Run:
there isn't you run a terminal with a command to run Mutt! Here's an example
(borrowing "XMonad.Utils.Run"'s 'runInTerm'):
> , ((modm, xK_m ), raiseMaybe (runInTerm "-title mutt" "mutt") (title =? "mutt"))
> , ((modm, xK_m), raiseMaybe (runInTerm "-title mutt" "mutt") (title =? "mutt"))
-}
raiseMaybe :: X () -> Query Bool -> X ()
raiseMaybe f thatUserQuery = withWindowSet $ \s -> do
maybeResult <- filterM (runQuery thatUserQuery) (W.allWindows s)
case maybeResult of
[] -> f
[] -> f
(x:_) -> focus x