module Z.Data.Text.Print
  ( 
    Print(..), toText, toString, toUTF8Builder, toUTF8Bytes
  
  , escapeTextJSON
  , B.stringUTF8, B.charUTF8, B.string7, B.char7, B.text
  
  
  , B.IFormat(..)
  , B.defaultIFormat
  , B.Padding(..)
  , B.int
  , B.intWith
  , B.integer
  
  , B.hex, B.hexUpper
  
  , B.FFormat(..)
  , B.double
  , B.doubleWith
  , B.float
  , B.floatWith
  , B.scientific
  , B.scientific'
  , B.scientificWith
  
  , B.paren, B.parenWhen, B.curly, B.square, B.angle, B.quotes, B.squotes
  , B.colon, B.comma, B.intercalateVec, B.intercalateList
  ) where
import           Control.Monad
import           Control.Exception              (SomeException)
import           Z.Data.ASCII
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.Ratio                     (Ratio, numerator, denominator)
import           Data.Tagged                    (Tagged (..))
import qualified Data.Scientific                as Sci
import qualified Data.Semigroup                 as Semigroup
import           Data.Time                      (Day, DiffTime, LocalTime, NominalDiffTime, TimeOfDay, UTCTime, ZonedTime)
import           Data.Time.Calendar             (CalendarDiffDays (..), DayOfWeek (..))
import           Data.Time.LocalTime            (CalendarDiffTime (..))
import           Data.Time.Clock.System         (SystemTime (..))
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                 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
class Print a where
    
    
    
    
    
    toUTF8BuilderP :: Int -> a  -> B.Builder ()
    default toUTF8BuilderP :: (Generic a, GToText (Rep a)) => Int -> a -> B.Builder ()
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP Int
p = forall {k} (f :: k -> *) (a :: k).
GToText f =>
Int -> f a -> Builder ()
gToUTF8BuilderP Int
p forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a x. Generic a => a -> Rep a x
from
toUTF8Builder :: Print a => a  -> B.Builder ()
{-# INLINABLE toUTF8Builder #-}
toUTF8Builder :: forall a. Print a => a -> Builder ()
toUTF8Builder = forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0
toUTF8Bytes :: Print a => a -> V.Bytes
{-# INLINABLE toUTF8Bytes #-}
toUTF8Bytes :: forall a. Print a => a -> Bytes
toUTF8Bytes = forall a. Builder a -> Bytes
B.build forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0
toText :: Print a => a -> Text
{-# INLINABLE toText #-}
toText :: forall a. Print a => a -> Text
toText = Bytes -> Text
Text forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Print a => a -> Bytes
toUTF8Bytes
toString :: Print a => a -> String
{-# INLINABLE toString #-}
toString :: forall a. Print a => a -> String
toString = Text -> String
T.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Print 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 :: forall (a :: k). Builder () -> Int -> (:*:) a b a -> Builder ()
gFieldToUTF8BuilderP Builder ()
sep Int
p (a a
a :*: b a
b) =
        forall {k} (f :: k -> *) (a :: k).
GFieldToText f =>
Builder () -> Int -> f a -> Builder ()
gFieldToUTF8BuilderP Builder ()
sep Int
p a a
a forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
sep forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> 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 :: forall (a :: k).
Builder ()
-> Int -> S1 ('MetaSel 'Nothing u ss ds) f a -> Builder ()
gFieldToUTF8BuilderP Builder ()
_ Int
p (M1 f a
x) = 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 :: forall (a :: k).
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 (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) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
" = " forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> 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 :: forall (a :: k). Int -> V1 a -> Builder ()
gToUTF8BuilderP Int
_ = forall a. HasCallStack => String -> a
error String
"Z.Data.Text.Print: empty data type"
instance (GToText f, GToText g) => GToText (f :+: g) where
    {-# INLINE gToUTF8BuilderP #-}
    gToUTF8BuilderP :: forall (a :: k). Int -> (:+:) f g a -> Builder ()
gToUTF8BuilderP Int
p (L1 f a
x) = 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) = forall {k} (f :: k -> *) (a :: k).
GToText f =>
Int -> f a -> Builder ()
gToUTF8BuilderP Int
p g a
x
instance (Constructor c) => GToText (C1 c U1) where
    {-# INLINE gToUTF8BuilderP #-}
    gToUTF8BuilderP :: forall (a :: k). Int -> C1 c U1 a -> Builder ()
gToUTF8BuilderP Int
_ C1 c U1 a
m1 = String -> Builder ()
B.stringModifiedUTF8 forall a b. (a -> b) -> a -> b
$ 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
instance (GFieldToText (S1 sc f), Constructor c) => GToText (C1 c (S1 sc f)) where
    {-# INLINE gToUTF8BuilderP #-}
    gToUTF8BuilderP :: forall (a :: k). 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 ()
B.parenWhen (Int
p forall a. Ord a => a -> a -> Bool
> Int
10) forall a b. (a -> b) -> a -> b
$ do
            String -> Builder ()
B.stringModifiedUTF8 forall a b. (a -> b) -> a -> b
$ 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 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 forall a b. (a -> b) -> a -> b
$ forall {k} (f :: k -> *) (a :: k).
GFieldToText f =>
Builder () -> Int -> f a -> Builder ()
gFieldToUTF8BuilderP (Char -> Builder ()
B.char7 Char
',' 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 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 :: forall (a :: k). Int -> C1 c (a :*: b) a -> Builder ()
gToUTF8BuilderP Int
p m1 :: C1 c (a :*: b) a
m1@(M1 (:*:) a b a
x) =
        case 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 ()
B.parenWhen (Int
p forall a. Ord a => a -> a -> Bool
> Int
10) forall a b. (a -> b) -> a -> b
$ do
                String -> Builder ()
B.stringModifiedUTF8 forall a b. (a -> b) -> a -> b
$ 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 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 forall a b. (a -> b) -> a -> b
$ forall {k} (f :: k -> *) (a :: k).
GFieldToText f =>
Builder () -> Int -> f a -> Builder ()
gFieldToUTF8BuilderP (Char -> Builder ()
B.char7 Char
',' forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> Builder ()
B.char7 Char
' ') Int
p (:*:) a b a
x
                else 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 ()
B.parenWhen (Int
p forall a. Ord a => a -> a -> Bool
> Int
p') forall a b. (a -> b) -> a -> b
$ do
                forall {k} (f :: k -> *) (a :: k).
GFieldToText f =>
Builder () -> Int -> f a -> Builder ()
gFieldToUTF8BuilderP
                    (Char -> Builder ()
B.char8 Char
' ' forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> Builder ()
B.stringModifiedUTF8 (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) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> Builder ()
B.char8 Char
' ') (Int
p'forall a. Num a => a -> a -> a
+Int
1) (:*:) a b a
x
instance Print a => GToText (K1 i a) where
    {-# INLINE gToUTF8BuilderP #-}
    gToUTF8BuilderP :: forall (a :: k). Int -> K1 i a a -> Builder ()
gToUTF8BuilderP Int
p (K1 a
x) = forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
p a
x
instance GToText f => GToText (D1 c f) where
    {-# INLINE gToUTF8BuilderP #-}
    gToUTF8BuilderP :: forall (a :: k). Int -> D1 c f a -> Builder ()
gToUTF8BuilderP Int
p (M1 f a
x) = forall {k} (f :: k -> *) (a :: k).
GToText f =>
Int -> f a -> Builder ()
gToUTF8BuilderP Int
p f a
x
instance Print Bool where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Bool -> Builder ()
toUTF8BuilderP Int
_ Bool
True = Builder ()
"True"
    toUTF8BuilderP Int
_ Bool
_    = Builder ()
"False"
instance Print Char where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Char -> Builder ()
toUTF8BuilderP Int
_ = String -> Builder ()
B.string8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
instance Print Double where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Double -> Builder ()
toUTF8BuilderP Int
p Double
x = Bool -> Builder () -> Builder ()
B.parenWhen (Int
p forall a. Ord a => a -> a -> Bool
> Int
6 Bool -> Bool -> Bool
&& Double
x forall a. Ord a => a -> a -> Bool
< Double
0) (Double -> Builder ()
B.double Double
x) ;}
instance Print Float  where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Float -> Builder ()
toUTF8BuilderP Int
p Float
x = Bool -> Builder () -> Builder ()
B.parenWhen (Int
p forall a. Ord a => a -> a -> Bool
> Int
6 Bool -> Bool -> Bool
&& Float
x forall a. Ord a => a -> a -> Bool
< Float
0) (Float -> Builder ()
B.float Float
x) ;}
instance Print Int     where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Int -> Builder ()
toUTF8BuilderP Int
p Int
x = Bool -> Builder () -> Builder ()
B.parenWhen (Int
p forall a. Ord a => a -> a -> Bool
> Int
6 Bool -> Bool -> Bool
&& Int
x forall a. Ord a => a -> a -> Bool
< Int
0) (forall a. (Integral a, Bounded a) => a -> Builder ()
B.int Int
x) ;}
instance Print Int8    where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Int8 -> Builder ()
toUTF8BuilderP Int
p Int8
x = Bool -> Builder () -> Builder ()
B.parenWhen (Int
p forall a. Ord a => a -> a -> Bool
> Int
6 Bool -> Bool -> Bool
&& Int8
x forall a. Ord a => a -> a -> Bool
< Int8
0) (forall a. (Integral a, Bounded a) => a -> Builder ()
B.int Int8
x) ;}
instance Print Int16   where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Int16 -> Builder ()
toUTF8BuilderP Int
p Int16
x = Bool -> Builder () -> Builder ()
B.parenWhen (Int
p forall a. Ord a => a -> a -> Bool
> Int
6 Bool -> Bool -> Bool
&& Int16
x forall a. Ord a => a -> a -> Bool
< Int16
0) (forall a. (Integral a, Bounded a) => a -> Builder ()
B.int Int16
x) ;}
instance Print Int32   where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Int32 -> Builder ()
toUTF8BuilderP Int
p Int32
x = Bool -> Builder () -> Builder ()
B.parenWhen (Int
p forall a. Ord a => a -> a -> Bool
> Int
6 Bool -> Bool -> Bool
&& Int32
x forall a. Ord a => a -> a -> Bool
< Int32
0) (forall a. (Integral a, Bounded a) => a -> Builder ()
B.int Int32
x) ;}
instance Print Int64   where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Int64 -> Builder ()
toUTF8BuilderP Int
p Int64
x = Bool -> Builder () -> Builder ()
B.parenWhen (Int
p forall a. Ord a => a -> a -> Bool
> Int
6 Bool -> Bool -> Bool
&& Int64
x forall a. Ord a => a -> a -> Bool
< Int64
0) (forall a. (Integral a, Bounded a) => a -> Builder ()
B.int Int64
x) ;}
instance Print Word    where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Word -> Builder ()
toUTF8BuilderP Int
_ = forall a. (Integral a, Bounded a) => a -> Builder ()
B.int;}
instance Print Word8   where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Word8 -> Builder ()
toUTF8BuilderP Int
_ = forall a. (Integral a, Bounded a) => a -> Builder ()
B.int;}
instance Print Word16  where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Word16 -> Builder ()
toUTF8BuilderP Int
_ = forall a. (Integral a, Bounded a) => a -> Builder ()
B.int;}
instance Print Word32  where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Word32 -> Builder ()
toUTF8BuilderP Int
_ = forall a. (Integral a, Bounded a) => a -> Builder ()
B.int;}
instance Print Word64  where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Word64 -> Builder ()
toUTF8BuilderP Int
_ = forall a. (Integral a, Bounded a) => a -> Builder ()
B.int;}
instance Print Integer  where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Integer -> Builder ()
toUTF8BuilderP Int
p Integer
x = Bool -> Builder () -> Builder ()
B.parenWhen (Int
p forall a. Ord a => a -> a -> Bool
> Int
6 Bool -> Bool -> Bool
&& Integer
x forall a. Ord a => a -> a -> Bool
< Integer
0) (Integer -> Builder ()
B.integer Integer
x) ;}
instance Print Natural  where {{-# INLINE toUTF8BuilderP #-}; toUTF8BuilderP :: Int -> Natural -> Builder ()
toUTF8BuilderP Int
_ = Integer -> Builder ()
B.integer forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral}
instance Print 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 Print () where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> () -> Builder ()
toUTF8BuilderP Int
_ () = Builder ()
"()"
instance Print Version where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Version -> Builder ()
toUTF8BuilderP Int
_ = String -> Builder ()
B.stringUTF8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
instance Print Text where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Text -> Builder ()
toUTF8BuilderP Int
_ = Text -> Builder ()
escapeTextJSON
escapeTextJSON :: T.Text -> B.Builder ()
{-# INLINABLE 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 forall a. Eq a => a -> a -> Bool
== Int
lforall a. Num a => a -> a -> a
+Int
2   
        then do
            forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray RealWorld Word8
mba Int
i DOUBLE_QUOTE
            forall (m :: * -> *) a.
(PrimMonad m, Prim a) =>
MutablePrimArray (PrimState m) a
-> Int -> PrimArray a -> Int -> Int -> m ()
copyPrimArray MutablePrimArray RealWorld Word8
mba (Int
iforall a. Num a => a -> a -> a
+Int
1) PrimArray Word8
ba Int
s Int
l
            forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray RealWorld Word8
mba (Int
iforall a. Num a => a -> a -> a
+Int
1forall a. Num a => a -> a -> a
+Int
l) DOUBLE_QUOTE
        else 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 (unsafeCoerce# :: forall a b. a -> b
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 Print Sci.Scientific where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Scientific -> Builder ()
toUTF8BuilderP Int
p Scientific
x = Bool -> Builder () -> Builder ()
B.parenWhen (Int
p forall a. Ord a => a -> a -> Bool
> Int
6 Bool -> Bool -> Bool
&& Scientific
x forall a. Ord a => a -> a -> Bool
< Scientific
0) (Scientific -> Builder ()
B.scientific Scientific
x)
instance Print a => Print [a] where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> [a] -> Builder ()
toUTF8BuilderP Int
_ = Builder () -> Builder ()
B.square forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Builder () -> (a -> Builder ()) -> [a] -> Builder ()
B.intercalateList Builder ()
B.comma (forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0)
instance Print a => Print (A.Array a) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Array a -> Builder ()
toUTF8BuilderP Int
_ = Builder () -> Builder ()
B.square forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (v :: * -> *) a.
Vec v a =>
Builder () -> (a -> Builder ()) -> v a -> Builder ()
B.intercalateVec Builder ()
B.comma (forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0)
instance Print a => Print (A.SmallArray a) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> SmallArray a -> Builder ()
toUTF8BuilderP Int
_ = Builder () -> Builder ()
B.square forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (v :: * -> *) a.
Vec v a =>
Builder () -> (a -> Builder ()) -> v a -> Builder ()
B.intercalateVec Builder ()
B.comma (forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0)
instance (A.PrimUnlifted a, Print a) => Print (A.UnliftedArray a) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> UnliftedArray a -> Builder ()
toUTF8BuilderP Int
_ = Builder () -> Builder ()
B.square forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (v :: * -> *) a.
Vec v a =>
Builder () -> (a -> Builder ()) -> v a -> Builder ()
B.intercalateVec Builder ()
B.comma (forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0)
instance (Prim a, Print a) => Print (A.PrimArray a) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> PrimArray a -> Builder ()
toUTF8BuilderP Int
_ = Builder () -> Builder ()
B.square forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (v :: * -> *) a.
Vec v a =>
Builder () -> (a -> Builder ()) -> v a -> Builder ()
B.intercalateVec Builder ()
B.comma (forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0)
instance Print a => Print (V.Vector a) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Vector a -> Builder ()
toUTF8BuilderP Int
_ = Builder () -> Builder ()
B.square forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (v :: * -> *) a.
Vec v a =>
Builder () -> (a -> Builder ()) -> v a -> Builder ()
B.intercalateVec Builder ()
B.comma (forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0)
instance (Prim a, Print a) => Print (V.PrimVector a) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> PrimVector a -> Builder ()
toUTF8BuilderP Int
_ = Builder () -> Builder ()
B.square forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (v :: * -> *) a.
Vec v a =>
Builder () -> (a -> Builder ()) -> v a -> Builder ()
B.intercalateVec Builder ()
B.comma (forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0)
instance (Print a, Print b) => Print (a, b) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> (a, b) -> Builder ()
toUTF8BuilderP Int
_ (a
a, b
b) = Builder () -> Builder ()
B.paren forall a b. (a -> b) -> a -> b
$  forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 a
a
                     forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 b
b
instance (Print a, Print b, Print c) => Print (a, b, c) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> (a, b, c) -> Builder ()
toUTF8BuilderP Int
_ (a
a, b
b, c
c) = Builder () -> Builder ()
B.paren forall a b. (a -> b) -> a -> b
$  forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 a
a
                     forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 b
b
                     forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 c
c
instance (Print a, Print b, Print c, Print d) => Print (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 forall a b. (a -> b) -> a -> b
$  forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 a
a
                     forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 b
b
                     forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 c
c
                     forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 d
d
instance (Print a, Print b, Print c, Print d, Print e) => Print (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 forall a b. (a -> b) -> a -> b
$  forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 a
a
                     forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 b
b
                     forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 c
c
                     forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 d
d
                     forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 e
e
instance (Print a, Print b, Print c, Print d, Print e, Print f) => Print (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 forall a b. (a -> b) -> a -> b
$  forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 a
a
                     forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 b
b
                     forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 c
c
                     forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 d
d
                     forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 e
e
                     forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 f
f
instance (Print a, Print b, Print c, Print d, Print e, Print f, Print g) => Print (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 forall a b. (a -> b) -> a -> b
$  forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 a
a
                     forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 b
b
                     forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 c
c
                     forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 d
d
                     forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 e
e
                     forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 f
f
                     forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
B.comma forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
0 g
g
instance Print a => Print (Maybe a) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Maybe a -> Builder ()
toUTF8BuilderP Int
p (Just a
x) = Bool -> Builder () -> Builder ()
B.parenWhen (Int
p forall a. Ord a => a -> a -> Bool
> Int
10) forall a b. (a -> b) -> a -> b
$ Builder ()
"Just " forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
11 a
x
    toUTF8BuilderP Int
_ Maybe a
_        = Builder ()
"Nothing"
instance (Print a, Print b) => Print (Either a b) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Either a b -> Builder ()
toUTF8BuilderP Int
p (Left a
x) = Bool -> Builder () -> Builder ()
B.parenWhen (Int
p forall a. Ord a => a -> a -> Bool
> Int
10) forall a b. (a -> b) -> a -> b
$ Builder ()
"Left " forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
11 a
x
    toUTF8BuilderP Int
p (Right b
x) = Bool -> Builder () -> Builder ()
B.parenWhen (Int
p forall a. Ord a => a -> a -> Bool
> Int
10) forall a b. (a -> b) -> a -> b
$ Builder ()
"Right " forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
11 b
x
instance (Print a, Integral a) => Print (Ratio a) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Ratio a -> Builder ()
toUTF8BuilderP Int
p Ratio a
r = Bool -> Builder () -> Builder ()
B.parenWhen (Int
p forall a. Ord a => a -> a -> Bool
> Int
7) forall a b. (a -> b) -> a -> b
$ do
        forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
8 (forall a. Ratio a -> a
numerator Ratio a
r)
        Builder ()
" % "
        forall a. Print a => Int -> a -> Builder ()
toUTF8BuilderP Int
8 (forall a. Ratio a -> a
denominator Ratio a
r)
instance HasResolution a => Print (Fixed a) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Fixed a -> Builder ()
toUTF8BuilderP Int
_ = String -> Builder ()
B.string8 forall b c a. (b -> c) -> (a -> b) -> a -> c
.  forall a. Show a => a -> String
show
instance Print CallStack where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> CallStack -> Builder ()
toUTF8BuilderP Int
_ = String -> Builder ()
B.string8 forall b c a. (b -> c) -> (a -> b) -> a -> c
.  forall a. Show a => a -> String
show
deriving newtype instance Print CChar
deriving newtype instance Print CSChar
deriving newtype instance Print CUChar
deriving newtype instance Print CShort
deriving newtype instance Print CUShort
deriving newtype instance Print CInt
deriving newtype instance Print CUInt
deriving newtype instance Print CLong
deriving newtype instance Print CULong
deriving newtype instance Print CPtrdiff
deriving newtype instance Print CSize
deriving newtype instance Print CWchar
deriving newtype instance Print CSigAtomic
deriving newtype instance Print CLLong
deriving newtype instance Print CULLong
deriving newtype instance Print CBool
deriving newtype instance Print CIntPtr
deriving newtype instance Print CUIntPtr
deriving newtype instance Print CIntMax
deriving newtype instance Print CUIntMax
deriving newtype instance Print CClock
deriving newtype instance Print CTime
deriving newtype instance Print CUSeconds
deriving newtype instance Print CSUSeconds
deriving newtype instance Print CFloat
deriving newtype instance Print CDouble
instance Print (Ptr a) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Ptr a -> Builder ()
toUTF8BuilderP Int
_ (Ptr Addr#
a) =
        Builder ()
"0x" forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. (FiniteBits a, Integral a) => a -> Builder ()
B.hex (Word# -> Word
W# (Int# -> Word#
int2Word#(Addr# -> Int#
addr2Int# Addr#
a)))
instance Print (ForeignPtr a) where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> ForeignPtr a -> Builder ()
toUTF8BuilderP Int
_ (ForeignPtr Addr#
a ForeignPtrContents
_) =
        Builder ()
"0x" forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. (FiniteBits a, Integral a) => a -> Builder ()
B.hex (Word# -> Word
W# (Int# -> Word#
int2Word#(Addr# -> Int#
addr2Int# Addr#
a)))
deriving anyclass instance Print ExitCode
deriving anyclass instance Print a => Print (Semigroup.Min a)
deriving anyclass instance Print a => Print (Semigroup.Max a)
deriving anyclass instance Print a => Print (Semigroup.First a)
deriving anyclass instance Print a => Print (Semigroup.Last a)
deriving anyclass instance Print a => Print (Semigroup.WrappedMonoid a)
deriving anyclass instance Print a => Print (Semigroup.Dual a)
deriving anyclass instance Print a => Print (Monoid.First a)
deriving anyclass instance Print a => Print (Monoid.Last a)
deriving anyclass instance Print a => Print (NonEmpty a)
deriving anyclass instance Print a => Print (Identity a)
deriving anyclass instance Print a => Print (Const a b)
deriving anyclass instance Print (Proxy a)
deriving anyclass instance Print b => Print (Tagged a b)
deriving anyclass instance Print (f (g a)) => Print (Compose f g a)
deriving anyclass instance (Print (f a), Print (g a)) => Print (Product f g a)
deriving anyclass instance (Print (f a), Print (g a), Print a) => Print (Sum f g a)
instance Print UTCTime where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> UTCTime -> Builder ()
toUTF8BuilderP Int
_ = UTCTime -> Builder ()
B.utcTime
instance Print ZonedTime where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> ZonedTime -> Builder ()
toUTF8BuilderP Int
_ = ZonedTime -> Builder ()
B.zonedTime
instance Print Day where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> Day -> Builder ()
toUTF8BuilderP Int
_ = Day -> Builder ()
B.day
instance Print LocalTime where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> LocalTime -> Builder ()
toUTF8BuilderP Int
_ = LocalTime -> Builder ()
B.localTime
instance Print TimeOfDay where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> TimeOfDay -> Builder ()
toUTF8BuilderP Int
_ = TimeOfDay -> Builder ()
B.timeOfDay
instance Print NominalDiffTime where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> NominalDiffTime -> Builder ()
toUTF8BuilderP Int
_ = Scientific -> Builder ()
B.scientific' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Real a, Fractional b) => a -> b
realToFrac
instance Print DiffTime where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> DiffTime -> Builder ()
toUTF8BuilderP Int
_ = Scientific -> Builder ()
B.scientific' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Real a, Fractional b) => a -> b
realToFrac
instance Print SystemTime where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> SystemTime -> Builder ()
toUTF8BuilderP Int
p (MkSystemTime Int64
s Word32
ns) = Bool -> Builder () -> Builder ()
B.parenWhen (Int
p forall a. Ord a => a -> a -> Bool
> Int
10) forall a b. (a -> b) -> a -> b
$ do
        Builder ()
"MkSystemTime {systemSeconds = "
        forall a. (Integral a, Bounded a) => a -> Builder ()
B.int Int64
s
        Builder ()
", systemNanoseconds = "
        forall a. (Integral a, Bounded a) => a -> Builder ()
B.int Word32
ns
        Builder ()
"}"
instance Print CalendarDiffTime where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> CalendarDiffTime -> Builder ()
toUTF8BuilderP Int
p (CalendarDiffTime Integer
m NominalDiffTime
nt) = Bool -> Builder () -> Builder ()
B.parenWhen (Int
p forall a. Ord a => a -> a -> Bool
> Int
10) forall a b. (a -> b) -> a -> b
$ do
        forall a. Unaligned a => a -> Builder ()
B.encodePrim Word8
LETTER_P
        Integer -> Builder ()
B.integer Integer
m
        forall a. Unaligned a => a -> Builder ()
B.encodePrim (Word8
LETTER_M, Word8
LETTER_T)
        Scientific -> Builder ()
B.scientific' (forall a b. (Real a, Fractional b) => a -> b
realToFrac NominalDiffTime
nt)
        forall a. Unaligned a => a -> Builder ()
B.encodePrim Word8
LETTER_S
instance Print CalendarDiffDays where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> CalendarDiffDays -> Builder ()
toUTF8BuilderP Int
p (CalendarDiffDays Integer
m Integer
d) = Bool -> Builder () -> Builder ()
B.parenWhen (Int
p forall a. Ord a => a -> a -> Bool
> Int
10) forall a b. (a -> b) -> a -> b
$ do
        forall a. Unaligned a => a -> Builder ()
B.encodePrim Word8
LETTER_P
        Integer -> Builder ()
B.integer Integer
m
        forall a. Unaligned a => a -> Builder ()
B.encodePrim Word8
LETTER_M
        Integer -> Builder ()
B.integer Integer
d
        forall a. Unaligned a => a -> Builder ()
B.encodePrim Word8
LETTER_D
instance Print DayOfWeek where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> DayOfWeek -> Builder ()
toUTF8BuilderP Int
_ DayOfWeek
Monday    = Builder ()
"Monday"
    toUTF8BuilderP Int
_ DayOfWeek
Tuesday   = Builder ()
"Tuesday"
    toUTF8BuilderP Int
_ DayOfWeek
Wednesday = Builder ()
"Wednesday"
    toUTF8BuilderP Int
_ DayOfWeek
Thursday  = Builder ()
"Thursday"
    toUTF8BuilderP Int
_ DayOfWeek
Friday    = Builder ()
"Friday"
    toUTF8BuilderP Int
_ DayOfWeek
Saturday  = Builder ()
"Saturday"
    toUTF8BuilderP Int
_ DayOfWeek
Sunday    = Builder ()
"Sunday"
instance Print SomeException where
    {-# INLINE toUTF8BuilderP #-}
    toUTF8BuilderP :: Int -> SomeException -> Builder ()
toUTF8BuilderP Int
p SomeException
x = String -> Builder ()
B.stringUTF8 forall a b. (a -> b) -> a -> b
$ forall a. Show a => Int -> a -> ShowS
showsPrec Int
p SomeException
x String
""