| Safe Haskell | None | 
|---|
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
- class EP q where
 - type EPAntiQuoter = forall q. EP q => AntiQuoter q
 - type EPAntiQuoterPass e = forall q. EP q => AntiQuoterPass e q
 - mkEPQuasiQuoter :: Data a => (String -> Q a) -> EPAntiQuoter -> QuasiQuoter
 - epPass :: Typeable e => AntiQuoterPass e Exp -> AntiQuoterPass e Pat -> EPAntiQuoterPass e
 - epPass' :: Typeable e => (e -> Maybe (Q Exp, Q Pat)) -> EPAntiQuoterPass e
 - epPass'' :: Typeable e => AntiQuoterPass e (Exp, Pat) -> EPAntiQuoterPass e
 - epResult :: EP q => AQResult Exp -> AQResult Pat -> AQResult q
 - epValue :: EP q => Q Exp -> Q Pat -> Q q
 - epPure :: EP q => Exp -> Pat -> q
 - data EPV f = EPV {}
 
Template syntax class
Typeclass with the common constructors of Exp and Pat, useful for
 building EPAntiQuoters.
Methods
Variable
Constructor with arguments
Literal value
Tuple
List
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.
epPass'' :: Typeable e => AntiQuoterPass e (Exp, Pat) -> EPAntiQuoterPass eSource
See epPass.
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.