exon-1.4.0.0: Customizable Quasiquote Interpolation
Safe HaskellSafe-Inferred
LanguageHaskell2010

Exon

Description

Customizable Quasiquote Interpolation

Synopsis

Introduction

This Haskell library provides quasiquote string interpolation with customizable concatenation for arbitrary types.

A quasiquote with the quoter exon is transformed into a chain of concatenations, allowing expressions to be interpolated between the characters #{ and }. A common use case is plain text interpolation:

>>> :set -XOverloadedStrings
>>> animal = "snake"
>>> location = "a tree"
>>> [exon|#{animal} in #{location}|]
"snake in a tree"

The quote is effectively converted to a sequence of Semigroup concatenations:

>>> animal <> " " <> "in" <> " " <> location
"snake in a tree"

It is precisely converted to an intermediate data structure, Segment, and concatenated using customizable classes:

>>> exonProcess [Expression animal, String " in ", Expression location]
"snake in a tree"

The default implementation uses Monoid and IsString, resulting in something like:

>>> foldl' (<>) mempty [animal, fromString " ", fromString "in", fromString " ", location] :: String
"snake in a tree"

This allows any type that implements those two classes to be used as the result:

>>> newtype Str = Str Text deriving stock (Show) deriving newtype (IsString, Semigroup, Monoid)
>>> [exon|#{animal} in #{location}|] :: Str
Str "snake in a tree"

The astute reader might notice that it is unclear what type animal is expected to be – it hasn't been annotated, yet it works for both the quote without type annotation as well as the one of type Str.

The reason for this phenomenon is that GHC types animal = "snake" as animal :: IsString a => a thanks to OverloadedStrings. When the quote is written without annotation, the evaluator defaults to String in order to print it (for example, hls-eval-plugin or GHCi).

When the two names are used in the quote with Str, they will be instantiated as Str as well.

One neat application of Exon is for writing showsPrec methods, whose type is String -> String and which are used to stringify a type with automatic parentheses when contained in a larger type:

data Numbers =
  Numbers Int (Maybe Int) Value

instance Show Numbers where
  showsPrec d Numbers number maybeNumber value =
    showParen (d > 10)
      [exon|Numbers #{showsPrec 11 number} #{showsPrec 11 maybeNumber} #{showsPrec 11 value}|]

Implicit conversion

Values of different types can be interpolated if they meet one of two conditions:

Exon requires auto-converted values to be interpolated with a different bracket, ##{, to avoid accidents:

>>> newtype Str = Str Text deriving stock (Show) deriving newtype (IsString, Semigroup, Monoid)
>>> newtype Animal = Animal ByteString deriving stock (Generic)
>>> animal = Animal "lemur"
>>> location = "a tree"
>>> [exon|##{animal} in #{location}|] :: Str
Str "lemur in a tree"

In this case, the two conditions are even combined – the Animal is unwrapped, UTF-8-decoded to Text, and rewrapped into Str.

If you absolutely want to splice newtypes with the same brackets, you can use the quoter exun (the un stands for unsafe).

exon :: QuasiQuoter Source #

A quasiquoter that allows interpolation, concatenating the resulting segments with (<>) or a an arbitrary user-defined implementation. See the introduction for details.

>>> [exon|write #{show (5 :: Int)} lines of ##{"code" :: ByteString}|] :: Text
"write 5 lines of code"

exonws :: QuasiQuoter Source #

A variant of exon that creates segments for each sequence of whitespace characters that can be processed differently by ExonAppend, ExonSegment or ExonString.

Since: 1.0.0.0

intron :: QuasiQuoter Source #

A variant of exon that ignores all literal whitespace in the quote (not in interpolated expressions).

[intron|x|] === skipWs [exonws|x|]

Since: 1.0.0.0

exun :: QuasiQuoter Source #

Unsafe version of exon, allowing automatic conversion with the same splice brackets as matching types.

Since: 1.0.0.0

exonWith :: Maybe (Q Exp, Q Exp) -> Bool -> Bool -> QuasiQuoter Source #

Constructor for a quasiquoter that wraps all segments with the first expression and unwraps the result with the second.

This can be used to define quoters with custom logic by providing instances of any of the classes in Exon.Class.Exon with the result type argument set to the wrapper type:

>>> import Exon.Class.Exon (ExonString (..))
>>> import Exon.Data.Segment (Segment(String))
>>> import qualified Data.Text.Lazy.Builder as Text
>>> newtype Nl = Nl Text deriving (Generic)
>>> getNl (Nl t) = t
>>> instance ExonString Nl Text.Builder where exonWhitespace _ = exonString @Nl "\n"
>>> exonnl = exonWith (Just ([e|Nl|], [e|getNl|])) True False
>>> [exonnl|one   two     three|]
"one\ntwo\nthree"

Since: 0.2.0.0

Performance

Generic string concatenation can be quite expensive. If a quote's result type is Text, as in:

>>> [exon|#{"x"} #{"y"}|] :: Text

then the resulting concatenation will use the Semigroup operation for Text, which has O(n) complexity for each pair of appended strings.

In order to improve performance, Exon allows the type used for concatenation (the builder) to differ from the result type, which is implemented by the class ExonBuilder. For example, the instance for Text selects Builder as the builder type and converts the segments and the result accordingly. In a quote of 1000 segments, this improves performance by a factor of 100!

However, if the result type is a newtype, the Text builder will not be used:

>>> newtype Str = Str Text deriving stock (Show) deriving newtype (IsString, Semigroup, Monoid)
>>> [exon|#{"x"} #{"y"}|] :: Str

This restriction can be circumvented by making Str an instance of Generic – in that case, Exon will unwrap the type (even multiply nested newtypes) and use the builder associated with the inner type. Str doesn't even need to derive IsString, Semigroup and Monoid in this case, as all the operations are performed on Builder.

In principle, this conversion could be done with Coercible as well, but type inference is really bad with that method.

Note that when using generic segment conversion in conjunction with this, the result type must also derive IsString.

Customizing Concatenation

Quote types don't have to be transparent wrappers for strings. Concatenation can be changed in a type's Semigroup:

>>> import Data.Text (toUpper)
>>> newtype Name = Name Text deriving newtype (Show, IsString)
>>> instance Semigroup Name where Name l <> Name r = Name (l <> " | " <> r)
>>> deriving instance Monoid Name
>>> lastName = Name "Fry"
>>> [intron|Philip J. #{lastName}|]
"Philip | J. | Fry"

This example uses the quoter intron, which ignores whitespace. The Semigroup then inserts custom separators.

The same result can be achieved by using the whitespace-aware quoter exonws and providing a specialized instance of some of Exon's classes, like ExonString:

newtype Name = Name Text deriving stock (Generic)
instance ExonString Name Text.Builder where
  exonWhitespace _ = Result " | "

This example additionally uses the Generic newtype unwrapping feature, allowing the customization to be performed directly in the efficient builder type.

class Exon (result :: Type) where Source #

This class is the main entry point for Exon.

The default instance unwraps all newtypes that are Generic and passes the innermost type to ExonBuild.

The original type is also used as a parameter to ExonBuild, so customizations can be based on it.

Methods

exonProcess :: NonEmpty (Segment result) -> result Source #

Concatenate a list of Segments.

Since: 1.0.0.0

Instances

Instances details
(OverNewtypes result inner, ExonBuild result inner) => Exon result Source # 
Instance details

Defined in Exon.Class.Exon

Methods

exonProcess :: NonEmpty (Segment result) -> result Source #

class ExonBuild (result :: Type) (inner :: Type) where Source #

This class implements the Segment concatenation logic.

  1. Each Segment is converted to the builder type by ExonSegment using exonBuilder to construct the builder from expressions.
  2. The segments are folded over ExonAppend.
  3. The result is converted from the builder type to the original type by ExonBuilder.

Each step may be overridden individually by writing overlapping instances for the involved classes.

Since: 1.0.0.0

Methods

exonBuild :: NonEmpty (Segment inner) -> inner Source #

Concatenate a list of Segments.

Instances

Instances details
(ExonAppend result builder, ExonSegment result inner builder, ExonBuilder inner builder) => ExonBuild result inner Source # 
Instance details

Defined in Exon.Class.Exon

Methods

exonBuild :: NonEmpty (Segment inner) -> inner Source #

class ExonAppend (result :: Type) (builder :: Type) where Source #

This class handles concatenation of segments, which might be a builder or the result type.

The default instance simply uses (<>), and there is only one special instance for String -> String, the type used by showsPrec.

Since: 1.0.0.0

Minimal complete definition

Nothing

Methods

exonAppend :: builder -> builder -> Result builder Source #

Concatenate two segments of the builder type.

default exonAppend :: Semigroup builder => builder -> builder -> Result builder Source #

exonConcat :: NonEmpty (Result builder) -> Result builder Source #

Concatenate a list of segments of the result type.

Folds the list over exonAppend, skipping over Empty segments.

A possible overload may implement lookahead to skip whitespace.

Since: 1.1.0.0

Instances

Instances details
Semigroup builder => ExonAppend result builder Source # 
Instance details

Defined in Exon.Class.Exon

Methods

exonAppend :: builder -> builder -> Result builder Source #

exonConcat :: NonEmpty (Result builder) -> Result builder Source #

ExonAppend result (String -> String) Source # 
Instance details

Defined in Exon.Class.Exon

class ExonSegment (result :: Type) (inner :: Type) (builder :: Type) where Source #

This class converts a Segment to a builder.

The default implementation performs the following conversions for the different segment variants:

Since: 1.0.0.0

Methods

exonSegment :: (inner -> builder) -> Segment inner -> Result builder Source #

Convert literal string segments to the result type.

Instances

Instances details
(ExonString result builder, ExonExpression result inner builder) => ExonSegment result inner builder Source # 
Instance details

Defined in Exon.Class.Exon

Methods

exonSegment :: (inner -> builder) -> Segment inner -> Result builder Source #

class ExonBuilder (inner :: Type) (builder :: Type) | inner -> builder where Source #

This class converts a segment into a builder.

A builder is an auxiliary data type that may improve performance when concatenating segments, like Builder. The default instance uses no builder and is implemented as id.

Since: 1.0.0.0

Minimal complete definition

Nothing

Methods

exonBuilder :: inner -> builder Source #

Construct a builder from the newtype-unwrapped result type.

default exonBuilder :: inner ~ builder => inner -> builder Source #

exonBuilderExtract :: Result builder -> inner Source #

Convert the result of the builder concatenation back to the newtype-unwrapped result type.

default exonBuilderExtract :: Monoid builder => inner ~ builder => Result builder -> inner Source #

Instances

Instances details
ExonBuilder ByteString Builder Source # 
Instance details

Defined in Exon.Class.Exon

ExonBuilder LByteString Builder Source # 
Instance details

Defined in Exon.Class.Exon

ExonBuilder LText Builder Source # 
Instance details

Defined in Exon.Class.Exon

ExonBuilder Text Builder Source # 
Instance details

Defined in Exon.Class.Exon

(Monoid builder, inner ~ builder) => ExonBuilder inner builder Source # 
Instance details

Defined in Exon.Class.Exon

Methods

exonBuilder :: inner -> builder Source #

exonBuilderExtract :: Result builder -> inner Source #

ExonBuilder a builder => ExonBuilder (ExonUse a) builder Source # 
Instance details

Defined in Exon.Class.Exon

Methods

exonBuilder :: ExonUse a -> builder Source #

exonBuilderExtract :: Result builder -> ExonUse a Source #

class ExonString (result :: Type) (builder :: Type) where Source #

This class generalizes IsString for use in ExonSegment.

When a plain text segment (not interpolated) is processed, it is converted to the result type, which usually happens via fromString.

For the type of showsPrec (String -> String), there is no instance of IsString, so this class provides an instance that works around that by calling showString.

Since: 1.0.0.0

Minimal complete definition

Nothing

Methods

exonString :: String -> Result builder Source #

Convert a String to the builder type.

default exonString :: IsString builder => String -> Result builder Source #

exonWhitespace :: String -> Result builder Source #

Convert a String containing whitespace to the builder type. This is only used by whitespace-aware quoters, like exonws or intron.

default exonWhitespace :: String -> Result builder Source #

Instances

Instances details
IsString a => ExonString result a Source # 
Instance details

Defined in Exon.Class.Exon

ExonString result (String -> String) Source #

The instance for the type used by showsPrec.

Instance details

Defined in Exon.Class.Exon

IsString builder => ExonString (SkipWs result) builder Source #

The instance used when the result type is wrapped in SkipWs, which is done by intron.

It returns Empty for any whitespace.

Instance details

Defined in Exon.SkipWs

Methods

exonString :: String -> Result builder Source #

exonWhitespace :: String -> Result builder Source #

class ExonExpression (result :: Type) (inner :: Type) (builder :: Type) where Source #

This class allows manipulation of interpolated expressions before they are processed, for example to replace empty strings with Empty for the purpose of collapsing multiple whitespaces.

The default instance does nothing.

Minimal complete definition

Nothing

Methods

exonExpression :: (inner -> builder) -> inner -> Result builder Source #

Process a builder value constructed from an expression before concatenation.

Instances

Instances details
ExonExpression result inner builder Source # 
Instance details

Defined in Exon.Class.Exon

Methods

exonExpression :: (inner -> builder) -> inner -> Result builder Source #

class ToSegment a b where Source #

This class determines how an expression is converted to an interpolation quote's result type.

For a quote like [exon|a #{exp :: T} c|] :: R, the instance ToSegment T R is used to turn T into R. Aside from specialized instances for stringly types, the default implementation uses Generic to unwrap newtypes that either match the result type exactly, or uses fromString for result types that implement IsString.

So given:

>>> newtype T = T Text deriving newtype (Generic)
>>> newtype R = R Text deriving newtype (IsString, Semigroup, Monoid)

the quote from earlier would generically unwrap T and use fromString to construct an R.

Methods

toSegment :: a -> b Source #

Instances

Instances details
IsString a => ToSegment ByteString a Source # 
Instance details

Defined in Exon.Class.ToSegment

Methods

toSegment :: ByteString -> a Source #

IsString a => ToSegment LByteString a Source # 
Instance details

Defined in Exon.Class.ToSegment

Methods

toSegment :: LByteString -> a Source #

IsString a => ToSegment LText a Source # 
Instance details

Defined in Exon.Class.ToSegment

Methods

toSegment :: LText -> a Source #

IsString a => ToSegment Text a Source # 
Instance details

Defined in Exon.Class.ToSegment

Methods

toSegment :: Text -> a Source #

IsString a => ToSegment String a Source # 
Instance details

Defined in Exon.Class.ToSegment

Methods

toSegment :: String -> a Source #

(IsNewtype a wrapped, NewtypeSegment wrapped a b) => ToSegment a b Source # 
Instance details

Defined in Exon.Class.ToSegment

Methods

toSegment :: a -> b Source #

newtype SkipWs a Source #

Wrapping a quote type with this causes whitespace to be ignored.

Since: 1.0.0.0

Constructors

SkipWs a 

Instances

Instances details
IsString a => IsString (SkipWs a) Source # 
Instance details

Defined in Exon.SkipWs

Methods

fromString :: String -> SkipWs a #

Generic (SkipWs a) Source # 
Instance details

Defined in Exon.SkipWs

Associated Types

type Rep (SkipWs a) :: Type -> Type #

Methods

from :: SkipWs a -> Rep (SkipWs a) x #

to :: Rep (SkipWs a) x -> SkipWs a #

Show a => Show (SkipWs a) Source # 
Instance details

Defined in Exon.SkipWs

Methods

showsPrec :: Int -> SkipWs a -> ShowS #

show :: SkipWs a -> String #

showList :: [SkipWs a] -> ShowS #

Eq a => Eq (SkipWs a) Source # 
Instance details

Defined in Exon.SkipWs

Methods

(==) :: SkipWs a -> SkipWs a -> Bool #

(/=) :: SkipWs a -> SkipWs a -> Bool #

IsString builder => ExonString (SkipWs result) builder Source #

The instance used when the result type is wrapped in SkipWs, which is done by intron.

It returns Empty for any whitespace.

Instance details

Defined in Exon.SkipWs

Methods

exonString :: String -> Result builder Source #

exonWhitespace :: String -> Result builder Source #

type Rep (SkipWs a) Source # 
Instance details

Defined in Exon.SkipWs

type Rep (SkipWs a) = D1 ('MetaData "SkipWs" "Exon.SkipWs" "exon-1.4.0.0-5H9MxWpqWGo2etxOZGQCuj" 'True) (C1 ('MetaCons "SkipWs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

skipWs :: SkipWs a -> a Source #

Defined separately because TH chokes on the selector.

Since: 1.0.0.0

newtype ExonUse a Source #

Wrapping a quote type with this causes a to be used irrespective of whether it is an unwrappable newtype.

Since: 1.0.0.0

Constructors

ExonUse 

Fields

Instances

Instances details
IsString a => IsString (ExonUse a) Source # 
Instance details

Defined in Exon.Class.Exon

Methods

fromString :: String -> ExonUse a #

Show a => Show (ExonUse a) Source # 
Instance details

Defined in Exon.Class.Exon

Methods

showsPrec :: Int -> ExonUse a -> ShowS #

show :: ExonUse a -> String #

showList :: [ExonUse a] -> ShowS #

Eq a => Eq (ExonUse a) Source # 
Instance details

Defined in Exon.Class.Exon

Methods

(==) :: ExonUse a -> ExonUse a -> Bool #

(/=) :: ExonUse a -> ExonUse a -> Bool #

ExonBuilder a builder => ExonBuilder (ExonUse a) builder Source # 
Instance details

Defined in Exon.Class.Exon

Methods

exonBuilder :: ExonUse a -> builder Source #

exonBuilderExtract :: Result builder -> ExonUse a Source #

Type inference

The type of an expression segment is usually known, for example when the interpolated value is an argument of the enclosing function:

>>> f :: Text -> Text; f t = [exon|value: #{t}|]
>>> f "snake"
"value: snake"

Here both the interpolated expression and the quote's result type are known.

However, expressions may be polymorphic:

>>> t :: IsString a => a; t = "snake"
>>> f :: Text; f = [exon|value: #{t}|]
>>> f
"value: snake"

The quasiquote parser turns this into the expression:

[Segment.String "value: ", Segment.Expression t] :: Text

The list of segments has the known type Text, obtained from the type signature of f. In this case, the type of t is instantiated as Text as well, causing no type inference problems.

However, if the quote is used polymorphically as well, as in:

printThing :: Show a => a -> IO ()
printThing [exon|value: #{t}|]

the type of the segment list would be ∀ a . IsString => [a], which would not be possible to concatenate, so t must be annotated.

Since the segment list is typechecked like any other expression, an expression segment with known type will determine the result type of an otherwise polymorphic quote:

>>> newtype Str = Str Text deriving stock (Show) deriving newtype (IsString, Semigroup, Monoid)
>>> [exon|pre #{"x" :: Str} post|]
Str "pre x post"

The result type is unambiguously fixed to Str.

Combinators

intercalate :: Monoid a => Foldable t => a -> t a -> a Source #

Monoidally combine all elements in the list, appending the separator between each pair of elements.

Data Types

data Segment a Source #

The parts of an interpolation quasiquote. Text is split at each whitespace and interpolation splice marked by #{ and }.

Instances

Instances details
Functor Segment Source # 
Instance details

Defined in Exon.Data.Segment

Methods

fmap :: (a -> b) -> Segment a -> Segment b #

(<$) :: a -> Segment b -> Segment a #

IsString (Segment a) Source # 
Instance details

Defined in Exon.Data.Segment

Methods

fromString :: String -> Segment a #

Show a => Show (Segment a) Source # 
Instance details

Defined in Exon.Data.Segment

Methods

showsPrec :: Int -> Segment a -> ShowS #

show :: Segment a -> String #

showList :: [Segment a] -> ShowS #

Eq a => Eq (Segment a) Source # 
Instance details

Defined in Exon.Data.Segment

Methods

(==) :: Segment a -> Segment a -> Bool #

(/=) :: Segment a -> Segment a -> Bool #

data Result a Source #

The combined segments, either empty or a value.

Constructors

Empty 
Result a 

Instances

Instances details
Foldable Result Source # 
Instance details

Defined in Exon.Data.Result

Methods

fold :: Monoid m => Result m -> m #

foldMap :: Monoid m => (a -> m) -> Result a -> m #

foldMap' :: Monoid m => (a -> m) -> Result a -> m #

foldr :: (a -> b -> b) -> b -> Result a -> b #

foldr' :: (a -> b -> b) -> b -> Result a -> b #

foldl :: (b -> a -> b) -> b -> Result a -> b #

foldl' :: (b -> a -> b) -> b -> Result a -> b #

foldr1 :: (a -> a -> a) -> Result a -> a #

foldl1 :: (a -> a -> a) -> Result a -> a #

toList :: Result a -> [a] #

null :: Result a -> Bool #

length :: Result a -> Int #

elem :: Eq a => a -> Result a -> Bool #

maximum :: Ord a => Result a -> a #

minimum :: Ord a => Result a -> a #

sum :: Num a => Result a -> a #

product :: Num a => Result a -> a #

Semigroup (Result a) => Monoid (Result a) Source # 
Instance details

Defined in Exon.Data.Result

Methods

mempty :: Result a #

mappend :: Result a -> Result a -> Result a #

mconcat :: [Result a] -> Result a #

Semigroup a => Semigroup (Result a) Source # 
Instance details

Defined in Exon.Data.Result

Methods

(<>) :: Result a -> Result a -> Result a #

sconcat :: NonEmpty (Result a) -> Result a #

stimes :: Integral b => b -> Result a -> Result a #

Show a => Show (Result a) Source # 
Instance details

Defined in Exon.Data.Result

Methods

showsPrec :: Int -> Result a -> ShowS #

show :: Result a -> String #

showList :: [Result a] -> ShowS #

Eq a => Eq (Result a) Source # 
Instance details

Defined in Exon.Data.Result

Methods

(==) :: Result a -> Result a -> Bool #

(/=) :: Result a -> Result a -> Bool #