Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Language.Haskell.TH.Quote
Contents
Description
Template Haskell supports quasiquoting, which permits users to construct
program fragments by directly writing concrete syntax. A quasiquoter is
essentially a function with takes a string to a Template Haskell AST.
This module defines the QuasiQuoter
datatype, which specifies a
quasiquoter q
which can be invoked using the syntax
[q| ... string to parse ... |]
when the QuasiQuotes
language
extension is enabled, and some utility functions for manipulating
quasiquoters. Nota bene: this package does not define any parsers,
that is up to you.
Synopsis
- data QuasiQuoter = QuasiQuoter {}
- quoteFile :: QuasiQuoter -> QuasiQuoter
- namedDefaultQuasiQuoter :: String -> QuasiQuoter
- defaultQuasiQuoter :: QuasiQuoter
- dataToQa :: (Quote m, Data a) => (Name -> k) -> (Lit -> m q) -> (k -> [m q] -> m q) -> (forall b. Data b => b -> Maybe (m q)) -> a -> m q
- dataToExpQ :: (Quote m, Data a) => (forall b. Data b => b -> Maybe (m Exp)) -> a -> m Exp
- dataToPatQ :: (Quote m, Data a) => (forall b. Data b => b -> Maybe (m Pat)) -> a -> m Pat
Documentation
data QuasiQuoter Source #
The QuasiQuoter
type, a value q
of this type can be used
in the syntax [q| ... string to parse ...|]
. In fact, for
convenience, a QuasiQuoter
actually defines multiple quasiquoters
to be used in different splice contexts. In the usual case of a
QuasiQuoter
that is only intended to be used in certain splice
contexts, the unused fields should just fail
. This is most easily
accomplished using namedefaultQuasiQuoter
or defaultQuasiQuoter
.
Constructors
QuasiQuoter | |
Fields
|
quoteFile :: QuasiQuoter -> QuasiQuoter Source #
quoteFile
takes a QuasiQuoter
and lifts it into one that read
the data out of a file. For example, suppose asmq
is an
assembly-language quoter, so that you can write [asmq| ld r1, r2 |]
as an expression. Then if you define asmq_f = quoteFile asmq
, then
the quote [asmq_f|foo.s|] will take input from file "foo.s"
instead
of the inline text
namedDefaultQuasiQuoter :: String -> QuasiQuoter Source #
A QuasiQuoter
that fails with a helpful error message in every
context. It is intended to be modified to create a QuasiQuoter
that
fails in all inappropriate contexts.
For example, you could write
myPatQQ = (namedDefaultQuasiQuoter "myPatQQ") { quotePat = ... }
If myPatQQ
is used in an expression context, the compiler will report
that, naming myPatQQ
.
See also defaultQuasiQuoter
, which does not name the QuasiQuoter
in
the error message, and might therefore be more appropriate when
the users of a particular QuasiQuoter
tend to define local "synonyms"
for it.
defaultQuasiQuoter :: QuasiQuoter Source #
A QuasiQuoter
that fails with a helpful error message in every
context. It is intended to be modified to create a QuasiQuoter
that
fails in all inappropriate contexts.
For example, you could write
myExpressionQQ = defaultQuasiQuoter { quoteExp = ... }
See also namedDefaultQuasiQuoter
, which names the QuasiQuoter
in the
error messages.
For backwards compatibility
dataToQa :: (Quote m, Data a) => (Name -> k) -> (Lit -> m q) -> (k -> [m q] -> m q) -> (forall b. Data b => b -> Maybe (m q)) -> a -> m q Source #
dataToQa
is an internal utility function for constructing generic
conversion functions from types with Data
instances to various
quasi-quoting representations. See the source of dataToExpQ
and
dataToPatQ
for two example usages: mkCon
, mkLit
and appQ
are overloadable to account for different syntax for
expressions and patterns; antiQ
allows you to override type-specific
cases, a common usage is just const Nothing
, which results in
no overloading.
dataToExpQ :: (Quote m, Data a) => (forall b. Data b => b -> Maybe (m Exp)) -> a -> m Exp Source #
dataToExpQ
converts a value to a Exp
representation of the
same value, in the SYB style. It is generalized to take a function
override type-specific cases; see liftData
for a more commonly
used variant.