exon-0.1.1.0: Monoidal Quasiquote Interpolation
Safe HaskellNone
LanguageHaskell2010

Exon.Class.Exon

Description

 
Synopsis

Documentation

data ExonDefault Source #

Instances

Instances details
(Monoid a, IsString a) => Exon ExonDefault a Source # 
Instance details

Defined in Exon.Class.Exon

Exon ExonDefault String Source # 
Instance details

Defined in Exon.Class.Exon

Exon ExonDefault ByteString Source # 
Instance details

Defined in Exon.Class.Exon

Exon ExonDefault Text Source # 
Instance details

Defined in Exon.Class.Exon

Exon ExonDefault LByteString Source # 
Instance details

Defined in Exon.Class.Exon

Exon ExonDefault LText Source # 
Instance details

Defined in Exon.Class.Exon

Exon ExonDefault (String -> String) Source # 
Instance details

Defined in Exon.Class.Exon

class Exon (tag :: Type) (a :: Type) where Source #

This class is responsible for combining segments of an interpolated string, allowing users to define their own rules for how the result is constructed. The default implementation converts each literal part with IsString and uses the result type's Monoid to concatenate them.

The raw parts are encoded as Segment, getting combined into a Result.

The default for convertSegment skips whitespace by encoding it into the Result constructor Empty, which is a unit object. To change this behavior, it can be easily overridden:

newtype Thing = Thing String deriving newtype (IsString, Semigroup, Monoid, Show)

instance Exon ExonDefault Thing where
  convertSegment = case
    Segment.String s -> Result (Thing s)
    Segment.Expression thing -> Result thing
    Segment.Whitespace _ -> Result (Thing " >>> ")

  insertWhitespace s1 ws s2 =
    appendSegment ExonDefault (appendSegment ExonDefault s1 (Segment.Whitespace ws)) s2

Minimal complete definition

Nothing

Methods

isEmpty :: a -> Bool Source #

This check is used to allow empty expression segments to be skipped when they are empty. The default is to never skip expressions.

convertSegment :: Segment a -> Result a Source #

Convert a Segment to a Result. The default implementation uses IsString and ignores whitespace, returning Empty.

default convertSegment :: IsString a => Segment a -> Result a Source #

appendSegment :: Result a -> Segment a -> Result a Source #

Append a Segment to a Result. The default implementation uses (<>).

default appendSegment :: Semigroup a => Result a -> Segment a -> Result a Source #

insertWhitespace :: Result a -> String -> Segment a -> Result a Source #

Append whitespace and a Segment to a Result, i.e. joining two parts of the interpolation by whitespace. The default implementation ignores the whitespace, calling appendSegment with the second argument.

default insertWhitespace :: Result a -> String -> Segment a -> Result a Source #

concatSegments :: NonEmpty (Segment a) -> a Source #

The entry point for concatenation, taking a list of segments parsed from the interpolation. The default implementation skips leading whitespace and calls appendSegment and insertWhitespace to concatenate.

default concatSegments :: Monoid a => NonEmpty (Segment a) -> a Source #

Instances

Instances details
(Monoid a, IsString a) => Exon ExonDefault a Source # 
Instance details

Defined in Exon.Class.Exon

Exon ExonDefault String Source # 
Instance details

Defined in Exon.Class.Exon

Exon ExonDefault ByteString Source # 
Instance details

Defined in Exon.Class.Exon

Exon ExonDefault Text Source # 
Instance details

Defined in Exon.Class.Exon

Exon ExonDefault LByteString Source # 
Instance details

Defined in Exon.Class.Exon

Exon ExonDefault LText Source # 
Instance details

Defined in Exon.Class.Exon

Exon ExonDefault (String -> String) Source # 
Instance details

Defined in Exon.Class.Exon

concatKeepWs :: forall tag a. Monoid a => Exon tag a => NonEmpty (Segment a) -> a Source #