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

Exon.Quote

Description

 
Synopsis

Documentation

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

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"

exun :: QuasiQuoter Source #

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

Since: 1.0.0.0

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

exonSegments :: QuasiQuoter Source #

Internal debugging quoter that produces the raw segments.

Since: 1.0.0.0