| Safe Haskell | None | 
|---|---|
| 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.
- data QuasiQuoter = QuasiQuoter {}
 - quoteFile :: QuasiQuoter -> QuasiQuoter
 - dataToQa :: forall a k q. Data a => (Name -> k) -> (Lit -> Q q) -> (k -> [Q q] -> Q q) -> (forall b. Data b => b -> Maybe (Q q)) -> a -> Q q
 - dataToExpQ :: Data a => (forall b. Data b => b -> Maybe (Q Exp)) -> a -> Q Exp
 - dataToPatQ :: Data a => (forall b. Data b => b -> Maybe (Q Pat)) -> a -> Q 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; if you are only interested
 in defining a quasiquoter to be used for expressions, you would
 define a QuasiQuoter with only quoteExp, and leave the other
 fields stubbed out with errors.
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
For backwards compatibility
dataToQa :: forall a k q. Data a => (Name -> k) -> (Lit -> Q q) -> (k -> [Q q] -> Q q) -> (forall b. Data b => b -> Maybe (Q q)) -> a -> Q 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.