-----------------------------------------------------------------------------
-- |
-- Module       : XMonad.Actions.FloatKeys
-- Description  :  Move and resize floating windows.
-- Copyright    : (c) Karsten Schoelzel <kuser@gmx.de>
-- License      : BSD
--
-- Maintainer   : Karsten Schoelzel <kuser@gmx.de>
-- Stability    : stable
-- Portability  : unportable
--
-- Move and resize floating windows.
-----------------------------------------------------------------------------

module XMonad.Actions.FloatKeys (
                -- * Usage
                -- $usage
                keysMoveWindow,
                keysMoveWindowTo,
                keysResizeWindow,
                keysAbsResizeWindow,
                P, G, ChangeDim
                ) where

import XMonad
import XMonad.Prelude (fi)

-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
--
-- >    import XMonad.Actions.FloatKeys
--
-- Then add appropriate key bindings, for example:
--
-- >  , ((modm,               xK_d     ), withFocused (keysResizeWindow (-10,-10) (1,1)))
-- >  , ((modm,               xK_s     ), withFocused (keysResizeWindow (10,10) (1,1)))
-- >  , ((modm .|. shiftMask, xK_d     ), withFocused (keysAbsResizeWindow (-10,-10) (1024,752)))
-- >  , ((modm .|. shiftMask, xK_s     ), withFocused (keysAbsResizeWindow (10,10) (1024,752)))
-- >  , ((modm,               xK_a     ), withFocused (keysMoveWindowTo (512,384) (1%2,1%2)))
--
-- For detailed instructions on editing your key bindings, see
-- "XMonad.Doc.Extending#Editing_key_bindings".

-- | @keysMoveWindow (dx, dy)@ moves the window by @dx@ pixels to the
--   right and @dy@ pixels down.
keysMoveWindow :: ChangeDim -> Window -> X ()
keysMoveWindow :: ChangeDim -> Window -> X ()
keysMoveWindow (Int
dx,Int
dy) Window
w = X Bool -> X () -> X ()
whenX (Window -> X Bool
isClient Window
w) (X () -> X ()) -> X () -> X ()
forall a b. (a -> b) -> a -> b
$ (Display -> X ()) -> X ()
forall a. (Display -> X a) -> X a
withDisplay ((Display -> X ()) -> X ()) -> (Display -> X ()) -> X ()
forall a b. (a -> b) -> a -> b
$ \Display
d ->
  Display -> Window -> (WindowAttributes -> X ()) -> X ()
withWindowAttributes Display
d Window
w ((WindowAttributes -> X ()) -> X ())
-> (WindowAttributes -> X ()) -> X ()
forall a b. (a -> b) -> a -> b
$ \WindowAttributes
wa -> do
    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 -> Position -> Position -> IO ()
moveWindow Display
d Window
w (Int -> Position
forall a b. (Integral a, Num b) => a -> b
fi (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fi (WindowAttributes -> CInt
wa_x WindowAttributes
wa) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
dx))
                        (Int -> Position
forall a b. (Integral a, Num b) => a -> b
fi (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fi (WindowAttributes -> CInt
wa_y WindowAttributes
wa) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
dy))
    Window -> X ()
float Window
w

-- | @keysMoveWindowTo (x, y) (gx, gy)@ moves the window relative
--   point @(gx, gy)@ to the point @(x,y)@, where @(gx,gy)@ gives a
--   position relative to the window border, i.e.  @gx = 0@ is the left
--   border, @gx = 1@ is the right border, @gy = 0@ is the top border, and
--   @gy = 1@ the bottom border.
--
--   For example, on a 1024x768 screen:
--
-- > keysMoveWindowTo (512,384) (1%2, 1%2) -- center the window on screen
-- > keysMoveWindowTo (1024,0) (1, 0)      -- put window in the top right corner
keysMoveWindowTo :: P -> G -> Window -> X ()
keysMoveWindowTo :: P -> G -> Window -> X ()
keysMoveWindowTo (Position
x,Position
y) (Rational
gx, Rational
gy) Window
w = X Bool -> X () -> X ()
whenX (Window -> X Bool
isClient Window
w) (X () -> X ()) -> X () -> X ()
forall a b. (a -> b) -> a -> b
$ (Display -> X ()) -> X ()
forall a. (Display -> X a) -> X a
withDisplay ((Display -> X ()) -> X ()) -> (Display -> X ()) -> X ()
forall a b. (a -> b) -> a -> b
$ \Display
d ->
  Display -> Window -> (WindowAttributes -> X ()) -> X ()
withWindowAttributes Display
d Window
w ((WindowAttributes -> X ()) -> X ())
-> (WindowAttributes -> X ()) -> X ()
forall a b. (a -> b) -> a -> b
$ \WindowAttributes
wa -> do
    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 -> Position -> Position -> IO ()
moveWindow Display
d Window
w (Position
x Position -> Position -> Position
forall a. Num a => a -> a -> a
- Rational -> Position
forall a b. (RealFrac a, Integral b) => a -> b
round (Rational
gx Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* CInt -> Rational
forall a b. (Integral a, Num b) => a -> b
fi (WindowAttributes -> CInt
wa_width WindowAttributes
wa)))
                        (Position
y Position -> Position -> Position
forall a. Num a => a -> a -> a
- Rational -> Position
forall a b. (RealFrac a, Integral b) => a -> b
round (Rational
gy Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* CInt -> Rational
forall a b. (Integral a, Num b) => a -> b
fi (WindowAttributes -> CInt
wa_height WindowAttributes
wa)))
    Window -> X ()
float Window
w

type G = (Rational, Rational)
type P = (Position, Position)
type ChangeDim = (Int, Int)

-- | @keysResizeWindow (dx, dy) (gx, gy)@ changes the width by @dx@
--   and the height by @dy@, leaving the window-relative point @(gx,
--   gy)@ fixed.
--
--   For example:
--
-- > keysResizeWindow (10, 0) (0, 0)      -- make the window 10 pixels larger to the right
-- > keysResizeWindow (10, 0) (0, 1%2)    -- does the same, unless sizeHints are applied
-- > keysResizeWindow (10, 10) (1%2, 1%2) -- add 5 pixels on each side
-- > keysResizeWindow (-10, -10) (0, 1)   -- shrink the window in direction of the bottom-left corner
keysResizeWindow :: ChangeDim -> G -> Window -> X ()
keysResizeWindow :: ChangeDim -> G -> Window -> X ()
keysResizeWindow = (SizeHints -> P -> D -> ChangeDim -> G -> (P, D))
-> ChangeDim -> G -> Window -> X ()
forall a b.
(SizeHints -> P -> D -> a -> b -> (P, D))
-> a -> b -> Window -> X ()
keysMoveResize SizeHints -> P -> D -> ChangeDim -> G -> (P, D)
keysResizeWindow'

-- | @keysAbsResizeWindow (dx, dy) (ax, ay)@ changes the width by @dx@
--   and the height by @dy@, leaving the screen absolute point @(ax,
--   ay)@ fixed.
--
--   For example:
--
-- > keysAbsResizeWindow (10, 10) (0, 0)   -- enlarge the window; if it is not in the top-left corner it will also be moved down and to the right.
keysAbsResizeWindow :: ChangeDim -> D -> Window -> X ()
keysAbsResizeWindow :: ChangeDim -> D -> Window -> X ()
keysAbsResizeWindow = (SizeHints -> P -> D -> ChangeDim -> D -> (P, D))
-> ChangeDim -> D -> Window -> X ()
forall a b.
(SizeHints -> P -> D -> a -> b -> (P, D))
-> a -> b -> Window -> X ()
keysMoveResize SizeHints -> P -> D -> ChangeDim -> D -> (P, D)
keysAbsResizeWindow'

keysAbsResizeWindow' :: SizeHints -> P -> D -> ChangeDim -> D -> (P,D)
keysAbsResizeWindow' :: SizeHints -> P -> D -> ChangeDim -> D -> (P, D)
keysAbsResizeWindow' SizeHints
sh (Position
x,Position
y) (Dimension
w,Dimension
h) (Int
dx,Int
dy) (Dimension
ax, Dimension
ay) = ((Rational -> Position
forall a b. (RealFrac a, Integral b) => a -> b
round Rational
nx, Rational -> Position
forall a b. (RealFrac a, Integral b) => a -> b
round Rational
ny), (Dimension
nw, Dimension
nh))
    where
        -- The width and height of a window are positive and thus
        -- converting to 'Dimension' should be safe.
        (Dimension
nw, Dimension
nh) = SizeHints -> ChangeDim -> D
forall a. Integral a => SizeHints -> (a, a) -> D
applySizeHintsContents SizeHints
sh (Dimension -> Int
forall a b. (Integral a, Num b) => a -> b
fi Dimension
w Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
dx, Dimension -> Int
forall a b. (Integral a, Num b) => a -> b
fi Dimension
h Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
dy)
        nx :: Rational
        nx :: Rational
nx = Dimension -> Rational
forall a b. (Integral a, Num b) => a -> b
fi (Dimension
ax Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
* Dimension
w Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
+ Dimension
nw Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
* (Position -> Dimension
forall a b. (Integral a, Num b) => a -> b
fi Position
x Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
- Dimension
ax)) Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/ Dimension -> Rational
forall a b. (Integral a, Num b) => a -> b
fi Dimension
w
        ny :: Rational
        ny :: Rational
ny = Dimension -> Rational
forall a b. (Integral a, Num b) => a -> b
fi (Dimension
ay Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
* Dimension
h Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
+ Dimension
nh Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
* (Position -> Dimension
forall a b. (Integral a, Num b) => a -> b
fi Position
y Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
- Dimension
ay)) Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/ Dimension -> Rational
forall a b. (Integral a, Num b) => a -> b
fi Dimension
h

keysResizeWindow' :: SizeHints -> P -> D -> ChangeDim -> G -> (P,D)
keysResizeWindow' :: SizeHints -> P -> D -> ChangeDim -> G -> (P, D)
keysResizeWindow' SizeHints
sh (Position
x,Position
y) (Dimension
w,Dimension
h) (Int
dx,Int
dy) (Rational
gx, Rational
gy) = ((Position
nx, Position
ny), (Dimension
nw, Dimension
nh))
    where
        (Dimension
nw, Dimension
nh) = SizeHints -> ChangeDim -> D
forall a. Integral a => SizeHints -> (a, a) -> D
applySizeHintsContents SizeHints
sh (Dimension -> Int
forall a b. (Integral a, Num b) => a -> b
fi Dimension
w Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
dx, Dimension -> Int
forall a b. (Integral a, Num b) => a -> b
fi Dimension
h Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
dy)
        nx :: Position
nx = Rational -> Position
forall a b. (RealFrac a, Integral b) => a -> b
round (Rational -> Position) -> Rational -> Position
forall a b. (a -> b) -> a -> b
$ Position -> Rational
forall a b. (Integral a, Num b) => a -> b
fi Position
x Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
+ Rational
gx Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* Dimension -> Rational
forall a b. (Integral a, Num b) => a -> b
fi Dimension
w Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
- Rational
gx Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* Dimension -> Rational
forall a b. (Integral a, Num b) => a -> b
fi Dimension
nw
        ny :: Position
ny = Rational -> Position
forall a b. (RealFrac a, Integral b) => a -> b
round (Rational -> Position) -> Rational -> Position
forall a b. (a -> b) -> a -> b
$ Position -> Rational
forall a b. (Integral a, Num b) => a -> b
fi Position
y Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
+ Rational
gy Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* Dimension -> Rational
forall a b. (Integral a, Num b) => a -> b
fi Dimension
h Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
- Rational
gy Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* Dimension -> Rational
forall a b. (Integral a, Num b) => a -> b
fi Dimension
nh

keysMoveResize :: (SizeHints -> P -> D -> a -> b -> (P,D)) -> a -> b -> Window -> X ()
keysMoveResize :: forall a b.
(SizeHints -> P -> D -> a -> b -> (P, D))
-> a -> b -> Window -> X ()
keysMoveResize SizeHints -> P -> D -> a -> b -> (P, D)
f a
move b
resize Window
w = X Bool -> X () -> X ()
whenX (Window -> X Bool
isClient Window
w) (X () -> X ()) -> X () -> X ()
forall a b. (a -> b) -> a -> b
$ (Display -> X ()) -> X ()
forall a. (Display -> X a) -> X a
withDisplay ((Display -> X ()) -> X ()) -> (Display -> X ()) -> X ()
forall a b. (a -> b) -> a -> b
$ \Display
d ->
  Display -> Window -> (WindowAttributes -> X ()) -> X ()
withWindowAttributes Display
d Window
w ((WindowAttributes -> X ()) -> X ())
-> (WindowAttributes -> X ()) -> X ()
forall a b. (a -> b) -> a -> b
$ \WindowAttributes
wa -> do
    SizeHints
sh <- IO SizeHints -> X SizeHints
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (IO SizeHints -> X SizeHints) -> IO SizeHints -> X SizeHints
forall a b. (a -> b) -> a -> b
$ Display -> Window -> IO SizeHints
getWMNormalHints Display
d Window
w
    let wa_dim :: D
wa_dim = (CInt -> Dimension
forall a b. (Integral a, Num b) => a -> b
fi (CInt -> Dimension) -> CInt -> Dimension
forall a b. (a -> b) -> a -> b
$ WindowAttributes -> CInt
wa_width WindowAttributes
wa, CInt -> Dimension
forall a b. (Integral a, Num b) => a -> b
fi (CInt -> Dimension) -> CInt -> Dimension
forall a b. (a -> b) -> a -> b
$ WindowAttributes -> CInt
wa_height WindowAttributes
wa)
        wa_pos :: P
wa_pos = (CInt -> Position
forall a b. (Integral a, Num b) => a -> b
fi (CInt -> Position) -> CInt -> Position
forall a b. (a -> b) -> a -> b
$ WindowAttributes -> CInt
wa_x WindowAttributes
wa, CInt -> Position
forall a b. (Integral a, Num b) => a -> b
fi (CInt -> Position) -> CInt -> Position
forall a b. (a -> b) -> a -> b
$ WindowAttributes -> CInt
wa_y WindowAttributes
wa)
        (P
wn_pos, D
wn_dim) = SizeHints -> P -> D -> a -> b -> (P, D)
f SizeHints
sh P
wa_pos D
wa_dim a
move b
resize
    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 -> Dimension -> Dimension -> IO ()
resizeWindow Display
d Window
w (Dimension -> Dimension -> IO ()) -> D -> IO ()
forall a b c. (a -> b -> c) -> (a, b) -> c
`uncurry` D
wn_dim
    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 -> Position -> Position -> IO ()
moveWindow Display
d Window
w (Position -> Position -> IO ()) -> P -> IO ()
forall a b c. (a -> b -> c) -> (a, b) -> c
`uncurry` P
wn_pos
    Window -> X ()
float Window
w