aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions/MouseGestures.hs
diff options
context:
space:
mode:
authorSpencer Janssen <sjanssen@cse.unl.edu>2007-11-01 21:10:59 +0100
committerSpencer Janssen <sjanssen@cse.unl.edu>2007-11-01 21:10:59 +0100
commit4866f2e367dfcf22a9591231ba40948826a1b438 (patch)
tree7a245caee3f146826b267d773b7eaa80386a818e /XMonad/Actions/MouseGestures.hs
parent47589e1913fb9530481caedb543978a30d4323ea (diff)
downloadXMonadContrib-4866f2e367dfcf22a9591231ba40948826a1b438.tar.gz
XMonadContrib-4866f2e367dfcf22a9591231ba40948826a1b438.tar.xz
XMonadContrib-4866f2e367dfcf22a9591231ba40948826a1b438.zip
Hierarchify
darcs-hash:20071101201059-a5988-fc1f1262bec1b69e13ba18ae7cefeafc8c4471d4.gz
Diffstat (limited to 'XMonad/Actions/MouseGestures.hs')
-rw-r--r--XMonad/Actions/MouseGestures.hs116
1 files changed, 116 insertions, 0 deletions
diff --git a/XMonad/Actions/MouseGestures.hs b/XMonad/Actions/MouseGestures.hs
new file mode 100644
index 0000000..32d7e60
--- /dev/null
+++ b/XMonad/Actions/MouseGestures.hs
@@ -0,0 +1,116 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Actions.MouseGestures
+-- Copyright : (c) Lukas Mai
+-- License : BSD3-style (see LICENSE)
+--
+-- Maintainer : <l.mai@web.de>
+-- Stability : unstable
+-- Portability : unportable
+--
+-- Support for simple mouse gestures
+--
+-----------------------------------------------------------------------------
+
+module XMonad.Actions.MouseGestures (
+ -- * Usage
+ -- $usage
+ Direction(..),
+ mouseGesture
+) where
+
+import XMonad
+import XMonad.Operations
+import Graphics.X11.Xlib
+import Graphics.X11.Xlib.Extras
+
+import Control.Monad.Reader
+import Data.IORef
+import qualified Data.Map as M
+import Data.Map (Map)
+
+import System.IO
+
+-- $usage
+-- In your Config.hs:
+--
+-- > import XMonad.Actions.MouseGestures
+-- > ...
+-- > mouseBindings = M.fromList $
+-- > [ ...
+-- > , ((modMask .|. shiftMask, button3), mouseGesture gestures)
+-- > ]
+-- > where
+-- > gestures = M.fromList
+-- > [ ([], focus)
+-- > , ([U], \w -> focus w >> windows W.swapUp)
+-- > , ([D], \w -> focus w >> windows W.swapDown)
+-- > , ([R, D], \_ -> sendMessage NextLayout)
+-- > ]
+--
+-- This is just an example, of course. You can use any mouse button and
+-- gesture definitions you want.
+
+data Direction = L | U | R | D
+ deriving (Eq, Ord, Show, Read, Enum, Bounded)
+
+type Pos = (Position, Position)
+
+delta :: Pos -> Pos -> Position
+delta (ax, ay) (bx, by) = max (d ax bx) (d ay by)
+ where
+ d a b = abs (a - b)
+
+dir :: Pos -> Pos -> Direction
+dir (ax, ay) (bx, by) = trans . (/ pi) $ atan2 (fromIntegral $ ay - by) (fromIntegral $ bx - ax)
+ where
+ trans :: Double -> Direction
+ trans x
+ | rg (-3/4) (-1/4) x = D
+ | rg (-1/4) (1/4) x = R
+ | rg (1/4) (3/4) x = U
+ | otherwise = L
+ rg a z x = a <= x && x < z
+
+debugging :: Int
+debugging = 0
+
+collect :: IORef (Pos, [(Direction, Pos, Pos)]) -> Position -> Position -> X ()
+collect st nx ny = do
+ let np = (nx, ny)
+ stx@(op, ds) <- io $ readIORef st
+ when (debugging > 0) $ io $ putStrLn $ show "Mouse Gesture" ++ unwords (map show (extract stx)) ++ (if debugging > 1 then "; " ++ show op ++ "-" ++ show np else "")
+ case ds of
+ []
+ | insignificant np op -> return ()
+ | otherwise -> io $ writeIORef st (op, [(dir op np, np, op)])
+ (d, zp, ap_) : ds'
+ | insignificant np zp -> return ()
+ | otherwise -> do
+ let
+ d' = dir zp np
+ ds''
+ | d == d' = (d, np, ap_) : ds'
+ | otherwise = (d', np, zp) : ds
+ io $ writeIORef st (op, ds'')
+ where
+ insignificant a b = delta a b < 10
+
+extract :: (Pos, [(Direction, Pos, Pos)]) -> [Direction]
+extract (_, xs) = reverse . map (\(x, _, _) -> x) $ xs
+
+mouseGesture :: Map [Direction] (Window -> X ()) -> Window -> X ()
+mouseGesture tbl win = withDisplay $ \dpy -> do
+ root <- asks theRoot
+ let win' = if win == none then root else win
+ acc <- io $ do
+ qp@(_, _, _, ix, iy, _, _, _) <- queryPointer dpy win'
+ when (debugging > 1) $ putStrLn $ show "queryPointer" ++ show qp
+ when (debugging > 1 && win' == none) $ putStrLn $ show "mouseGesture" ++ "zomg none"
+ newIORef ((fromIntegral ix, fromIntegral iy), [])
+ mouseDrag (collect acc) $ do
+ when (debugging > 0) $ io $ putStrLn $ show ""
+ gest <- io $ liftM extract $ readIORef acc
+ case M.lookup gest tbl of
+ Nothing -> return ()
+ Just f -> f win'