Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
This module exists to make it possible to define code that works across
a wide range of
template-haskell
versions with as little CPP as possible.
To that end, this module currently backports the following
template-haskell
constructs:
-
The
Quote
class -
The
Code
type -
The
getPackageRoot
andmakeRelativeToProject
utility functions
Refer to the Haddocks below for examples of how to use each of these in a backwards-compatible way.
Synopsis
- class Monad m => Quote m where
- unsafeQToQuote :: Quote m => Q a -> m a
- unTypeQQuote :: forall (r :: RuntimeRep ) (a :: TYPE r) m. Quote m => m ( TExp a) -> m Exp
- unsafeTExpCoerceQuote :: forall (r :: RuntimeRep ) (a :: TYPE r) m. Quote m => m Exp -> m ( TExp a)
- liftQuote :: forall t m. ( Lift t, Quote m) => t -> m Exp
- liftTypedQuote :: forall t m. ( Lift t, Quote m) => t -> Code m t
- liftStringQuote :: Quote m => String -> m Exp
-
newtype
Code
m (a ::
TYPE
(r ::
RuntimeRep
)) =
Code
{
- examineCode :: m ( TExp a)
- type CodeQ = Code Q :: TYPE r -> *
- class IsCode q (a :: TYPE r) c | c -> a q where
- unsafeCodeCoerce :: forall (r :: RuntimeRep ) (a :: TYPE r) m. Quote m => m Exp -> Code m a
- liftCode :: forall (r :: RuntimeRep ) (a :: TYPE r) m. m ( TExp a) -> Code m a
- unTypeCode :: forall (r :: RuntimeRep ) (a :: TYPE r) m. Quote m => Code m a -> m Exp
- hoistCode :: forall m n (r :: RuntimeRep ) (a :: TYPE r). Monad m => ( forall x. m x -> n x) -> Code m a -> Code n a
- bindCode :: forall m a (r :: RuntimeRep ) (b :: TYPE r). Monad m => m a -> (a -> Code m b) -> Code m b
- bindCode_ :: forall m a (r :: RuntimeRep ) (b :: TYPE r). Monad m => m a -> Code m b -> Code m b
- joinCode :: forall m (r :: RuntimeRep ) (a :: TYPE r). Monad m => m ( Code m a) -> Code m a
- type Splice m (a :: TYPE r) = m ( TExp a)
- type SpliceQ (a :: TYPE r) = Splice Q a
- bindSplice :: forall m a (r :: RuntimeRep ) (b :: TYPE r). Monad m => m a -> (a -> Splice m b) -> Splice m b
- bindSplice_ :: forall m a (r :: RuntimeRep ) (b :: TYPE r). Monad m => m a -> Splice m b -> Splice m b
- examineSplice :: forall (r :: RuntimeRep ) m (a :: TYPE r). Splice m a -> m ( TExp a)
- hoistSplice :: forall m n (r :: RuntimeRep ) (a :: TYPE r). Monad m => ( forall x. m x -> n x) -> Splice m a -> Splice n a
- joinSplice :: forall m (r :: RuntimeRep ) (a :: TYPE r). Monad m => m ( Splice m a) -> Splice m a
- liftSplice :: forall (r :: RuntimeRep ) (a :: TYPE r) m. m ( TExp a) -> Splice m a
- liftTypedFromUntypedSplice :: ( Lift t, Quote m) => t -> Splice m t
- unsafeSpliceCoerce :: forall (r :: RuntimeRep ) (a :: TYPE r) m. Quote m => m Exp -> Splice m a
- unTypeSplice :: forall (r :: RuntimeRep ) (a :: TYPE r) m. Quote m => Splice m a -> m Exp
- expToSplice :: Applicative m => TExp a -> Splice m a
- getPackageRoot :: Q FilePath
- makeRelativeToProject :: FilePath -> Q FilePath
The
Quote
class
The
Quote
class (first proposed in
GHC Proposal 246
)
was introduced in
template-haskell-2.17.0.0
. This module defines a version
of
Quote
that is backward-compatible with older
template-haskell
releases and is forward-compatible with the existing
Quote
class.
In addition to
Quote
, this module also backports versions of functions in
Language.Haskell.TH.Syntax
that work over any
Quote
instance instead of
just
Q
. Since this module is designed to coexist with the existing
definitions in
template-haskell
as much as possible, the backported
functions are suffixed with
-Quote
to avoid name clashes. For instance,
the backported version of
lift
is named
liftQuote
.
The one exception to the no-name-clashes policy is the backported
newName
method of
Quote
. We could have conceivably named it
newNameQuote
, but
then it would not have been possible to define backwards-compatible
Quote
instances without the use of CPP. As a result, some care must be exercised
when combining this module with
Language.Haskell.TH
or
Language.Haskell.TH.Syntax
on older versions of
template-haskell
, as
they both export a version of
newName
with a different type. Here is an
example of how to safely combine these modules:
{-# LANGUAGE GeneralizedNewtypeDeriving, TemplateHaskell #-} import Control.Monad.State (MonadState(..), State, evalState) import Language.Haskell.TH hiding (newName
) import Language.Haskell.TH.Syntax hiding (newName
) import Language.Haskell.TH.Syntax.Compat newtype PureQ a = MkPureQ (State Uniq a) deriving (Functor, Applicative, Monad, MonadState Uniq) runPureQ :: PureQ a -> a runPureQ m = case m of MkPureQ m' -> evalState m' 0 instanceQuote
PureQ wherenewName
s = state $ i -> (mkNameU s i, i + 1) main :: IO () main = putStrLn $ runPureQ $ do a <- newName "a" return $ nameBase a
We do not make an effort to backport any combinators from the
Language.Haskell.TH.Lib
module, as the surface area is simply too large.
If you wish to generalize code that uses these combinators to work over
Quote
in a backwards-compatible way, use the
unsafeQToQuote
function.
class Monad m => Quote m where Source #
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
.
newName :: String -> m Name Source #
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
.
Quote
functionality
The
unsafeQToQuote
function
unsafeQToQuote :: Quote m => Q a -> m a Source #
Use a
Q
computation in a
Quote
context. This function is only safe
when the
Q
computation performs actions from the
Quote
instance for
Q
or any of
Quote
's subclasses (
Functor
,
Applicative
, and
Monad
).
Attempting to perform actions from the
MonadFail
,
MonadIO
, or
Quasi
instances for
Q
will result in runtime errors.
This is useful when you have some
Q
-valued functions that only performs
actions from
Quote
and wish to generalise it from
Q
to
Quote
without
having to rewrite the internals of the function. This is especially handy
for code defined in terms of combinators from
Language.Haskell.TH.Lib
,
which were all hard-coded to
Q
prior to
template-haskell-2.17.0.0
. For
instance, consider this function:
apply ::Exp
->Exp
->Q
Exp
apply f x =appE
(return x) (return y)
There are two ways to generalize this function to use
Quote
in a
backwards-compatible way. One way to do so is to rewrite
apply
to avoid
the use of
appE
, like so:
applyQuote ::Quote
m =>Exp
->Exp
-> mExp
applyQuote f x = return (AppE
x y)
For a small example like
applyQuote
, there isn't much work involved. But
this can become tiresome for larger examples. In such cases,
unsafeQToQuote
can do the heavy lifting for you. For example,
applyQuote
can also be defined as:
applyQuote ::Quote
m =>Exp
->Exp
-> mExp
applyQuote f x =unsafeQToQuote
(apply f x)
Functions from
Language.Haskell.TH.Syntax
unTypeQQuote :: forall (r :: RuntimeRep ) (a :: TYPE r) m. Quote m => m ( TExp a) -> m Exp Source #
Discard the type annotation and produce a plain Template Haskell expression
Levity-polymorphic since template-haskell-2.16.0.0 .
This is a variant of the
unTypeQ
function that is always guaranteed to
use a
Quote
constraint, even on old versions of
template-haskell
.
As this function interacts with typed Template Haskell, this function is
only defined on
template-haskell-2.9.0.0
(GHC 7.8) or later.
unsafeTExpCoerceQuote :: forall (r :: RuntimeRep ) (a :: TYPE r) m. Quote m => m Exp -> m ( TExp a) Source #
Annotate the Template Haskell expression with a type
This is unsafe because GHC cannot check for you that the expression really does have the type you claim it has.
Levity-polymorphic since template-haskell-2.16.0.0 .
This is a variant of the
unsafeTExpCoerce
function that is always
guaranteed to use a
Quote
constraint, even on old versions of
template-haskell
.
As this function interacts with typed Template Haskell, this function is
only defined on
template-haskell-2.9.0.0
(GHC 7.8) or later.
liftTypedQuote :: forall t m. ( Lift t, Quote m) => t -> Code m t Source #
Turn a value into a Template Haskell typed expression, suitable for use in a typed splice.
This is a variant of the
liftTyped
method of
Lift
that is
always guaranteed to use a
Quote
constraint and return a
Code
, even on
old versions of
template-haskell
.
As this function interacts with typed Template Haskell, this function is
only defined on
template-haskell-2.9.0.0
(GHC 7.8) or later. While the
liftTyped
method of
Lift
was first introduced in
template-haskell-2.16.0.0
, we are able to backport it back to
template-haskell-2.9.0.0
by making use of the
lift
method on
older versions of
template-haskell
. This crucially relies on the
Lift
law that
to work,
so beware if you use
lift
x ≡
unTypeQ
(
liftTyped
x)
liftTypedQuote
with an unlawful
Lift
instance.
Levity-polymorphic since template-haskell-2.17.0.0 .
liftStringQuote :: Quote m => String -> m Exp Source #
This is a variant of the
liftString
function that is always
guaranteed to use a
Quote
constraint, even on old versions of
template-haskell
.
The
Code
and
CodeQ
types
The
Code
type (first proposed in
GHC Proposal 195
)
was introduced in
template-haskell-2.17.0.0
. This module defines a version
of
Code
that is backward-compatible with older
template-haskell
releases and is forward-compatible with the existing
Code
class.
In addition to
Code
, this module also backports the functions in
Language.Haskell.TH.Syntax
that manipulate
Code
values.
One troublesome aspect of writing backwards-compatible code involving
Code
is that GHC 9.0 changed the types of typed Template Haskell splices. Before,
they were of type
, but they are now of type
Q
(
TExp
a)
.
This modules provides two mechanisms for smoothing over the differences
between these two types:
Code
Q
a
-
The
IsCode
class can be used to convertCode
orTExp
values toCode
, and vice versa. -
The
Splice
type synonym uses CPP so thatSplice
q aCode
q aq (
on older versions of GHC. This module also defines versions ofTExp
a)Code
- andTExp
-related combinators that work overSplice
.
Refer to the Haddocks for
IsCode
and
Splice
for more information on each
approach. Both approaches have pros and cons, and as a result, neither
approach is a one-size-fits-all solution.
Because
Code
interacts with typed Template Haskell, the
Code
type and
any function that mentions
Code
in its type are only defined on
template-haskell-2.9.0.0
(GHC 7.8) or later.
newtype Code m (a :: TYPE (r :: RuntimeRep )) Source #
Levity-polymorphic since template-haskell-2.16.0.0 .
Code | |
|
Code
functionality
The
IsCode
class
class IsCode q (a :: TYPE r) c | c -> a q where Source #
A class that allows one to smooth over the differences between
(the type of typed Template Haskell quotations on
Code
m
a
template-haskell-2.17.0.0
or later) and
(the type of
typed Template Haskell quotations on older versions of
m
(
TExp
a)
template-haskell
).
Here are two examples that demonstrate how to use each method of
IsCode
:
{-# LANGUAGE TemplateHaskell #-} import Language.Haskell.TH import Language.Haskell.TH.Syntax.Compat --toCode
will ensure that the end result is aCode
, regardless of -- whether the quote itself returns aCode
or aTExp
. myCode ::Code
Q
Int myCode =toCode
[|| 42 ||] --fromCode
will ensure that the inputCode
is suitable for splicing -- (i.e., it will return aCode
or aTExp
depending on the --template-haskell
version in use). fortyTwo :: Int fortyTwo = $$(fromCode
myCode)
Levity-polymorphic since template-haskell-2.16.0.0 .
toCode :: c -> Code q a Source #
Convert something to a
Code
.
fromCode :: Code q a -> c Source #
Convert to something from a
Code
.
Limitations of
IsCode
IsCode
makes it possible to backport code involving typed Template Haskell
quotations and splices where the types are monomorphized to
Q
. GHC 9.0
and later, however, make it possible to use typed TH quotations and splices
that are polymorphic over any
Quote
instance. Unfortunately, the
th-compat
library does not yet have a good story for backporting
Quote
-polymorphic quotations or splices. For example, consider this code:
instance (Lift
a,Quote
q,Num
a) =>Num
(Code
q a) where -- ... x + y = [|| $$x + $$y ||] -- ...
How might we backport this code? If we were in a setting where
q
were
monomorphized to
Q
, we could simply write this:
x + y =toCode
[|| $$(fromCode
x) + $$(fromCode
y) ||]
In a
Quote
-polymorphic setting, however, we run into issues. While this
will compile on GHC 9.0 or later, it will not compile on earlier GHC
versions because all typed TH quotations and splices must use
Q
. At
present, the
th-compat
library does not offer any solution to this
problem.
unsafeCodeCoerce :: forall (r :: RuntimeRep ) (a :: TYPE r) m. Quote m => m Exp -> Code m a Source #
Unsafely convert an untyped code representation into a typed code representation.
Levity-polymorphic since template-haskell-2.16.0.0 .
liftCode :: forall (r :: RuntimeRep ) (a :: TYPE r) m. m ( TExp a) -> Code m a Source #
Lift a monadic action producing code into the typed
Code
representation
Levity-polymorphic since template-haskell-2.16.0.0 .
unTypeCode :: forall (r :: RuntimeRep ) (a :: TYPE r) m. Quote m => Code m a -> m Exp Source #
Extract the untyped representation from the typed representation
Levity-polymorphic since template-haskell-2.16.0.0 .
hoistCode :: forall m n (r :: RuntimeRep ) (a :: TYPE r). Monad m => ( forall x. m x -> n x) -> Code m a -> Code n a Source #
Modify the ambient monad used during code generation. For example, you
can use
hoistCode
to handle a state effect:
handleState :: Code (StateT Int Q) a -> Code Q a handleState = hoistCode (flip runState 0)
Levity-polymorphic since template-haskell-2.16.0.0 .
bindCode :: forall m a (r :: RuntimeRep ) (b :: TYPE r). Monad m => m a -> (a -> Code m b) -> Code m b Source #
Variant of (>>=) which allows effectful computations to be injected into code generation.
Levity-polymorphic since template-haskell-2.16.0.0 .
bindCode_ :: forall m a (r :: RuntimeRep ) (b :: TYPE r). Monad m => m a -> Code m b -> Code m b Source #
Variant of (>>) which allows effectful computations to be injected into code generation.
Levity-polymorphic since template-haskell-2.16.0.0 .
joinCode :: forall m (r :: RuntimeRep ) (a :: TYPE r). Monad m => m ( Code m a) -> Code m a Source #
A useful combinator for embedding monadic actions into
Code
myCode :: ... => Code m a
myCode = joinCode $ do
x <- someSideEffect
return (makeCodeWith x)
Levity-polymorphic since template-haskell-2.16.0.0 .
Compatibility with
Splice
s
This section of code is useful for library authors looking to provide
a typed
TemplateHaskell
interface that is backwards- and
forward-compatible. This section may be useful for you if you
specifically intend for the splice to be done directly.
Prior to GHC 9, you'd offer a value with type
.
After GHC 9, these values are no longer acceptable in a typed splice:
typed splices must operate in
Q
(
TExp
a)
Code m a
instead.
The
type is used to work with both versions - it is a type
alias, and depending on the version of
Splice
m a
template-haskell
that was
compiled, it will either be
or
Code
m a
m (
.
TExp
a)
The function
liftSplice
can be used to convert a
expression into a
Q
(
TExp
a)
expression in a compatible manner - by
lifting to
Code
Q
a
SpliceQ
, you get the right behavior depending on your
template-haskell
version.
The function
examineSplice
can be used on typed QuasiQuoters, and the
result will be converted into an appropriate
m (
. This
allows you to use typed quasiquoters in a
TExp
a)
do
block, much like
examineCode
does with
Code
.
With
expToSplice
, you can substitute uses of
pure
when given the
specific type:
pureTExp ::TExp
a ->Q
(TExp
a) pureTExp = pure
This allows you to splice
values directly into a typed
quasiquoter.
TExp
a
type Splice m (a :: TYPE r) = m ( TExp a) Source #
is a type alias for:
Splice
m a
-
Code
m atemplate-haskell-2.17.0.0
or later, or -
m (
, if using an older version ofTExp
a)template-haskell
.
This should be used with caution, as its definition differs depending on
which version of
template-haskell
you are using. It is mostly useful for
contexts in which one is writing a definition that is intended to be used
directly in a typed Template Haskell splice, as the types of TH splices
differ between
template-haskell
versions as well.
Levity-polymorphic since template-haskell-2.16.0.0 .
type SpliceQ (a :: TYPE r) = Splice Q a Source #
is a type alias for:
SpliceQ
a
-
Code
Q
atemplate-haskell-2.17.0.0
or later, or -
Q
(TExp
a)template-haskell
.
This should be used with caution, as its definition differs depending on
which version of
template-haskell
you are using. It is mostly useful for
contexts in which one is writing a definition that is intended to be used
directly in a typed Template Haskell splice, as the types of TH splices
differ between
template-haskell
versions as well.
Levity-polymorphic since template-haskell-2.16.0.0 .
bindSplice :: forall m a (r :: RuntimeRep ) (b :: TYPE r). Monad m => m a -> (a -> Splice m b) -> Splice m b Source #
A variant of
bindCode
that works over
Splice
s. Because this function
uses
Splice
, the type of this function will be different depending on
which version of
template-haskell
you are using. (See the Haddocks for
Splice
for more information on this point.)
Levity-polymorphic since template-haskell-2.16.0.0 .
bindSplice_ :: forall m a (r :: RuntimeRep ) (b :: TYPE r). Monad m => m a -> Splice m b -> Splice m b Source #
A variant of
bindCode_
that works over
Splice
s. Because this function
uses
Splice
, the type of this function will be different depending on
which version of
template-haskell
you are using. (See the Haddocks for
Splice
for more information on this point.)
Levity-polymorphic since template-haskell-2.16.0.0 .
examineSplice :: forall (r :: RuntimeRep ) m (a :: TYPE r). Splice m a -> m ( TExp a) Source #
A variant of
examineCode
that takes a
Splice
as an argument. Because
this function takes a
Splice
as an argyment, the type of this function
will be different depending on which version of
template-haskell
you are
using. (See the Haddocks for
Splice
for more information on this point.)
Levity-polymorphic since template-haskell-2.16.0.0 .
hoistSplice :: forall m n (r :: RuntimeRep ) (a :: TYPE r). Monad m => ( forall x. m x -> n x) -> Splice m a -> Splice n a Source #
A variant of
hoistCode
that works over
Splice
s. Because this function
uses
Splice
, the type of this function will be different depending on
which version of
template-haskell
you are using. (See the Haddocks for
Splice
for more information on this point.)
Levity-polymorphic since template-haskell-2.16.0.0 .
joinSplice :: forall m (r :: RuntimeRep ) (a :: TYPE r). Monad m => m ( Splice m a) -> Splice m a Source #
A variant of
joinCode
that works over
Splice
s. Because this function
uses
Splice
, the type of this function will be different depending on
which version of
template-haskell
you are using. (See the Haddocks for
Splice
for more information on this point.)
Levity-polymorphic since template-haskell-2.16.0.0 .
liftSplice :: forall (r :: RuntimeRep ) (a :: TYPE r) m. m ( TExp a) -> Splice m a Source #
A variant of
liftCode
that returns a
Splice
. Because this function
returns a
Splice
, the return type of this function will be different
depending on which version of
template-haskell
you are using. (See the
Haddocks for
Splice
for more
information on this point.)
Levity-polymorphic since template-haskell-2.16.0.0 .
liftTypedFromUntypedSplice :: ( Lift t, Quote m) => t -> Splice m t Source #
A variant of
liftTypedQuote
that is:
-
Always implemented in terms of
lift
behind the scenes, and -
Returns a
Splice
. This means that the return type of this function will be different depending on which version oftemplate-haskell
you are using. (See the Haddocks forSplice
for more information on this point.)
This is especially useful for minimizing CPP in one particular scenario:
implementing
liftTyped
in hand-written
Lift
instances
where the corresponding
lift
implementation cannot be derived. For
instance, consider this example from the
text
library:
instanceLift
Text wherelift
= appE (varE 'pack) . stringE . unpack #if MIN_VERSION_template_haskell(2,17,0)liftTyped
=unsafeCodeCoerce
.lift
#elif MIN_VERSION_template_haskell(2,16,0)liftTyped
=unsafeTExpCoerce
.lift
#endif
The precise details of how this
lift
implementation works are not
important, only that it is something that
DeriveLift
could not generate.
The main point of this example is to illustrate how tiresome it is to write
the CPP necessary to define
liftTyped
in a way that works across
multiple versions of
template-haskell
. With
liftTypedFromUntypedSplice
,
however, this becomes slightly easier to manage:
instanceLift
Text wherelift
= appE (varE 'pack) . stringE . unpack #if MIN_VERSION_template_haskell(2,16,0)liftTyped
=liftTypedFromUntypedSplice
#endif
Note that due to the way this function is defined, this will only work
for
Lift
instances
t
such that
(t :: Type)
. If you wish to
manually define
liftTyped
for a type with a different kind, you
will have to use
unsafeSpliceCoerce
to overcome levity polymorphism
restrictions.
unsafeSpliceCoerce :: forall (r :: RuntimeRep ) (a :: TYPE r) m. Quote m => m Exp -> Splice m a Source #
Unsafely convert an untyped splice representation into a typed
Splice
representation. Because this function returns a
Splice
, the return type of
this function will be different depending on which version of
template-haskell
you are using. (See the Haddocks for
Splice
for more
information on this point.)
This is especially useful for minimizing CPP when:
-
You need to implement
liftTyped
in a hand-writtenLift
instance where the correspondinglift
implementation cannot be derived, and -
The data type receiving a
Lift
instance has a kind besidesType
.
Condition (2) is important because while it is possible to simply define
'Syntax.liftTyped =
for
liftTypedFromUntypedSplice
Lift
instances
t
such that
(t :: Type)
, this will not work for types with
different types, such as unboxed types or unlifted newtypes. This is because
GHC restrictions prevent defining
liftTypedFromUntypedSplice
in a levity
polymorphic fashion, so one must use
unsafeSpliceCoerce
to work around
these restrictions. Here is an example of how to use
unsafeSpliceCoerce
:
instanceLift
Int# wherelift
x = litE (intPrimL (fromIntegral (I# x))) #if MIN_VERSION_template_haskell(2,16,0)liftTyped
x =unsafeSpliceCoerce
(lift
x) #endif
Levity-polymorphic since template-haskell-2.16.0.0 .
unTypeSplice :: forall (r :: RuntimeRep ) (a :: TYPE r) m. Quote m => Splice m a -> m Exp Source #
A variant of
unTypeCode
that takes a
Splice
as an argument. Because
this function takes a
Splice
as an argyment, the type of this function
will be different depending on which version of
template-haskell
you are
using. (See the Haddocks for
Splice
for more information on this point.)
Levity-polymorphic since template-haskell-2.16.0.0 .
expToSplice :: Applicative m => TExp a -> Splice m a Source #
Lift a
into a
TExp
a
Splice
. This is useful when splicing
in the result of a computation into a typed QuasiQuoter.
One example is
traverse
ing over a list of elements and returning an
expression from each element.
mkInt ::String
->Q
(TExp
Int
) mkInt str = [|| length $$str ||] mkInts :: [String
] ->Q
[TExp
Int
] mkInts = traverse mkInt
This gives us a list of
TExp
, not a
TExp
of a list. We
can push the list inside the type with this function:
listTE :: [TExp
a] ->TExp
[a] listTE =TExp
.ListE
.map
unType
In a
do
block using
liftSplice
, we can bind the resulting
out of the expression.
TExp
[
Int
]
foo ::Q
(TExp
Int) foo = do ints <- mkInts ["hello", "world", "goodybe", "bob"] [|| sum $$(pure (listTE ints)) ||]
Prior to GHC 9, with the
Q
type, we can write
,
which is a valid thing to use in a typed quasiquoter.
However, after GHC 9, this code will fail to type check. There is no
pure
::
TExp
a ->
Q
(
TExp
a)
Applicative
instance for
, so we need another way to
splice it in.
Code
m a
A GHC 9 only solution can use
and
Code
:: m (
TExp
a) -> Code
m a
pure
together, like:
.
Code
.
pure
With
expToSplice
, we can splice it in a backwards compatible way.
A fully backwards- and forwards-compatible example looks like this:
mkInt ::String
->Q
Int
mkInt str =examineSplice
[|| length $$str ||] mkInts :: [String
] ->Q
[TExp
Int
] mkInts = traverse mkInt foo ::SpliceQ
Int
foo =liftSplice
$ do ints <- mkInts ["hello", "world", "goodybe", "bob"]examineSplice
[|| sum $$(expToSplice (listTE ints)) ||]
Since: 0.1.3
Package root functions
getPackageRoot :: Q FilePath Source #
Get the package root for the current package which is being compiled. This can be set explicitly with the -package-root flag but is normally just the current working directory.
The motivation for this flag is to provide a principled means to remove the assumption from splices that they will be executed in the directory where the cabal file resides. Projects such as haskell-language-server can't and don't change directory when compiling files but instead set the -package-root flag appropiately.
This is best-effort compatibility implementation.
This function looks at the source location of the Haskell file calling it,
finds the first parent directory with a
.cabal
file, and uses that as the
root directory for fixing the relative path.