{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
#if MIN_VERSION_text(0,9,0)
{-# LANGUAGE TemplateHaskell #-}
#endif
{-# OPTIONS_GHC -fno-warn-deprecations #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module TextShow.Data.Text () where
import qualified Data.Text as TS
import Data.Text.Encoding.Error (UnicodeException(..))
import qualified Data.Text.Lazy as TL
import Data.Text.Lazy.Builder (Builder, fromString, toLazyText)
import Prelude ()
import Prelude.Compat
import TextShow.Classes (TextShow(..))
import TextShow.Data.Char (showbString)
import TextShow.Data.Integral (showbHex)
import TextShow.TH.Internal (deriveTextShow)
#if MIN_VERSION_text(1,0,0)
import Data.Text.Encoding (Decoding(..))
import Data.Text.Lazy.Builder (singleton)
import GHC.Show (appPrec)
import TextShow.Classes (showbParen)
import TextShow.Data.ByteString ()
#endif
#if MIN_VERSION_text(1,1,0)
import Data.Text.Internal.Fusion.Size (Size)
#endif
instance TextShow TS.Text where
showb :: Text -> Builder
showb = String -> Builder
showbString forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
TS.unpack
{-# INLINE showb #-}
instance TextShow TL.Text where
showb :: Text -> Builder
showb = String -> Builder
showbString forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
TL.unpack
{-# INLINE showb #-}
instance TextShow Builder where
showb :: Builder -> Builder
showb = forall a. TextShow a => a -> Builder
showb forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
toLazyText
{-# INLINE showb #-}
instance TextShow UnicodeException where
showb :: UnicodeException -> Builder
showb (DecodeError String
desc (Just Word8
w))
= Builder
"Cannot decode byte '\\x" forall a. Semigroup a => a -> a -> a
<> forall a. (Integral a, TextShow a) => a -> Builder
showbHex Word8
w forall a. Semigroup a => a -> a -> a
<> Builder
"': " forall a. Semigroup a => a -> a -> a
<> String -> Builder
fromString String
desc
showb (DecodeError String
desc Maybe Word8
Nothing)
= Builder
"Cannot decode input: " forall a. Semigroup a => a -> a -> a
<> String -> Builder
fromString String
desc
showb (EncodeError String
desc (Just Char
c))
= Builder
"Cannot encode character '\\x" forall a. Semigroup a => a -> a -> a
<> forall a. (Integral a, TextShow a) => a -> Builder
showbHex (forall a. Enum a => a -> Int
fromEnum Char
c) forall a. Semigroup a => a -> a -> a
<> Builder
"': " forall a. Semigroup a => a -> a -> a
<> String -> Builder
fromString String
desc
showb (EncodeError String
desc Maybe Char
Nothing)
= Builder
"Cannot encode input: " forall a. Semigroup a => a -> a -> a
<> String -> Builder
fromString String
desc
#if MIN_VERSION_text(1,0,0)
instance TextShow Decoding where
showbPrec :: Int -> Decoding -> Builder
showbPrec Int
p (Some Text
t ByteString
bs ByteString -> Decoding
_) = Bool -> Builder -> Builder
showbParen (Int
p forall a. Ord a => a -> a -> Bool
> Int
appPrec) forall a b. (a -> b) -> a -> b
$
Builder
"Some " forall a. Semigroup a => a -> a -> a
<> forall a. TextShow a => a -> Builder
showb Text
t forall a. Semigroup a => a -> a -> a
<>
Char -> Builder
singleton Char
' ' forall a. Semigroup a => a -> a -> a
<> forall a. TextShow a => a -> Builder
showb ByteString
bs forall a. Semigroup a => a -> a -> a
<>
Builder
" _"
{-# INLINE showbPrec #-}
#endif
#if MIN_VERSION_text(1,1,0)
$(deriveTextShow ''Size)
#endif