[xmonad] darcs patch: add configurable X Event handling

David Roundy droundy at darcs.net
Mon Nov 12 10:06:50 EST 2007


On Sun, Nov 11, 2007 at 05:56:39PM -0500, Devin Mullins wrote:
> Question:
>   Should it be eventHooks :: [Event -> X Bool] instead of eventHook :: Event ->
>   X Bool, or should there be a composeEvents function, like ManageHook.composeAll?

I'd actually prefer something like ::

type EventHook = Event -> X (Bool, Maybe EventHook)

This way, we could define an event hook that will remove itself, or modify
itself (or store state).  As it is, this eventHook is rather limited.

then:

eventHook :: EventHook

And we could define one or more composeEvents functions.

I think I'd also prefer for the EventHook to accept a SomeMessage, rather
than an X event.  This would allow us to communicate with EventHooks using
our existing sendMessage function... or allow EventHooks to be written that
intercept messages.  So that we could (if we chose) unify EventHooks with
some of the aspects of ManageHooks simply by sending Messages on
new-window-creation.  So my real preference would be:

type MessageHook = SomeMessage -> X (Bool, Maybe MessageHook)

and then we'd send all Events or Messages to the MessageHook before
processing them with handle or the layout.

At this point, I wonder whether we should follow the layouts more closely
and make the MessageHooks be data rather than functions, so that they can
store state that persists across mod-q.  So we'd have something like:

class Show mh => MessageHandler mh where
      handleMessage :: mh -> SomeMessage -> X (Bool, Maybe mh)
      handleMessage mh m = do b <- staticHandle mh m
                              return (b, Nothing)
      staticHandle :: mh -> SomeMessage -> X Bool
      staticHandle mh m = observeMessage m >> return False
      observeMessage :: mh -> SomeMessage -> X ()
      observeMessage _ _ = return ()

At this point, we've got message handlers that can store state across
restarts (using the same mechanism we use for Layouts), can intercept any
Message, etc.

I defined three methods so folks who don't want changing state, or don't
want to actually intercept messages don't have to worry about how to return
more complicated state correctly.

So your example would be:

data FocusDoesntFollowMouse = FocusDoesntFollowMouse deriving ( Read, Show )
instance MessageHandler FocusDoesntFollowMouse where
    staticHandle _ m | Just (CrossingEvent {}) = return False
                     | otherwise = return False

It's a bit more verbose, but of course, we'd want it in XMC, so the user
wouldn't be much bothered by this.  The user would just specify something
like

  defaultConfig { messageHandler = FocusDoesntFollowMouse }

Of course, we'd want combinators, but those'd be pretty straightforward.

Thoughts?
-- 
David Roundy
Department of Physics
Oregon State University


More information about the xmonad mailing list