aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad
diff options
context:
space:
mode:
authorAdam Vogt <vogt.adam@gmail.com>2009-09-30 22:41:51 +0200
committerAdam Vogt <vogt.adam@gmail.com>2009-09-30 22:41:51 +0200
commitcedf55fe4756e5724726564803c1ccd1f31ae9a9 (patch)
treea1d1f739caba8e3d41c4a242efddea3d01ea7e6e /XMonad
parent2c4d858189f16201cea7fa11bbb0a523995e97c3 (diff)
downloadXMonadContrib-cedf55fe4756e5724726564803c1ccd1f31ae9a9.tar.gz
XMonadContrib-cedf55fe4756e5724726564803c1ccd1f31ae9a9.tar.xz
XMonadContrib-cedf55fe4756e5724726564803c1ccd1f31ae9a9.zip
Factor out redundancy in L.MouseResizableTile.handleResize
Ignore-this: 77d8e635a06237b220f427fa64045a3a darcs-hash:20090930204151-1499c-91a52e54e5a52317201d2f08bb4f6386cdd43c9e.gz
Diffstat (limited to 'XMonad')
-rw-r--r--XMonad/Layout/MouseResizableTile.hs27
1 files changed, 9 insertions, 18 deletions
diff --git a/XMonad/Layout/MouseResizableTile.hs b/XMonad/Layout/MouseResizableTile.hs
index 2d19056..05a60cc 100644
--- a/XMonad/Layout/MouseResizableTile.hs
+++ b/XMonad/Layout/MouseResizableTile.hs
@@ -237,26 +237,17 @@ deleteDragger (draggerWin, _) = deleteWindow draggerWin
handleResize :: [DraggerWithWin] -> Bool -> Event -> X ()
handleResize draggers' isM ButtonEvent { ev_window = ew, ev_event_type = et }
- | et == buttonPress = do
- case (lookup ew draggers') of
- Just (MasterDragger lowerBound range) -> do
- mouseDrag (\x y -> do
- let axis = chooseAxis isM x y
- fraction = fromIntegral (axis - lowerBound) / range
- sendMessage (SetMasterFraction fraction)) (return ())
- Just (LeftSlaveDragger lowerBound range num) -> do
- mouseDrag (\x y -> do
- let axis = chooseAxis isM y x
- fraction = fromIntegral (axis - lowerBound) / range
- sendMessage (SetLeftSlaveFraction num fraction)) (return ())
- Just (RightSlaveDragger lowerBound range num) -> do
- mouseDrag (\x y -> do
- let axis = chooseAxis isM y x
- fraction = fromIntegral (axis - lowerBound) / range
- sendMessage (SetRightSlaveFraction num fraction)) (return ())
- Nothing -> return ()
+ | et == buttonPress, Just x <- lookup ew draggers' = case x of
+ MasterDragger lb r -> mouseDrag' id lb r SetMasterFraction
+ LeftSlaveDragger lb r num -> mouseDrag' flip lb r (SetLeftSlaveFraction num)
+ RightSlaveDragger lb r num -> mouseDrag' flip lb r (SetRightSlaveFraction num)
where
chooseAxis isM' axis1 axis2 = if isM' then axis2 else axis1
+ mouseDrag' flp lowerBound range msg = flip mouseDrag (return ()) $ \x y -> do
+ let axis = flp (chooseAxis isM) x y
+ fraction = fromIntegral (axis - lowerBound) / range
+ sendMessage (msg fraction)
+
handleResize _ _ _ = return ()
createInputWindow :: Glyph -> Rectangle -> X Window