Added navigation strategy sideNavigation and parameterised variant sideNavigationWithBias to X.A.Navigation2D.

This commit is contained in:
L.S. Leary 2017-12-09 14:32:08 +13:00
parent 51857a1a20
commit 4a98a27950
2 changed files with 99 additions and 12 deletions

View File

@ -71,6 +71,11 @@
### Bug Fixes and Minor Changes ### Bug Fixes and Minor Changes
* `XMonad.Actions.Navigation2D`
Added `sideNavigation` and a parameterised variant, providing a navigation
strategy with fewer quirks for tiled layouts using X.L.Spacing.
* `XMonad.Layout.Gaps` * `XMonad.Layout.Gaps`
Extended the sendMessage interface with `ModifyGaps` to allow arbitrary Extended the sendMessage interface with `ModifyGaps` to allow arbitrary

View File

@ -43,6 +43,8 @@ module XMonad.Actions.Navigation2D ( -- * Usage
, Navigation2D , Navigation2D
, lineNavigation , lineNavigation
, centerNavigation , centerNavigation
, sideNavigation
, sideNavigationWithBias
, hybridOf , hybridOf
, hybridNavigation , hybridNavigation
, fullScreenRect , fullScreenRect
@ -60,6 +62,7 @@ import Control.Applicative
import qualified Data.List as L import qualified Data.List as L
import qualified Data.Map as M import qualified Data.Map as M
import Data.Maybe import Data.Maybe
import Data.Ord (comparing)
import XMonad hiding (Screen) import XMonad hiding (Screen)
import qualified XMonad.StackSet as W import qualified XMonad.StackSet as W
import qualified XMonad.Util.ExtensibleState as XS import qualified XMonad.Util.ExtensibleState as XS
@ -71,16 +74,17 @@ import XMonad.Util.Types
-- Navigation2D provides directional navigation (go left, right, up, down) for -- Navigation2D provides directional navigation (go left, right, up, down) for
-- windows and screens. It treats floating and tiled windows as two separate -- windows and screens. It treats floating and tiled windows as two separate
-- layers and provides mechanisms to navigate within each layer and to switch -- layers and provides mechanisms to navigate within each layer and to switch
-- between layers. Navigation2D provides two different navigation strategies -- between layers. Navigation2D provides three different navigation strategies
-- (see <#Technical_Discussion> for details): /Line navigation/ feels rather -- (see <#Technical_Discussion> for details): /Line navigation/ and
-- natural but may make it impossible to navigate to a given window from the -- /Side navigation/ feel rather natural but may make it impossible to navigate
-- current window, particularly in the floating layer. /Center navigation/ -- to a given window from the current window, particularly in the floating
-- feels less natural in certain situations but ensures that all windows can be -- layer. /Center navigation/ feels less natural in certain situations but
-- reached without the need to involve the mouse. A third option is to use -- ensures that all windows can be reached without the need to involve the
-- a /Hybrid/ of the two strategies, automatically choosing whichever provides -- mouse. Another option is to use a /Hybrid/ of the three strategies,
-- a suitable target window. Navigation2D allows different navigation strategies -- automatically choosing whichever first provides a suitable target window.
-- to be used in the two layers and allows customization of the navigation strategy -- Navigation2D allows different navigation strategies to be used in the two
-- for the tiled layer based on the layout currently in effect. -- 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\/xmonad.hs@: -- You can use this module with (a subset of) the following in your @~\/.xmonad\/xmonad.hs@:
-- --
@ -319,9 +323,38 @@ lineNavigation = N 1 doLineNavigation
centerNavigation :: Navigation2D centerNavigation :: Navigation2D
centerNavigation = N 2 doCenterNavigation centerNavigation = N 2 doCenterNavigation
-- | 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.
sideNavigation :: Navigation2D
sideNavigation = N 1 (doSideNavigationWithBias 1)
-- | 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.
sideNavigationWithBias :: Int -> Navigation2D
sideNavigationWithBias b = N 1 (doSideNavigationWithBias b)
-- | Hybrid of two modes of navigation, preferring the motions of the first. -- | Hybrid of two modes of navigation, preferring the motions of the first.
-- This is useful because line navigation often fails on gaps, whereas center -- Use this if you want to fall back on a second strategy whenever the first
-- navigation often fails when moving from small to large windows. -- 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.
hybridOf :: Navigation2D -> Navigation2D -> Navigation2D hybridOf :: Navigation2D -> Navigation2D -> Navigation2D
hybridOf (N g1 s1) (N g2 s2) = N (max g1 g2) $ applyToBoth s1 s2 hybridOf (N g1 s1) (N g2 s2) = N (max g1 g2) $ applyToBoth s1 s2
where where
@ -773,6 +806,55 @@ doCenterNavigation dir (cur, rect) winrects
-- or it has the same distance but comes later -- or it has the same distance but comes later
-- in the window stack -- in the window stack
-- x -y w h format is a pain. Let's use side coordinates. We assume x1 <= x2 and
-- y1 <= y2, and make the assumption valid by initialising SideRects with the
-- property and carefully preserving it over any individual transformation.
data SideRect = SideRect { x1 :: Int, x2 :: Int, y1 :: Int, y2 :: Int }
deriving Show
-- Conversion from Rectangle format to SideRect.
toSR :: Rectangle -> SideRect
toSR (Rectangle x y w h) = SideRect (fi x) (fi x + fi w) (-fi y - fi h) (-fi y)
-- Implements side navigation with bias.
doSideNavigationWithBias ::
Eq a => Int -> Direction2D -> Rect a -> [Rect a] -> Maybe a
doSideNavigationWithBias bias dir (cur, rect)
= fmap fst . listToMaybe
. L.sortBy (comparing dist) . foldr acClosest []
. filter (`toRightOf` (cur, transform rect))
. map (fmap transform)
where
-- Getting the center of the current window so we can make it the new origin.
cOf r = ((x1 r + x2 r) `div` 2, (y1 r + y2 r) `div` 2)
(x0, y0) = cOf . toSR $ rect
-- Translate the given SideRect by (-x0, -y0).
translate r = SideRect (x1 r - x0) (x2 r - x0) (y1 r - y0) (y2 r - y0)
-- Rotate the given SideRect 90 degrees counter-clockwise about the origin.
rHalfPiCC r = SideRect (-y2 r) (-y1 r) (x1 r) (x2 r)
-- Apply the above function until d becomes synonymous with R (wolog).
rotateToR d = let (_, _:l) = break (d ==) [U, L, D, R]
in foldr (const $ (.) rHalfPiCC) id l
transform = rotateToR dir . translate . toSR
-- (_, r) `toRightOf` (_, c) iff r has points to the right of c that aren't
-- below or above c, i.e. iff:
-- [x1 r, x2 r] x [y1 r, y2 r] intersects (x2 c, infinity) x (y1 c, y2 c)
toRightOf (_, r) (_, c) = (x2 r > x2 c) && (y2 r > y1 c) && (y1 r < y2 c)
-- Greedily accumulate the windows tied for the leftmost left side.
acClosest (w, r) l@((_, r'):_) | x1 r == x1 r' = (w, r) : l
| x1 r > x1 r' = l
acClosest (w, r) _ = (w, r) : []
-- Given a (_, SideRect), calculate how far it is from the y=bias line.
dist (_, r) | (y1 r <= bias) && (bias <= y2 r) = 0
| otherwise = min (abs $ y1 r - bias) (abs $ y2 r - bias)
-- | Swaps the current window with the window given as argument -- | Swaps the current window with the window given as argument
swap :: Window -> WindowSet -> WindowSet swap :: Window -> WindowSet -> WindowSet
swap win winset = W.focusWindow cur swap win winset = W.focusWindow cur