stub for MappingNotifyEvent, based on dwm. But the X11-extras binding for this event needs doing (sjanssen?)

This commit is contained in:
Don Stewart 2007-03-08 13:05:17 +00:00
parent 39f52d8fa8
commit 131aad3ce4

43
Main.hs
View File

@ -72,7 +72,7 @@ main = do
r <- io $ rootWindow dpy dflt r <- io $ rootWindow dpy dflt
io $ do selectInput dpy r (substructureRedirectMask .|. substructureNotifyMask) io $ do selectInput dpy r (substructureRedirectMask .|. substructureNotifyMask)
sync dpy False sync dpy False
registerKeys dpy r grabKeys dpy r
(_, _, ws) <- io $ queryTree dpy r (_, _, ws) <- io $ queryTree dpy r
forM_ ws $ \w -> do forM_ ws $ \w -> do
wa <- io $ getWindowAttributes dpy w wa <- io $ getWindowAttributes dpy w
@ -86,19 +86,42 @@ main = do
e <- io $ allocaXEvent $ \ev -> nextEvent dpy ev >> getEvent ev e <- io $ allocaXEvent $ \ev -> nextEvent dpy ev >> getEvent ev
handle e handle e
-- register keys -- | Grab the keys back
registerKeys dpy r = forM_ (M.keys keys) $ \(m,s) -> io $ do grabKeys :: Display -> Window -> W ()
kc <- keysymToKeycode dpy s grabKeys dpy r = forM_ (M.keys keys) $ \(m,s) -> io $ do
grabKey dpy kc m r True grabModeAsync grabModeAsync kc <- keysymToKeycode dpy s
grabKey dpy kc m r True grabModeAsync grabModeAsync
-- --
-- | handle. Handle X events -- | handle. Handle X events
-- dwm handles:
--
-- [ButtonPress] = buttonpress,
-- [ConfigureRequest] = configurerequest,
-- [DestroyNotify] = destroynotify,
-- [EnterNotify] = enternotify,
-- [LeaveNotify] = leavenotify,
-- [Expose] = expose,
-- [KeyPress] = keypress,
-- [MappingNotify] = mappingnotify,
-- [MapRequest] = maprequest,
-- [PropertyNotify] = propertynotify,
-- [UnmapNotify] = unmapnotify
-- --
handle :: Event -> W () handle :: Event -> W ()
handle (MapRequestEvent {window = w}) = manage w handle (MapRequestEvent {window = w}) = manage w
handle (DestroyWindowEvent {window = w}) = unmanage w handle (DestroyWindowEvent {window = w}) = unmanage w
handle (UnmapEvent {window = w}) = unmanage w handle (UnmapEvent {window = w}) = unmanage w
handle (MappingNotifyEvent {window = w}) = do
trace $ "Got mapping notify event for window: " ++ show w
{-
, mapping= m@(r,_,_)}) = do
io $ refreshKeyboardMapping m
when (r == mappingKeyboard) $ withDisplay $ \d -> grabKeys d w
-}
handle (KeyEvent {event_type = t, state = m, keycode = code}) handle (KeyEvent {event_type = t, state = m, keycode = code})
| t == keyPress = withDisplay $ \dpy -> do | t == keyPress = withDisplay $ \dpy -> do
s <- io $ keycodeToKeysym dpy code 0 s <- io $ keycodeToKeysym dpy code 0
@ -117,7 +140,15 @@ handle e@(ConfigureRequestEvent {}) = do
} }
io $ sync dpy False io $ sync dpy False
handle e = trace (eventName e) -- return () -- Typical events I see still unhandled:
-- ConfigureNotify
-- MapNotify
-- CreateNotify
-- KeyRelease
--
-- In particular, ConfigureNotify and MapNotify a lot on firefox
--
handle e = trace (eventName e)
-- --------------------------------------------------------------------- -- ---------------------------------------------------------------------
-- Managing windows -- Managing windows