[Haskell-cafe] Haskell syntax inside QuasiQuote

Matt Morrow mjm2002 at gmail.com
Sun Oct 26 09:22:37 EDT 2008


I've just uploaded an alpha version of the translation to hackage:

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/haskell-src-meta-0.0.1

(I starting thinking after I uploaded that maybe haskell-src-th is a
better name..)

Here's one strategy for a haskell QQ:

------------------------------------------------------------
module HsQQ where

import Language.Haskell.Meta
import Language.Haskell.TH.Lib
import Language.Haskell.TH.Quote
import Language.Haskell.TH.Syntax

-- |
-- > ghci> [$hs|\x -> (x,x)|] 42
-- > (42,42)
-- > ghci> (\[$hs|a@(x,_)|] -> (a,x)) (42,88)
-- > ((42,88),42)
hs :: QuasiQuoter
hs = QuasiQuoter
      (either fail transformE . parseExp)
      (either fail transformP . parsePat)

transformE :: Exp -> ExpQ
transformE = return

transformP :: Pat -> PatQ
transformP = return
------------------------------------------------------------

I'll post updates as I add to the pkg over the next few days.

Cheers,
Matt



On 10/21/08, Reiner Pope <reiner.pope at gmail.com> wrote:
> It sounds like you're doing exactly what I'm looking for. I look forward to
> more.
>
> Reiner
>
> On Tue, Oct 21, 2008 at 4:28 PM, Matt Morrow <mjm2002 at gmail.com> wrote:
>
>> > Is there a simple way to do this, i.e. using existing libraries?
>>
>> Yes indeed. I'll be traveling over the next two days, and am shooting
>> for a fully functional hackage release by mid next week.
>>
>> > What I need is a Haskell expression parser which outputs values of type
>> > Language.Haskell.TH.Syntax.QExp, but I can't see one available in the TH
>> > libraries, or in the haskell-src(-exts) libraries.
>>
>> My strategy is to use the existing haskell-src-exts parser, then
>> translate that AST to the TH AST.
>>
>> Once I've got settled in one place, I'll follow up with a brain dump :)
>>
>> > Cheers,
>> > Reiner
>>
>> Matt
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>


More information about the Haskell-Cafe mailing list