#if MIN_VERSION_text(0,9,0)
#endif
module TextShow.Data.Text (
showbText
, showbTextLazy
, showbBuilder
, showbI16Prec
, showbUnicodeException
#if MIN_VERSION_text(1,0,0)
, showbDecodingPrec
#endif
#if MIN_VERSION_text(1,1,0)
, showbSizePrec
#endif
) where
import Data.Monoid.Compat ((<>))
import qualified Data.Text as TS
import Data.Text.Encoding.Error (UnicodeException(..))
import Data.Text.Foreign (I16)
import qualified Data.Text.Lazy as TL
import Data.Text.Lazy.Builder (Builder, fromString, toLazyText)
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 (showbByteStringStrict)
#endif
#if MIN_VERSION_text(1,1,0)
import Data.Text.Internal.Fusion.Size (Size)
#endif
#include "inline.h"
showbText :: TS.Text -> Builder
showbText = showbString . TS.unpack
showbTextLazy :: TL.Text -> Builder
showbTextLazy = showbString . TL.unpack
showbBuilder :: Builder -> Builder
showbBuilder = showbTextLazy . toLazyText
showbI16Prec :: Int -> I16 -> Builder
showbI16Prec = showbPrec
showbUnicodeException :: UnicodeException -> Builder
showbUnicodeException (DecodeError desc (Just w))
= "Cannot decode byte '\\x" <> showbHex w <> "': " <> fromString desc
showbUnicodeException (DecodeError desc Nothing)
= "Cannot decode input: " <> fromString desc
showbUnicodeException (EncodeError desc (Just c))
= "Cannot encode character '\\x" <> showbHex (fromEnum c) <> "': " <> fromString desc
showbUnicodeException (EncodeError desc Nothing)
= "Cannot encode input: " <> fromString desc
#if MIN_VERSION_text(1,0,0)
showbDecodingPrec :: Int -> Decoding -> Builder
showbDecodingPrec p (Some t bs _) = showbParen (p > appPrec) $
fromString "Some " <> showbText t <>
singleton ' ' <> showbByteStringStrict bs <>
fromString " _"
#endif
#if MIN_VERSION_text(1,1,0)
showbSizePrec :: Int -> Size -> Builder
showbSizePrec = showbPrec
#endif
instance TextShow TS.Text where
showb = showbText
INLINE_INST_FUN(showb)
instance TextShow TL.Text where
showb = showbTextLazy
INLINE_INST_FUN(showb)
instance TextShow Builder where
showb = showbBuilder
INLINE_INST_FUN(showb)
$(deriveTextShow ''I16)
instance TextShow UnicodeException where
showb = showbUnicodeException
INLINE_INST_FUN(showb)
#if MIN_VERSION_text(1,0,0)
instance TextShow Decoding where
showbPrec = showbDecodingPrec
INLINE_INST_FUN(showbPrec)
#endif
#if MIN_VERSION_text(1,1,0)
$(deriveTextShow ''Size)
#endif