aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions/MouseGestures.hs
diff options
context:
space:
mode:
authorLukas Mai <l.mai@web.de>2007-11-09 03:07:55 +0100
committerLukas Mai <l.mai@web.de>2007-11-09 03:07:55 +0100
commit3d29789952d06aba39914f22772756ec2146960b (patch)
tree4873da9e5dda9d95475db3c5f00e29e474297064 /XMonad/Actions/MouseGestures.hs
parentc823d73e9af1096727bccbd4abd6d237a78ea271 (diff)
downloadXMonadContrib-3d29789952d06aba39914f22772756ec2146960b.tar.gz
XMonadContrib-3d29789952d06aba39914f22772756ec2146960b.tar.xz
XMonadContrib-3d29789952d06aba39914f22772756ec2146960b.zip
update inactive debugging code in MouseGestures; no visible changes
darcs-hash:20071109020755-462cf-88b4b53f2889a8c912eb5af1b7eb2c47980c8616.gz
Diffstat (limited to 'XMonad/Actions/MouseGestures.hs')
-rw-r--r--XMonad/Actions/MouseGestures.hs13
1 files changed, 9 insertions, 4 deletions
diff --git a/XMonad/Actions/MouseGestures.hs b/XMonad/Actions/MouseGestures.hs
index 241a063..7732ddc 100644
--- a/XMonad/Actions/MouseGestures.hs
+++ b/XMonad/Actions/MouseGestures.hs
@@ -85,7 +85,8 @@ 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 "")
+ when (debugging > 0)
+ . io . hPutStrLn stderr $ show "Mouse Gesture" ++ unwords (map show (extract stx)) ++ (if debugging > 1 then "; " ++ show op ++ "-" ++ show np else "")
case ds of
[]
| insignificant np op -> return ()
@@ -110,15 +111,19 @@ extract (_, xs) = reverse . map (\(x, _, _) -> x) $ xs
-- the corresponding action.
mouseGesture :: Map [Direction] (Window -> X ()) -> Window -> X ()
mouseGesture tbl win = withDisplay $ \dpy -> do
+ when (debugging > 1)
+ . io . hPutStrLn stderr $ "mouseGesture " ++ show (win, dpy)
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"
+ when (debugging > 1)
+ . hPutStrLn stderr $ show "queryPointer" ++ show qp
+ when (debugging > 1 && win' == none)
+ . hPutStrLn stderr $ show "mouseGesture" ++ "zomg none"
newIORef ((fromIntegral ix, fromIntegral iy), [])
mouseDrag (collect acc) $ do
- when (debugging > 0) $ io $ putStrLn $ show ""
+ when (debugging > 0) . io . hPutStrLn stderr $ show ""
gest <- io $ liftM extract $ readIORef acc
case M.lookup gest tbl of
Nothing -> return ()