exon-1.6.1.1: Customizable quasiquote interpolation
Safe HaskellSafe-Inferred
LanguageGHC2021

Exon.Class.Exon

Description

 
Synopsis

Documentation

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 a 

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 #

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 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 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 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 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 #

exonProcessWith :: forall wrapped result. Exon wrapped => (result -> wrapped) -> (wrapped -> result) -> NonEmpty (Segment result) -> result Source #

Call exonProcess, but unwrap the arguments and rewrap the result using the supplied functions.

Since: 1.0.0.0