Quasiquotation page on HaskellWiki needs updating

Hi all, It seems the Quasiquotation page on HaskellWiki http://www.haskell.org/haskellwiki/Quasiquotation has fallen behind the actually Quasiquotation implementation that is in ghc-7.4.2 and later. Specifically, the QuasiQuoter constructor that the Wiki takes two parameters: data QuasiQuoter = QuasiQuoter { quoteExp :: String -> Q Exp , quotePat :: String -> Q Pat } while the one in ghc-7.4 and later takes four: data QuasiQuoter = QuasiQuoter { quoteExp :: String -> Q Exp , quotePat :: String -> Q Pat , quoteType :: String -> Q Type , quoteDec :: String -> Q [Dec] } I'm just starting out with quasquotation and am not yet qualified to update this page myself. Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/

On Sat, Nov 24, 2012 at 1:32 AM, Erik de Castro Lopo
Hi all,
It seems the Quasiquotation page on HaskellWiki
http://www.haskell.org/haskellwiki/Quasiquotation
has fallen behind the actually Quasiquotation implementation that is in ghc-7.4.2 and later.
Specifically, the QuasiQuoter constructor that the Wiki takes two parameters:
data QuasiQuoter = QuasiQuoter { quoteExp :: String -> Q Exp , quotePat :: String -> Q Pat }
while the one in ghc-7.4 and later takes four:
data QuasiQuoter = QuasiQuoter { quoteExp :: String -> Q Exp , quotePat :: String -> Q Pat , quoteType :: String -> Q Type , quoteDec :: String -> Q [Dec] }
I'm just starting out with quasquotation and am not yet qualified to update this page myself.
Erik
Hi Erik, I've made a tiny edit so that the code will work on either version. The extra functions are only called if you put quasiquoters in places that are Type or Dec. It's harder to come up with useful quasiquoters for those locations, which is probably why quoteDec and quoteType were added later. Here's a pretty useless example of using those fields: in M1.hs
{-# LANGUAGE TemplateHaskell #-} module M1 where import Language.Haskell.TH.Quote
e = QuasiQuoter { quoteDec = \ _ -> [d| x = 1 |], quoteType = \ _ -> [t| Int |] }
Then in another module:
{-# LANGUAGE QuasiQuotes #-} import M1 [e| this text goes to (quoteDec e) and ends up as x = 1|] y = 1 :: [e|this text goes to (quoteType e) and ends up as if just Int was written here|]
-- Adam
participants (2)
-
adam vogt
-
Erik de Castro Lopo