[xmonad] Re: Compile-time verification of keymaps
Adam Vogt
vogt.adam at gmail.com
Tue Mar 23 21:42:15 EDT 2010
* On Tuesday, March 23 2010, Gwern Branwen wrote:
...
> I brought this technique up in #haskell today, where aavogt pointed
> out that the issue about not being able to access config parameters
> inside the TH splice could be worked around as long as the TH splice
> returned a partially applied function which wanted the necessary
> parameters and would use them appropriately inside itself - that is
> (very loosely), instead of $(check fookeymap), it'd be more $(check
> (\x y -> fookeymap x y)). The TH would only inspect the keys of the
> tuples, and not the functions inside the second space in the tuple.
That idea didn't work out using regular TH splices (those taking a Q
Exp), because there is no Lift instance for functions, but maybe one can
be written.
The duplicates found using the QuasiQuoter are only those that have
syntactic equality: getDupes compares all the Exp that are the first
elements of each pair that makes a keybinding. For EZConfig-style keys
where the key is indicated by a string, it is less of a problem, but
note that it can still fail with the following:
> main = xmonad $ defaultConfig `additionalKeysP`
> M.toList -- could be avoided by removing the M.fromList in fromUniqueList
> [$fromUniqueList|
> ("M1-a",spawn "aaaaaa"),
> ("M-a", spawn "bbbbbb")
> |]
The conversion done in additionalKeysP could be built into the
quasiquoter to avoid that problem, though that code cannot be reused
without a bit of rearrangement (specifically the XConfig arguments can
be replaced with a default modmask).
The `fromUniqueList' that I've written so far could be a bit smarter
with respect to showing the duplicates and other kinds of invalid input
(which are pattern match failures for now).
>fromUniqueList = QuasiQuoter
> { quoteExp = either fail (\(input::Exp) -> do
> ListE input' <- return input
> duplicates <- liftM getDupes $ forM input' $ \x -> do
> TupE [key,_] <- return x
> return key
>
> unless (null duplicates) $ fail ("Keys overlap:" ++ show duplicates)
> [| M.fromList $(return input) |]
> )
> . parseExp . ('[':) . (++"]")
> , quotePat = error "KM.fromUniqueList: quotePat"
> }
>
>getDupes :: Eq a => [a] -> [a]
>getDupes xs = xs \\ nub xs
---snip---
>
>So, with a basic solution working, we ought to consider whether to use
>it. (I assume there's some way to hide the TH splice inside
>xmonad-core so we don't require any user-visible changes.) This is
>additional static checking, and it removes one unfortunate feature of
>list syntax, so it seems good to me.
A quasi-quote cannot be hidden like that: this little bit of extra
checking takes the String that's inside the quote, which isn't
accessible to functions in the xmonad library. But the syntax is pretty
light anyhow.
Possibly a concern for us is that QuasiQuote syntax may be improved
sometime:
http://www.haskell.org/pipermail/glasgow-haskell-users/2010-February/018335.html
Another drawback is the dependency on the haskell-src-meta library,
whose maintainer has not been reachable. A version that works with
ghc-6.12 can found at one of:
darcs get http://moonpatio.com/repos/haskell-src-meta_NEW_TH/ # 'official'
darcs get http://code.haskell.org/~aavogt/haskell-src-meta/ # a couple small 'improvements'
Maybe my analysis is overly negative here, but we can do better than
this alternative or the current setup.
--
Adam
More information about the xmonad
mailing list