make mouse bindings configurable

This commit is contained in:
Jason Creighton 2007-06-02 04:06:47 +00:00
parent 0be589ae8c
commit 72a50ead89
4 changed files with 69 additions and 54 deletions

View File

@ -141,3 +141,10 @@ keys = M.fromList $
[((m .|. modMask, key), screenWorkspace sc >>= f) [((m .|. modMask, key), screenWorkspace sc >>= f)
| (key, sc) <- zip [xK_w, xK_e, xK_r] [0..] | (key, sc) <- zip [xK_w, xK_e, xK_r] [0..]
, (f, m) <- [(view, 0), (shift, shiftMask)]] , (f, m) <- [(view, 0), (shift, shiftMask)]]
mouseBindings :: M.Map (KeyMask, Button) (Window -> X ())
mouseBindings = M.fromList $
[ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w))
, ((modMask, button2), (\w -> focus w >> swapMaster))
, ((modMask, button3), (\w -> focus w >> mouseResizeWindow w))
]

View File

@ -1,6 +1,3 @@
module Config where module Config where
import Graphics.X11.Xlib.Types (Dimension) import Graphics.X11.Xlib.Types (Dimension)
import Graphics.X11.Xlib (KeyMask)
borderWidth :: Dimension borderWidth :: Dimension
modMask :: KeyMask
numlockMask :: KeyMask

61
Main.hs
View File

@ -73,6 +73,8 @@ main = do
selectInput dpy rootw $ substructureRedirectMask .|. substructureNotifyMask selectInput dpy rootw $ substructureRedirectMask .|. substructureNotifyMask
.|. enterWindowMask .|. leaveWindowMask .|. structureNotifyMask .|. enterWindowMask .|. leaveWindowMask .|. structureNotifyMask
grabKeys dpy rootw grabKeys dpy rootw
grabButtons dpy rootw
sync dpy False sync dpy False
ws <- scan dpy rootw ws <- scan dpy rootw
@ -110,45 +112,19 @@ grabKeys dpy rootw = do
where grab kc m = grabKey dpy kc m rootw True grabModeAsync grabModeAsync where grab kc m = grabKey dpy kc m rootw True grabModeAsync grabModeAsync
grabButtons :: Display -> Window -> IO ()
grabButtons dpy rootw = do
ungrabButton dpy anyButton anyModifier rootw
mapM_ (\(m,b) -> mapM_ (grab b . (m .|.)) extraModifiers) (M.keys mouseBindings)
where grab button mask = grabButton dpy button mask rootw False buttonPressMask
grabModeAsync grabModeSync none none
extraModifiers :: [KeyMask]
extraModifiers = [0, numlockMask, lockMask, numlockMask .|. lockMask ]
cleanMask :: KeyMask -> KeyMask cleanMask :: KeyMask -> KeyMask
cleanMask = (complement (numlockMask .|. lockMask) .&.) cleanMask = (complement (numlockMask .|. lockMask) .&.)
------------------------------------------------------------------------
-- mouse handling
-- | Accumulate mouse motion events
mouseDrag :: (XMotionEvent -> IO ()) -> X ()
mouseDrag f = do
XConf { theRoot = root, display = d } <- ask
io $ grabPointer d root False (buttonReleaseMask .|. pointerMotionMask)
grabModeAsync grabModeAsync none none currentTime
io $ allocaXEvent $ \p -> fix $ \again -> do -- event loop
maskEvent d (buttonReleaseMask .|. pointerMotionMask) p
et <- get_EventType p
when (et == motionNotify) $ get_MotionEvent p >>= f >> again
io $ ungrabPointer d currentTime
mouseMoveWindow :: Window -> X ()
mouseMoveWindow w = withDisplay $ \d -> do
io $ raiseWindow d w
wa <- io $ getWindowAttributes d w
(_, _, _, ox, oy, _, _, _) <- io $ queryPointer d w
mouseDrag $ \(_, _, _, ex, ey, _, _, _, _, _) ->
moveWindow d w (fromIntegral (fromIntegral (wa_x wa) + (ex - ox)))
(fromIntegral (fromIntegral (wa_y wa) + (ey - oy)))
float w
mouseResizeWindow :: Window -> X ()
mouseResizeWindow w = withDisplay $ \d -> do
io $ raiseWindow d w
wa <- io $ getWindowAttributes d w
io $ warpPointer d none w 0 0 0 0 (fromIntegral (wa_width wa))
(fromIntegral (wa_height wa))
mouseDrag $ \(_, _, _, ex, ey, _, _, _, _, _) ->
resizeWindow d w (fromIntegral (max 1 (ex - fromIntegral (wa_x wa))))
(fromIntegral (max 1 (ey - fromIntegral (wa_y wa))))
float w
-- --------------------------------------------------------------------- -- ---------------------------------------------------------------------
-- | Event handler. Map X events onto calls into Operations.hs, which -- | Event handler. Map X events onto calls into Operations.hs, which
-- modify our internal model of the window manager state. -- modify our internal model of the window manager state.
@ -184,11 +160,14 @@ handle e@(MappingNotifyEvent {ev_window = w}) = do
when (ev_request e == mappingKeyboard) $ withDisplay $ io . flip grabKeys w when (ev_request e == mappingKeyboard) $ withDisplay $ io . flip grabKeys w
-- click on an unfocused window, makes it focused on this workspace -- click on an unfocused window, makes it focused on this workspace
handle (ButtonEvent {ev_window = w, ev_event_type = t, ev_state = m, ev_button = b }) handle (ButtonEvent { ev_window = w, ev_subwindow = subw, ev_event_type = t, ev_state = m, ev_button = b })
| t == buttonPress && cleanMask m == modMask && b == button1 = mouseMoveWindow w | t == buttonPress = do isr <- isRoot w
| t == buttonPress && cleanMask m == modMask && b == button2 = focus w >> swapMaster -- If it's the root window, then it's something we
| t == buttonPress && cleanMask m == modMask && b == button3 = mouseResizeWindow w -- grabbed in grabButtons. Otherwise, it's
| t == buttonPress = focus w -- click-to-focus.
if isr
then whenJust (M.lookup (cleanMask m, b) mouseBindings) ($ subw)
else focus w
-- entered a normal window, makes this focused. -- entered a normal window, makes this focused.
handle e@(CrossingEvent {ev_window = w, ev_event_type = t}) handle e@(CrossingEvent {ev_window = w, ev_event_type = t})

View File

@ -15,7 +15,7 @@ module Operations where
import XMonad import XMonad
import qualified StackSet as W import qualified StackSet as W
import {-# SOURCE #-} Config (borderWidth, modMask, numlockMask) import {-# SOURCE #-} Config (borderWidth)
import Data.Maybe import Data.Maybe
import Data.List (genericIndex, intersectBy, partition, delete) import Data.List (genericIndex, intersectBy, partition, delete)
@ -240,17 +240,13 @@ rescreen = do
-- --------------------------------------------------------------------- -- ---------------------------------------------------------------------
extraModifiers :: [KeyMask]
extraModifiers = [0, numlockMask, lockMask, numlockMask .|. lockMask ]
-- | setButtonGrab. Tell whether or not to intercept clicks on a given window -- | setButtonGrab. Tell whether or not to intercept clicks on a given window
setButtonGrab :: Bool -> Window -> X () setButtonGrab :: Bool -> Window -> X ()
setButtonGrab grabAll w = withDisplay $ \d -> io $ do setButtonGrab grab w = withDisplay $ \d -> io $
when (not grabAll) $ ungrabButton d anyButton anyModifier w if grab
mapM_ (grab d) masks then grabButton d anyButton anyModifier w False buttonPressMask
where masks = if grabAll then [anyModifier] else map (modMask .|.) extraModifiers grabModeAsync grabModeSync none none
grab d m = grabButton d anyButton m w False (buttonPressMask .|. buttonReleaseMask) else ungrabButton d anyButton anyModifier w
grabModeAsync grabModeSync none none
-- --------------------------------------------------------------------- -- ---------------------------------------------------------------------
-- Setting keyboard focus -- Setting keyboard focus
@ -433,3 +429,39 @@ float w = withDisplay $ \d -> do
-- --
-- toggleFloating :: Window -> X () -- toggleFloating :: Window -> X ()
-- toggleFloating w = gets windowset >>= \ws -> if M.member w (W.floating ws) then sink w else float w -- toggleFloating w = gets windowset >>= \ws -> if M.member w (W.floating ws) then sink w else float w
------------------------------------------------------------------------
-- mouse handling
-- | Accumulate mouse motion events
mouseDrag :: (XMotionEvent -> IO ()) -> X ()
mouseDrag f = do
XConf { theRoot = root, display = d } <- ask
io $ grabPointer d root False (buttonReleaseMask .|. pointerMotionMask)
grabModeAsync grabModeAsync none none currentTime
io $ allocaXEvent $ \p -> fix $ \again -> do -- event loop
maskEvent d (buttonReleaseMask .|. pointerMotionMask) p
et <- get_EventType p
when (et == motionNotify) $ get_MotionEvent p >>= f >> again
io $ ungrabPointer d currentTime
mouseMoveWindow :: Window -> X ()
mouseMoveWindow w = withDisplay $ \d -> do
io $ raiseWindow d w
wa <- io $ getWindowAttributes d w
(_, _, _, ox, oy, _, _, _) <- io $ queryPointer d w
mouseDrag $ \(_, _, _, ex, ey, _, _, _, _, _) ->
moveWindow d w (fromIntegral (fromIntegral (wa_x wa) + (ex - ox)))
(fromIntegral (fromIntegral (wa_y wa) + (ey - oy)))
float w
mouseResizeWindow :: Window -> X ()
mouseResizeWindow w = withDisplay $ \d -> do
io $ raiseWindow d w
wa <- io $ getWindowAttributes d w
io $ warpPointer d none w 0 0 0 0 (fromIntegral (wa_width wa))
(fromIntegral (wa_height wa))
mouseDrag $ \(_, _, _, ex, ey, _, _, _, _, _) ->
resizeWindow d w (fromIntegral (max 1 (ex - fromIntegral (wa_x wa))))
(fromIntegral (max 1 (ey - fromIntegral (wa_y wa))))
float w