{-# OPTIONS -Wno-orphans #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PackageImports #-}
{-# LANGUAGE Strict #-}
{-# LANGUAGE TypeFamilies #-}
module Data.String.Interpolate.Conversion.ByteStringSink
()
where
import Data.Text.Conversions
import qualified Data.ByteString as B
import qualified Data.ByteString.Builder as LB
import qualified Data.ByteString.Lazy as LB
import qualified Data.Text as T
import qualified Data.Text.Lazy as LT hiding ( singleton )
import qualified Data.Text.Lazy.Builder as LT
import Data.String.Interpolate.Conversion.Classes
import Data.String.Interpolate.Conversion.Encoding ( encodeCharUTF8 )
#ifdef BYTESTRING_BUILDER
instance InterpSink 'True B.ByteString where
type Builder 'True B.ByteString = LB.Builder
ofString _ = B . LB.byteString . unUTF8 . convertText
build _ (B l) (B r) = B $ l `mappend` r
finalize _ = LB.toStrict . LB.toLazyByteString . unB
instance InterpSink 'True LB.ByteString where
type Builder 'True LB.ByteString = LB.Builder
ofString _ = B . LB.lazyByteString . unUTF8 . convertText
build _ (B l) (B r) = B $ l `mappend` r
finalize _ = LB.toLazyByteString . unB
#else
instance InterpSink 'True B.ByteString where
type Builder 'True B.ByteString = B.ByteString
ofString :: Proxy 'True -> String -> B ByteString (Builder 'True ByteString)
ofString Proxy 'True
_ = ByteString -> B ByteString ByteString
forall dst a. a -> B dst a
B (ByteString -> B ByteString ByteString)
-> (String -> ByteString) -> String -> B ByteString ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTF8 ByteString -> ByteString
forall a. UTF8 a -> a
unUTF8 (UTF8 ByteString -> ByteString)
-> (String -> UTF8 ByteString) -> String -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> UTF8 ByteString
forall a b. (ToText a, FromText b) => a -> b
convertText
build :: Proxy 'True
-> B ByteString (Builder 'True ByteString)
-> B ByteString (Builder 'True ByteString)
-> B ByteString (Builder 'True ByteString)
build Proxy 'True
_ (B Builder 'True ByteString
l) (B Builder 'True ByteString
r) = ByteString -> B ByteString ByteString
forall dst a. a -> B dst a
B (ByteString -> B ByteString ByteString)
-> ByteString -> B ByteString ByteString
forall a b. (a -> b) -> a -> b
$ ByteString
Builder 'True ByteString
l ByteString -> ByteString -> ByteString
forall a. Monoid a => a -> a -> a
`mappend` ByteString
Builder 'True ByteString
r
finalize :: Proxy 'True
-> B ByteString (Builder 'True ByteString) -> ByteString
finalize Proxy 'True
_ = B ByteString (Builder 'True ByteString) -> ByteString
forall dst a. B dst a -> a
unB
instance InterpSink 'True LB.ByteString where
type Builder 'True LB.ByteString = LB.ByteString
ofString :: Proxy 'True -> String -> B ByteString (Builder 'True ByteString)
ofString Proxy 'True
_ = ByteString -> B ByteString ByteString
forall dst a. a -> B dst a
B (ByteString -> B ByteString ByteString)
-> (String -> ByteString) -> String -> B ByteString ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTF8 ByteString -> ByteString
forall a. UTF8 a -> a
unUTF8 (UTF8 ByteString -> ByteString)
-> (String -> UTF8 ByteString) -> String -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> UTF8 ByteString
forall a b. (ToText a, FromText b) => a -> b
convertText
build :: Proxy 'True
-> B ByteString (Builder 'True ByteString)
-> B ByteString (Builder 'True ByteString)
-> B ByteString (Builder 'True ByteString)
build Proxy 'True
_ (B Builder 'True ByteString
l) (B Builder 'True ByteString
r) = ByteString -> B ByteString ByteString
forall dst a. a -> B dst a
B (ByteString -> B ByteString ByteString)
-> ByteString -> B ByteString ByteString
forall a b. (a -> b) -> a -> b
$ ByteString
Builder 'True ByteString
l ByteString -> ByteString -> ByteString
forall a. Monoid a => a -> a -> a
`mappend` ByteString
Builder 'True ByteString
r
finalize :: Proxy 'True
-> B ByteString (Builder 'True ByteString) -> ByteString
finalize Proxy 'True
_ = B ByteString (Builder 'True ByteString) -> ByteString
forall dst a. B dst a -> a
unB
#endif
instance InterpSink 'True LB.Builder where
type Builder 'True LB.Builder = LB.Builder
ofString :: Proxy 'True -> String -> B Builder (Builder 'True Builder)
ofString Proxy 'True
_ = Builder -> B Builder Builder
forall dst a. a -> B dst a
B (Builder -> B Builder Builder)
-> (String -> Builder) -> String -> B Builder Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Builder
LB.lazyByteString (ByteString -> Builder)
-> (String -> ByteString) -> String -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTF8 ByteString -> ByteString
forall a. UTF8 a -> a
unUTF8 (UTF8 ByteString -> ByteString)
-> (String -> UTF8 ByteString) -> String -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> UTF8 ByteString
forall a b. (ToText a, FromText b) => a -> b
convertText
build :: Proxy 'True
-> B Builder (Builder 'True Builder)
-> B Builder (Builder 'True Builder)
-> B Builder (Builder 'True Builder)
build Proxy 'True
_ (B Builder 'True Builder
l) (B Builder 'True Builder
r) = Builder -> B Builder Builder
forall dst a. a -> B dst a
B (Builder -> B Builder Builder) -> Builder -> B Builder Builder
forall a b. (a -> b) -> a -> b
$ Builder
Builder 'True Builder
l Builder -> Builder -> Builder
forall a. Monoid a => a -> a -> a
`mappend` Builder
Builder 'True Builder
r
finalize :: Proxy 'True -> B Builder (Builder 'True Builder) -> Builder
finalize Proxy 'True
_ = B Builder (Builder 'True Builder) -> Builder
forall dst a. B dst a -> a
unB
#ifdef BYTESTRING_BUILDER
instance {-# OVERLAPPABLE #-} Show src => Interpolatable 'True src B.ByteString where
interpolate _ = B . LB.byteString . unUTF8 . convertText . show
instance {-# OVERLAPS #-} Interpolatable 'True Char B.ByteString where
interpolate _ = B . encodeCharUTF8
instance {-# OVERLAPS #-} Interpolatable 'True String B.ByteString where
interpolate _ = B . LB.byteString . unUTF8 . convertText
instance {-# OVERLAPS #-} Interpolatable 'True T.Text B.ByteString where
interpolate _ = B . LB.byteString . unUTF8 . convertText
instance {-# OVERLAPS #-} Interpolatable 'True LT.Text B.ByteString where
interpolate _ = B . LB.byteString . unUTF8 . convertText
instance {-# OVERLAPS #-} Interpolatable 'True LT.Builder B.ByteString where
interpolate _ = B . LB.byteString . unUTF8 . convertText . LT.toLazyText
instance {-# OVERLAPS #-} Interpolatable 'True B.ByteString B.ByteString where
interpolate _ = B . LB.byteString
instance {-# OVERLAPS #-} Interpolatable 'True LB.ByteString B.ByteString where
interpolate _ = B . LB.lazyByteString
instance {-# OVERLAPS #-} Interpolatable 'True LB.Builder B.ByteString where
interpolate _ = B
instance {-# OVERLAPPABLE #-} Show src => Interpolatable 'True src LB.ByteString where
interpolate _ = B . LB.lazyByteString . unUTF8 . convertText . show
instance {-# OVERLAPS #-} Interpolatable 'True Char LB.ByteString where
interpolate _ = B . encodeCharUTF8
instance {-# OVERLAPS #-} Interpolatable 'True String LB.ByteString where
interpolate _ = B . LB.lazyByteString . unUTF8 . convertText
instance {-# OVERLAPS #-} Interpolatable 'True T.Text LB.ByteString where
interpolate _ = B . LB.lazyByteString . unUTF8 . convertText
instance {-# OVERLAPS #-} Interpolatable 'True LT.Text LB.ByteString where
interpolate _ = B . LB.lazyByteString . unUTF8 . convertText
instance {-# OVERLAPS #-} Interpolatable 'True LT.Builder LB.ByteString where
interpolate _ = B . LB.lazyByteString . unUTF8 . convertText . LT.toLazyText
instance {-# OVERLAPS #-} Interpolatable 'True B.ByteString LB.ByteString where
interpolate _ = B . LB.byteString
instance {-# OVERLAPS #-} Interpolatable 'True LB.ByteString LB.ByteString where
interpolate _ = B . LB.lazyByteString
instance {-# OVERLAPS #-} Interpolatable 'True LB.Builder LB.ByteString where
interpolate _ = B
#else
instance {-# OVERLAPPABLE #-} Show src => Interpolatable 'True src B.ByteString where
interpolate :: Proxy 'True -> src -> B ByteString (Builder 'True ByteString)
interpolate Proxy 'True
_ = ByteString -> B ByteString ByteString
forall dst a. a -> B dst a
B (ByteString -> B ByteString ByteString)
-> (src -> ByteString) -> src -> B ByteString ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTF8 ByteString -> ByteString
forall a. UTF8 a -> a
unUTF8 (UTF8 ByteString -> ByteString)
-> (src -> UTF8 ByteString) -> src -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> UTF8 ByteString
forall a b. (ToText a, FromText b) => a -> b
convertText (String -> UTF8 ByteString)
-> (src -> String) -> src -> UTF8 ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. src -> String
forall a. Show a => a -> String
show
instance {-# OVERLAPS #-} Interpolatable 'True Char B.ByteString where
interpolate :: Proxy 'True -> Char -> B ByteString (Builder 'True ByteString)
interpolate Proxy 'True
_ = ByteString -> B ByteString ByteString
forall dst a. a -> B dst a
B (ByteString -> B ByteString ByteString)
-> (Char -> ByteString) -> Char -> B ByteString ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
LB.toStrict (ByteString -> ByteString)
-> (Char -> ByteString) -> Char -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> ByteString
LB.toLazyByteString (Builder -> ByteString) -> (Char -> Builder) -> Char -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Builder
encodeCharUTF8
instance {-# OVERLAPS #-} Interpolatable 'True String B.ByteString where
interpolate :: Proxy 'True -> String -> B ByteString (Builder 'True ByteString)
interpolate Proxy 'True
_ = ByteString -> B ByteString ByteString
forall dst a. a -> B dst a
B (ByteString -> B ByteString ByteString)
-> (String -> ByteString) -> String -> B ByteString ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTF8 ByteString -> ByteString
forall a. UTF8 a -> a
unUTF8 (UTF8 ByteString -> ByteString)
-> (String -> UTF8 ByteString) -> String -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> UTF8 ByteString
forall a b. (ToText a, FromText b) => a -> b
convertText
instance {-# OVERLAPS #-} Interpolatable 'True T.Text B.ByteString where
interpolate :: Proxy 'True -> Text -> B ByteString (Builder 'True ByteString)
interpolate Proxy 'True
_ = ByteString -> B ByteString ByteString
forall dst a. a -> B dst a
B (ByteString -> B ByteString ByteString)
-> (Text -> ByteString) -> Text -> B ByteString ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTF8 ByteString -> ByteString
forall a. UTF8 a -> a
unUTF8 (UTF8 ByteString -> ByteString)
-> (Text -> UTF8 ByteString) -> Text -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> UTF8 ByteString
forall a b. (ToText a, FromText b) => a -> b
convertText
instance {-# OVERLAPS #-} Interpolatable 'True LT.Text B.ByteString where
interpolate :: Proxy 'True -> Text -> B ByteString (Builder 'True ByteString)
interpolate Proxy 'True
_ = ByteString -> B ByteString ByteString
forall dst a. a -> B dst a
B (ByteString -> B ByteString ByteString)
-> (Text -> ByteString) -> Text -> B ByteString ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTF8 ByteString -> ByteString
forall a. UTF8 a -> a
unUTF8 (UTF8 ByteString -> ByteString)
-> (Text -> UTF8 ByteString) -> Text -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> UTF8 ByteString
forall a b. (ToText a, FromText b) => a -> b
convertText
instance {-# OVERLAPS #-} Interpolatable 'True LT.Builder B.ByteString where
interpolate :: Proxy 'True -> Builder -> B ByteString (Builder 'True ByteString)
interpolate Proxy 'True
_ = ByteString -> B ByteString ByteString
forall dst a. a -> B dst a
B (ByteString -> B ByteString ByteString)
-> (Builder -> ByteString) -> Builder -> B ByteString ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTF8 ByteString -> ByteString
forall a. UTF8 a -> a
unUTF8 (UTF8 ByteString -> ByteString)
-> (Builder -> UTF8 ByteString) -> Builder -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> UTF8 ByteString
forall a b. (ToText a, FromText b) => a -> b
convertText (Text -> UTF8 ByteString)
-> (Builder -> Text) -> Builder -> UTF8 ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
LT.toLazyText
instance {-# OVERLAPS #-} Interpolatable 'True B.ByteString B.ByteString where
interpolate :: Proxy 'True
-> ByteString -> B ByteString (Builder 'True ByteString)
interpolate Proxy 'True
_ = ByteString -> B ByteString (Builder 'True ByteString)
forall dst a. a -> B dst a
B
instance {-# OVERLAPS #-} Interpolatable 'True LB.ByteString B.ByteString where
interpolate :: Proxy 'True
-> ByteString -> B ByteString (Builder 'True ByteString)
interpolate Proxy 'True
_ = ByteString -> B ByteString ByteString
forall dst a. a -> B dst a
B (ByteString -> B ByteString ByteString)
-> (ByteString -> ByteString)
-> ByteString
-> B ByteString ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
LB.toStrict
instance {-# OVERLAPS #-} Interpolatable 'True LB.Builder B.ByteString where
interpolate :: Proxy 'True -> Builder -> B ByteString (Builder 'True ByteString)
interpolate Proxy 'True
_ = ByteString -> B ByteString ByteString
forall dst a. a -> B dst a
B (ByteString -> B ByteString ByteString)
-> (Builder -> ByteString) -> Builder -> B ByteString ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
LB.toStrict (ByteString -> ByteString)
-> (Builder -> ByteString) -> Builder -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> ByteString
LB.toLazyByteString
instance {-# OVERLAPPABLE #-} Show src => Interpolatable 'True src LB.ByteString where
interpolate :: Proxy 'True -> src -> B ByteString (Builder 'True ByteString)
interpolate Proxy 'True
_ = ByteString -> B ByteString ByteString
forall dst a. a -> B dst a
B (ByteString -> B ByteString ByteString)
-> (src -> ByteString) -> src -> B ByteString ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTF8 ByteString -> ByteString
forall a. UTF8 a -> a
unUTF8 (UTF8 ByteString -> ByteString)
-> (src -> UTF8 ByteString) -> src -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> UTF8 ByteString
forall a b. (ToText a, FromText b) => a -> b
convertText (String -> UTF8 ByteString)
-> (src -> String) -> src -> UTF8 ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. src -> String
forall a. Show a => a -> String
show
instance {-# OVERLAPS #-} Interpolatable 'True Char LB.ByteString where
interpolate :: Proxy 'True -> Char -> B ByteString (Builder 'True ByteString)
interpolate Proxy 'True
_ = ByteString -> B ByteString ByteString
forall dst a. a -> B dst a
B (ByteString -> B ByteString ByteString)
-> (Char -> ByteString) -> Char -> B ByteString ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> ByteString
LB.toLazyByteString (Builder -> ByteString) -> (Char -> Builder) -> Char -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Builder
encodeCharUTF8
instance {-# OVERLAPS #-} Interpolatable 'True String LB.ByteString where
interpolate :: Proxy 'True -> String -> B ByteString (Builder 'True ByteString)
interpolate Proxy 'True
_ = ByteString -> B ByteString ByteString
forall dst a. a -> B dst a
B (ByteString -> B ByteString ByteString)
-> (String -> ByteString) -> String -> B ByteString ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTF8 ByteString -> ByteString
forall a. UTF8 a -> a
unUTF8 (UTF8 ByteString -> ByteString)
-> (String -> UTF8 ByteString) -> String -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> UTF8 ByteString
forall a b. (ToText a, FromText b) => a -> b
convertText
instance {-# OVERLAPS #-} Interpolatable 'True T.Text LB.ByteString where
interpolate :: Proxy 'True -> Text -> B ByteString (Builder 'True ByteString)
interpolate Proxy 'True
_ = ByteString -> B ByteString ByteString
forall dst a. a -> B dst a
B (ByteString -> B ByteString ByteString)
-> (Text -> ByteString) -> Text -> B ByteString ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTF8 ByteString -> ByteString
forall a. UTF8 a -> a
unUTF8 (UTF8 ByteString -> ByteString)
-> (Text -> UTF8 ByteString) -> Text -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> UTF8 ByteString
forall a b. (ToText a, FromText b) => a -> b
convertText
instance {-# OVERLAPS #-} Interpolatable 'True LT.Text LB.ByteString where
interpolate :: Proxy 'True -> Text -> B ByteString (Builder 'True ByteString)
interpolate Proxy 'True
_ = ByteString -> B ByteString ByteString
forall dst a. a -> B dst a
B (ByteString -> B ByteString ByteString)
-> (Text -> ByteString) -> Text -> B ByteString ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTF8 ByteString -> ByteString
forall a. UTF8 a -> a
unUTF8 (UTF8 ByteString -> ByteString)
-> (Text -> UTF8 ByteString) -> Text -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> UTF8 ByteString
forall a b. (ToText a, FromText b) => a -> b
convertText
instance {-# OVERLAPS #-} Interpolatable 'True LT.Builder LB.ByteString where
interpolate :: Proxy 'True -> Builder -> B ByteString (Builder 'True ByteString)
interpolate Proxy 'True
_ = ByteString -> B ByteString ByteString
forall dst a. a -> B dst a
B (ByteString -> B ByteString ByteString)
-> (Builder -> ByteString) -> Builder -> B ByteString ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTF8 ByteString -> ByteString
forall a. UTF8 a -> a
unUTF8 (UTF8 ByteString -> ByteString)
-> (Builder -> UTF8 ByteString) -> Builder -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> UTF8 ByteString
forall a b. (ToText a, FromText b) => a -> b
convertText (Text -> UTF8 ByteString)
-> (Builder -> Text) -> Builder -> UTF8 ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
LT.toLazyText
instance {-# OVERLAPS #-} Interpolatable 'True B.ByteString LB.ByteString where
interpolate :: Proxy 'True
-> ByteString -> B ByteString (Builder 'True ByteString)
interpolate Proxy 'True
_ = ByteString -> B ByteString ByteString
forall dst a. a -> B dst a
B (ByteString -> B ByteString ByteString)
-> (ByteString -> ByteString)
-> ByteString
-> B ByteString ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
LB.fromStrict
instance {-# OVERLAPS #-} Interpolatable 'True LB.ByteString LB.ByteString where
interpolate :: Proxy 'True
-> ByteString -> B ByteString (Builder 'True ByteString)
interpolate Proxy 'True
_ = ByteString -> B ByteString (Builder 'True ByteString)
forall dst a. a -> B dst a
B
instance {-# OVERLAPS #-} Interpolatable 'True LB.Builder LB.ByteString where
interpolate :: Proxy 'True -> Builder -> B ByteString (Builder 'True ByteString)
interpolate Proxy 'True
_ = ByteString -> B ByteString ByteString
forall dst a. a -> B dst a
B (ByteString -> B ByteString ByteString)
-> (Builder -> ByteString) -> Builder -> B ByteString ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> ByteString
LB.toLazyByteString
#endif
instance {-# OVERLAPPABLE #-} Show src => Interpolatable 'True src LB.Builder where
interpolate :: Proxy 'True -> src -> B Builder (Builder 'True Builder)
interpolate Proxy 'True
_ = Builder -> B Builder Builder
forall dst a. a -> B dst a
B (Builder -> B Builder Builder)
-> (src -> Builder) -> src -> B Builder Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Builder
LB.lazyByteString (ByteString -> Builder) -> (src -> ByteString) -> src -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTF8 ByteString -> ByteString
forall a. UTF8 a -> a
unUTF8 (UTF8 ByteString -> ByteString)
-> (src -> UTF8 ByteString) -> src -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> UTF8 ByteString
forall a b. (ToText a, FromText b) => a -> b
convertText (String -> UTF8 ByteString)
-> (src -> String) -> src -> UTF8 ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. src -> String
forall a. Show a => a -> String
show
instance {-# OVERLAPS #-} Interpolatable 'True Char LB.Builder where
interpolate :: Proxy 'True -> Char -> B Builder (Builder 'True Builder)
interpolate Proxy 'True
_ = Builder -> B Builder Builder
forall dst a. a -> B dst a
B (Builder -> B Builder Builder)
-> (Char -> Builder) -> Char -> B Builder Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Builder
encodeCharUTF8
instance {-# OVERLAPS #-} Interpolatable 'True String LB.Builder where
interpolate :: Proxy 'True -> String -> B Builder (Builder 'True Builder)
interpolate Proxy 'True
_ = Builder -> B Builder Builder
forall dst a. a -> B dst a
B (Builder -> B Builder Builder)
-> (String -> Builder) -> String -> B Builder Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Builder
LB.lazyByteString (ByteString -> Builder)
-> (String -> ByteString) -> String -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTF8 ByteString -> ByteString
forall a. UTF8 a -> a
unUTF8 (UTF8 ByteString -> ByteString)
-> (String -> UTF8 ByteString) -> String -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> UTF8 ByteString
forall a b. (ToText a, FromText b) => a -> b
convertText
instance {-# OVERLAPS #-} Interpolatable 'True T.Text LB.Builder where
interpolate :: Proxy 'True -> Text -> B Builder (Builder 'True Builder)
interpolate Proxy 'True
_ = Builder -> B Builder Builder
forall dst a. a -> B dst a
B (Builder -> B Builder Builder)
-> (Text -> Builder) -> Text -> B Builder Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Builder
LB.lazyByteString (ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTF8 ByteString -> ByteString
forall a. UTF8 a -> a
unUTF8 (UTF8 ByteString -> ByteString)
-> (Text -> UTF8 ByteString) -> Text -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> UTF8 ByteString
forall a b. (ToText a, FromText b) => a -> b
convertText
instance {-# OVERLAPS #-} Interpolatable 'True LT.Text LB.Builder where
interpolate :: Proxy 'True -> Text -> B Builder (Builder 'True Builder)
interpolate Proxy 'True
_ = Builder -> B Builder Builder
forall dst a. a -> B dst a
B (Builder -> B Builder Builder)
-> (Text -> Builder) -> Text -> B Builder Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Builder
LB.lazyByteString (ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTF8 ByteString -> ByteString
forall a. UTF8 a -> a
unUTF8 (UTF8 ByteString -> ByteString)
-> (Text -> UTF8 ByteString) -> Text -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> UTF8 ByteString
forall a b. (ToText a, FromText b) => a -> b
convertText
instance {-# OVERLAPS #-} Interpolatable 'True LT.Builder LB.Builder where
interpolate :: Proxy 'True -> Builder -> B Builder (Builder 'True Builder)
interpolate Proxy 'True
_ = Builder -> B Builder Builder
forall dst a. a -> B dst a
B (Builder -> B Builder Builder)
-> (Builder -> Builder) -> Builder -> B Builder Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Builder
LB.lazyByteString (ByteString -> Builder)
-> (Builder -> ByteString) -> Builder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTF8 ByteString -> ByteString
forall a. UTF8 a -> a
unUTF8 (UTF8 ByteString -> ByteString)
-> (Builder -> UTF8 ByteString) -> Builder -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> UTF8 ByteString
forall a b. (ToText a, FromText b) => a -> b
convertText (Text -> UTF8 ByteString)
-> (Builder -> Text) -> Builder -> UTF8 ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
LT.toLazyText
instance {-# OVERLAPS #-} Interpolatable 'True B.ByteString LB.Builder where
interpolate :: Proxy 'True -> ByteString -> B Builder (Builder 'True Builder)
interpolate Proxy 'True
_ = Builder -> B Builder Builder
forall dst a. a -> B dst a
B (Builder -> B Builder Builder)
-> (ByteString -> Builder) -> ByteString -> B Builder Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Builder
LB.byteString
instance {-# OVERLAPS #-} Interpolatable 'True LB.ByteString LB.Builder where
interpolate :: Proxy 'True -> ByteString -> B Builder (Builder 'True Builder)
interpolate Proxy 'True
_ = Builder -> B Builder Builder
forall dst a. a -> B dst a
B (Builder -> B Builder Builder)
-> (ByteString -> Builder) -> ByteString -> B Builder Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Builder
LB.lazyByteString
instance {-# OVERLAPS #-} Interpolatable 'True LB.Builder LB.Builder where
interpolate :: Proxy 'True -> Builder -> B Builder (Builder 'True Builder)
interpolate Proxy 'True
_ = Builder -> B Builder (Builder 'True Builder)
forall dst a. a -> B dst a
B