Safe Haskell | None |
---|
Language.Haskell.AntiQuoter.Base
Description
Base module for AntiQuoter
s, defining some basic type-aliases and and
combinators for antiquoting.
To for examples in the documentation of this library the following data types defining the untyped lambda calculus syntax:
data Expr = VarE Var | Lam Var Expr | App Expr Expr | AntiExpr String deriving (Typeable, Data) data Var = Var String | AntiVar String deriving (Typeable, Data)
(note: the idea for using lambda calculus comes from the original paper on quasi-quoting http://www.eecs.harvard.edu/~mainland/ghc-quasiquoting/mainland07quasiquoting.pdf)
A simple quasi-quoter without support for antiquoting can be defined by:
lExp = QuasiQuoter { quoteExp = dataToExpQ (const Nothing) . parseExpr , quotePat = dataToPatQ (const Nothing) . parseExpr , quoteType = error "No type quoter" , quoteDec = error "No declaration quoter" } parseExpr :: String -> Expr parseExpr = undefined -- implementation omitted
Now to add antiquoting it is needed to treat the AntiExpr and AntiVar
constructors as special and translate them ourselves. This introduces an
, which is a specific translation rule from source syntax
AntiQuoterPass
e pe
to template haskell type p
. In the example this can be used to defined:
antiExprE :: AntiQuoterPass Expr Exp antiExprE (AntiExpr s) = Just . varE $ mkName s antiExprE _ = Nothing antiVarE :: AntiQuoterPass Var Exp antiVarE (AntiVar s) = Just . varE $ mkName s antiVarE _ = Nothing antiExprP :: AntiQuoterPass Expr Pat antiExprP (AntiExpr s) = Just . varP $ mkName s antiExprP _ = Nothing antiVarP :: AntiQuoterPass Var Pat antiVarP (AntiVar s) = Just . varP $ mkName s antiVarP _ = Nothing
Both rules should be used when antiquoting as an exception to the base case
(using the default translation, const Nothing
). Which can be done using
(
, creating an <>>
)AntiQuoter
. Where an AntiQuoter
represents a
combination of AntiQuoterPass
es which can be used to antiquote multiple
datatypes. In the example this would result in
lExp = QuasiQuoter { quoteExp = dataToExpQ antiE . parseExpr , quotePat = dataToPatQ antiP . parseExpr , quoteType = error "No type quoter" , quoteDec = error "No declaration quoter" } where antiE :: AntiQuoter Exp antiE = antiExprE <>> antiVarE <>> const Nothing antiP :: AntiQuoter Pat antiP = antiExprP <>> antiVarP <>> const Nothing
Two little improvements could be made, const Nothing
could be replaced by
noAntiQuoter
and the building of the QuasiQuoter
could be simplified by
using mkQuasiQuoter
.
- type AntiQuoterPass e q = e -> Maybe (Q q)
- type AntiQuoter q = forall e. Typeable e => AntiQuoterPass e q
- type AQResult q = Maybe (Q q)
- mkQuasiQuoter :: Data a => (String -> Q a) -> AntiQuoter Exp -> AntiQuoter Pat -> QuasiQuoter
- fromPass :: Typeable e => AntiQuoterPass e q -> AntiQuoter q
- noAntiQuoter :: AntiQuoter q
- (<<>>) :: AntiQuoter q -> AntiQuoter q -> AntiQuoter q
- (<<>) :: Typeable e => AntiQuoter q -> AntiQuoterPass e q -> AntiQuoter q
- (<>>) :: Typeable e => AntiQuoterPass e q -> AntiQuoter q -> AntiQuoter q
- extQ :: (Typeable a, Typeable b) => (a -> q) -> (b -> q) -> a -> q
- newtype WrappedAQResult q = AQRW {}
AntiQuoters
type AntiQuoterPass e q = e -> Maybe (Q q)Source
type AntiQuoter q = forall e. Typeable e => AntiQuoterPass e qSource
An AntiQuoter
is the combination of several AntiQuoterPass
es, which
could have different source types. In the example the
AntiQuoterPass Expr Exp
and AntiQuoterPass Var Exp
were combined into
a single AntiQuoter Exp
, which antiquoted both Expr
and Pat
.
type AQResult q = Maybe (Q q)Source
Result of an AntiQuoterPass
(AntiQuoterPass e q = e -> AQResult q).
This type-alias is mostly used for combinators which only provides the
result of the antiquotation and the usecase (thus the pattern to match)
should be filled in by the user.
See AntiQuoterPass
on what Nothing
and Just
mean.
Using AntiQuoters
mkQuasiQuoter :: Data a => (String -> Q a) -> AntiQuoter Exp -> AntiQuoter Pat -> QuasiQuoterSource
Create an QuasiQuoter for expressions and patterns from a parser and two
antiquoters. The quasiquoter from the example could also have been
constructed by using mkQuasiQuoter (return . parse) antiE antiP
.
fromPass :: Typeable e => AntiQuoterPass e q -> AntiQuoter qSource
Create an AntiQuoter
from an single pass.
noAntiQuoter :: AntiQuoter qSource
An AnitQuoter
that does no antiquoting by only return Nothing,
noAntiQuoter = const Nothing
(<<>>) :: AntiQuoter q -> AntiQuoter q -> AntiQuoter qSource
Combines two AntiQuoter
s with the same result. It is left biased, thus
if the first antiquoter returns Just result
that is used, otherwise the
second AntiQuoter is tried.
Together with noAntiQuoter
this forms a monoid, but as AntiQuoter is a
type synonyme no instance is declared.
(<<>) :: Typeable e => AntiQuoter q -> AntiQuoterPass e q -> AntiQuoter qSource
Create an AntiQuoter
by combining an AntiQuoter
and an
AntiQuoterPass
. This is left biased, see (<<>>
).
(<>>) :: Typeable e => AntiQuoterPass e q -> AntiQuoter q -> AntiQuoter qSource
Create an AntiQuoter
by combining an AntiQuoterPass
and an
AntiQuoter
. This is left biased, see (<<>>
).
Convenience reexport
WARNING: when combining AntiQuoter(Pass)es using extQ
only the
last (rightmost) pass will be used for any source type. The <<>
and <>>
don't suffer from this problem.
extQ :: (Typeable a, Typeable b) => (a -> q) -> (b -> q) -> a -> q
Extend a generic query by a type-specific case