{-|
Module      : Z.Data.Text.Builder
Description : UTF8 compatible builders.
Copyright   : (c) Dong Han, 2017-2019
License     : BSD
Maintainer  : winterland1989@gmail.com
Stability   : experimental
Portability : non-portable

This module re-exports some UTF8 compatible textual builders from 'Z.Data.Builder'.

We also provide a faster alternative to 'Show' class, i.e. 'ShowT', which can be deriving using 'Generic'.
For example to use 'ShowT' class:

@
{-# LANGUAGE DeriveGeneric, DeriveAnyClass, DerivingStrategies #-}

import qualified Z.Data.Text.ShowT as T

data Foo = Bar Bytes | Qux Text Int deriving Generic
                                    deriving anyclass T.ShowT

@

-}

module Z.Data.Text.ShowT
  ( -- * ShowT class
    ShowT(..), toText, toString, toUTF8Builder, toUTF8Bytes
  -- * Basic UTF8 builders
  , escapeTextJSON
  , B.stringUTF8, B.charUTF8, B.string7, B.char7, B.text
  -- * Numeric builders
  -- ** Integral type formatting
  , B.IFormat(..)
  , B.defaultIFormat
  , B.Padding(..)
  , B.int
  , B.intWith
  , B.integer
  -- ** Fixded size hexidecimal formatting
  , B.hex, B.hexUpper
  -- ** IEEE float formating
  , B.FFormat(..)
  , B.double
  , B.doubleWith
  , B.float
  , B.floatWith
  , B.scientific
  , B.scientificWith
  -- * Helpers
  , B.paren, B.curly, B.square, B.angle, B.quotes, B.squotes
  , B.colon, B.comma, B.intercalateVec, B.intercalateList
  , parenWhen
  ) where

import           Control.Monad
import qualified Data.Scientific                as Sci
import           Data.Fixed
import           Data.Primitive.PrimArray
import           Data.Functor.Compose
import           Data.Functor.Const
import           Data.Functor.Identity
import           Data.Functor.Product
import           Data.Functor.Sum
import           Data.Int
import           Data.List.NonEmpty             (NonEmpty (..))
import qualified Data.Monoid                    as Monoid
import           Data.Proxy                     (Proxy(..))
import           Data.Ratio                     (Ratio, numerator, denominator)
import           Data.Tagged                    (Tagged (..))
import qualified Data.Semigroup                 as Semigroup
import           Data.Typeable
import           Foreign.C.Types
import           GHC.Exts
import           GHC.ForeignPtr
import           GHC.Generics
import           GHC.Natural
import           GHC.Stack
import           GHC.Word
import           Data.Version
import           System.Exit
import           Data.Primitive.Types
import qualified Z.Data.Builder.Base            as B
import qualified Z.Data.Builder.Numeric         as B
import qualified Z.Data.Text.Base               as T
import           Z.Data.Text.Base               (Text(..))
import qualified Z.Data.Array                   as A
import qualified Z.Data.Vector.Base             as V

#define DOUBLE_QUOTE 34

--------------------------------------------------------------------------------
-- Data types

-- | A class similar to 'Show', serving the purpose that quickly convert a data type to a 'Text' value.
--
-- You can use newtype or generic deriving to implement instance of this class quickly:
--
-- @
--  {-\# LANGUAGE GeneralizedNewtypeDeriving \#-}
--  {-\# LANGUAGE DeriveAnyClass \#-}
--  {-\# LANGUAGE DeriveGeneric \#-}
--  {-\# LANGUAGE DerivingStrategies \#-}
--
--  import GHC.Generics
--
--  newtype FooInt = FooInt Int deriving (Generic)
--                            deriving anyclass ShowT
--
-- > toText (FooInt 3)
-- > "FooInt 3"
--
--  newtype FooInt = FooInt Int deriving (Generic)
--                            deriving newtype ShowT
--
-- > toText (FooInt 3)
-- > "3"
-- @
--
class ShowT a where
    -- | Convert data to 'B.Builder' with precendence.
    --
    -- You should return a 'B.Builder' writing in UTF8 encoding only, i.e.
    --
    -- @Z.Data.Text.validateMaybe (Z.Data.Builder.buildBytes (toUTF8BuilderP p a)) /= Nothing@
    toUTF8BuilderP :: Int -> a  -> B.Builder ()

    default toUTF8BuilderP :: (Generic a, GToText (Rep a)) => Int -> a -> B.Builder ()
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP Int
p = Int -> Rep a Any -> Builder ()
forall k (f :: k -> *) (a :: k).
GToText f =>
Int -> f a -> Builder ()
gToUTF8BuilderP Int
p (Rep a Any -> Builder ()) -> (a -> Rep a Any) -> a -> Builder ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Rep a Any
forall a x. Generic a => a -> Rep a x
from

-- | Convert data to 'B.Builder'.
toUTF8Builder :: ShowT a => a  -> B.Builder ()
{-# INLINE toUTF8Builder #-}
toUTF8Builder :: a -> Builder ()
toUTF8Builder = Int -> a -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0

-- | Convert data to 'V.Bytes' in UTF8 encoding.
toUTF8Bytes :: ShowT a => a -> V.Bytes
{-# INLINE toUTF8Bytes #-}
toUTF8Bytes :: a -> Bytes
toUTF8Bytes = Builder () -> Bytes
forall a. Builder a -> Bytes
B.build (Builder () -> Bytes) -> (a -> Builder ()) -> a -> Bytes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0

-- | Convert data to 'Text'.
toText :: ShowT a => a -> Text
{-# INLINE toText #-}
toText :: a -> Text
toText = Bytes -> Text
Text (Bytes -> Text) -> (a -> Bytes) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Bytes
forall a. ShowT a => a -> Bytes
toUTF8Bytes

-- | Convert data to 'String', faster 'show' replacement.
toString :: ShowT a => a -> String
{-# INLINE toString #-}
toString :: a -> String
toString = Text -> String
T.unpack (Text -> String) -> (a -> Text) -> a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. ShowT a => a -> Text
toText

class GToText f where
    gToUTF8BuilderP :: Int -> f a -> B.Builder ()

class GFieldToText f where
    gFieldToUTF8BuilderP :: B.Builder () -> Int -> f a -> B.Builder ()

instance (GFieldToText a, GFieldToText b) => GFieldToText (a :*: b) where
    {-# INLINE gFieldToUTF8BuilderP #-}
    gFieldToUTF8BuilderP :: Builder () -> Int -> (:*:) a b a -> Builder ()
gFieldToUTF8BuilderP Builder ()
sep Int
p (a a
a :*: b a
b) =
        Builder () -> Int -> a a -> Builder ()
forall k (f :: k -> *) (a :: k).
GFieldToText f =>
Builder () -> Int -> f a -> Builder ()
gFieldToUTF8BuilderP Builder ()
sep Int
p a a
a Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
sep Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder () -> Int -> b a -> Builder ()
forall k (f :: k -> *) (a :: k).
GFieldToText f =>
Builder () -> Int -> f a -> Builder ()
gFieldToUTF8BuilderP Builder ()
sep Int
p b a
b

instance (GToText f) => GFieldToText (S1 (MetaSel Nothing u ss ds) f) where
    {-# INLINE gFieldToUTF8BuilderP #-}
    gFieldToUTF8BuilderP :: Builder ()
-> Int -> S1 ('MetaSel 'Nothing u ss ds) f a -> Builder ()
gFieldToUTF8BuilderP Builder ()
_ Int
p (M1 f a
x) = Int -> f a -> Builder ()
forall k (f :: k -> *) (a :: k).
GToText f =>
Int -> f a -> Builder ()
gToUTF8BuilderP Int
p f a
x

instance (GToText f, Selector (MetaSel (Just l) u ss ds)) => GFieldToText (S1 (MetaSel (Just l) u ss ds) f) where
    {-# INLINE gFieldToUTF8BuilderP #-}
    gFieldToUTF8BuilderP :: Builder ()
-> Int -> S1 ('MetaSel ('Just l) u ss ds) f a -> Builder ()
gFieldToUTF8BuilderP Builder ()
_ Int
_ m1 :: S1 ('MetaSel ('Just l) u ss ds) f a
m1@(M1 f a
x) =
        String -> Builder ()
B.stringModifiedUTF8 (S1 ('MetaSel ('Just l) u ss ds) f a -> String
forall k (s :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
       (f :: k1 -> *) (a :: k1).
Selector s =>
t s f a -> String
selName S1 ('MetaSel ('Just l) u ss ds) f a
m1) Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
" = " Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> f a -> Builder ()
forall k (f :: k -> *) (a :: k).
GToText f =>
Int -> f a -> Builder ()
gToUTF8BuilderP Int
0 f a
x

instance GToText V1 where
    {-# INLINE gToUTF8BuilderP #-}
    gToUTF8BuilderP :: Int -> V1 a -> Builder ()
gToUTF8BuilderP Int
_ = String -> V1 a -> Builder ()
forall a. HasCallStack => String -> a
error String
"Z.Data.Text.ShowT: empty data type"

instance (GToText f, GToText g) => GToText (f :+: g) where
    {-# INLINE gToUTF8BuilderP #-}
    gToUTF8BuilderP :: Int -> (:+:) f g a -> Builder ()
gToUTF8BuilderP Int
p (L1 f a
x) = Int -> f a -> Builder ()
forall k (f :: k -> *) (a :: k).
GToText f =>
Int -> f a -> Builder ()
gToUTF8BuilderP Int
p f a
x
    gToUTF8BuilderP Int
p (R1 g a
x) = Int -> g a -> Builder ()
forall k (f :: k -> *) (a :: k).
GToText f =>
Int -> f a -> Builder ()
gToUTF8BuilderP Int
p g a
x

-- | Constructor without payload, convert to String
instance (Constructor c) => GToText (C1 c U1) where
    {-# INLINE gToUTF8BuilderP #-}
    gToUTF8BuilderP :: Int -> C1 c U1 a -> Builder ()
gToUTF8BuilderP Int
_ C1 c U1 a
m1 = String -> Builder ()
B.stringModifiedUTF8 (String -> Builder ()) -> String -> Builder ()
forall a b. (a -> b) -> a -> b
$ C1 c U1 a -> String
forall k (c :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
       (f :: k1 -> *) (a :: k1).
Constructor c =>
t c f a -> String
conName C1 c U1 a
m1

-- | Constructor with payloads
instance (GFieldToText (S1 sc f), Constructor c) => GToText (C1 c (S1 sc f)) where
    {-# INLINE gToUTF8BuilderP #-}
    gToUTF8BuilderP :: Int -> C1 c (S1 sc f) a -> Builder ()
gToUTF8BuilderP Int
p m1 :: C1 c (S1 sc f) a
m1@(M1 S1 sc f a
x) =
        Bool -> Builder () -> Builder ()
parenWhen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (Builder () -> Builder ()) -> Builder () -> Builder ()
forall a b. (a -> b) -> a -> b
$ do
            String -> Builder ()
B.stringModifiedUTF8 (String -> Builder ()) -> String -> Builder ()
forall a b. (a -> b) -> a -> b
$ C1 c (S1 sc f) a -> String
forall k (c :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
       (f :: k1 -> *) (a :: k1).
Constructor c =>
t c f a -> String
conName C1 c (S1 sc f) a
m1
            Char -> Builder ()
B.char8 Char
' '
            if C1 c (S1 sc f) a -> Bool
forall k (c :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
       (f :: k1 -> *) (a :: k1).
Constructor c =>
t c f a -> Bool
conIsRecord C1 c (S1 sc f) a
m1
            then Builder () -> Builder ()
B.curly (Builder () -> Builder ()) -> Builder () -> Builder ()
forall a b. (a -> b) -> a -> b
$ Builder () -> Int -> S1 sc f a -> Builder ()
forall k (f :: k -> *) (a :: k).
GFieldToText f =>
Builder () -> Int -> f a -> Builder ()
gFieldToUTF8BuilderP (Char -> Builder ()
B.char7 Char
',' Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> Builder ()
B.char7 Char
' ') Int
p S1 sc f a
x
            else Builder () -> Int -> S1 sc f a -> Builder ()
forall k (f :: k -> *) (a :: k).
GFieldToText f =>
Builder () -> Int -> f a -> Builder ()
gFieldToUTF8BuilderP (Char -> Builder ()
B.char7 Char
' ') Int
11 S1 sc f a
x

instance (GFieldToText (a :*: b), Constructor c) => GToText (C1 c (a :*: b)) where
    {-# INLINE gToUTF8BuilderP #-}
    gToUTF8BuilderP :: Int -> C1 c (a :*: b) a -> Builder ()
gToUTF8BuilderP Int
p m1 :: C1 c (a :*: b) a
m1@(M1 (:*:) a b a
x) =
        case C1 c (a :*: b) a -> Fixity
forall k (c :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
       (f :: k1 -> *) (a :: k1).
Constructor c =>
t c f a -> Fixity
conFixity C1 c (a :*: b) a
m1 of
            Fixity
Prefix -> Bool -> Builder () -> Builder ()
parenWhen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (Builder () -> Builder ()) -> Builder () -> Builder ()
forall a b. (a -> b) -> a -> b
$ do
                String -> Builder ()
B.stringModifiedUTF8 (String -> Builder ()) -> String -> Builder ()
forall a b. (a -> b) -> a -> b
$ C1 c (a :*: b) a -> String
forall k (c :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
       (f :: k1 -> *) (a :: k1).
Constructor c =>
t c f a -> String
conName C1 c (a :*: b) a
m1
                Char -> Builder ()
B.char8 Char
' '
                if C1 c (a :*: b) a -> Bool
forall k (c :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
       (f :: k1 -> *) (a :: k1).
Constructor c =>
t c f a -> Bool
conIsRecord C1 c (a :*: b) a
m1
                then Builder () -> Builder ()
B.curly (Builder () -> Builder ()) -> Builder () -> Builder ()
forall a b. (a -> b) -> a -> b
$ Builder () -> Int -> (:*:) a b a -> Builder ()
forall k (f :: k -> *) (a :: k).
GFieldToText f =>
Builder () -> Int -> f a -> Builder ()
gFieldToUTF8BuilderP (Char -> Builder ()
B.char7 Char
',' Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> Builder ()
B.char7 Char
' ') Int
p (:*:) a b a
x
                else Builder () -> Int -> (:*:) a b a -> Builder ()
forall k (f :: k -> *) (a :: k).
GFieldToText f =>
Builder () -> Int -> f a -> Builder ()
gFieldToUTF8BuilderP (Char -> Builder ()
B.char7 Char
' ') Int
11 (:*:) a b a
x
            Infix Associativity
_ Int
p' -> Bool -> Builder () -> Builder ()
parenWhen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
p') (Builder () -> Builder ()) -> Builder () -> Builder ()
forall a b. (a -> b) -> a -> b
$ do
                Builder () -> Int -> (:*:) a b a -> Builder ()
forall k (f :: k -> *) (a :: k).
GFieldToText f =>
Builder () -> Int -> f a -> Builder ()
gFieldToUTF8BuilderP
                    (Char -> Builder ()
B.char8 Char
' ' Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> Builder ()
B.stringModifiedUTF8 (C1 c (a :*: b) a -> String
forall k (c :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
       (f :: k1 -> *) (a :: k1).
Constructor c =>
t c f a -> String
conName C1 c (a :*: b) a
m1) Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> Builder ()
B.char8 Char
' ') (Int
p'Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) (:*:) a b a
x

instance ShowT a => GToText (K1 i a) where
    {-# INLINE gToUTF8BuilderP #-}
    gToUTF8BuilderP :: Int -> K1 i a a -> Builder ()
gToUTF8BuilderP Int
p (K1 a
x) = Int -> a -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
p a
x

-- | Add "(..)" around builders when condition is met, otherwise add nothing.
--
-- This is useful when defining 'ShowT' instances.
parenWhen :: Bool -> B.Builder () -> B.Builder ()
{-# INLINE parenWhen #-}
parenWhen :: Bool -> Builder () -> Builder ()
parenWhen Bool
True Builder ()
b = Builder () -> Builder ()
B.paren Builder ()
b
parenWhen Bool
_    Builder ()
b = Builder ()
b

--------------------------------------------------------------------------------
-- Data types
instance GToText f => GToText (D1 c f) where
    {-# INLINE gToUTF8BuilderP #-}
    gToUTF8BuilderP :: Int -> D1 c f a -> Builder ()
gToUTF8BuilderP Int
p (M1 f a
x) = Int -> f a -> Builder ()
forall k (f :: k -> *) (a :: k).
GToText f =>
Int -> f a -> Builder ()
gToUTF8BuilderP Int
p f a
x

instance ShowT Bool where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Bool -> Builder ()
toUTF8BuilderP Int
_ Bool
True = Builder ()
"True"
    toUTF8BuilderP Int
_ Bool
_    = Builder ()
"False"


instance ShowT Char where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Char -> Builder ()
toUTF8BuilderP Int
_ = String -> Builder ()
B.string8 (String -> Builder ()) -> (Char -> String) -> Char -> Builder ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> String
forall a. Show a => a -> String
show

instance ShowT Double where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Double -> Builder ()
toUTF8BuilderP Int
_ = Double -> Builder ()
B.double;}
instance ShowT Float  where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Float -> Builder ()
toUTF8BuilderP Int
_ = Float -> Builder ()
B.float;}

instance ShowT Int     where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Int -> Builder ()
toUTF8BuilderP Int
_ = Int -> Builder ()
forall a. (Integral a, Bounded a) => a -> Builder ()
B.int;}
instance ShowT Int8    where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Int8 -> Builder ()
toUTF8BuilderP Int
_ = Int8 -> Builder ()
forall a. (Integral a, Bounded a) => a -> Builder ()
B.int;}
instance ShowT Int16   where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Int16 -> Builder ()
toUTF8BuilderP Int
_ = Int16 -> Builder ()
forall a. (Integral a, Bounded a) => a -> Builder ()
B.int;}
instance ShowT Int32   where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Int32 -> Builder ()
toUTF8BuilderP Int
_ = Int32 -> Builder ()
forall a. (Integral a, Bounded a) => a -> Builder ()
B.int;}
instance ShowT Int64   where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Int64 -> Builder ()
toUTF8BuilderP Int
_ = Int64 -> Builder ()
forall a. (Integral a, Bounded a) => a -> Builder ()
B.int;}
instance ShowT Word    where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Word -> Builder ()
toUTF8BuilderP Int
_ = Word -> Builder ()
forall a. (Integral a, Bounded a) => a -> Builder ()
B.int;}
instance ShowT Word8   where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Word8 -> Builder ()
toUTF8BuilderP Int
_ = Word8 -> Builder ()
forall a. (Integral a, Bounded a) => a -> Builder ()
B.int;}
instance ShowT Word16  where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Word16 -> Builder ()
toUTF8BuilderP Int
_ = Word16 -> Builder ()
forall a. (Integral a, Bounded a) => a -> Builder ()
B.int;}
instance ShowT Word32  where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Word32 -> Builder ()
toUTF8BuilderP Int
_ = Word32 -> Builder ()
forall a. (Integral a, Bounded a) => a -> Builder ()
B.int;}
instance ShowT Word64  where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Word64 -> Builder ()
toUTF8BuilderP Int
_ = Word64 -> Builder ()
forall a. (Integral a, Bounded a) => a -> Builder ()
B.int;}

instance ShowT Integer  where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Integer -> Builder ()
toUTF8BuilderP Int
_ = Integer -> Builder ()
B.integer;}
instance ShowT Natural  where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Natural -> Builder ()
toUTF8BuilderP Int
_ = Integer -> Builder ()
B.integer (Integer -> Builder ())
-> (Natural -> Integer) -> Natural -> Builder ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Natural -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral}
instance ShowT Ordering where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Ordering -> Builder ()
toUTF8BuilderP Int
_ Ordering
GT = Builder ()
"GT"
    toUTF8BuilderP Int
_ Ordering
EQ = Builder ()
"EQ"
    toUTF8BuilderP Int
_ Ordering
_  = Builder ()
"LT"

instance ShowT () where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> () -> Builder ()
toUTF8BuilderP Int
_ () = Builder ()
"()"

instance ShowT Version where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Version -> Builder ()
toUTF8BuilderP Int
_ = String -> Builder ()
B.stringUTF8 (String -> Builder ())
-> (Version -> String) -> Version -> Builder ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> String
forall a. Show a => a -> String
show

-- | The escaping rules is same with 'Show' instance: we reuse JSON escaping rules here, so it will be faster.
instance ShowT Text where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Text -> Builder ()
toUTF8BuilderP Int
_ = Text -> Builder ()
escapeTextJSON

-- | Escape text using JSON string escaping rules and add double quotes, escaping rules:
--
-- @
--    \'\\b\':  \"\\b\"
--    \'\\f\':  \"\\f\"
--    \'\\n\':  \"\\n\"
--    \'\\r\':  \"\\r\"
--    \'\\t\':  \"\\t\"
--    \'\"\':  \"\\\"\"
--    \'\\\':  \"\\\\\"
--    \'\/\':  \"\\/\"
--    other chars <= 0x1F: "\\u00XX"
-- @
--
escapeTextJSON :: T.Text -> B.Builder ()
{-# INLINE escapeTextJSON #-}
escapeTextJSON :: Text -> Builder ()
escapeTextJSON (T.Text (V.PrimVector ba :: PrimArray Word8
ba@(PrimArray ByteArray#
ba#) Int
s Int
l)) = do
    let !siz :: Int
siz = ByteArray# -> Int -> Int -> Int
escape_json_string_length ByteArray#
ba# Int
s Int
l
    Int
-> (MutablePrimArray RealWorld Word8 -> Int -> IO ()) -> Builder ()
B.writeN Int
siz (\ mba :: MutablePrimArray RealWorld Word8
mba@(MutablePrimArray MutableByteArray# RealWorld
mba#) Int
i -> do
        if Int
siz Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
lInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
2   -- no need to escape
        then do
            MutablePrimArray (PrimState IO) Word8 -> Int -> Word8 -> IO ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray RealWorld Word8
MutablePrimArray (PrimState IO) Word8
mba Int
i DOUBLE_QUOTE
            MutablePrimArray (PrimState IO) Word8
-> Int -> PrimArray Word8 -> Int -> Int -> IO ()
forall (m :: * -> *) a.
(PrimMonad m, Prim a) =>
MutablePrimArray (PrimState m) a
-> Int -> PrimArray a -> Int -> Int -> m ()
copyPrimArray MutablePrimArray RealWorld Word8
MutablePrimArray (PrimState IO) Word8
mba (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) PrimArray Word8
ba Int
s Int
l
            MutablePrimArray (PrimState IO) Word8 -> Int -> Word8 -> IO ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray RealWorld Word8
MutablePrimArray (PrimState IO) Word8
mba (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
l) DOUBLE_QUOTE
        else IO Int -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ByteArray#
-> Int -> Int -> MutableByteArray# RealWorld -> Int -> IO Int
escape_json_string ByteArray#
ba# Int
s Int
l (MutableByteArray# RealWorld -> MutableByteArray# RealWorld
unsafeCoerce# MutableByteArray# RealWorld
mba#) Int
i))

foreign import ccall unsafe escape_json_string_length
    :: ByteArray# -> Int -> Int -> Int

foreign import ccall unsafe escape_json_string
    :: ByteArray# -> Int -> Int -> MutableByteArray# RealWorld -> Int -> IO Int

instance ShowT Sci.Scientific where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Scientific -> Builder ()
toUTF8BuilderP Int
_ = Scientific -> Builder ()
B.scientific

instance ShowT a => ShowT [a] where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> [a] -> Builder ()
toUTF8BuilderP Int
_ = Builder () -> Builder ()
B.square (Builder () -> Builder ())
-> ([a] -> Builder ()) -> [a] -> Builder ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder () -> (a -> Builder ()) -> [a] -> Builder ()
forall a. Builder () -> (a -> Builder ()) -> [a] -> Builder ()
B.intercalateList Builder ()
B.comma (Int -> a -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0)

instance ShowT a => ShowT (A.Array a) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Array a -> Builder ()
toUTF8BuilderP Int
_ = Builder () -> Builder ()
B.square (Builder () -> Builder ())
-> (Array a -> Builder ()) -> Array a -> Builder ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder () -> (a -> Builder ()) -> Array a -> Builder ()
forall (v :: * -> *) a.
Vec v a =>
Builder () -> (a -> Builder ()) -> v a -> Builder ()
B.intercalateVec Builder ()
B.comma (Int -> a -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0)

instance ShowT a => ShowT (A.SmallArray a) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> SmallArray a -> Builder ()
toUTF8BuilderP Int
_ = Builder () -> Builder ()
B.square (Builder () -> Builder ())
-> (SmallArray a -> Builder ()) -> SmallArray a -> Builder ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder () -> (a -> Builder ()) -> SmallArray a -> Builder ()
forall (v :: * -> *) a.
Vec v a =>
Builder () -> (a -> Builder ()) -> v a -> Builder ()
B.intercalateVec Builder ()
B.comma (Int -> a -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0)

instance (A.PrimUnlifted a, ShowT a) => ShowT (A.UnliftedArray a) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> UnliftedArray a -> Builder ()
toUTF8BuilderP Int
_ = Builder () -> Builder ()
B.square (Builder () -> Builder ())
-> (UnliftedArray a -> Builder ()) -> UnliftedArray a -> Builder ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder () -> (a -> Builder ()) -> UnliftedArray a -> Builder ()
forall (v :: * -> *) a.
Vec v a =>
Builder () -> (a -> Builder ()) -> v a -> Builder ()
B.intercalateVec Builder ()
B.comma (Int -> a -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0)

instance (Prim a, ShowT a) => ShowT (A.PrimArray a) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> PrimArray a -> Builder ()
toUTF8BuilderP Int
_ = Builder () -> Builder ()
B.square (Builder () -> Builder ())
-> (PrimArray a -> Builder ()) -> PrimArray a -> Builder ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder () -> (a -> Builder ()) -> PrimArray a -> Builder ()
forall (v :: * -> *) a.
Vec v a =>
Builder () -> (a -> Builder ()) -> v a -> Builder ()
B.intercalateVec Builder ()
B.comma (Int -> a -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0)

instance ShowT a => ShowT (V.Vector a) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Vector a -> Builder ()
toUTF8BuilderP Int
_ = Builder () -> Builder ()
B.square (Builder () -> Builder ())
-> (Vector a -> Builder ()) -> Vector a -> Builder ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder () -> (a -> Builder ()) -> Vector a -> Builder ()
forall (v :: * -> *) a.
Vec v a =>
Builder () -> (a -> Builder ()) -> v a -> Builder ()
B.intercalateVec Builder ()
B.comma (Int -> a -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0)

instance (Prim a, ShowT a) => ShowT (V.PrimVector a) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> PrimVector a -> Builder ()
toUTF8BuilderP Int
_ = Builder () -> Builder ()
B.square (Builder () -> Builder ())
-> (PrimVector a -> Builder ()) -> PrimVector a -> Builder ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder () -> (a -> Builder ()) -> PrimVector a -> Builder ()
forall (v :: * -> *) a.
Vec v a =>
Builder () -> (a -> Builder ()) -> v a -> Builder ()
B.intercalateVec Builder ()
B.comma (Int -> a -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0)

instance (ShowT a, ShowT b) => ShowT (a, b) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> (a, b) -> Builder ()
toUTF8BuilderP Int
_ (a
a, b
b) = Builder () -> Builder ()
B.paren (Builder () -> Builder ()) -> Builder () -> Builder ()
forall a b. (a -> b) -> a -> b
$  Int -> a -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 a
a
                     Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> b -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 b
b

instance (ShowT a, ShowT b, ShowT c) => ShowT (a, b, c) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> (a, b, c) -> Builder ()
toUTF8BuilderP Int
_ (a
a, b
b, c
c) = Builder () -> Builder ()
B.paren (Builder () -> Builder ()) -> Builder () -> Builder ()
forall a b. (a -> b) -> a -> b
$  Int -> a -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 a
a
                     Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> b -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 b
b
                     Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> c -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 c
c

instance (ShowT a, ShowT b, ShowT c, ShowT d) => ShowT (a, b, c, d) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> (a, b, c, d) -> Builder ()
toUTF8BuilderP Int
_ (a
a, b
b, c
c, d
d) = Builder () -> Builder ()
B.paren (Builder () -> Builder ()) -> Builder () -> Builder ()
forall a b. (a -> b) -> a -> b
$  Int -> a -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 a
a
                     Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> b -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 b
b
                     Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> c -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 c
c
                     Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> d -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 d
d

instance (ShowT a, ShowT b, ShowT c, ShowT d, ShowT e) => ShowT (a, b, c, d, e) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> (a, b, c, d, e) -> Builder ()
toUTF8BuilderP Int
_ (a
a, b
b, c
c, d
d, e
e) = Builder () -> Builder ()
B.paren (Builder () -> Builder ()) -> Builder () -> Builder ()
forall a b. (a -> b) -> a -> b
$  Int -> a -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 a
a
                     Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> b -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 b
b
                     Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> c -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 c
c
                     Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> d -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 d
d
                     Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> e -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 e
e

instance (ShowT a, ShowT b, ShowT c, ShowT d, ShowT e, ShowT f) => ShowT (a, b, c, d, e, f) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> (a, b, c, d, e, f) -> Builder ()
toUTF8BuilderP Int
_ (a
a, b
b, c
c, d
d, e
e, f
f) = Builder () -> Builder ()
B.paren (Builder () -> Builder ()) -> Builder () -> Builder ()
forall a b. (a -> b) -> a -> b
$  Int -> a -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 a
a
                     Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> b -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 b
b
                     Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> c -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 c
c
                     Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> d -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 d
d
                     Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> e -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 e
e
                     Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> f -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 f
f

instance (ShowT a, ShowT b, ShowT c, ShowT d, ShowT e, ShowT f, ShowT g) => ShowT (a, b, c, d, e, f, g) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> (a, b, c, d, e, f, g) -> Builder ()
toUTF8BuilderP Int
_ (a
a, b
b, c
c, d
d, e
e, f
f, g
g) = Builder () -> Builder ()
B.paren (Builder () -> Builder ()) -> Builder () -> Builder ()
forall a b. (a -> b) -> a -> b
$  Int -> a -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 a
a
                     Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> b -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 b
b
                     Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> c -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 c
c
                     Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> d -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 d
d
                     Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> e -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 e
e
                     Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> f -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 f
f
                     Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> g -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 g
g

instance ShowT a => ShowT (Maybe a) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Maybe a -> Builder ()
toUTF8BuilderP Int
p (Just a
x) = Bool -> Builder () -> Builder ()
parenWhen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (Builder () -> Builder ()) -> Builder () -> Builder ()
forall a b. (a -> b) -> a -> b
$ Builder ()
"Just " Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> a -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
11 a
x
    toUTF8BuilderP Int
_ Maybe a
_        = Builder ()
"Nothing"

instance (ShowT a, ShowT b) => ShowT (Either a b) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Either a b -> Builder ()
toUTF8BuilderP Int
p (Left a
x) = Bool -> Builder () -> Builder ()
parenWhen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (Builder () -> Builder ()) -> Builder () -> Builder ()
forall a b. (a -> b) -> a -> b
$ Builder ()
"Left " Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> a -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
11 a
x
    toUTF8BuilderP Int
p (Right b
x) = Bool -> Builder () -> Builder ()
parenWhen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (Builder () -> Builder ()) -> Builder () -> Builder ()
forall a b. (a -> b) -> a -> b
$ Builder ()
"Right " Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> b -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
11 b
x

instance (ShowT a, Integral a) => ShowT (Ratio a) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Ratio a -> Builder ()
toUTF8BuilderP Int
p Ratio a
r = Bool -> Builder () -> Builder ()
parenWhen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (Builder () -> Builder ()) -> Builder () -> Builder ()
forall a b. (a -> b) -> a -> b
$ do
        Int -> a -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
8 (Ratio a -> a
forall a. Ratio a -> a
numerator Ratio a
r)
        Builder ()
" % "
        Int -> a -> Builder ()
forall a. ShowT a => Int -> a -> Builder ()
toUTF8BuilderP Int
8 (Ratio a -> a
forall a. Ratio a -> a
denominator Ratio a
r)

instance HasResolution a => ShowT (Fixed a) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Fixed a -> Builder ()
toUTF8BuilderP Int
_ = String -> Builder ()
B.string8 (String -> Builder ())
-> (Fixed a -> String) -> Fixed a -> Builder ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
.  Fixed a -> String
forall a. Show a => a -> String
show

instance ShowT CallStack where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> CallStack -> Builder ()
toUTF8BuilderP Int
_ = String -> Builder ()
B.string8 (String -> Builder ())
-> (CallStack -> String) -> CallStack -> Builder ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
.  CallStack -> String
forall a. Show a => a -> String
show

deriving newtype instance ShowT CChar
deriving newtype instance ShowT CSChar
deriving newtype instance ShowT CUChar
deriving newtype instance ShowT CShort
deriving newtype instance ShowT CUShort
deriving newtype instance ShowT CInt
deriving newtype instance ShowT CUInt
deriving newtype instance ShowT CLong
deriving newtype instance ShowT CULong
deriving newtype instance ShowT CPtrdiff
deriving newtype instance ShowT CSize
deriving newtype instance ShowT CWchar
deriving newtype instance ShowT CSigAtomic
deriving newtype instance ShowT CLLong
deriving newtype instance ShowT CULLong
deriving newtype instance ShowT CBool
deriving newtype instance ShowT CIntPtr
deriving newtype instance ShowT CUIntPtr
deriving newtype instance ShowT CIntMax
deriving newtype instance ShowT CUIntMax
deriving newtype instance ShowT CClock
deriving newtype instance ShowT CTime
deriving newtype instance ShowT CUSeconds
deriving newtype instance ShowT CSUSeconds
deriving newtype instance ShowT CFloat
deriving newtype instance ShowT CDouble

instance ShowT (Ptr a) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Ptr a -> Builder ()
toUTF8BuilderP Int
_ (Ptr Addr#
a) =
        Builder ()
"0x" Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Word -> Builder ()
forall a. (FiniteBits a, Integral a) => a -> Builder ()
B.hex (Word# -> Word
W# (Int# -> Word#
int2Word#(Addr# -> Int#
addr2Int# Addr#
a)))
instance ShowT (ForeignPtr a) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> ForeignPtr a -> Builder ()
toUTF8BuilderP Int
_ (ForeignPtr Addr#
a ForeignPtrContents
_) =
        Builder ()
"0x" Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Word -> Builder ()
forall a. (FiniteBits a, Integral a) => a -> Builder ()
B.hex (Word# -> Word
W# (Int# -> Word#
int2Word#(Addr# -> Int#
addr2Int# Addr#
a)))

deriving anyclass instance ShowT ExitCode

deriving anyclass instance ShowT a => ShowT (Semigroup.Min a)
deriving anyclass instance ShowT a => ShowT (Semigroup.Max a)
deriving anyclass instance ShowT a => ShowT (Semigroup.First a)
deriving anyclass instance ShowT a => ShowT (Semigroup.Last a)
deriving anyclass instance ShowT a => ShowT (Semigroup.WrappedMonoid a)
deriving anyclass instance ShowT a => ShowT (Semigroup.Dual a)
deriving anyclass instance ShowT a => ShowT (Monoid.First a)
deriving anyclass instance ShowT a => ShowT (Monoid.Last a)
deriving anyclass instance ShowT a => ShowT (NonEmpty a)
deriving anyclass instance ShowT a => ShowT (Identity a)
deriving anyclass instance ShowT a => ShowT (Const a b)
deriving anyclass instance ShowT (Proxy a)
deriving anyclass instance ShowT b => ShowT (Tagged a b)
deriving anyclass instance ShowT (f (g a)) => ShowT (Compose f g a)
deriving anyclass instance (ShowT (f a), ShowT (g a)) => ShowT (Product f g a)
deriving anyclass instance (ShowT (f a), ShowT (g a), ShowT a) => ShowT (Sum f g a)