aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions/FlexibleResize.hs
blob: 9f111f781f2eb948388e03c69e912d93dc70c5e3 (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Actions.FlexibleResize
-- Copyright   :  (c) Lukas Mai
-- License     :  BSD3-style (see LICENSE)
-- 
-- Maintainer  :  <l.mai@web.de>
-- Stability   :  unstable
-- Portability :  unportable
--
-- Lets you resize floating windows from any corner.
--
-----------------------------------------------------------------------------

module XMonad.Actions.FlexibleResize (
	-- * Usage
	-- $usage
	XMonad.Actions.FlexibleResize.mouseResizeWindow
) where

import XMonad
import XMonad.Operations
import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras
import Foreign.C.Types

-- $usage
-- Put something like this in your Config.hs file:
--
-- > import qualified XMonad.Actions.FlexibleResize as Flex
-- > mouseBindings = M.fromList
-- >     [ ...
-- >     , ((modMask, button3), (\w -> focus w >> Flex.mouseResizeWindow w)) ]

-- %import qualified XMonad.Actions.FlexibleResize as Flex
-- %mousebind , ((modMask, button3), (\\w -> focus w >> Flex.mouseResizeWindow w))

mouseResizeWindow :: Window -> X ()
mouseResizeWindow w = whenX (isClient w) $ withDisplay $ \d -> do
    io $ raiseWindow d w
    wa <- io $ getWindowAttributes d w
    sh <- io $ getWMNormalHints d w
    (_, _, _, _, _, ix, iy, _) <- io $ queryPointer d w
    let
        [pos_x, pos_y, width, height] = map (fromIntegral . ($ wa)) [wa_x, wa_y, wa_width, wa_height]
        west  = firstHalf ix width
        north = firstHalf iy height
        (cx, fx, gx) = mkSel west  width  pos_x
        (cy, fy, gy) = mkSel north height pos_y
    io $ warpPointer d none w 0 0 0 0 cx cy
    mouseDrag (\ex ey -> do
                 wa' <- io $ getWindowAttributes d w
                 let [px, py] = map (fromIntegral . ($ wa')) [wa_x, wa_y]
                 io $ moveResizeWindow d w (fx px (fromIntegral ex))
                                           (fy py (fromIntegral ey))
                            `uncurry` applySizeHints sh (gx $ fromIntegral ex, gy $ fromIntegral ey))
              (float w)
    where
    firstHalf :: CInt -> Position -> Bool
    firstHalf a b = fromIntegral a * 2 <= b
    cfst = curry fst
    csnd = curry snd
    mkSel :: Bool -> Position -> Position -> (Position, a -> a -> a, CInt -> Position)
    mkSel b k p =
        if b
            then (0, csnd, ((k + p) -) . fromIntegral)
            else (k, cfst, subtract p  . fromIntegral)