| Portability | unportable | 
|---|---|
| Stability | unstable | 
| Maintainer | Clemens Fruhwirth <clemens@endorphin.org> | 
XMonad.Actions.GridSelect
Contents
Description
GridSelect displays items(e.g. the opened windows) in a 2D grid and lets the user select from it with the cursor/hjkl keys or the mouse.
- data  GSConfig a = GSConfig {- gs_cellheight :: Integer
- gs_cellwidth :: Integer
- gs_cellpadding :: Integer
- gs_colorizer :: a -> Bool -> X (String, String)
- gs_font :: String
- gs_navigate :: NavigateMap
- gs_originFractX :: Double
- gs_originFractY :: Double
 
- defaultGSConfig :: HasColorizer a => GSConfig a
- type NavigateMap = Map (KeyMask, KeySym) (TwoDPosition -> TwoDPosition)
- type TwoDPosition = (Integer, Integer)
- buildDefaultGSConfig :: (a -> Bool -> X (String, String)) -> GSConfig a
- gridselect :: GSConfig a -> [(String, a)] -> X (Maybe a)
- gridselectWindow :: GSConfig Window -> X (Maybe Window)
- withSelectedWindow :: (Window -> X ()) -> GSConfig Window -> X ()
- bringSelected :: GSConfig Window -> X ()
- goToSelected :: GSConfig Window -> X ()
- spawnSelected :: GSConfig String -> [String] -> X ()
- runSelectedAction :: GSConfig (X ()) -> [(String, X ())] -> X ()
- class  HasColorizer a  where- defaultColorizer :: a -> Bool -> X (String, String)
 
- fromClassName :: Window -> Bool -> X (String, String)
- stringColorizer :: String -> Bool -> X (String, String)
- colorRangeFromClassName :: (Word8, Word8, Word8) -> (Word8, Word8, Word8) -> (Word8, Word8, Word8) -> (Word8, Word8, Word8) -> (Word8, Word8, Word8) -> Window -> Bool -> X (String, String)
Usage
You can use this module with the following in your ~/.xmonad/xmonad.hs:
import XMonad.Actions.GridSelect
Then add a keybinding, e.g.
, ((modm, xK_g), goToSelected defaultGSConfig)
This module also supports displaying arbitrary information in a grid and letting the user select from it. E.g. to spawn an application from a given list, you can use the following:
, ((modm, xK_s), spawnSelected defaultGSConfig ["xterm","gmplayer","gvim"])
Customizing
Using a common GSConfig
It is possible to bind a gsconfig at top-level in your configuration. Like so:
 -- the top of your config
 {-# LANGUAGE NoMonomorphismRestriction #-}
 import XMonad
 ...
 gsconfig1 = defaultGSConfig { gs_cellheight = 30, gs_cellWidth = 100 }
An example where buildDefaultGSConfig is used instead of defaultGSConfig
 in order to specify a custom colorizer is gsconfig2 (found in
 XMonad.Actions.GridSelect):
 gsconfig2 colorizer = (buildDefaultGSConfig colorizer) { gs_cellheight = 30, gs_cellWidth = 100 }
 -- | A green monochrome colorizer based on window class
 greenColorizer = colorRangeFromClassName
                      black            -- lowest inactive bg
                      (0x70,0xFF,0x70) -- highest inactive bg
                      black            -- active bg
                      white            -- inactive fg
                      white            -- active fg
   where black = minBound
         white = maxBound
Then you can bind to:
     ,((modm, xK_g), goToSelected  $ gsconfig2 myWinColorizer)
     ,((modm, xK_p), spawnSelected $ spawnSelected defaultColorizer)
Custom keybindings
Adding more keybindings for gridselect to listen to is similar:
At the top of your config:
 {-# LANGAUGE NoMonomorphismRestriction #-}
 import XMonad
 import qualified Data.Map as M
Then define gsconfig3 which may be used in exactly the same manner as gsconfig1:
 gsconfig3 = defaultGSConfig
    { gs_cellheight = 30
    , gs_cellwidth = 100
    , gs_navigate = M.unions
            [reset
            ,nethackKeys
            ,gs_navigate                               -- get the default navigation bindings
                $ defaultGSConfig `asTypeOf` gsconfig3 -- needed to fix an ambiguous type variable
            ]
    }
   where addPair (a,b) (x,y) = (a+x,b+y)
         nethackKeys = M.map addPair $ M.fromList
                               [((0,xK_y),(-1,-1))
                               ,((0,xK_i),(1,-1))
                               ,((0,xK_n),(-1,1))
                               ,((0,xK_m),(1,1))
                               ]
         -- jump back to the center with the spacebar, regardless of the current position.
         reset = M.singleton (0,xK_space) (const (0,0))
Configuration
Constructors
| GSConfig | |
| Fields 
 | |
defaultGSConfig :: HasColorizer a => GSConfig aSource
A basic configuration for gridselect, with the colorizer chosen based on the type.
If you want to replace the gs_colorizer field, use buildDefaultGSConfig
 instead, to avoid ambiguous type variables.
type NavigateMap = Map (KeyMask, KeySym) (TwoDPosition -> TwoDPosition)Source
type TwoDPosition = (Integer, Integer)Source
buildDefaultGSConfig :: (a -> Bool -> X (String, String)) -> GSConfig aSource
Builds a default gs config from a colorizer function.
Variations on gridselect
gridselect :: GSConfig a -> [(String, a)] -> X (Maybe a)Source
Brings up a 2D grid of elements in the center of the screen, and one can select an element with cursors keys. The selected element is returned.
gridselectWindow :: GSConfig Window -> X (Maybe Window)Source
Like gridSelect but with the current windows and their titles as elements
withSelectedWindow :: (Window -> X ()) -> GSConfig Window -> X ()Source
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.
goToSelected :: GSConfig Window -> X ()Source
Switches to selected window's workspace and focuses that window.
spawnSelected :: GSConfig String -> [String] -> X ()Source
Select an application to spawn from a given list
runSelectedAction :: GSConfig (X ()) -> [(String, X ())] -> X ()Source
Select an action and run it in the X monad
Colorizers
class HasColorizer a whereSource
That is fromClassName if you are selecting a Window, or
 defaultColorizer if you are selecting a String. The catch-all instance
 HasColorizer a uses the focusedBorderColor and normalBorderColor
 colors.
Instances
fromClassName :: Window -> Bool -> X (String, String)Source
Colorize a window depending on it's className.
Arguments
| :: (Word8, Word8, Word8) | Beginning of the color range | 
| -> (Word8, Word8, Word8) | End of the color range | 
| -> (Word8, Word8, Word8) | Background of the active window | 
| -> (Word8, Word8, Word8) | Inactive text color | 
| -> (Word8, Word8, Word8) | Active text color | 
| -> Window | |
| -> Bool | |
| -> X (String, String) | 
A colorizer that picks a color inside a range, and depending on the window's class.
Screenshots
Selecting a workspace:
 
Selecting a window by title:
