[Haskell-cafe] Template Haskell very wordy w/r/t Decs and Types
Simon Peyton-Jones
simonpj at microsoft.com
Wed May 27 15:38:34 EDT 2009
Folks
Quite a few people have asked for splices in Template Haskell *types*, and I have finally gotten around to implementing them. So now you can write things like
instance Binary $(blah blah) where ...
or f :: $(wubble bubble) -> Int
as requested, for example, in the message below. Give it a whirl. You need the HEAD; in a day or two you should find binary snapshots if you don't want to build from source.
Simon
PS: Note that you (still) cannot write a splice in a *binding* position. Thus you can't write
f $(blah blah) = e
or
data T $(blah blah) = MkT Int
I don't intend to change this; see the commentary at http://hackage.haskell.org/trac/ghc/ticket/1476
| -----Original Message-----
| From: haskell-cafe-bounces at haskell.org [mailto:haskell-cafe-bounces at haskell.org] On
| Behalf Of Ross Mellgren
| Sent: 25 January 2009 19:55
| To: Haskell Cafe
| Subject: [Haskell-cafe] Template Haskell very wordy w/r/t Decs and Types
|
| Hi all,
|
| I'm writing a small module that exposes a template haskell splice that
| takes a (very simplified) C struct definition and builds:
|
| - A data type definition,
| - an instance for Data.Binary.Binary,
| - and optionally a pretty print function for it
|
| However, it seems to do this I have to write a bunch of really ugly
| code that builds up the TH data structures "by hand" because quoting
| only works with splices for expressions, or so it seems.
|
| For example, to generate the binary instance I have this code:
|
| import qualified Language.Haskell.TH as TH
|
| -- tyname is the name of the data type I've already created, as a
| TH.Name
| -- tempnames is a list of temporary variable names that are used in
| lambda patterns
| -- fields is a list of tuples describing each field
| -- makeGetExp recursively builds a monadic computation consisting
| mostly of Binary.getWord32be >>= \ tempvar -> ...
|
| binaryInstDec <- liftM (TH.InstanceD [] (TH.AppT (TH.ConT $
| TH.mkName "Data.Binary.Binary") (TH.ConT tyname)))
| [d| get = $(makeGetExp (reverse $ zip
| fields tempnames) returnExp)
| put = undefined |]
|
| I'd really rather write:
|
| binaryInstDec <- [d|
| instance Binary.Binary $(tyname) where
| get = $(makeGetExp (reverse $ zip fields tempnames)
| returnExp)
| put = undefined |]
|
| But GHC gives me a syntax error on the tyname splice. The docs seem to
| indicate this is the way it is -- that splices in type locations is
| plain not implemented.
|
| My question is whether or not this is just the way it is, and people
| writing TH declaration splices tend to have to start manually
| assembling a bunch of it, or is there some trick I've missed? Perhaps
| even better are there some tricks that people tend to use to make this
| less painful?
|
| I did try using some of the lowercased monadic constructors in
| Language.Haskell.TH.Lib but I didn't seem to get anything more succint
| out of it.
More information about the Glasgow-haskell-users
mailing list