syntax-trees-0.1.2: Convert between different Haskell syntax trees.

Language.Haskell.SyntaxTrees.ExtsToTH

Description

Provides an instance that translates haskell-src-exts expression trees into Template Haskell expression trees in a way that depends only on the haskell-src-exts syntax tree and agreement on the pretty-printed representation of Haskell between haskell-src-exts pretty-printer and Template Haskell quotations (as opposed to depending on both TH and haskell-src-exts syntax tree representations).

Instead of converting between data types, haskell-src-exts syntax trees are pretty-printed and wrapped in a TH quotation which is then interpreted as a Haskell program, yielding a TH Exp tree. Free variables in the haskell-src-exts tree are preserved by lifting them to TH splices prior to pretty-printing.

e.g. parseToTH "let x = 1 in x + y" = Right (LetE [ValD (VarP x_1) (NormalB (LitE (IntegerL 1))) []] (InfixE (Just (VarE x_1)) (VarE GHC.Num.+) (Just (VarE y))))

Synopsis

Documentation

translateExtsToTH :: Exp -> Either Exp ExpSource

Translate a Language.Haskell.Exts.Exp (haskell-src-exts) syntax tree to a Language.Haskell.TH.Exp (template-haskell) syntax tree

parseToTH :: String -> Either String ExpSource

Parse a string to a Language.Haskell.TH.Exp (template-haskell) expression via intermediate representation as a Exts.Exp tree.

parseToTarget :: Translation s t => Witness s -> String -> Either String tSource

Parse a string to a tree of type t, via intermediate representation as a tree of type s. Requires a witness of the intermediate type s to be passed as the first argument.

If parsing fails then parseToTarget s = Left s, otherwise parseToTarget s = Right t where t is the parsed tree.

translateTree :: Translation s t => s -> Either s tSource

Translate a tree of type s to a tree of type t.

If translation fails then translate s = Left s, otherwise translate s = Right t where t is the translated tree.