Copyright | (c) 2011 Norbert Zeh <nzeh@cs.dal.ca> |
---|---|
License | BSD3-style (see LICENSE) |
Maintainer | Norbert Zeh <nzeh@cs.dal.ca> |
Stability | unstable |
Portability | unportable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Navigation2D is an xmonad extension that allows easy directional navigation of windows and screens (in a multi-monitor setup).
Synopsis
- navigation2D :: Navigation2DConfig -> (KeySym, KeySym, KeySym, KeySym) -> [(ButtonMask, Direction2D -> Bool -> X ())] -> Bool -> XConfig l -> XConfig l
- navigation2DP :: Navigation2DConfig -> (String, String, String, String) -> [(String, Direction2D -> Bool -> X ())] -> Bool -> XConfig l -> XConfig l
- additionalNav2DKeys :: (KeySym, KeySym, KeySym, KeySym) -> [(ButtonMask, Direction2D -> Bool -> X ())] -> Bool -> XConfig l -> XConfig l
- additionalNav2DKeysP :: (String, String, String, String) -> [(String, Direction2D -> Bool -> X ())] -> Bool -> XConfig l -> XConfig l
- withNavigation2DConfig :: Navigation2DConfig -> XConfig a -> XConfig a
- data Navigation2DConfig = Navigation2DConfig {
- defaultTiledNavigation :: Navigation2D
- floatNavigation :: Navigation2D
- screenNavigation :: Navigation2D
- layoutNavigation :: [(String, Navigation2D)]
- unmappedWindowRect :: [(String, Screen -> Window -> X (Maybe Rectangle))]
- def :: Default a => a
- data Navigation2D
- lineNavigation :: Navigation2D
- centerNavigation :: Navigation2D
- sideNavigation :: Navigation2D
- sideNavigationWithBias :: Int -> Navigation2D
- hybridOf :: Navigation2D -> Navigation2D -> Navigation2D
- fullScreenRect :: Screen -> Window -> X (Maybe Rectangle)
- singleWindowRect :: Screen -> Window -> X (Maybe Rectangle)
- switchLayer :: X ()
- windowGo :: Direction2D -> Bool -> X ()
- windowSwap :: Direction2D -> Bool -> X ()
- windowToScreen :: Direction2D -> Bool -> X ()
- screenGo :: Direction2D -> Bool -> X ()
- screenSwap :: Direction2D -> Bool -> X ()
- data Direction2D
Usage
Navigation2D provides directional navigation (go left, right, up, down) for windows and screens. It treats floating and tiled windows as two separate layers and provides mechanisms to navigate within each layer and to switch between layers. Navigation2D provides three different navigation strategies (see #Technical_Discussion for details): Line navigation and Side navigation feel rather natural but may make it impossible to navigate to a given window from the current window, particularly in the floating layer. Center navigation feels less natural in certain situations but ensures that all windows can be reached without the need to involve the mouse. Another option is to use a Hybrid of the three strategies, automatically choosing whichever first provides a suitable target window. Navigation2D allows different navigation strategies to be used in the two layers and allows customization of the navigation strategy for the tiled layer based on the layout currently in effect.
You can use this module with (a subset of) the following in your xmonad.hs
:
import XMonad.Actions.Navigation2D
Then add the configuration of the module to your main function:
main = xmonad $ navigation2D def (xK_Up, xK_Left, xK_Down, xK_Right) [(mod4Mask, windowGo ), (mod4Mask .|. shiftMask, windowSwap)] False $ def
NOTE: the def
argument to navigation2D
contains the strategy
that decides which windows actually get selected. While the default
behaviour tries to keep them into account, if you use modules that
influence tiling in some way, like XMonad.Layout.Spacing or
XMonad.Layout.Gaps, you should think about using a different
strategy, if you find the default behaviour to be unnatural. Check
out the finer points below for more information.
Alternatively to navigation2D
, you can use navigation2DP
:
main = xmonad $ navigation2DP def ("<Up>", "<Left>", "<Down>", "<Right>") [("M-", windowGo ), ("M-S-", windowSwap)] False $ def
That's it. If instead you'd like more control, you can combine
withNavigation2DConfig
and additionalNav2DKeys
or additionalNav2DKeysP
:
main = xmonad $ withNavigation2DConfig def $ additionalNav2DKeys (xK_Up, xK_Left, xK_Down, xK_Right) [(mod4Mask, windowGo ), (mod4Mask .|. shiftMask, windowSwap)] False $ additionalNav2DKeys (xK_u, xK_l, xK_d, xK_r) [(mod4Mask, screenGo ), (mod4Mask .|. shiftMask, screenSwap)] False $ def
Or you can add the configuration of the module to your main function:
main = xmonad $ withNavigation2DConfig def $ def
And specify your keybindings normally:
-- Switch between layers , ((modm, xK_space), switchLayer) -- Directional navigation of windows , ((modm, xK_Right), windowGo R False) , ((modm, xK_Left ), windowGo L False) , ((modm, xK_Up ), windowGo U False) , ((modm, xK_Down ), windowGo D False) -- Swap adjacent windows , ((modm .|. controlMask, xK_Right), windowSwap R False) , ((modm .|. controlMask, xK_Left ), windowSwap L False) , ((modm .|. controlMask, xK_Up ), windowSwap U False) , ((modm .|. controlMask, xK_Down ), windowSwap D False) -- Directional navigation of screens , ((modm, xK_r ), screenGo R False) , ((modm, xK_l ), screenGo L False) , ((modm, xK_u ), screenGo U False) , ((modm, xK_d ), screenGo D False) -- Swap workspaces on adjacent screens , ((modm .|. controlMask, xK_r ), screenSwap R False) , ((modm .|. controlMask, xK_l ), screenSwap L False) , ((modm .|. controlMask, xK_u ), screenSwap U False) , ((modm .|. controlMask, xK_d ), screenSwap D False) -- Send window to adjacent screen , ((modm .|. mod1Mask, xK_r ), windowToScreen R False) , ((modm .|. mod1Mask, xK_l ), windowToScreen L False) , ((modm .|. mod1Mask, xK_u ), windowToScreen U False) , ((modm .|. mod1Mask, xK_d ), windowToScreen D False)
For detailed instruction on editing the key binding see:
Finer points
The above should get you started. Here are some finer points:
Navigation2D has the ability to wrap around at screen edges. For example, if
you navigated to the rightmost window on the rightmost screen and you
continued to go right, this would get you to the leftmost window on the
leftmost screen. This feature may be useful for switching between screens
that are far apart but may be confusing at least to novice users. Therefore,
it is disabled in the above example (e.g., navigation beyond the rightmost
window on the rightmost screen is not possible and trying to do so will
simply not do anything.) If you want this feature, change all the False
values in the above example to True
. You could also decide you want
wrapping only for a subset of the operations and no wrapping for others.
By default, all layouts use the defaultTiledNavigation
strategy
specified in the Navigation2DConfig
(by default, line navigation is
used). Many more navigation strategies are available; some may feel
more natural, depending on the layout and user:
There is also the ability to combine two strategies with hybridOf
.
To override the default behaviour for some layouts, add a pair ("layout name",
navigation strategy) to the layoutNavigation
list in the
Navigation2DConfig
, where "layout name" is the string reported by the
layout's description method (normally what is shown as the layout name in
your status bar). For example, all navigation strategies normally allow only
navigation between mapped windows. The first step to overcome this, for
example, for the Full layout, is to switch to center navigation for the Full
layout:
myNavigation2DConfig = def { layoutNavigation = [("Full", centerNavigation)] } main = xmonad $ withNavigation2DConfig myNavigation2DConfig $ def
The navigation between windows is based on their screen rectangles, which are available and meaningful only for mapped windows. Thus, as already said, the default is to allow navigation only between mapped windows. However, there are layouts that do not keep all windows mapped. One example is the Full layout, which unmaps all windows except the one that has the focus, thereby preventing navigation to any other window in the layout. To make navigation to unmapped windows possible, unmapped windows need to be assigned rectangles to pretend they are mapped, and a natural way to do this for the Full layout is to pretend all windows occupy the full screen and are stacked on top of each other so that only the frontmost one is visible. This can be done as follows:
myNavigation2DConfig = def { layoutNavigation = [("Full", centerNavigation)] , unmappedWindowRect = [("Full", singleWindowRect)] } main = xmonad $ withNavigation2DConfig myNavigation2DConfig $ def
With this setup, Left/Up navigation behaves like standard
focusUp
and Right/Down navigation behaves like
focusDown
, thus allowing navigation between windows in the
layout.
In general, each entry in the unmappedWindowRect
association list is a pair
("layout description", function), where the function computes a rectangle
for each unmapped window from the screen it is on and the window ID.
Currently, Navigation2D provides only two functions of this type:
singleWindowRect
and fullScreenRect
.
With per-layout navigation strategies, if different layouts are in effect on different screens in a multi-monitor setup, and different navigation strategies are defined for these active layouts, the most general of these navigation strategies is used across all screens (because Navigation2D does not distinguish between windows on different workspaces), where center navigation is more general than line navigation, as discussed formally under #Technical_Discussion.
Alternative directional navigation modules
There exist two alternatives to Navigation2D: XMonad.Actions.WindowNavigation and XMonad.Layout.WindowNavigation. X.L.WindowNavigation has the advantage of colouring windows to indicate the window that would receive the focus in each navigation direction, but it does not support navigation across multiple monitors, does not support directional navigation of floating windows, and has a very unintuitive definition of which window receives the focus next in each direction. X.A.WindowNavigation does support navigation across multiple monitors but does not provide window colouring while retaining the unintuitive navigational semantics of X.L.WindowNavigation. This makes it very difficult to predict which window receives the focus next. Neither X.A.WindowNavigation nor X.L.WindowNavigation supports directional navigation of screens.
Incompatibilities
Currently Navigation2D is known not to play nicely with tabbed layouts, but
it should work well with any other tiled layout. My hope is to address the
incompatibility with tabbed layouts in a future version. The navigation to
unmapped windows, for example in a Full layout, by assigning rectangles to
unmapped windows is more a workaround than a clean solution. Figuring out
how to deal with tabbed layouts may also lead to a more general and cleaner
solution to query the layout for a window's rectangle that may make this
workaround unnecessary. At that point, the unmappedWindowRect
field of the
Navigation2DConfig
will disappear.
Detailed technical discussion
An in-depth discussion of the navigational strategies implemented in Navigation2D, including formal proofs of their properties, can be found at http://www.cs.dal.ca/~nzeh/xmonad/Navigation2D.pdf.
Exported functions and types
navigation2D :: Navigation2DConfig -> (KeySym, KeySym, KeySym, KeySym) -> [(ButtonMask, Direction2D -> Bool -> X ())] -> Bool -> XConfig l -> XConfig l Source #
Convenience function for enabling Navigation2D with typical keybindings. Takes a Navigation2DConfig, an (up, left, down, right) tuple, a mapping from modifier key to action, and a bool to indicate if wrapping should occur, and returns a function from XConfig to XConfig. Example:
navigation2D def (xK_w, xK_a, xK_s, xK_d) [(mod4Mask, windowGo), (mod4Mask .|. shiftMask, windowSwap)] False myConfig
navigation2DP :: Navigation2DConfig -> (String, String, String, String) -> [(String, Direction2D -> Bool -> X ())] -> Bool -> XConfig l -> XConfig l Source #
Convenience function for enabling Navigation2D with typical keybindings,
using the syntax defined in mkKeymap
. Takes a
Navigation2DConfig, an (up, left, down, right) tuple, a mapping from key
prefix to action, and a bool to indicate if wrapping should occur, and
returns a function from XConfig to XConfig. Example:
navigation2DP def ("w", "a", "s", "d") [("M-", windowGo), ("M-S-", windowSwap)] False myConfig
additionalNav2DKeys :: (KeySym, KeySym, KeySym, KeySym) -> [(ButtonMask, Direction2D -> Bool -> X ())] -> Bool -> XConfig l -> XConfig l Source #
Convenience function for adding keybindings. Takes an (up, left, down, right) tuple, a mapping from key prefix to action, and a bool to indicate if wrapping should occur, and returns a function from XConfig to XConfig. Example:
additionalNav2DKeys (xK_w, xK_a, xK_s, xK_d) [(mod4Mask, windowGo), (mod4Mask .|. shiftMask, windowSwap)] False myConfig
additionalNav2DKeysP :: (String, String, String, String) -> [(String, Direction2D -> Bool -> X ())] -> Bool -> XConfig l -> XConfig l Source #
Convenience function for adding keybindings, using the syntax defined in
mkKeymap
. Takes an (up, left, down, right) tuple, a
mapping from key prefix to action, and a bool to indicate if wrapping should
occur, and returns a function from XConfig to XConfig. Example:
additionalNav2DKeysP ("w", "a", "s", "d") [("M-", windowGo), ("M-S-", windowSwap)] False myConfig
withNavigation2DConfig :: Navigation2DConfig -> XConfig a -> XConfig a Source #
Modifies the xmonad configuration to store the Navigation2D configuration
data Navigation2DConfig Source #
Stores the configuration of directional navigation. The Default
instance
uses line navigation for the tiled layer and for navigation between screens,
and center navigation for the float layer. No custom navigation strategies
or rectangles for unmapped windows are defined for individual layouts.
Navigation2DConfig | |
|
Instances
lineNavigation :: Navigation2D Source #
Line navigation. To illustrate this navigation strategy, consider navigating to the left from the current window. In this case, we draw a horizontal line through the center of the current window and consider all windows that intersect this horizontal line and whose right boundaries are to the left of the left boundary of the current window. From among these windows, we choose the one with the rightmost right boundary.
centerNavigation :: Navigation2D Source #
Center navigation. Again, consider navigating to the left. Then we
consider the cone bounded by the two rays shot at 45-degree angles in
north-west and south-west direction from the center of the current window. A
window is a candidate to receive the focus if its center lies in this cone.
We choose the window whose center has minimum L1-distance from the current
window center. The tie breaking strategy for windows with the same distance
is a bit complicated (see #Technical_Discussion) but ensures that all
windows can be reached and that windows with the same center are traversed in
their order in the window stack, that is, in the order
focusUp
and focusDown
would traverse
them.
sideNavigation :: Navigation2D Source #
Side navigation. Consider navigating to the right this time. The strategy is to take the line segment forming the right boundary of the current window, and push it to the right until it intersects with at least one other window. Of those windows, one with a point that is the closest to the centre of the line (+1) is selected. This is probably the most intuitive strategy for the tiled layer when using XMonad.Layout.Spacing.
sideNavigationWithBias :: Int -> Navigation2D Source #
Side navigation with bias. Consider a case where the screen is divided up into three vertical panes; the side panes occupied by one window each and the central pane split across the middle by two windows. By the criteria of side navigation, the two central windows are equally good choices when navigating inwards from one of the side panes. Hence in order to be equitable, symmetric and pleasant to use, different windows are chosen when navigating from different sides. In particular, the lower is chosen when going left and the higher when going right, causing L, L, R, R, L, L, etc to cycle through the four windows clockwise. This is implemented by using a bias of 1. Bias is how many pixels off centre the vertical split can be before this behaviour is lost and the same window chosen every time. A negative bias swaps the preferred window for each direction. A bias of zero disables the behaviour.
hybridOf :: Navigation2D -> Navigation2D -> Navigation2D Source #
Hybrid of two modes of navigation, preferring the motions of the first.
Use this if you want to fall back on a second strategy whenever the first
does not find a candidate window. E.g.
hybridOf lineNavigation centerNavigation
is a good strategy for the
floating layer, and hybridOf sideNavigation centerNavigation
will enable
you to take advantage of some of the latter strategy's more interesting
motions in the tiled layer.
fullScreenRect :: Screen -> Window -> X (Maybe Rectangle) Source #
Maps each window to a fullscreen rect. This may not be the same rectangle the
window maps to under the Full layout or a similar layout if the layout
respects statusbar struts. In such cases, it may be better to use
singleWindowRect
.
singleWindowRect :: Screen -> Window -> X (Maybe Rectangle) Source #
Maps each window to the rectangle it would receive if it was the only window in the layout. Useful, for example, for determining the default rectangle for unmapped windows in a Full layout that respects statusbar struts.
switchLayer :: X () Source #
Switches focus to the closest window in the other layer (floating if the current window is tiled, tiled if the current window is floating). Closest means that the L1-distance between the centers of the windows is minimized.
windowGo :: Direction2D -> Bool -> X () Source #
Moves the focus to the next window in the given direction and in the same layer as the current window. The second argument indicates whether navigation should wrap around (e.g., from the left edge of the leftmost screen to the right edge of the rightmost screen).
windowSwap :: Direction2D -> Bool -> X () Source #
Swaps the current window with the next window in the given direction and in
the same layer as the current window. (In the floating layer, all that
changes for the two windows is their stacking order if they're on the same
screen. If they're on different screens, each window is moved to the other
window's screen but retains its position and size relative to the screen.)
The second argument indicates wrapping (see windowGo
).
windowToScreen :: Direction2D -> Bool -> X () Source #
Moves the current window to the next screen in the given direction. The
second argument indicates wrapping (see windowGo
).
screenGo :: Direction2D -> Bool -> X () Source #
Moves the focus to the next screen in the given direction. The second
argument indicates wrapping (see windowGo
).
screenSwap :: Direction2D -> Bool -> X () Source #
Swaps the workspace on the current screen with the workspace on the screen
in the given direction. The second argument indicates wrapping (see
windowGo
).
data Direction2D Source #
Two-dimensional directions: