aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions/FlexibleManipulate.hs
diff options
context:
space:
mode:
authorBrent Yorgey <byorgey@gmail.com>2007-11-24 01:07:54 +0100
committerBrent Yorgey <byorgey@gmail.com>2007-11-24 01:07:54 +0100
commit173380adaab40fd3e85f3a63920297a3b6401af5 (patch)
tree1a4e34f91a28ebbc4c8b87b40a9fe8a99877b58e /XMonad/Actions/FlexibleManipulate.hs
parentc6f5a0f9faca0cb952e140566ecf3e144d4e5a59 (diff)
downloadXMonadContrib-173380adaab40fd3e85f3a63920297a3b6401af5.tar.gz
XMonadContrib-173380adaab40fd3e85f3a63920297a3b6401af5.tar.xz
XMonadContrib-173380adaab40fd3e85f3a63920297a3b6401af5.zip
FlexibleManipulate: haddock updates
darcs-hash:20071124000754-bd4d7-8398396e1bc3889ba25d96d38289c3a4350303d8.gz
Diffstat (limited to '')
-rw-r--r--XMonad/Actions/FlexibleManipulate.hs52
1 files changed, 32 insertions, 20 deletions
diff --git a/XMonad/Actions/FlexibleManipulate.hs b/XMonad/Actions/FlexibleManipulate.hs
index b7fa25d..8b18acc 100644
--- a/XMonad/Actions/FlexibleManipulate.hs
+++ b/XMonad/Actions/FlexibleManipulate.hs
@@ -5,16 +5,16 @@
-- Module : XMonad.Actions.FlexibleManipulate
-- Copyright : (c) Michael Sloan
-- License : BSD3-style (see LICENSE)
---
+--
-- Maintainer : <mgsloan@gmail.com>
-- Stability : unstable
-- Portability : unportable
--
--- Lets you move and resize floating windows without warping the mouse.
+-- Move and resize floating windows without warping the mouse.
--
-----------------------------------------------------------------------------
--- Based on the FlexibleResize code by Lukas Mai (Mauke)
+-- Based on the FlexibleResize code by Lukas Mai (mauke).
module XMonad.Actions.FlexibleManipulate (
-- * Usage
@@ -28,41 +28,53 @@ import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras
-- $usage
--- Add this import to your Config.hs file:
+-- First, add this import to your @~\/.xmonad\/xmonad.hs@:
--
-- > import qualified XMonad.Actions.FlexibleManipulate as Flex
--
--- Set one of the mouse button bindings up like this:
+-- Now set up the desired mouse binding, for example:
+--
+-- > , ((modMask, button1), (\w -> focus w >> Flex.mouseWindow Flex.linear w))
+--
+-- * Flex.'linear' indicates that positions between the edges and the
+-- middle indicate a combination scale\/position.
+--
+-- * Flex.'discrete' indicates that there are discrete pick
+-- regions. (The window is divided by thirds for each axis.)
--
--- > mouseBindings = M.fromList
--- > [ ((modMask, button1), (\w -> focus w >> Flex.mouseWindow Flex.linear w)) ], ...
+-- * Flex.'resize' performs only a resize of the window, based on which
+-- quadrant the mouse is in.
--
--- Flex.linear indicates that positions between the edges and the middle
--- indicate a combination scale\/position.
--- Flex.discrete indicates that there are discrete pick regions. (window
--- is divided by thirds for each axis)
--- Flex.resize performs only resize of the window, based on which quadrant
--- the mouse is in
--- Flex.position is similar to the built-in mouseMoveWindow
+-- * Flex.'position' is similar to the built-in
+-- 'XMonad.Operations.mouseMoveWindow'.
--
-- You can also write your own function for this parameter. It should take
-- a value between 0 and 1 indicating position, and return a value indicating
--- the corresponding position if plain Flex.linear was used.
-
--- %import qualified XMonad.Actions.FlexibleManipulate as Flex
--- %mousebind , ((modMask, button1), (\\w -> focus w >> Flex.mouseWindow Flex.linear w))
+-- the corresponding position if plain Flex.'linear' was used.
discrete, linear, resize, position :: Double -> Double
+-- | Manipulate the window based on discrete pick regions; the window
+-- is divided into regions by thirds along each axis.
discrete x | x < 0.33 = 0
| x > 0.66 = 1
| otherwise = 0.5
+-- | Scale\/reposition the window by factors obtained from the mouse
+-- position by linear interpolation. Dragging precisely on a corner
+-- resizes that corner; dragging precisely in the middle moves the
+-- window without resizing; anything else is an interpolation
+-- between the two.
linear = id
+-- | Only resize the window, based on the window quadrant the mouse is in.
resize x = if x < 0.5 then 0 else 1
+
+-- | Only reposition the window.
position = const 0.5
+-- | Given an interpolation function, implement an appropriate window
+-- manipulation action.
mouseWindow :: (Double -> Double) -> Window -> X ()
mouseWindow f w = whenX (isClient w) $ withDisplay $ \d -> do
io $ raiseWindow d w
@@ -86,7 +98,7 @@ mouseWindow f w = whenX (isClient w) $ withDisplay $ \d -> do
(float w)
float w
-
+
where
pointerPos (_,_,_,px,py,_,_,_) = (fromIntegral px,fromIntegral py) :: Pnt
winAttrs :: WindowAttributes -> [Pnt]
@@ -103,7 +115,7 @@ pairUp (x:y:xs) = (x, y) : (pairUp xs)
mapP :: (a -> b) -> (a, a) -> (b, b)
mapP f (x, y) = (f x, f y)
-zipP :: (a -> b -> c) -> (a,a) -> (b,b) -> (c,c)
+zipP :: (a -> b -> c) -> (a,a) -> (b,b) -> (c,c)
zipP f (ax,ay) (bx,by) = (f ax bx, f ay by)
minP :: Ord a => (a,a) -> (a,a) -> (a,a)