{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PackageImports #-}
{-# LANGUAGE TypeFamilies #-}
module Data.String.Interpolate.Conversion where
import Data.Maybe ( fromMaybe )
import Data.Monoid ( (<>) )
import Data.Proxy
import Data.String ( IsString, fromString )
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 qualified "utf8-string" Data.ByteString.Lazy.UTF8 as LUTF8
import qualified "utf8-string" Data.ByteString.UTF8 as UTF8
import "base" Text.Read ( readMaybe )
import "base" Text.Show ( ShowS, showString )
newtype B dst a = B { unB :: a }
deriving (Eq, Show)
type family IsCustomSink dst where
IsCustomSink T.Text = 'True
IsCustomSink LT.Text = 'True
IsCustomSink B.ByteString = 'True
IsCustomSink LB.ByteString = 'True
IsCustomSink _ = 'False
class IsCustomSink dst ~ flag => InterpSink (flag :: Bool) dst where
type Builder flag dst :: *
ofString :: Proxy flag -> String -> B dst (Builder flag dst)
build :: Proxy flag -> B dst (Builder flag dst) -> B dst (Builder flag dst) -> B dst (Builder flag dst)
finalize :: Proxy flag -> B dst (Builder flag dst) -> dst
class InterpSink flag dst => Interpolatable (flag :: Bool) src dst where
interpolate :: Proxy flag -> src -> B dst (Builder flag dst)
instance (IsCustomSink str ~ 'False, IsString str) => InterpSink 'False str where
type Builder 'False str = ShowS
ofString _ = B . showString
build _ (B f) (B g) = B $ f . g
finalize _ = fromString . ($ "") . unB
instance InterpSink 'True T.Text where
type Builder 'True T.Text = LT.Builder
ofString _ = B . LT.fromString
build _ (B l) (B r) = B $ l <> r
finalize _ = LT.toStrict . LT.toLazyText . unB
instance InterpSink 'True LT.Text where
type Builder 'True LT.Text = LT.Builder
ofString _ = B . LT.fromString
build _ (B l) (B r) = B $ l <> r
finalize _ = LT.toLazyText . unB
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 <> 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 <> r
finalize _ = LB.toLazyByteString . unB
instance {-# OVERLAPPABLE #-} (Show src, IsString dst, IsCustomSink dst ~ 'False) => Interpolatable 'False src dst where
interpolate _ = B . shows
instance {-# OVERLAPS #-} (IsString dst, IsCustomSink dst ~ 'False) => Interpolatable 'False String dst where
interpolate _ = B . showString
instance {-# OVERLAPS #-} (IsString dst, IsCustomSink dst ~ 'False) => Interpolatable 'False T.Text dst where
interpolate _ = B . showString . T.unpack
instance {-# OVERLAPS #-} (IsString dst, IsCustomSink dst ~ 'False) => Interpolatable 'False LT.Text dst where
interpolate _ = B . showString . LT.unpack
instance {-# OVERLAPS #-} (IsString dst, IsCustomSink dst ~ 'False) => Interpolatable 'False B.ByteString dst where
interpolate _ = B . showString . UTF8.toString
instance {-# OVERLAPS #-} (IsString dst, IsCustomSink dst ~ 'False) => Interpolatable 'False LB.ByteString dst where
interpolate _ = B . showString . LUTF8.toString
instance {-# OVERLAPPABLE #-} Show src => Interpolatable 'True src T.Text where
interpolate _ = B . LT.fromString . show
instance {-# OVERLAPS #-} Interpolatable 'True String T.Text where
interpolate _ = B . LT.fromString
instance {-# OVERLAPS #-} Interpolatable 'True T.Text T.Text where
interpolate _ = B . LT.fromText
instance {-# OVERLAPS #-} Interpolatable 'True LT.Text T.Text where
interpolate _ = B . LT.fromLazyText
instance {-# OVERLAPS #-} Interpolatable 'True B.ByteString T.Text where
interpolate _ = B . bsToTextBuilder
instance {-# OVERLAPS #-} Interpolatable 'True LB.ByteString T.Text where
interpolate _ = B . lbsToTextBuilder
instance {-# OVERLAPPABLE #-} Show src => Interpolatable 'True src LT.Text where
interpolate _ = B . LT.fromString . show
instance {-# OVERLAPS #-} Interpolatable 'True String LT.Text where
interpolate _ = B . LT.fromString
instance {-# OVERLAPS #-} Interpolatable 'True T.Text LT.Text where
interpolate _ = B . LT.fromText
instance {-# OVERLAPS #-} Interpolatable 'True LT.Text LT.Text where
interpolate _ = B . LT.fromLazyText
instance {-# OVERLAPS #-} Interpolatable 'True B.ByteString LT.Text where
interpolate _ = B . bsToTextBuilder
instance {-# OVERLAPS #-} Interpolatable 'True LB.ByteString LT.Text where
interpolate _ = B . lbsToTextBuilder
instance {-# OVERLAPPABLE #-} Show src => Interpolatable 'True src B.ByteString where
interpolate _ = B . LB.byteString . unUTF8 . convertText . show
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 B.ByteString B.ByteString where
interpolate _ = B . LB.byteString
instance {-# OVERLAPS #-} Interpolatable 'True LB.ByteString B.ByteString where
interpolate _ = B . LB.lazyByteString
instance {-# OVERLAPPABLE #-} Show src => Interpolatable 'True src LB.ByteString where
interpolate _ = B . LB.lazyByteString . unUTF8 . convertText . show
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 B.ByteString LB.ByteString where
interpolate _ = B . LB.byteString
instance {-# OVERLAPS #-} Interpolatable 'True LB.ByteString LB.ByteString where
interpolate _ = B . LB.lazyByteString
bsToTextBuilder :: B.ByteString -> LT.Builder
bsToTextBuilder = UTF8.foldr (\char bldr -> LT.singleton char <> bldr) mempty
lbsToTextBuilder :: LB.ByteString -> LT.Builder
lbsToTextBuilder = LUTF8.foldr (\char bldr -> LT.singleton char <> bldr) mempty