New branch implementing typed/untyped Template Haskell

Geoffrey Mainland mainland at apeiron.net
Thu May 16 18:38:48 CEST 2013


No new branch in the base repo, but otherwise correct!

On 05/16/2013 05:35 PM, Simon Peyton-Jones wrote:
> Excellent.  Jacques: do try it out!
>
> I believe that there are new branches in these repos (Geoff yell if not)
> 	ghc
> 	testsuite
> 	base
> 	template-haskell
>
> I can't help feeling that
> 	[|| foo ||]
> 	$$(foo)
> is too heavy a syntax, and will make it seem horrid an clunky.  Two-character brackets are bad enough. What about
> 	[@ foo @]
> 	&(foo)
> Other suggestions welcome.  Trivial yet important.
>
> Simon
>
> Microsoft Research Limited (company number 03369488) is registered in England and Wales
> Registered office 21 Station Road, Cambridge, CB1 2FB 
>
> | -----Original Message-----
> | From: ghc-devs-bounces at haskell.org [mailto:ghc-devs-bounces at haskell.org]
> | On Behalf Of Geoffrey Mainland
> | Sent: 16 May 2013 16:22
> | To: ghc-devs at haskell.org
> | Cc: carette at mcmaster.ca
> | Subject: New branch implementing typed/untyped Template Haskell
> | 
> | I have pushed a new branch, th-new, that partially implements the
> | proposal outlined in Simon PJ's "New directions for Template Haskell"
> | post at:
> | 
> | http://hackage.haskell.org/trac/ghc/blog/Template%20Haskell%20Proposal
> | 
> | The main missing features are top-level pattern splices and local
> | declaration splices.
> | 
> | Typed expression quotations and typed expression splices *are*
> | implemented. Syntax is as in Simon's original proposal: [|| ||] for
> | typed expression brackets and $$(...) for typed expression splices. One
> | can now write:
> | 
> | power :: Int -> TExp (Int -> Int)
> | power n = [|| \x -> $$(go n [|| x ||]) ||]
> | where
> | go :: Int -> TExp Int -> TExp Int
> | go 0 x = [|| 1 ||]
> | go n x = [|| $$x * $$(go (n-1) x) ||]
> | 
> | In fact, one can even write:
> | 
> | power :: Num a => Int -> TExp (a -> a)
> | power n = [|| \x -> $$(go n [|| x ||]) ||]
> | where
> | go :: Num a => Int -> TExp a -> TExp a
> | go 0 x = [|| 1 ||]
> | go n x = [|| $$x * $$(go (n-1) x) ||]
> | 
> | Writing the following
> | 
> | f :: TExp Char -> TExp Integer
> | f x = [|| $$x * 3 ||]
> | 
> | gives the error
> | 
> | Main.hs:28:7:
> | Couldn't match type ‛Char’ with ‛Integer’
> | Expected type: TExp Integer
> | Actual type: TExp Char
> | In the Template Haskell quotation [|| $$x * 3 ||]
> | In the expression: [|| $$x * 3 ||]
> | In an equation for ‛f’: f x = [|| $$x * 3 ||]
> | 
> | The th-new branch of ghc has accompanying branches for template-haskell
> | and testsuite, both named th-new. These are mirrors of my local branch,
> | and I reserve the right to rebase them :). That said, please do try it
> | out!
> | 
> | Geoff
> | 
> | 
> | _______________________________________________
> | ghc-devs mailing list
> | ghc-devs at haskell.org
> | http://www.haskell.org/mailman/listinfo/ghc-devs




More information about the ghc-devs mailing list