aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions
diff options
context:
space:
mode:
authorAnders Engstrom <ankaan@gmail.com>2009-05-30 20:54:37 +0200
committerAnders Engstrom <ankaan@gmail.com>2009-05-30 20:54:37 +0200
commit773e9d3df02804275c5a9013c53edb42c55e3eef (patch)
tree16b300d0160b1584751a21683e86b229421952cc /XMonad/Actions
parent8b6cf6c8f8ee64bbdba2a1c69744352ad2366b4b (diff)
downloadXMonadContrib-773e9d3df02804275c5a9013c53edb42c55e3eef.tar.gz
XMonadContrib-773e9d3df02804275c5a9013c53edb42c55e3eef.tar.xz
XMonadContrib-773e9d3df02804275c5a9013c53edb42c55e3eef.zip
FlexibleResize - Resize from edge, don't move adjust at opposite edge
Ignore-this: 3c6c0748a4b0d14bd39bcb88f10aade6 When resizing other corners than bottom-right, instead of adjusting to even columns/rows on the opposite side to it the same way as if resizing was made from the bottom right. Also add the possibility to add an area in the middle of an edge where only that edge is resized, not the closest corner. darcs-hash:20090530185437-8978f-82de436312c45d105593603fd58f293056f91c11.gz
Diffstat (limited to 'XMonad/Actions')
-rw-r--r--XMonad/Actions/FlexibleResize.hs56
1 files changed, 35 insertions, 21 deletions
diff --git a/XMonad/Actions/FlexibleResize.hs b/XMonad/Actions/FlexibleResize.hs
index 534bcaf..380f70e 100644
--- a/XMonad/Actions/FlexibleResize.hs
+++ b/XMonad/Actions/FlexibleResize.hs
@@ -15,7 +15,8 @@
module XMonad.Actions.FlexibleResize (
-- * Usage
-- $usage
- XMonad.Actions.FlexibleResize.mouseResizeWindow
+ XMonad.Actions.FlexibleResize.mouseResizeWindow,
+ XMonad.Actions.FlexibleResize.mouseResizeEdgeWindow
) where
import XMonad
@@ -35,33 +36,46 @@ import Foreign.C.Types
-- | Resize a floating window from whichever corner the mouse is
-- closest to.
-mouseResizeWindow :: Window -> X ()
-mouseResizeWindow w = whenX (isClient w) $ withDisplay $ \d -> do
+mouseResizeWindow
+ :: Window -- ^ The window to resize.
+ -> X ()
+mouseResizeWindow = mouseResizeEdgeWindow 0
+
+
+-- | Resize a floating window from whichever corner or edge the mouse is
+-- closest to.
+mouseResizeEdgeWindow
+ :: Rational -- ^ The size of the area where only one edge is resized.
+ -> Window -- ^ The window to resize.
+ -> X ()
+mouseResizeEdgeWindow edge 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
+ [pos_x, pos_y, width, height] = map (fi . ($ wa)) [wa_x, wa_y, wa_width, wa_height]
+ west = findPos ix width
+ north = findPos 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` applySizeHintsContents sh (gx $ fromIntegral ex, gy $ fromIntegral ey))
+ mouseDrag (\ex ey -> do let (nw,nh) = applySizeHintsContents sh (gx ex, gy ey)
+ io $ moveResizeWindow d w (fx nw) (fy nh) nw nh)
(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)
+ findPos :: CInt -> Position -> Maybe Bool
+ findPos m s = if p < 0.5 - edge/2
+ then Just True
+ else if p < 0.5 + edge/2
+ then Nothing
+ else Just False
+ where p = fi m / fi s
+ mkSel :: Maybe Bool -> Position -> Position -> (Position, Dimension -> Position, Position -> Dimension)
+ mkSel b k p = case b of
+ Just True -> (0, (fi k + fi p -).fi, (fi k + fi p -).fi)
+ Nothing -> (k `div` 2, const p, const $ fi k)
+ Just False -> (k, const p, subtract (fi p) . fi)
+
+fi :: (Num b, Integral a) => a -> b
+fi = fromIntegral