antiquoter-0.1.0.0: Combinator library for quasi- and anti-quoting.

Safe HaskellNone

Language.Haskell.AntiQuoter.ExpPat

Contents

Description

Tools for writing one AntiQuoter which can be used for both expressions and patterns, thereby reducing copy-and-paste programming.

For example in the original paper on quasi quoting http://www.eecs.harvard.edu/~mainland/ghc-quasiquoting/mainland07quasiquoting.pdf antiquoting is demonstrated by defining the following antiquoters:

 antiVarE :: Var -> Maybe ExpQ
 antiVarE (AV v ) = Just $ varE $ mkName v
 antiVarE _ = Nothing
 antiVarP :: Var -> Maybe PatQ
 antiVarP (AV v ) = Just $ varP $ mkName v
 antiVarP _ = Nothing

and a simmilar pair for antiquoting variables. The problem is that the definition for the pattern antiquoter is almost a duplicate of the one for expressions. This similarity between antiquoting expressions and patterns is captured in the EP class which can be used to write antiquoters which can yield both expressions and patterns. Using the combinators defined on top of this class (see Language.Haskell.AntiQuoter.Combinators) the example can be rewritten as

 antiVar :: EP q => Var ->  Maybe (Q q) -- equivalent to antiVar :: EPAntiQuoterPass Var
 antiVar (AV v) = Just $ varQ $ mkName v
 antiVar _      = Nothing

Synopsis

Template syntax class

class EP q whereSource

Typeclass with the common constructors of Exp and Pat, useful for building EPAntiQuoters.

Methods

var :: Name -> qSource

Variable

con :: Name -> [q] -> qSource

Constructor with arguments

lit :: Lit -> qSource

Literal value

tup :: [q] -> qSource

Tuple

list :: [q] -> qSource

List

fromEPV :: EPV f -> f qSource

Internal unwrapper when the implementation for Exp and Pat should differ.

Instances

type EPAntiQuoter = forall q. EP q => AntiQuoter qSource

An AntiQuoter that works for Exp and Pats.

type EPAntiQuoterPass e = forall q. EP q => AntiQuoterPass e qSource

mkEPQuasiQuoter :: Data a => (String -> Q a) -> EPAntiQuoter -> QuasiQuoterSource

As mkQuasiQuoter but uses an generalized AntiQuoter.

epPass :: Typeable e => AntiQuoterPass e Exp -> AntiQuoterPass e Pat -> EPAntiQuoterPass eSource

Combine two AntiQuoterPasses, one for expression context and another for pattern context, into a single pass for an expression of patter context.

epResult :: EP q => AQResult Exp -> AQResult Pat -> AQResult qSource

Make a context dependent result for expression and pattern contexts.

epValue :: EP q => Q Exp -> Q Pat -> Q qSource

Make an context dependent value for expression and pattern contexts.

epPure :: EP q => Exp -> Pat -> qSource

Constructs an EP value by choosing from an Exp of Pat as appropriate in the context.

Internal

data EPV f Source

Container for a f of both an Exp and a Pat. Used internally when the result for Exp and Pat differ.

Constructors

EPV 

Fields

eep :: f Exp
 
pep :: f Pat