[Template-haskell] Re: Saving the AST generated by Template Haskell

Alfonso Acosta alfonso.acosta at gmail.com
Wed Feb 21 12:37:33 EST 2007


The example wasn't really clear, I anyway solved the issue. Here is a summary.

The problem:

There are some  cases (at least when developing a DSEL with Templpate
Haskell like I am) in which it might be really useful to keep the AST
gathered by the TH quasi quotes for later processing during execution
(not just at compile time as it is normally done).

The solution:

In order to do that it is necessary to splice the MetaAST (A TH AST
expressed in TH AST syntax as well) of the AST which wants to be kept
at compilation time. That MetaAST can be obtained by merely coding a
Lift instance for Language.Haskell.TH.(Exp,Dec,Type), most of it is
barely boilerplate code.


In my opinion it would be a good idea to include an Lift instantiation
of Language.Haskell.TH.(Exp,Dec,Type) in the TH library.

On 1/25/07, Alfonso Acosta <alfonso.acosta at gmail.com> wrote:
> Hi all,
>
> I'm using Template Haskell to design a small subset of a Hardware
> Description DSEL (Domain Specific Embedded Language).
>
> My language supports higher order as the user can supply small
> functions as arguments. I chose to parse them with TH because it
> allows me to use plain Haskell for the function syntax (instead of
> reinventing the wheel) but mostly because gives parsing for free.
>
> The AST of the functions must be kept by the embedded compiler so that
> it can be later translated to a target language by one of the
> potential backends of the embedded compiler.
>
> The problem is ... how to store that AST?
>
> Let me show an example
>
> ----
> import Language.Haskell.TH.Syntax
>
> -- sample function from the DSLE library
> hdMapSY :: (HDPrimType a, HDPrimType b) =>  HDFun (a -> b) -> HDSignal
> a ->  HDSignal b
>
>
> -- We keep the function's AST (to make program transformations in the backends)
> newtype HDPrimFun = HDPrimFun [Dec]
>  deriving Show
>
> -- Type safety layer,  we keep the function to make sure TH checks the
> type (and possible further simulations)
> data HDFun a = HDFun [Dec] a
>  deriving Show
>
> -- Helper constructor function, which suffers from the Saving-the-AST problem
> -- mkMetaAST currently returns a phony value
> mkHDFun :: Q [Dec] -> Q Exp
> mkHDFun qd = do dx <- qd
>                 metaASTnm <- newName "metaAST"
>                 let funnm = getFunName dx
>                     metaAST = mkMetaAST dx
>                     metaASTdec = ValD (VarP metaASTnm) (NormalB metaAST) []
>                 return $ LetE (metaASTdec:dx) (AppE
>                                                 (AppE
>                                                   (ConE $ mkName "HDFun")
>                                                   (AppE
>                                                     (ConE $ mkName "HDPrimFun")
>                                                     (VarE metaASTnm)))
>                                                 (VarE funnm))
>
>  where getFunName :: [Dec] -> Name
>        getFunName [FunD nm _] = nm
>        getFunName _ = error "mkHDFun: toy example, just and exactly one dec!"
>        -- This function should create an AST expression from the AST
>        -- but it would be a big pain to code
>        mkMetaAST :: [Dec] -> Exp
>        mkMetaAST _ = AppE (ConE (mkName "LitE"))
>                                         (LitE (StringL "big pain to code!"))
>
> ---
>
> An example program coded in the DSLE could could be something like ..
>
> myCircuit :: HDSignal Int -> HDSignal Int
> myCircuit = hdMapSY ($mkHDFun [d| f input = input+1 |])
>
>
> So the question is ..
>
> How can mkHDfun save the AST of "f input = input+1"  (for which it
> needs to create and return  a metaAST) without the effort of having to
> create boiler plate code for the whole TH library types?
>
> Did anyone do something similar before?
>
> I workaround would be saving the String of the AST with show, but Dec
> nor Exp belong to the Read class, :S
>
> Thanks in advance,
>
> Alfonso Acosta
>


More information about the template-haskell mailing list