Add userCode function for the popular m catchX return ()

This commit is contained in:
Spencer Janssen 2007-10-12 01:42:17 +00:00
parent 1eaee82e85
commit 1f625a6c0d
3 changed files with 10 additions and 7 deletions

View File

@ -164,8 +164,7 @@ handle :: Event -> X ()
handle (KeyEvent {ev_event_type = t, ev_state = m, ev_keycode = code}) handle (KeyEvent {ev_event_type = t, ev_state = m, ev_keycode = code})
| t == keyPress = withDisplay $ \dpy -> do | t == keyPress = withDisplay $ \dpy -> do
s <- io $ keycodeToKeysym dpy code 0 s <- io $ keycodeToKeysym dpy code 0
whenJust (M.lookup (cleanMask m,s) keys) id userCode $ whenJust (M.lookup (cleanMask m,s) keys) id
`catchX` return ()
-- manage a new window -- manage a new window
handle (MapRequestEvent {ev_window = w}) = withDisplay $ \dpy -> do handle (MapRequestEvent {ev_window = w}) = withDisplay $ \dpy -> do
@ -213,8 +212,7 @@ handle e@(ButtonEvent {ev_window = w,ev_event_type = t,ev_button = b })
-- If it's the root window, then it's something we -- If it's the root window, then it's something we
-- grabbed in grabButtons. Otherwise, it's click-to-focus. -- grabbed in grabButtons. Otherwise, it's click-to-focus.
isr <- isRoot w isr <- isRoot w
if isr then whenJust (M.lookup (cleanMask (ev_state e), b) mouseBindings) ($ ev_subwindow e) if isr then userCode $ whenJust (M.lookup (cleanMask (ev_state e), b) mouseBindings) ($ ev_subwindow e)
`catchX` return ()
else focus w else focus w
sendMessage e -- Always send button events. sendMessage e -- Always send button events.
@ -258,6 +256,6 @@ handle (ConfigureEvent {ev_window = w}) = whenX (isRoot w) rescreen
-- property notify -- property notify
handle PropertyEvent { ev_event_type = t, ev_atom = a } handle PropertyEvent { ev_event_type = t, ev_atom = a }
| t == propertyNotify && a == wM_NAME = logHook `catchX` return () | t == propertyNotify && a == wM_NAME = userCode logHook
handle e = broadcastMessage e -- trace (eventName e) -- ignoring handle e = broadcastMessage e -- trace (eventName e) -- ignoring

View File

@ -169,7 +169,7 @@ windows f = do
whenJust (W.peek ws) $ \w -> io $ setWindowBorder d w fbc whenJust (W.peek ws) $ \w -> io $ setWindowBorder d w fbc
setTopFocus setTopFocus
logHook `catchX` return () userCode logHook
-- io performGC -- really helps, but seems to trigger GC bugs? -- io performGC -- really helps, but seems to trigger GC bugs?
-- hide every window that was potentially visible before, but is not -- hide every window that was potentially visible before, but is not

View File

@ -18,7 +18,7 @@
module XMonad ( module XMonad (
X, WindowSet, WindowSpace, WorkspaceId, ScreenId(..), ScreenDetail(..), XState(..), XConf(..), LayoutClass(..), Layout(..), ReadableLayout(..), X, WindowSet, WindowSpace, WorkspaceId, ScreenId(..), ScreenDetail(..), XState(..), XConf(..), LayoutClass(..), Layout(..), ReadableLayout(..),
Typeable, Message, SomeMessage(..), fromMessage, runLayout, Typeable, Message, SomeMessage(..), fromMessage, runLayout,
runX, catchX, io, catchIO, withDisplay, withWindowSet, isRoot, getAtom, spawn, restart, trace, whenJust, whenX, runX, catchX, userCode, io, catchIO, withDisplay, withWindowSet, isRoot, getAtom, spawn, restart, trace, whenJust, whenX,
atom_WM_STATE, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW atom_WM_STATE, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW
) where ) where
@ -95,6 +95,11 @@ catchX (X job) (X errcase) = do
put s' put s'
return a return a
-- | Execute the argument, catching all exceptions. Either this function or
-- catchX should be used at all callsites of user customized code.
userCode :: X () -> X ()
userCode a = catchX a (return ())
-- --------------------------------------------------------------------- -- ---------------------------------------------------------------------
-- Convenient wrappers to state -- Convenient wrappers to state