From dd682ca5f47c021bf491ab6d4ea75752933daa40 Mon Sep 17 00:00:00 2001 From: Roman Cheplyaka Date: Mon, 10 Nov 2008 19:46:44 +0100 Subject: GridSelect: various improvements Added documentation Restricted export list for the sake of haddock Added functions: withSelectedWindow bringSelected (by Clemens Fruhwirth) goToSelected (by Dominik Bruhn) darcs-hash:20081110184644-3ebed-9468e8235f934582d03446afa7c9392c387d650d.gz --- XMonad/Actions/GridSelect.hs | 49 ++++++++++++++++++++++++++++++++++++++++++-- 1 file changed, 47 insertions(+), 2 deletions(-) (limited to 'XMonad/Actions/GridSelect.hs') diff --git a/XMonad/Actions/GridSelect.hs b/XMonad/Actions/GridSelect.hs index c73aaae..4daaa60 100644 --- a/XMonad/Actions/GridSelect.hs +++ b/XMonad/Actions/GridSelect.hs @@ -13,7 +13,16 @@ -- ----------------------------------------------------------------------------- -module XMonad.Actions.GridSelect where +module XMonad.Actions.GridSelect ( + -- * Usage + -- $usage + GSConfig(..), + defaultGSConfig, + gridselect, + withSelectedWindow, + bringSelected, + goToSelected + ) where import Data.Maybe import Data.Bits import Control.Monad.State @@ -25,8 +34,20 @@ import XMonad.Prompt (mkUnmanagedWindow) import XMonad.StackSet as W import XMonad.Layout.Decoration import XMonad.Util.NamedWindows +import XMonad.Actions.WindowBringer (bringWindow) import Text.Printf +-- $usage +-- +-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@: +-- +-- > import XMonad.Actions.GridSelect +-- +-- Then add a keybinding, e.g. +-- +-- > , ((modMask x, xK_g), goToSelected defaultGSConfig) +-- + data GSConfig = GSConfig { gs_cellheight :: Integer, gs_cellwidth :: Integer, @@ -192,6 +213,8 @@ default_colorizer w active = do twodigitHex :: Integer -> String twodigitHex a = printf "%02x" a +-- | Brings up a 2D grid of windows in the center of the screen, and one can +-- select a window with cursors keys. The selected window is returned. gridselect :: GSConfig -> X (Maybe Window) gridselect gsconfig = withDisplay $ \dpy -> do @@ -227,6 +250,16 @@ gridselect gsconfig = releaseXMF font return selectedWindow +-- | Brings up a 2D grid of windows in the center of the screen, and one can +-- select a window with cursors keys. The selected window is then passed to +-- a callback function. +withSelectedWindow :: (Window -> X ()) -> GSConfig -> X () +withSelectedWindow callback conf = do + mbWindow <- gridselect conf + case mbWindow of + Just w -> callback w + Nothing -> return () + windowMap :: X [(String,Window)] windowMap = do @@ -242,5 +275,17 @@ decorateName' w = do defaultGSConfig :: GSConfig defaultGSConfig = GSConfig 50 130 10 default_colorizer "xft:Sans-8" -borderColor :: [Char] +borderColor :: String borderColor = "white" + +-- | Brings selected window to the current workspace. +bringSelected :: GSConfig -> X () +bringSelected = withSelectedWindow $ \w -> do + windows (bringWindow w) + XMonad.focus w + windows W.shiftMaster + +-- | Switches to selected window's workspace and focuses that window. +goToSelected :: GSConfig -> X () +goToSelected = withSelectedWindow $ windows . W.focusWindow + -- cgit v1.2.3