aboutsummaryrefslogtreecommitdiffstats
path: root/FlexibleResize.hs
diff options
context:
space:
mode:
authorl.mai <l.mai@web.de>2007-06-29 19:10:38 +0200
committerl.mai <l.mai@web.de>2007-06-29 19:10:38 +0200
commit8c57d383a08a3dec19c39473dc3127f560508f7f (patch)
tree10a5b7b6c9fbcf49a5c515f46b8092d377cb1769 /FlexibleResize.hs
parent9f50fe94eda4f03e938d73490c3f082b6698f7b4 (diff)
downloadXMonadContrib-8c57d383a08a3dec19c39473dc3127f560508f7f.tar.gz
XMonadContrib-8c57d383a08a3dec19c39473dc3127f560508f7f.tar.xz
XMonadContrib-8c57d383a08a3dec19c39473dc3127f560508f7f.zip
flexible resizing for floating windows
The default resize handler for floating windows warps the mouse pointer to the bottom right corner of the window (fixing the opposite, upper left, corner). This extension lets you use any of the four window corners as grabbing points, allowing more flexible resizing. darcs-hash:20070629171038-42ea9-1a2b98ca2071dd5988e529b8395148b6a838ba9b.gz
Diffstat (limited to 'FlexibleResize.hs')
-rw-r--r--FlexibleResize.hs63
1 files changed, 63 insertions, 0 deletions
diff --git a/FlexibleResize.hs b/FlexibleResize.hs
new file mode 100644
index 0000000..9d5d098
--- /dev/null
+++ b/FlexibleResize.hs
@@ -0,0 +1,63 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonadContrib.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 XMonadContrib.FlexibleResize (
+ -- * Usage
+ -- $usage
+ XMonadContrib.FlexibleResize.mouseResizeWindow
+) where
+
+import XMonad
+import 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 XMonadContrib.FlexibleResize as Flex
+-- > mouseBindings = M.fromList
+-- > [ ...
+-- > , ((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' <- getWindowAttributes d w
+ let [px, py] = map (fromIntegral . ($ wa')) [wa_x, wa_y]
+ moveResizeWindow d w (fromIntegral $ fx px ex) (fromIntegral $ fy py ey)
+ `uncurry` applySizeHints sh (gx ex, gy 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 -> Dimension)
+ mkSel b k p =
+ if b
+ then (0, csnd, fromIntegral . max 1 . ((k + p) -) . fromIntegral)
+ else (k, cfst, fromIntegral . max 1 . subtract p . fromIntegral)