| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Monad.Quote
Description
A monad transformer for the Quote type class from template-haskell.
The "Overloaded Quotations" proposal has been implemented in GHC 9.0, and generalizes the type of quotation brackets from
[| \x -> x + 1 |] ::QExp
to
[| \x -> x + 1 |] ::Quotem => mExp
where the Quote type class only has a single function, newName, in order to generate
fresh Names.
By default, template-haskell provides Quote instances for Q and IO.
This library provides pure versions, PureQ and its transformer variant QuoteT, in order to
e.g. extract an Exp from the bracket above in a pure context.
See runPureQ and runQuoteT for concrete examples.
The Quote class
class Monad m => Quote (m :: Type -> Type) where #
The Quote class implements the minimal interface which is necessary for
desugaring quotations.
- The
Monad msuperclass is needed to stitch together the different AST fragments. newNameis used when desugaring binding structures such as lambdas to generate fresh names.
Therefore the type of an untyped quotation in GHC is `Quote m => m Exp`
For many years the type of a quotation was fixed to be `Q Exp` but by
more precisely specifying the minimal interface it enables the Exp to
be extracted purely from the quotation without interacting with Q.
Methods
Generate a fresh name, which cannot be captured.
For example, this:
f = $(do
nm1 <- newName "x"
let nm2 = mkName "x"
return (LamE [VarP nm1] (LamE [VarP nm2] (VarE nm1)))
)will produce the splice
f = \x0 -> \x -> x0
In particular, the occurrence VarE nm1 refers to the binding VarP nm1,
and is not captured by the binding VarP nm2.
Although names generated by newName cannot be captured, they can
capture other names. For example, this:
g = $(do nm1 <- newName "x" let nm2 = mkName "x" return (LamE [VarP nm2] (LamE [VarP nm1] (VarE nm2))) )
will produce the splice
g = \x -> \x0 -> x0
since the occurrence VarE nm2 is captured by the innermost binding
of x, namely VarP nm1.
The PureQ monad
The QuoteT monad transformer
The QuoteT monad transformer. Also see runQuoteT.
Useful to add a Quote instance to any monad transformer stack.
Instances
| MonadTrans QuoteT Source # | |
Defined in Control.Monad.Quote.Internal | |
| (MonadReader r m, MonadWriter w m, MonadState s m) => MonadRWS r w s (QuoteT m) Source # | |
Defined in Control.Monad.Quote.Internal | |
| MonadWriter w m => MonadWriter w (QuoteT m) Source # | |
| MonadState s m => MonadState s (QuoteT m) Source # | |
| MonadReader r m => MonadReader r (QuoteT m) Source # | |
| MonadError e m => MonadError e (QuoteT m) Source # | |
Defined in Control.Monad.Quote.Internal | |
| Monad m => Monad (QuoteT m) Source # | |
| Functor m => Functor (QuoteT m) Source # | |
| MonadFix m => MonadFix (QuoteT m) Source # | |
Defined in Control.Monad.Quote.Internal | |
| MonadFail m => MonadFail (QuoteT m) Source # | |
Defined in Control.Monad.Quote.Internal | |
| Monad m => Applicative (QuoteT m) Source # | |
| MonadIO m => MonadIO (QuoteT m) Source # | |
Defined in Control.Monad.Quote.Internal | |
| MonadPlus m => Alternative (QuoteT m) Source # | |
| MonadPlus m => MonadPlus (QuoteT m) Source # | |
| MonadCont m => MonadCont (QuoteT m) Source # | |
| Monad m => Quote (QuoteT m) Source # | |
runQuoteT :: Monad m => QuoteT m a -> m a Source #
Extract m a from , where QuoteT m a is always an instance of QuoteT mQuote.
On GHC 9.0+, you can use this to extract an Exp out of a quotation bracket:
>>>import qualified Language.Haskell.TH.Lib as TH>>>:{let mExp :: (Quote m, MonadReader String m) => m Exp mExp = [| \a -> a <> $(TH.stringE =<< ask) |] exp :: Exp exp = flip runReader " world" . runQuoteT $ mExp in exp :} LamE [VarP a_0] (InfixE (Just (VarE a_0)) (VarE GHC.Base.<>) (Just (LitE (StringL " world"))))