[xmonad] Why isn't mappend for Query flipped?

Brent Yorgey byorgey at seas.upenn.edu
Tue Jun 9 12:49:04 EDT 2009


In XMonad.Core, we have

  type ManageHook = Query (Endo WindowSet)

  newtype Query a = Query (ReaderT Window X a)
      deriving (Functor, Monad, MonadReader Window, MonadIO)

  instance Monoid a => Monoid (Query a) where
      mempty  = return mempty
      mappend = liftM2 mappend

So 'mappend' for Query is just the 'mappend' for Endo, lifted over the
ReaderT.  But of course, 'mappend' for Endo is just function
composition.  The upshot is that

  m1 <+> m2

does m2, and THEN m1.  Mostly no one notices since ManageHooks tend to
consist of a bunch of actions with disjoint premises, so it doesn't
matter in which order they are run.  But this order is quite
counterintuitive when trying to sequence multiple actions in a
ManageHook (as someone was just trying to do in #xmonad today, which
is how I ran across this issue).

I propose to change the Monoid instance for Query so that 

    mappend = liftM2 (flip mappend)

Of course, this has the undesirable side effect of breaking any
configs where the order actually matters.  But it would certainly make
more sense moving forward, IMO.

Thoughts?

-Brent


More information about the xmonad mailing list