| Safe Haskell | None |
|---|
Language.Haskell.AntiQuoter.ExpPat
Contents
Description
Exp and Pat are for most part used in simmilar fashion. Most
AntiQuoter(Pass)es have to be written for both datatypes and their
implementation is more or less identical in structure. To reduce copy-and-paste
programming it would be best if it would only need one AntiQuoter(Pass) that
works on both Exp and Pat.
This module defines the EP typeclass expressing the similarity between Exp
and Pat and some basic functions to use them with AntiQuoterPasses. The
Language.Haskell.AntiQuoter.Combinators defines the combinator functions on
top of these functions, which are probably more suitable for users.
As an example of the problem take the antiquoters in Language.Haskell.AntiQuoter.Base where there are two AntiQuoterPasses for each source type, for Var they are
antiVarE :: AntiQuoterPass Var Exp antiVarE (AV v ) = Just $ varE $ mkName v antiVarE _ = Nothing antiVarP :: AntiQuoterPass Var Pat antiVarP (AV v ) = Just $ varP $ mkName v antiVarP _ = Nothing
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 an 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 => AntiQuoterPass Var 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 Pat results.
type EPAntiQuoterPass e = forall q. EP q => AntiQuoterPass e qSource
An AntiQuoterPass that works for Exp and Pat results.
mkEPQuasiQuoter :: Data a => (String -> Q a) -> EPAntiQuoter -> QuasiQuoterSource
As mkQuasiQuoter but uses an generalized AntiQuoter.
Low level functions used when the result for Exp and Pat differs.
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 which can be used in both contexts.
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.