quotet-0.0.1.1: Monad transformer for Quote from template-haskell
Safe HaskellNone
LanguageHaskell2010

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 |] ::            Q Exp

to

[| \x -> x + 1 |] :: Quote m => m Exp

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.

Synopsis

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 m superclass is needed to stitch together the different AST fragments.
  • newName is 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

newName :: String -> m Name #

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.

Instances

Instances details
Quote Q 
Instance details

Defined in Language.Haskell.TH.Syntax.Compat

Methods

newName :: String -> Q Name #

Monad m => Quote (QuoteT m) Source # 
Instance details

Defined in Control.Monad.Quote.Internal

Methods

newName :: String -> QuoteT m Name #

The PureQ monad

type PureQ = QuoteT Identity Source #

A pure variant of the QuoteT monad transformer.

Useful to get an Exp out of a Quote m => m Exp via runPureQ.

runPureQ :: PureQ a -> a Source #

Extract a from PureQ a, where PureQ is an instance of Quote.

On GHC 9.0+, you can use this to extract an Exp out of a quotation bracket:

>>> runPureQ [| \x -> x + 5 |]
LamE [VarP x_0] (InfixE (Just (VarE x_0)) (VarE GHC.Num.+) (Just (LitE (IntegerL 5))))

The QuoteT monad transformer

data QuoteT m a Source #

The QuoteT monad transformer. Also see runQuoteT.

Useful to add a Quote instance to any monad transformer stack.

Internally, this is a newtype of StateT Uniq.

Instances

Instances details
MonadTrans QuoteT Source # 
Instance details

Defined in Control.Monad.Quote.Internal

Methods

lift :: Monad m => m a -> QuoteT m a #

(MonadReader r m, MonadWriter w m, MonadState s m) => MonadRWS r w s (QuoteT m) Source # 
Instance details

Defined in Control.Monad.Quote.Internal

MonadWriter w m => MonadWriter w (QuoteT m) Source # 
Instance details

Defined in Control.Monad.Quote.Internal

Methods

writer :: (a, w) -> QuoteT m a #

tell :: w -> QuoteT m () #

listen :: QuoteT m a -> QuoteT m (a, w) #

pass :: QuoteT m (a, w -> w) -> QuoteT m a #

MonadState s m => MonadState s (QuoteT m) Source # 
Instance details

Defined in Control.Monad.Quote.Internal

Methods

get :: QuoteT m s #

put :: s -> QuoteT m () #

state :: (s -> (a, s)) -> QuoteT m a #

MonadReader r m => MonadReader r (QuoteT m) Source # 
Instance details

Defined in Control.Monad.Quote.Internal

Methods

ask :: QuoteT m r #

local :: (r -> r) -> QuoteT m a -> QuoteT m a #

reader :: (r -> a) -> QuoteT m a #

MonadError e m => MonadError e (QuoteT m) Source # 
Instance details

Defined in Control.Monad.Quote.Internal

Methods

throwError :: e -> QuoteT m a #

catchError :: QuoteT m a -> (e -> QuoteT m a) -> QuoteT m a #

Monad m => Monad (QuoteT m) Source # 
Instance details

Defined in Control.Monad.Quote.Internal

Methods

(>>=) :: QuoteT m a -> (a -> QuoteT m b) -> QuoteT m b #

(>>) :: QuoteT m a -> QuoteT m b -> QuoteT m b #

return :: a -> QuoteT m a #

Functor m => Functor (QuoteT m) Source # 
Instance details

Defined in Control.Monad.Quote.Internal

Methods

fmap :: (a -> b) -> QuoteT m a -> QuoteT m b #

(<$) :: a -> QuoteT m b -> QuoteT m a #

MonadFix m => MonadFix (QuoteT m) Source # 
Instance details

Defined in Control.Monad.Quote.Internal

Methods

mfix :: (a -> QuoteT m a) -> QuoteT m a #

MonadFail m => MonadFail (QuoteT m) Source # 
Instance details

Defined in Control.Monad.Quote.Internal

Methods

fail :: String -> QuoteT m a #

Monad m => Applicative (QuoteT m) Source # 
Instance details

Defined in Control.Monad.Quote.Internal

Methods

pure :: a -> QuoteT m a #

(<*>) :: QuoteT m (a -> b) -> QuoteT m a -> QuoteT m b #

liftA2 :: (a -> b -> c) -> QuoteT m a -> QuoteT m b -> QuoteT m c #

(*>) :: QuoteT m a -> QuoteT m b -> QuoteT m b #

(<*) :: QuoteT m a -> QuoteT m b -> QuoteT m a #

MonadIO m => MonadIO (QuoteT m) Source # 
Instance details

Defined in Control.Monad.Quote.Internal

Methods

liftIO :: IO a -> QuoteT m a #

MonadPlus m => Alternative (QuoteT m) Source # 
Instance details

Defined in Control.Monad.Quote.Internal

Methods

empty :: QuoteT m a #

(<|>) :: QuoteT m a -> QuoteT m a -> QuoteT m a #

some :: QuoteT m a -> QuoteT m [a] #

many :: QuoteT m a -> QuoteT m [a] #

MonadPlus m => MonadPlus (QuoteT m) Source # 
Instance details

Defined in Control.Monad.Quote.Internal

Methods

mzero :: QuoteT m a #

mplus :: QuoteT m a -> QuoteT m a -> QuoteT m a #

MonadCont m => MonadCont (QuoteT m) Source # 
Instance details

Defined in Control.Monad.Quote.Internal

Methods

callCC :: ((a -> QuoteT m b) -> QuoteT m a) -> QuoteT m a #

Monad m => Quote (QuoteT m) Source # 
Instance details

Defined in Control.Monad.Quote.Internal

Methods

newName :: String -> QuoteT m Name #

runQuoteT :: Monad m => QuoteT m a -> m a Source #

Extract m a from QuoteT m a, where QuoteT m is always an instance of Quote.

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"))))