{-# LANGUAGE ScopedTypeVariables #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  XMonadContrib.UpdatePointer
-- Description :  Causes the pointer to follow whichever window focus changes to.
-- Copyright   :  (c) Robert Marlow <robreim@bobturf.org>, 2015 Evgeny Kurnevsky
-- License     :  BSD3-style (see LICENSE)
--
-- Maintainer  :  Robert Marlow <robreim@bobturf.org>
-- Stability   :  stable
-- Portability :  portable
--
-- Causes the pointer to follow whichever window focus changes to. Compliments
-- the idea of switching focus as the mouse crosses window boundaries to
-- keep the mouse near the currently focused window
--
-----------------------------------------------------------------------------

module XMonad.Actions.UpdatePointer
    (
     -- * Usage
     -- $usage
     updatePointer
    )
    where

import XMonad
import XMonad.Prelude
import XMonad.StackSet (member, peek, screenDetail, current)

import Control.Arrow ((&&&), (***))

-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad
-- > import XMonad.Actions.UpdatePointer
--
-- Enable it by including it in your logHook definition, e.g.:
--
-- > logHook = updatePointer (0.5, 0.5) (1, 1)
--
-- which will move the pointer to the nearest point of a newly focused
-- window. The first argument establishes a reference point within the
-- newly-focused window, while the second argument linearly interpolates
-- between said reference point and the edges of the newly-focused window to
-- obtain a bounding box for the pointer.
--
-- > logHook = updatePointer (0.5, 0.5) (0, 0) -- exact centre of window
-- > logHook = updatePointer (0.25, 0.25) (0.25, 0.25) -- near the top-left
-- > logHook = updatePointer (0.5, 0.5) (1.1, 1.1) -- within 110% of the edge
--
-- To use this with an existing logHook, use >> :
--
-- > logHook = dynamicLog
-- >           >> updatePointer (1, 1) (0, 0)
--
-- which moves the pointer to the bottom-right corner of the focused window.

-- | Update the pointer's location to the currently focused
-- window or empty screen unless it's already there, or unless the user was changing
-- focus with the mouse
--
-- See also 'XMonad.Actions.UpdateFocus.focusUnderPointer' for an inverse
-- operation that updates the focus instead. The two can be combined in a
-- single config if neither goes into 'logHook' but are invoked explicitly in
-- individual key bindings.
updatePointer :: (Rational, Rational) -> (Rational, Rational) -> X ()
updatePointer :: (Rational, Rational) -> (Rational, Rational) -> X ()
updatePointer (Rational, Rational)
refPos (Rational, Rational)
ratio = do
  WindowSet
ws <- (XState -> WindowSet) -> X WindowSet
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets XState -> WindowSet
windowset
  Display
dpy <- (XConf -> Display) -> X Display
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks XConf -> Display
display
  let defaultRect :: Rectangle
defaultRect = ScreenDetail -> Rectangle
screenRect (ScreenDetail -> Rectangle) -> ScreenDetail -> Rectangle
forall a b. (a -> b) -> a -> b
$ Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
-> ScreenDetail
forall i l a sid sd. Screen i l a sid sd -> sd
screenDetail (Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
 -> ScreenDetail)
-> Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
-> ScreenDetail
forall a b. (a -> b) -> a -> b
$ WindowSet
-> Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
forall i l a sid sd. StackSet i l a sid sd -> Screen i l a sid sd
current WindowSet
ws
  Rectangle
rect <- case WindowSet -> Maybe Window
forall i l a s sd. StackSet i l a s sd -> Maybe a
peek WindowSet
ws of
        Maybe Window
Nothing -> Rectangle -> X Rectangle
forall (m :: * -> *) a. Monad m => a -> m a
return Rectangle
defaultRect
        Just Window
w  -> Rectangle
-> (WindowAttributes -> Rectangle)
-> Maybe WindowAttributes
-> Rectangle
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Rectangle
defaultRect WindowAttributes -> Rectangle
windowAttributesToRectangle
               (Maybe WindowAttributes -> Rectangle)
-> X (Maybe WindowAttributes) -> X Rectangle
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Window -> X (Maybe WindowAttributes)
safeGetWindowAttributes Window
w

  Window
root <- (XConf -> Window) -> X Window
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks XConf -> Window
theRoot
  Bool
mouseIsMoving <- (XConf -> Bool) -> X Bool
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks XConf -> Bool
mouseFocused
  (Bool
_sameRoot,Window
_,Window
currentWindow,CInt
rootX,CInt
rootY,CInt
_,CInt
_,Modifier
_) <- IO (Bool, Window, Window, CInt, CInt, CInt, CInt, Modifier)
-> X (Bool, Window, Window, CInt, CInt, CInt, CInt, Modifier)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO (Bool, Window, Window, CInt, CInt, CInt, CInt, Modifier)
 -> X (Bool, Window, Window, CInt, CInt, CInt, CInt, Modifier))
-> IO (Bool, Window, Window, CInt, CInt, CInt, CInt, Modifier)
-> X (Bool, Window, Window, CInt, CInt, CInt, CInt, Modifier)
forall a b. (a -> b) -> a -> b
$ Display
-> Window
-> IO (Bool, Window, Window, CInt, CInt, CInt, CInt, Modifier)
queryPointer Display
dpy Window
root
  Maybe (Position -> Position -> X (), X ())
drag <- (XState -> Maybe (Position -> Position -> X (), X ()))
-> X (Maybe (Position -> Position -> X (), X ()))
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets XState -> Maybe (Position -> Position -> X (), X ())
dragging
  Bool -> X () -> X ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Position -> Position -> Rectangle -> Bool
pointWithin (CInt -> Position
forall a b. (Integral a, Num b) => a -> b
fi CInt
rootX) (CInt -> Position
forall a b. (Integral a, Num b) => a -> b
fi CInt
rootY) Rectangle
rect
          Bool -> Bool -> Bool
|| Bool
mouseIsMoving
          Bool -> Bool -> Bool
|| Maybe (Position -> Position -> X (), X ()) -> Bool
forall a. Maybe a -> Bool
isJust Maybe (Position -> Position -> X (), X ())
drag
          Bool -> Bool -> Bool
|| Bool -> Bool
not (Window
currentWindow Window -> WindowSet -> Bool
forall a i l s sd. Eq a => a -> StackSet i l a s sd -> Bool
`member` WindowSet
ws Bool -> Bool -> Bool
|| Window
currentWindow Window -> Window -> Bool
forall a. Eq a => a -> a -> Bool
== Window
none)) (X () -> X ()) -> X () -> X ()
forall a b. (a -> b) -> a -> b
$ let
    -- focused rectangle
    (Position
rectX, Position
rectY) = (Rectangle -> Position
rect_x (Rectangle -> Position)
-> (Rectangle -> Position) -> Rectangle -> (Position, Position)
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& Rectangle -> Position
rect_y) Rectangle
rect
    (Position
rectW, Position
rectH) = (Dimension -> Position
forall a b. (Integral a, Num b) => a -> b
fi (Dimension -> Position)
-> (Rectangle -> Dimension) -> Rectangle -> Position
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rectangle -> Dimension
rect_width (Rectangle -> Position)
-> (Rectangle -> Position) -> Rectangle -> (Position, Position)
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& Dimension -> Position
forall a b. (Integral a, Num b) => a -> b
fi (Dimension -> Position)
-> (Rectangle -> Dimension) -> Rectangle -> Position
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rectangle -> Dimension
rect_height) Rectangle
rect
    -- reference position, with (0,0) and (1,1) being top-left and bottom-right
    refX :: Rational
refX = Rational -> Position -> Position -> Rational
forall r a b. (RealFrac r, Real a, Real b) => r -> a -> b -> r
lerp ((Rational, Rational) -> Rational
forall a b. (a, b) -> a
fst (Rational, Rational)
refPos) Position
rectX (Position
rectX Position -> Position -> Position
forall a. Num a => a -> a -> a
+ Position
rectW)
    refY :: Rational
refY = Rational -> Position -> Position -> Rational
forall r a b. (RealFrac r, Real a, Real b) => r -> a -> b -> r
lerp ((Rational, Rational) -> Rational
forall a b. (a, b) -> b
snd (Rational, Rational)
refPos) Position
rectY (Position
rectY Position -> Position -> Position
forall a. Num a => a -> a -> a
+ Position
rectH)
    -- final pointer bounds, lerped *outwards* from reference position
    boundsX :: (Rational, Rational)
boundsX = ((Position -> Rational)
 -> (Position -> Rational)
 -> (Position, Position)
 -> (Rational, Rational))
-> (Position -> Rational)
-> (Position, Position)
-> (Rational, Rational)
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (Position -> Rational)
-> (Position -> Rational)
-> (Position, Position)
-> (Rational, Rational)
forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
(***) (Rational -> Rational -> Position -> Rational
forall r a b. (RealFrac r, Real a, Real b) => r -> a -> b -> r
lerp ((Rational, Rational) -> Rational
forall a b. (a, b) -> a
fst (Rational, Rational)
ratio) Rational
refX) (Position
rectX, Position
rectX Position -> Position -> Position
forall a. Num a => a -> a -> a
+ Position
rectW)
    boundsY :: (Rational, Rational)
boundsY = ((Position -> Rational)
 -> (Position -> Rational)
 -> (Position, Position)
 -> (Rational, Rational))
-> (Position -> Rational)
-> (Position, Position)
-> (Rational, Rational)
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (Position -> Rational)
-> (Position -> Rational)
-> (Position, Position)
-> (Rational, Rational)
forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
(***) (Rational -> Rational -> Position -> Rational
forall r a b. (RealFrac r, Real a, Real b) => r -> a -> b -> r
lerp ((Rational, Rational) -> Rational
forall a b. (a, b) -> b
snd (Rational, Rational)
ratio) Rational
refY) (Position
rectY, Position
rectY Position -> Position -> Position
forall a. Num a => a -> a -> a
+ Position
rectH)
    -- ideally we ought to move the pointer in a straight line towards the
    -- reference point until it is within the above bounds, but…
    in IO () -> X ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO () -> X ()) -> IO () -> X ()
forall a b. (a -> b) -> a -> b
$ Display
-> Window
-> Window
-> Position
-> Position
-> Dimension
-> Dimension
-> Position
-> Position
-> IO ()
warpPointer Display
dpy Window
none Window
root Position
0 Position
0 Dimension
0 Dimension
0
        (Rational -> Position
forall a b. (RealFrac a, Integral b) => a -> b
round (Rational -> Position)
-> (Rational -> Rational) -> Rational -> Position
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Rational, Rational) -> Rational -> Rational
forall a. Ord a => (a, a) -> a -> a
clip (Rational, Rational)
boundsX (Rational -> Position) -> Rational -> Position
forall a b. (a -> b) -> a -> b
$ CInt -> Rational
forall a b. (Integral a, Num b) => a -> b
fi CInt
rootX)
        (Rational -> Position
forall a b. (RealFrac a, Integral b) => a -> b
round (Rational -> Position)
-> (Rational -> Rational) -> Rational -> Position
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Rational, Rational) -> Rational -> Rational
forall a. Ord a => (a, a) -> a -> a
clip (Rational, Rational)
boundsY (Rational -> Position) -> Rational -> Position
forall a b. (a -> b) -> a -> b
$ CInt -> Rational
forall a b. (Integral a, Num b) => a -> b
fi CInt
rootY)

windowAttributesToRectangle :: WindowAttributes -> Rectangle
windowAttributesToRectangle :: WindowAttributes -> Rectangle
windowAttributesToRectangle WindowAttributes
wa = Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle (CInt -> Position
forall a b. (Integral a, Num b) => a -> b
fi (WindowAttributes -> CInt
wa_x WindowAttributes
wa))
                                           (CInt -> Position
forall a b. (Integral a, Num b) => a -> b
fi (WindowAttributes -> CInt
wa_y WindowAttributes
wa))
                                           (CInt -> Dimension
forall a b. (Integral a, Num b) => a -> b
fi (WindowAttributes -> CInt
wa_width WindowAttributes
wa CInt -> CInt -> CInt
forall a. Num a => a -> a -> a
+ CInt
2 CInt -> CInt -> CInt
forall a. Num a => a -> a -> a
* WindowAttributes -> CInt
wa_border_width WindowAttributes
wa))
                                           (CInt -> Dimension
forall a b. (Integral a, Num b) => a -> b
fi (WindowAttributes -> CInt
wa_height WindowAttributes
wa CInt -> CInt -> CInt
forall a. Num a => a -> a -> a
+ CInt
2 CInt -> CInt -> CInt
forall a. Num a => a -> a -> a
* WindowAttributes -> CInt
wa_border_width WindowAttributes
wa))

lerp :: (RealFrac r, Real a, Real b) => r -> a -> b -> r
lerp :: forall r a b. (RealFrac r, Real a, Real b) => r -> a -> b -> r
lerp r
r a
a b
b = (r
1 r -> r -> r
forall a. Num a => a -> a -> a
- r
r) r -> r -> r
forall a. Num a => a -> a -> a
* a -> r
forall a b. (Real a, Fractional b) => a -> b
realToFrac a
a r -> r -> r
forall a. Num a => a -> a -> a
+ r
r r -> r -> r
forall a. Num a => a -> a -> a
* b -> r
forall a b. (Real a, Fractional b) => a -> b
realToFrac b
b

clip :: Ord a => (a, a) -> a -> a
clip :: forall a. Ord a => (a, a) -> a -> a
clip (a
lower, a
upper) a
x
  | a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
lower = a
lower
  | a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
> a
upper = a
upper
  | Bool
otherwise = a
x