[Haskell-cafe] Template Haskell very wordy w/r/t Decs and Types
Ross Mellgren
rmm-haskell at z.odi.ac
Sun Jan 25 14:54:55 EST 2009
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.
-Ross
P.S. This is for a one-off weekend project, and the code is fugly, so
I'm not posting it in its entirety here. If you want the whole module
and are willing not to laugh, I'd be glad to send it along ;-)
Background:
I'm doing this because I'm writing a tool to snoop around the
filesystem structures of HFS+ to try and help a friend recover some
data off a sufficiently dead drive that fsck doesn't want to touch it,
and I don't want to pay money just to find out the drive is too toasty
to pull out the data.
In any case, the HFS+ docs have a bunch of C struct definitions that
comprise the structures, and I got tired of hand-writing data
definitions and binary instances, so I figured I'd make TH do it for me.
More information about the Haskell-Cafe
mailing list