Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- newtype SkipWs a = SkipWs a
- skipWs :: SkipWs a -> a
- newtype ExonUse a = ExonUse {
- exonUse :: a
- class ExonBuilder (inner :: Type) (builder :: Type) | inner -> builder where
- exonBuilder :: inner -> builder
- exonBuilderExtract :: Result builder -> inner
- class ExonString (result :: Type) (builder :: Type) where
- exonString :: String -> Result builder
- exonWhitespace :: String -> Result builder
- class ExonSegment (result :: Type) (builder :: Type) where
- exonSegment :: Segment builder -> Result builder
- class ExonAppend (result :: Type) (builder :: Type) where
- exonAppend :: builder -> builder -> Result builder
- exonAppendResult :: forall result builder. ExonAppend result builder => Result builder -> Result builder -> Result builder
- class ExonBuild (result :: Type) (inner :: Type) where
- class Exon (result :: Type) where
- exonProcess :: NonEmpty (Segment result) -> result
- exonProcessWith :: forall wrapped result. Exon wrapped => (result -> wrapped) -> (wrapped -> result) -> NonEmpty (Segment result) -> result
Documentation
Wrapping a quote type with this causes whitespace to be ignored.
Since: 1.0.0.0
SkipWs a |
Instances
IsString a => IsString (SkipWs a) Source # | |
Defined in Exon.Class.Exon fromString :: String -> SkipWs a # | |
Generic (SkipWs a) Source # | |
Show a => Show (SkipWs a) Source # | |
Eq a => Eq (SkipWs a) Source # | |
IsString builder => ExonString (SkipWs result) builder Source # | The instance used when the result type is wrapped in It returns |
Defined in Exon.Class.Exon exonString :: String -> Result builder Source # exonWhitespace :: String -> Result builder Source # | |
type Rep (SkipWs a) Source # | |
Defined in Exon.Class.Exon |
Wrapping a quote type with this causes a
to be used irrespective of whether it is an unwrappable newtype.
Since: 1.0.0.0
Instances
IsString a => IsString (ExonUse a) Source # | |
Defined in Exon.Class.Exon fromString :: String -> ExonUse a # | |
Show a => Show (ExonUse a) Source # | |
Eq a => Eq (ExonUse a) Source # | |
ExonBuilder a builder => ExonBuilder (ExonUse a) builder Source # | |
Defined in Exon.Class.Exon 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
exonBuilder :: inner -> builder Source #
Construct a builder from the newtype-unwrapped result type.
exonBuilderExtract :: Result builder -> inner Source #
Convert the result of the builder concatenation back to the newtype-unwrapped result type.
Instances
ExonBuilder ByteString Builder Source # | |
Defined in Exon.Class.Exon exonBuilder :: ByteString -> Builder Source # | |
ExonBuilder LByteString Builder Source # | |
Defined in Exon.Class.Exon | |
ExonBuilder LText Builder Source # | |
Defined in Exon.Class.Exon | |
ExonBuilder Text Builder Source # | |
Defined in Exon.Class.Exon | |
(Monoid builder, result ~ builder) => ExonBuilder result builder Source # | |
Defined in Exon.Class.Exon exonBuilder :: result -> builder Source # exonBuilderExtract :: Result builder -> result Source # | |
ExonBuilder a builder => ExonBuilder (ExonUse a) builder Source # | |
Defined in Exon.Class.Exon 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
(
), there is no instance of String
-> String
IsString
, so this class
provides an instance that works around that by calling showString
.
Since: 1.0.0.0
Nothing
exonString :: String -> Result builder Source #
Convert a String
to the builder type.
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
IsString a => ExonString result a Source # | |
Defined in Exon.Class.Exon exonString :: String -> Result a Source # exonWhitespace :: String -> Result a Source # | |
ExonString result (String -> String) Source # | The instance for the type used by |
Defined in Exon.Class.Exon | |
IsString builder => ExonString (SkipWs result) builder Source # | The instance used when the result type is wrapped in It returns |
Defined in Exon.Class.Exon exonString :: String -> Result builder Source # exonWhitespace :: String -> Result builder Source # |
class ExonSegment (result :: Type) (builder :: Type) where Source #
This class converts a Segment
to a builder.
The default implementation performs the following conversions for the differnet segment variants:
- Segment.String and Segment.Whitespace are plain
String
s parsed literally from the quasiquote. They are converted to the builder type byfromString
(handled byExonString
). - Segment.Whitespace is ignored when the quoter
intron
was used. - Segment.Expression contains a value of the builder type, which is returned as-is.
Since: 1.0.0.0
exonSegment :: Segment builder -> Result builder Source #
Convert literal string segments to the result type.
Instances
ExonString result builder => ExonSegment result builder Source # | |
Defined in Exon.Class.Exon exonSegment :: Segment builder -> 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
, the type
used by String
-> String
showsPrec
.
Since: 1.0.0.0
exonAppend :: builder -> builder -> Result builder Source #
Concatenate two segments of the builder type.
Instances
Semigroup builder => ExonAppend result builder Source # | |
Defined in Exon.Class.Exon exonAppend :: builder -> builder -> Result builder Source # | |
ExonAppend result (String -> String) Source # | |
exonAppendResult :: forall result builder. ExonAppend result builder => Result builder -> Result builder -> Result builder Source #
Wrapper for exonAppend
that handles the Empty
case.
Since: 1.0.0.0
class ExonBuild (result :: Type) (inner :: Type) where Source #
This class implements the Segment
concatenation logic.
- Each
Expression
is converted to the builder type byExonBuilder
. - Each
String
andWhitespace
is converted to the builder type byExonSegment
andExonString
. - The segments are folded over
ExonAppend
. - The result is converted from the builder type to the original type by
ExonBuilder
.
Each step may be overridden individually
Since: 1.0.0.0
Instances
(ExonAppend result builder, ExonSegment result builder, ExonBuilder inner builder) => ExonBuild result 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.
exonProcess :: NonEmpty (Segment result) -> result Source #
Concatenate a list of Segment
s.
Since: 1.0.0.0
Instances
(OverNewtypes result inner, ExonBuild result inner) => Exon result Source # | |
Defined in Exon.Class.Exon 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