{-# LANGUAGE MagicHash, CPP, UnboxedTuples #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE LambdaCase #-}
----------------------------------------------------------------------------

-- |

-- Module      :  Mason.Builder

-- Copyright   :  (c) Fumiaki Kinoshita 2019-

-- License     :  BSD3

--

-- Maintainer  :  Fumiaki Kinoshita <fumiexcel@gmail.com>

--

----------------------------------------------------------------------------

module Mason.Builder
  ( Builder
  , BuilderFor
  , Buildable
  -- * Runners

  , StrictByteStringBackend
  , toStrictByteString
  , LazyByteStringBackend
  , toLazyByteString
  , BufferedIOBackend
  , hPutBuilderLen
  , hPutBuilder
  , sendBuilder
  , withPopper
  , StreamingBackend
  , toStreamingBody
  -- * Primitives

  , flush
  -- * Bytes

  , byteString
  , lazyByteString
  , shortByteString
  -- * Text

  , textUtf8
  , encodeUtf8Builder
  , encodeUtf8BuilderEscaped
  , char7
  , string7
  , char8
  , string8
  , charUtf8
  , stringUtf8
  -- * Primitive

  , storable
  , int8
  , word8
  , int16LE
  , int32LE
  , int64LE
  , word16LE
  , word32LE
  , word64LE
  , floatLE
  , doubleLE
  , int16BE
  , int32BE
  , int64BE
  , word16BE
  , word32BE
  , word64BE
  , floatBE
  , doubleBE
  -- * Numeral

  , floatDec
  , doubleDec
  , doubleSI
  , doubleExp
  , doubleFixed
  , word8Dec
  , word16Dec
  , word32Dec
  , word64Dec
  , wordDec
  , int8Dec
  , int16Dec
  , int32Dec
  , int64Dec
  , intDec
  , intDecPadded
  , integerDec
  , word8Hex
  , word16Hex
  , word32Hex
  , word64Hex
  , wordHex
  , int8HexFixed
  , int16HexFixed
  , int32HexFixed
  , int64HexFixed
  , word8HexFixed
  , word16HexFixed
  , word32HexFixed
  , word64HexFixed
  , floatHexFixed
  , doubleHexFixed
  , byteStringHex
  , lazyByteStringHex
  -- * Variable-length encoding

  , intVLQ
  , intVLQBP
  , wordVLQ
  , wordVLQBP
  , prefixVarInt
  , prefixVarIntBP
  -- * Combinators

  , intersperse
  , Mason.Builder.unwords
  , Mason.Builder.unlines
  , viaShow
  -- * Advanced

  , paddedBoundedPrim
  , zeroPaddedBoundedPrim
  , primFixed
  , primBounded
  , lengthPrefixedWithin

  ) where

import Control.Monad
import qualified Data.Array as A
import Data.Bits
import Data.Foldable (toList)
import Data.Word
import Data.Int
import qualified Data.Text as T
import Foreign.C.Types
import Foreign.Ptr (Ptr, plusPtr, castPtr)
import Foreign.Storable
import qualified Data.ByteString as B
import qualified Data.ByteString.Internal as B
import qualified Data.ByteString.Lazy as BL
import Mason.Builder.Internal as B
import qualified Data.ByteString.Builder.Prim as P
import qualified Data.ByteString.Builder.Prim.Internal as P
#if !MIN_VERSION_bytestring(0,10,12)
import Data.ByteString.Builder.Prim (boudedPrim)
#endif
import System.IO (Handle)

-- | Put the content of a 'Builder' to a 'Handle'.

hPutBuilder :: Handle -> BuilderFor PutEnv -> IO ()
hPutBuilder :: Handle -> BuilderFor PutEnv -> IO ()
hPutBuilder Handle
h BuilderFor PutEnv
b = forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ Handle -> BuilderFor PutEnv -> IO Int
hPutBuilderLen Handle
h BuilderFor PutEnv
b
{-# INLINE hPutBuilder #-}

-- | Combine chunks of a lazy 'BL.ByteString'

lazyByteString :: BL.ByteString -> Builder
lazyByteString :: ByteString -> Builder
lazyByteString ByteString
x = forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap forall s. Buildable s => ByteString -> BuilderFor s
byteString (ByteString -> [ByteString]
BL.toChunks ByteString
x)
{-# INLINE lazyByteString #-}

------------------------------------------------------------------------------

-- Binary encodings

------------------------------------------------------------------------------


-- | Encode a single signed byte as-is.

--

{-# INLINE int8 #-}
int8 :: Int8 -> Builder
int8 :: Int8 -> Builder
int8 Int8
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Int8
P.int8 Int8
x

-- | Encode a single unsigned byte as-is.

--

{-# INLINE word8 #-}
word8 :: Word8 -> Builder
word8 :: Word8 -> Builder
word8 Word8
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Word8
P.word8 Word8
x


------------------------------------------------------------------------------

-- Binary little-endian encodings

------------------------------------------------------------------------------


-- | Encode an 'Int16' in little endian format.

{-# INLINE int16LE #-}
int16LE :: Int16 -> Builder
int16LE :: Int16 -> Builder
int16LE Int16
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Int16
P.int16LE Int16
x

-- | Encode an 'Int32' in little endian format.

{-# INLINE int32LE #-}
int32LE :: Int32 -> Builder
int32LE :: Int32 -> Builder
int32LE Int32
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Int32
P.int32LE Int32
x

-- | Encode an 'Int64' in little endian format.

{-# INLINE int64LE #-}
int64LE :: Int64 -> Builder
int64LE :: Int64 -> Builder
int64LE Int64
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Int64
P.int64LE Int64
x

-- | Encode a 'Word16' in little endian format.

{-# INLINE word16LE #-}
word16LE :: Word16 -> Builder
word16LE :: Word16 -> Builder
word16LE Word16
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Word16
P.word16LE Word16
x

-- | Encode a 'Word32' in little endian format.

{-# INLINE word32LE #-}
word32LE :: Word32 -> Builder
word32LE :: Word32 -> Builder
word32LE Word32
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Word32
P.word32LE Word32
x

-- | Encode a 'Word64' in little endian format.

{-# INLINE word64LE #-}
word64LE :: Word64 -> Builder
word64LE :: Word64 -> Builder
word64LE Word64
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Word64
P.word64LE Word64
x

-- | Encode a 'Float' in little endian format.

{-# INLINE floatLE #-}
floatLE :: Float -> Builder
floatLE :: Float -> Builder
floatLE Float
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Float
P.floatLE Float
x

-- | Encode a 'Double' in little endian format.

{-# INLINE doubleLE #-}
doubleLE :: Double -> Builder
doubleLE :: Double -> Builder
doubleLE Double
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Double
P.doubleLE Double
x


------------------------------------------------------------------------------

-- Binary big-endian encodings

------------------------------------------------------------------------------


-- | Encode an 'Int16' in big endian format.

{-# INLINE int16BE #-}
int16BE :: Int16 -> Builder
int16BE :: Int16 -> Builder
int16BE Int16
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Int16
P.int16BE Int16
x

-- | Encode an 'Int32' in big endian format.

{-# INLINE int32BE #-}
int32BE :: Int32 -> Builder
int32BE :: Int32 -> Builder
int32BE Int32
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Int32
P.int32BE Int32
x

-- | Encode an 'Int64' in big endian format.

{-# INLINE int64BE #-}
int64BE :: Int64 -> Builder
int64BE :: Int64 -> Builder
int64BE Int64
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Int64
P.int64BE Int64
x

-- | Encode a 'Word16' in big endian format.

{-# INLINE word16BE #-}
word16BE :: Word16 -> Builder
word16BE :: Word16 -> Builder
word16BE Word16
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Word16
P.word16BE Word16
x

-- | Encode a 'Word32' in big endian format.

{-# INLINE word32BE #-}
word32BE :: Word32 -> Builder
word32BE :: Word32 -> Builder
word32BE Word32
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Word32
P.word32BE Word32
x

-- | Encode a 'Word64' in big endian format.

{-# INLINE word64BE #-}
word64BE :: Word64 -> Builder
word64BE :: Word64 -> Builder
word64BE Word64
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Word64
P.word64BE Word64
x

-- | Encode a 'Float' in big endian format.

{-# INLINE floatBE #-}
floatBE :: Float -> Builder
floatBE :: Float -> Builder
floatBE Float
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Float
P.floatBE Float
x

-- | Encode a 'Double' in big endian format.

{-# INLINE doubleBE #-}
doubleBE :: Double -> Builder
doubleBE :: Double -> Builder
doubleBE Double
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Double
P.doubleBE Double
x

------------------------------------------------------------------------------

-- ASCII encoding

------------------------------------------------------------------------------


-- | Char7 encode a 'Char'.

{-# INLINE char7 #-}
char7 :: Char -> Builder
char7 :: Char -> Builder
char7 Char
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Char
P.char7 Char
x

-- | Char7 encode a 'String'.

{-# INLINE string7 #-}
string7 :: String -> Builder
string7 :: String -> Builder
string7 String
x = forall (t :: * -> *) s a.
(Foldable t, Buildable s) =>
FixedPrim a -> t a -> BuilderFor s
B.primMapListFixed FixedPrim Char
P.char7 String
x

------------------------------------------------------------------------------

-- ISO/IEC 8859-1 encoding

------------------------------------------------------------------------------


-- | Char8 encode a 'Char'.

{-# INLINE char8 #-}
char8 :: Char -> Builder
char8 :: Char -> Builder
char8 Char
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Char
P.char8 Char
x

-- | Char8 encode a 'String'.

{-# INLINE string8 #-}
string8 :: String -> Builder
string8 :: String -> Builder
string8 String
x = forall (t :: * -> *) s a.
(Foldable t, Buildable s) =>
FixedPrim a -> t a -> BuilderFor s
B.primMapListFixed FixedPrim Char
P.char8 String
x

------------------------------------------------------------------------------

-- UTF-8 encoding

------------------------------------------------------------------------------


-- | UTF-8 encode a 'Char'.

{-# INLINE charUtf8 #-}
charUtf8 :: Char -> Builder
charUtf8 :: Char -> Builder
charUtf8 Char
x = forall s a. Buildable s => BoundedPrim a -> a -> BuilderFor s
B.primBounded BoundedPrim Char
P.charUtf8 Char
x

-- | Encode 'T.Text' as a UTF-8 byte stream. Synonym for 'textUtf8'.

encodeUtf8Builder :: T.Text -> Builder
encodeUtf8Builder :: Text -> Builder
encodeUtf8Builder Text
x = Text -> Builder
textUtf8 Text
x
{-# INLINE encodeUtf8Builder #-}

-- | Encode 'T.Text' as a UTF-8 byte stream.

textUtf8 :: T.Text -> Builder
textUtf8 :: Text -> Builder
textUtf8 Text
x = forall s. Buildable s => BoundedPrim Word8 -> Text -> BuilderFor s
B.encodeUtf8BuilderEscaped (forall a. FixedPrim a -> BoundedPrim a
P.liftFixedToBounded FixedPrim Word8
P.word8) Text
x
{-# INLINE textUtf8 #-}

--------------------

-- Unsigned integers

--------------------


-- | Decimal encoding of a 'Word8' using the ASCII digits.

{-# INLINE word8Dec #-}
word8Dec :: Word8 -> Builder
word8Dec :: Word8 -> Builder
word8Dec Word8
x = forall s a. Buildable s => BoundedPrim a -> a -> BuilderFor s
B.primBounded BoundedPrim Word8
P.word8Dec Word8
x

-- | Decimal encoding of a 'Word16' using the ASCII digits.

{-# INLINE word16Dec #-}
word16Dec :: Word16 -> Builder
word16Dec :: Word16 -> Builder
word16Dec Word16
x = forall s a. Buildable s => BoundedPrim a -> a -> BuilderFor s
B.primBounded BoundedPrim Word16
P.word16Dec Word16
x

-- | Decimal encoding of a 'Word32' using the ASCII digits.

{-# INLINE word32Dec #-}
word32Dec :: Word32 -> Builder
word32Dec :: Word32 -> Builder
word32Dec Word32
x = forall s a. Buildable s => BoundedPrim a -> a -> BuilderFor s
B.primBounded BoundedPrim Word32
P.word32Dec Word32
x

-- | Decimal encoding of a 'Word64' using the ASCII digits.

{-# INLINE word64Dec #-}
word64Dec :: Word64 -> Builder
word64Dec :: Word64 -> Builder
word64Dec Word64
x = forall s a. Buildable s => BoundedPrim a -> a -> BuilderFor s
B.primBounded BoundedPrim Word64
P.word64Dec Word64
x

-- | Decimal encoding of a 'Word' using the ASCII digits.

{-# INLINE wordDec #-}
wordDec :: Word -> Builder
wordDec :: Word -> Builder
wordDec Word
x = forall s a. Buildable s => BoundedPrim a -> a -> BuilderFor s
B.primBounded BoundedPrim Word
P.wordDec Word
x

-- Floating point numbers

-------------------------


-- | /Currently slow./ Decimal encoding of an IEEE 'Float'.

{-# INLINE floatDec #-}
floatDec :: Float -> Builder
floatDec :: Float -> Builder
floatDec Float
x = String -> Builder
string7 (forall a. Show a => a -> String
show Float
x)

wrapDoubleDec :: Double -> (Double -> Builder) -> Builder
wrapDoubleDec :: Double -> (Double -> Builder) -> Builder
wrapDoubleDec Double
x Double -> Builder
k
  | forall a. RealFloat a => a -> Bool
isNaN Double
x = String -> Builder
string7 String
"NaN"
  | forall a. RealFloat a => a -> Bool
isInfinite Double
x = if Double
x forall a. Ord a => a -> a -> Bool
< Double
0 then String -> Builder
string7 String
"-Infinity" else String -> Builder
string7 String
"Infinity"
  | forall a. RealFloat a => a -> Bool
isNegativeZero Double
x = Char -> Builder
char7 Char
'-' forall a. Semigroup a => a -> a -> a
<> Double -> Builder
k Double
0.0
  | Double
x forall a. Ord a => a -> a -> Bool
< Double
0 = Char -> Builder
char7 Char
'-' forall a. Semigroup a => a -> a -> a
<> Double -> Builder
k (-Double
x)
  | Bool
otherwise = Double -> Builder
k Double
x
{-# INLINE wrapDoubleDec #-}

-- | Decimal encoding of an IEEE 'Double'.

{-# INLINE doubleDec #-}
doubleDec :: Double -> Builder
doubleDec :: Double -> Builder
doubleDec Double
val = Double -> (Double -> Builder) -> Builder
wrapDoubleDec Double
val forall a b. (a -> b) -> a -> b
$ \case
  Double
0 -> String -> Builder
string7 String
"0.0"
  Double
x -> forall {s}. Buildable s => Double -> BuilderFor s
grisu Double
x
  where
    grisu :: Double -> BuilderFor s
grisu Double
v = forall s.
Buildable s =>
Int -> (Ptr Word8 -> IO (Ptr Word8)) -> BuilderFor s
withPtr Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr Word8
ptr -> do
      CInt
n <- Double -> Ptr Word8 -> IO CInt
dtoa_grisu3 Double
v Ptr Word8
ptr
      forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
ptr (forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
n)

foreign import ccall unsafe "static dtoa_grisu3"
  dtoa_grisu3 :: Double -> Ptr Word8 -> IO CInt

-- | Attach an SI prefix so that abs(mantissa) is within [1, 1000). Omits c, d, da and h.

doubleSI :: Int -- ^ precision: must be equal or greater than 3

  -> Double
  -> Builder
doubleSI :: Int -> Double -> Builder
doubleSI Int
prec Double
_ | Int
prec forall a. Ord a => a -> a -> Bool
< Int
3 = forall a. HasCallStack => String -> a
error String
"Mason.Builder.doubleSI: precision less than 3"
doubleSI Int
prec Double
val = Double -> (Double -> Builder) -> Builder
wrapDoubleDec Double
val forall a b. (a -> b) -> a -> b
$ \case
  Double
0 -> Int -> Builder
zeroes Int
prec
  Double
val' -> forall s. (s -> Buffer -> IO Buffer) -> BuilderFor s
Builder forall a b. (a -> b) -> a -> b
$ \s
env Buffer
buf -> forall r.
Int -> Double -> (Ptr Word8 -> Int -> Int -> IO r) -> IO r
withGrisu3Rounded Int
prec Double
val' forall a b. (a -> b) -> a -> b
$ \Ptr Word8
ptr Int
len Int
e -> do
    let (Int
pindex, Int
dp) = forall a. Integral a => a -> a -> (a, a)
divMod (Int
e forall a. Num a => a -> a -> a
- Int
1) Int
3
    forall a. Show a => a -> IO ()
print (Int
dp, Int
prec, Int
len)
    let mantissa :: BuilderFor s
mantissa
          -- when the decimal separator would be at the end

          | Int
dp forall a. Num a => a -> a -> a
+ Int
1 forall a. Eq a => a -> a -> Bool
== Int
prec = forall s.
Buildable s =>
Int -> (Ptr Word8 -> IO (Ptr Word8)) -> BuilderFor s
withPtr (Int
prec forall a. Num a => a -> a -> a
+ Int
dp forall a. Num a => a -> a -> a
- Int
2) forall a b. (a -> b) -> a -> b
$ \Ptr Word8
dst -> do
            Ptr Word8
_ <- Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)
B.memset Ptr Word8
dst Word8
48 forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
prec forall a. Num a => a -> a -> a
+ Int
dp forall a. Num a => a -> a -> a
- Int
2)
            Ptr Word8 -> Ptr Word8 -> Int -> IO ()
B.memcpy Ptr Word8
dst Ptr Word8
ptr forall a b. (a -> b) -> a -> b
$ forall a. Ord a => a -> a -> a
min Int
len Int
prec
            forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Ptr Word8
dst forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
prec forall a. Num a => a -> a -> a
+ Int
dp forall a. Num a => a -> a -> a
- Int
2)
          | Bool
otherwise = forall s.
Buildable s =>
Int -> (Ptr Word8 -> IO (Ptr Word8)) -> BuilderFor s
withPtr (Int
prec forall a. Num a => a -> a -> a
+ Int
1) forall a b. (a -> b) -> a -> b
$ \Ptr Word8
dst -> do
            Ptr Word8
_ <- Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)
B.memset Ptr Word8
dst Word8
48 forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
prec forall a. Num a => a -> a -> a
+ Int
1)
            Ptr Word8 -> Ptr Word8 -> Int -> IO ()
B.memcpy Ptr Word8
dst Ptr Word8
ptr forall a b. (a -> b) -> a -> b
$ forall a. Ord a => a -> a -> a
min Int
len forall a b. (a -> b) -> a -> b
$ Int
dp forall a. Num a => a -> a -> a
+ Int
1
            forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
dst (Int
dp forall a. Num a => a -> a -> a
+ Int
1) Word8
46
            Ptr Word8 -> Ptr Word8 -> Int -> IO ()
B.memcpy (Ptr Word8
dst forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
dp forall a. Num a => a -> a -> a
+ Int
2)) (Ptr Word8
ptr forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
dp forall a. Num a => a -> a -> a
+ Int
1)) forall a b. (a -> b) -> a -> b
$ forall a. Ord a => a -> a -> a
max Int
0 forall a b. (a -> b) -> a -> b
$ Int
len forall a. Num a => a -> a -> a
- Int
dp forall a. Num a => a -> a -> a
- Int
1
            forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Ptr Word8
dst forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
prec forall a. Num a => a -> a -> a
+ Int
1)
    let prefix :: BuilderFor s
prefix
          | Int
pindex forall a. Eq a => a -> a -> Bool
== Int
0 = forall a. Monoid a => a
mempty
          | Int
pindex forall a. Ord a => a -> a -> Bool
> Int
8 Bool -> Bool -> Bool
|| Int
pindex forall a. Ord a => a -> a -> Bool
< (-Int
8) = Char -> Builder
char7 Char
'e' forall a. Semigroup a => a -> a -> a
<> Int -> Builder
intDec (Int
3 forall a. Num a => a -> a -> a
* Int
pindex)
          | Bool
otherwise = Char -> Builder
charUtf8 (Array Int Char
prefices forall i e. Ix i => Array i e -> i -> e
A.! Int
pindex)
    forall s. BuilderFor s -> s -> Buffer -> IO Buffer
unBuilder (BuilderFor s
mantissa forall a. Semigroup a => a -> a -> a
<> BuilderFor s
prefix) s
env Buffer
buf
  where
    prefices :: Array Int Char
prefices = forall i e. Ix i => (i, i) -> [e] -> Array i e
A.listArray (-Int
8,Int
8) String
"yzafpnμm\NULkMGTPEZY"

zeroes :: Int -> Builder
zeroes :: Int -> Builder
zeroes Int
n = forall s.
Buildable s =>
Int -> (Ptr Word8 -> IO (Ptr Word8)) -> BuilderFor s
withPtr (Int
n forall a. Num a => a -> a -> a
+ Int
1) forall a b. (a -> b) -> a -> b
$ \Ptr Word8
dst -> do
  Ptr Word8
_ <- Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)
B.memset Ptr Word8
dst Word8
48 forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Int
n forall a. Num a => a -> a -> a
+ Int
1
  forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
dst Int
1 Word8
46
  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Ptr Word8
dst forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
n forall a. Num a => a -> a -> a
+ Int
1)

-- | Always use exponents

doubleExp :: Int -- ^ number of digits in the mantissa

  -> Double
  -> Builder
doubleExp :: Int -> Double -> Builder
doubleExp Int
prec Double
_ | Int
prec forall a. Ord a => a -> a -> Bool
< Int
1 = forall a. HasCallStack => String -> a
error String
"Mason.Builder.doubleFixed: precision too small"
doubleExp Int
prec Double
val = Double -> (Double -> Builder) -> Builder
wrapDoubleDec Double
val forall a b. (a -> b) -> a -> b
$ \case
  Double
0 -> Int -> Builder
zeroes Int
prec forall a. Semigroup a => a -> a -> a
<> String -> Builder
string7 String
"e0"
  Double
val' -> forall s. (s -> Buffer -> IO Buffer) -> BuilderFor s
Builder forall a b. (a -> b) -> a -> b
$ \s
env Buffer
buf -> forall r.
Int -> Double -> (Ptr Word8 -> Int -> Int -> IO r) -> IO r
withGrisu3Rounded Int
prec Double
val' forall a b. (a -> b) -> a -> b
$ \Ptr Word8
ptr Int
len Int
dp -> do
    let len' :: Int
len' = Int
1 forall a. Num a => a -> a -> a
+ Int
prec

    Word8
firstDigit <- forall a. Storable a => Ptr a -> IO a
peek Ptr Word8
ptr

    forall s. BuilderFor s -> s -> Buffer -> IO Buffer
unBuilder (forall s.
Buildable s =>
Int -> (Ptr Word8 -> IO (Ptr Word8)) -> BuilderFor s
withPtr Int
len' (\Ptr Word8
dst -> do
      Ptr Word8
_ <- Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)
B.memset Ptr Word8
dst Word8
48 forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len'
      forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word8
dst Word8
firstDigit
      forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word8
dst forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1) (Word8
46 :: Word8)
      Ptr Word8 -> Ptr Word8 -> Int -> IO ()
B.memcpy (Ptr Word8
dst forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
2) (Ptr Word8
ptr forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1) (forall a. Ord a => a -> a -> a
min (Int
len forall a. Num a => a -> a -> a
- Int
1) Int
len')
      forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Word8
dst forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
len'))
      forall a. Semigroup a => a -> a -> a
<> Char -> Builder
char7 Char
'e' forall a. Semigroup a => a -> a -> a
<> Int -> Builder
intDec (Int
dp forall a. Num a => a -> a -> a
- Int
1)) s
env Buffer
buf

-- | Fixed precision

doubleFixed :: Int -- ^ decimal points

  -> Double
  -> Builder
doubleFixed :: Int -> Double -> Builder
doubleFixed Int
0 Double
val = Int -> Builder
intDec (forall a b. (RealFrac a, Integral b) => a -> b
round Double
val)
doubleFixed Int
prec Double
_ | Int
prec forall a. Ord a => a -> a -> Bool
< Int
0 = forall a. HasCallStack => String -> a
error String
"Mason.Builder.doubleFixed: negative precision"
doubleFixed Int
prec Double
val = Double -> (Double -> Builder) -> Builder
wrapDoubleDec Double
val forall a b. (a -> b) -> a -> b
$ \case
  Double
0 -> Int -> Builder
zeroes (Int
prec forall a. Num a => a -> a -> a
+ Int
1)
  Double
val' -> forall s. (s -> Buffer -> IO Buffer) -> BuilderFor s
Builder forall a b. (a -> b) -> a -> b
$ \s
env Buffer
buf -> forall r.
Double -> IO r -> (Ptr Word8 -> Int -> Int -> IO r) -> IO r
withGrisu3 Double
val' (forall s. BuilderFor s -> s -> Buffer -> IO Buffer
unBuilder (Double -> Builder
doubleDec Double
val) s
env Buffer
buf) forall a b. (a -> b) -> a -> b
$ \Ptr Word8
ptr0 Int
len Int
e0 -> do
    Bool
bump <- Int -> Int -> Ptr Word8 -> IO Bool
roundDigit (Int
prec forall a. Num a => a -> a -> a
+ Int
e0) Int
len Ptr Word8
ptr0
    let dp :: Int
dp
          | Bool
bump = Int
e0 forall a. Num a => a -> a -> a
+ Int
1
          | Bool
otherwise = Int
e0
    let ptr :: Ptr Word8
ptr
          | Bool
bump = Ptr Word8
ptr0
          | Bool
otherwise = Ptr Word8
ptr0 forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1
    let len' :: Int
len' = Int
1 forall a. Num a => a -> a -> a
+ Int
prec forall a. Num a => a -> a -> a
+ forall a. Ord a => a -> a -> a
max Int
1 Int
dp

    forall s. BuilderFor s -> s -> Buffer -> IO Buffer
unBuilder (forall s.
Buildable s =>
Int -> (Ptr Word8 -> IO (Ptr Word8)) -> BuilderFor s
withPtr Int
len' forall a b. (a -> b) -> a -> b
$ \Ptr Word8
dst -> do
      Ptr Word8
_ <- Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)
B.memset Ptr Word8
dst Word8
48 forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len'
      if Int
dp forall a. Ord a => a -> a -> Bool
>= Int
1
        then do
          Ptr Word8 -> Ptr Word8 -> Int -> IO ()
B.memcpy Ptr Word8
dst Ptr Word8
ptr forall a b. (a -> b) -> a -> b
$ forall a. Ord a => a -> a -> a
min Int
len Int
dp
          forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
dst Int
dp Word8
46
          Ptr Word8 -> Ptr Word8 -> Int -> IO ()
B.memcpy (Ptr Word8
dst forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
dp forall a. Num a => a -> a -> a
+ Int
1)) (Ptr Word8
ptr forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
dp) forall a b. (a -> b) -> a -> b
$ forall a. Ord a => a -> a -> a
max Int
0 (Int
len forall a. Num a => a -> a -> a
- Int
dp)
        else do
          forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
dst Int
1 Word8
46
          Ptr Word8 -> Ptr Word8 -> Int -> IO ()
B.memcpy (Ptr Word8
dst forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
2 forall a. Num a => a -> a -> a
- Int
dp)) Ptr Word8
ptr Int
len
      forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Ptr Word8
dst forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
len'
      ) s
env Buffer
buf

------------------------------------------------------------------------------

-- Decimal Encoding

------------------------------------------------------------------------------


-- Signed integers

------------------


-- | Decimal encoding of an 'Int8' using the ASCII digits.

--

-- e.g.

--

-- > toLazyByteString (int8Dec 42)   = "42"

-- > toLazyByteString (int8Dec (-1)) = "-1"

--

{-# INLINE int8Dec #-}
int8Dec :: Int8 -> Builder
int8Dec :: Int8 -> Builder
int8Dec Int8
x = forall s a. Buildable s => BoundedPrim a -> a -> BuilderFor s
B.primBounded BoundedPrim Int8
P.int8Dec Int8
x

-- | Decimal encoding of an 'Int16' using the ASCII digits.

{-# INLINE int16Dec #-}
int16Dec :: Int16 -> Builder
int16Dec :: Int16 -> Builder
int16Dec Int16
x = forall s a. Buildable s => BoundedPrim a -> a -> BuilderFor s
B.primBounded BoundedPrim Int16
P.int16Dec Int16
x

-- | Decimal encoding of an 'Int32' using the ASCII digits.

{-# INLINE int32Dec #-}
int32Dec :: Int32 -> Builder
int32Dec :: Int32 -> Builder
int32Dec Int32
x = forall s a. Buildable s => BoundedPrim a -> a -> BuilderFor s
B.primBounded BoundedPrim Int32
P.int32Dec Int32
x

-- | Decimal encoding of an 'Int64' using the ASCII digits.

{-# INLINE int64Dec #-}
int64Dec :: Int64 -> Builder
int64Dec :: Int64 -> Builder
int64Dec Int64
x = forall s a. Buildable s => BoundedPrim a -> a -> BuilderFor s
B.primBounded BoundedPrim Int64
P.int64Dec Int64
x

-- | Decimal encoding of an 'Int' using the ASCII digits.

{-# INLINE intDec #-}
intDec :: Int -> Builder
intDec :: Int -> Builder
intDec Int
x = forall s a. Buildable s => BoundedPrim a -> a -> BuilderFor s
B.primBounded BoundedPrim Int
P.intDec Int
x

-- | 'intDec' with 0 padding

intDecPadded :: Int -> Int -> Builder
intDecPadded :: Int -> Int -> Builder
intDecPadded Int
n = forall a. Int -> BoundedPrim a -> a -> Builder
zeroPaddedBoundedPrim Int
n BoundedPrim Int
P.intDec
{-# INLINE intDecPadded #-}

------------------------------------------------------------------------------

-- Hexadecimal Encoding

------------------------------------------------------------------------------


-- without lead

---------------


-- | Shortest hexadecimal encoding of a 'Word8' using lower-case characters.

{-# INLINE word8Hex #-}
word8Hex :: Word8 -> Builder
word8Hex :: Word8 -> Builder
word8Hex Word8
x = forall s a. Buildable s => BoundedPrim a -> a -> BuilderFor s
B.primBounded BoundedPrim Word8
P.word8Hex Word8
x

-- | Shortest hexadecimal encoding of a 'Word16' using lower-case characters.

{-# INLINE word16Hex #-}
word16Hex :: Word16 -> Builder
word16Hex :: Word16 -> Builder
word16Hex Word16
x = forall s a. Buildable s => BoundedPrim a -> a -> BuilderFor s
B.primBounded BoundedPrim Word16
P.word16Hex Word16
x

-- | Shortest hexadecimal encoding of a 'Word32' using lower-case characters.

{-# INLINE word32Hex #-}
word32Hex :: Word32 -> Builder
word32Hex :: Word32 -> Builder
word32Hex Word32
x = forall s a. Buildable s => BoundedPrim a -> a -> BuilderFor s
B.primBounded BoundedPrim Word32
P.word32Hex Word32
x

-- | Shortest hexadecimal encoding of a 'Word64' using lower-case characters.

{-# INLINE word64Hex #-}
word64Hex :: Word64 -> Builder
word64Hex :: Word64 -> Builder
word64Hex Word64
x = forall s a. Buildable s => BoundedPrim a -> a -> BuilderFor s
B.primBounded BoundedPrim Word64
P.word64Hex Word64
x

-- | Shortest hexadecimal encoding of a 'Word' using lower-case characters.

{-# INLINE wordHex #-}
wordHex :: Word -> Builder
wordHex :: Word -> Builder
wordHex Word
x = forall s a. Buildable s => BoundedPrim a -> a -> BuilderFor s
B.primBounded BoundedPrim Word
P.wordHex Word
x

-- fixed width; leading zeroes

------------------------------


-- | Encode a 'Int8' using 2 nibbles (hexadecimal digits).

{-# INLINE int8HexFixed #-}
int8HexFixed :: Int8 -> Builder
int8HexFixed :: Int8 -> Builder
int8HexFixed Int8
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Int8
P.int8HexFixed Int8
x

-- | Encode a 'Int16' using 4 nibbles.

{-# INLINE int16HexFixed #-}
int16HexFixed :: Int16 -> Builder
int16HexFixed :: Int16 -> Builder
int16HexFixed Int16
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Int16
P.int16HexFixed Int16
x

-- | Encode a 'Int32' using 8 nibbles.

{-# INLINE int32HexFixed #-}
int32HexFixed :: Int32 -> Builder
int32HexFixed :: Int32 -> Builder
int32HexFixed Int32
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Int32
P.int32HexFixed Int32
x

-- | Encode a 'Int64' using 16 nibbles.

{-# INLINE int64HexFixed #-}
int64HexFixed :: Int64 -> Builder
int64HexFixed :: Int64 -> Builder
int64HexFixed Int64
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Int64
P.int64HexFixed Int64
x

-- | Encode a 'Word8' using 2 nibbles (hexadecimal digits).

{-# INLINE word8HexFixed #-}
word8HexFixed :: Word8 -> Builder
word8HexFixed :: Word8 -> Builder
word8HexFixed Word8
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Word8
P.word8HexFixed Word8
x

-- | Encode a 'Word16' using 4 nibbles.

{-# INLINE word16HexFixed #-}
word16HexFixed :: Word16 -> Builder
word16HexFixed :: Word16 -> Builder
word16HexFixed Word16
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Word16
P.word16HexFixed Word16
x

-- | Encode a 'Word32' using 8 nibbles.

{-# INLINE word32HexFixed #-}
word32HexFixed :: Word32 -> Builder
word32HexFixed :: Word32 -> Builder
word32HexFixed Word32
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Word32
P.word32HexFixed Word32
x

-- | Encode a 'Word64' using 16 nibbles.

{-# INLINE word64HexFixed #-}
word64HexFixed :: Word64 -> Builder
word64HexFixed :: Word64 -> Builder
word64HexFixed Word64
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Word64
P.word64HexFixed Word64
x

-- | Encode an IEEE 'Float' using 8 nibbles.

{-# INLINE floatHexFixed #-}
floatHexFixed :: Float -> Builder
floatHexFixed :: Float -> Builder
floatHexFixed Float
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Float
P.floatHexFixed Float
x

-- | Encode an IEEE 'Double' using 16 nibbles.

{-# INLINE doubleHexFixed #-}
doubleHexFixed :: Double -> Builder
doubleHexFixed :: Double -> Builder
doubleHexFixed Double
x = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
B.primFixed FixedPrim Double
P.doubleHexFixed Double
x

-- | Encode each byte of a 'S.ByteString' using its fixed-width hex encoding.

{-# NOINLINE byteStringHex #-} -- share code

byteStringHex :: B.ByteString -> Builder
byteStringHex :: ByteString -> Builder
byteStringHex ByteString
x = forall s.
Buildable s =>
FixedPrim Word8 -> ByteString -> BuilderFor s
B.primMapByteStringFixed FixedPrim Word8
P.word8HexFixed ByteString
x

-- | Encode each byte of a lazy 'L.ByteString' using its fixed-width hex encoding.

{-# NOINLINE lazyByteStringHex #-} -- share code

lazyByteStringHex :: BL.ByteString -> Builder
lazyByteStringHex :: ByteString -> Builder
lazyByteStringHex ByteString
x = forall s.
Buildable s =>
FixedPrim Word8 -> ByteString -> BuilderFor s
B.primMapLazyByteStringFixed FixedPrim Word8
P.word8HexFixed ByteString
x

-- | Select an implementation depending on the bit-size of 'Word's.

-- Currently, it produces a runtime failure if the bitsize is different.

-- This is detected by the testsuite.

{-# INLINE caseWordSize_32_64 #-}
caseWordSize_32_64 :: a -- Value to use for 32-bit 'Word's

                   -> a -- Value to use for 64-bit 'Word's

                   -> a
caseWordSize_32_64 :: forall a. a -> a -> a
caseWordSize_32_64 a
f32 a
f64 =
#if MIN_VERSION_base(4,7,0)
  case forall b. FiniteBits b => b -> Int
finiteBitSize (forall a. HasCallStack => a
undefined :: Word) of
#else
  case bitSize (undefined :: Word) of
#endif
    Int
32 -> a
f32
    Int
64 -> a
f64
    Int
s  -> forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"caseWordSize_32_64: unsupported Word bit-size " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
s

maxPow10 :: Integer
maxPow10 :: Integer
maxPow10 = forall a. Integral a => a -> Integer
toInteger forall a b. (a -> b) -> a -> b
$ (Int
10 :: Int) forall a b. (Num a, Integral b) => a -> b -> a
^ forall a. a -> a -> a
caseWordSize_32_64 (Int
9 :: Int) Int
18

-- | Decimal encoding of an 'Integer' using the ASCII digits.

-- Simon Meier's improved implementation from https://github.com/haskell/bytestring/commit/92f19a5d94761042b44a433d7331107611e4d717

integerDec :: Integer -> Builder
integerDec :: Integer -> Builder
integerDec Integer
i
    | Int
i' <- forall a. Num a => Integer -> a
fromInteger Integer
i, forall a. Integral a => a -> Integer
toInteger Int
i' forall a. Eq a => a -> a -> Bool
== Integer
i = Int -> Builder
intDec Int
i'
    | Integer
i forall a. Ord a => a -> a -> Bool
< Integer
0     = forall s a. Buildable s => FixedPrim a -> a -> BuilderFor s
primFixed FixedPrim Char
P.char8 Char
'-' forall a. Monoid a => a -> a -> a
`mappend` Integer -> Builder
go (-Integer
i)
    | Bool
otherwise =                                   Integer -> Builder
go Integer
i
  where
    errImpossible :: String -> a
errImpossible String
fun =
        forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"integerDec: " forall a. [a] -> [a] -> [a]
++ String
fun forall a. [a] -> [a] -> [a]
++ String
": the impossible happened."

    go :: Integer -> Builder
    go :: Integer -> Builder
go Integer
n | Integer
n forall a. Ord a => a -> a -> Bool
< Integer
maxPow10 = Int -> Builder
intDec (forall a. Num a => Integer -> a
fromInteger Integer
n)
         | Bool
otherwise    =
             case [Integer] -> [Int]
putH (Integer -> Integer -> [Integer]
splitf (Integer
maxPow10 forall a. Num a => a -> a -> a
* Integer
maxPow10) Integer
n) of
               (Int
x:[Int]
xs) -> Int -> Builder
intDec Int
x forall a. Monoid a => a -> a -> a
`mappend` forall s a. Buildable s => BoundedPrim a -> [a] -> BuilderFor s
primMapListBounded BoundedPrim Int
intDecPadded18 [Int]
xs
               []     -> forall {a}. String -> a
errImpossible String
"integerDec: go"

    splitf :: Integer -> Integer -> [Integer]
    splitf :: Integer -> Integer -> [Integer]
splitf Integer
pow10 Integer
n0
      | Integer
pow10 forall a. Ord a => a -> a -> Bool
> Integer
n0  = [Integer
n0]
      | Bool
otherwise   = [Integer] -> [Integer]
splith (Integer -> Integer -> [Integer]
splitf (Integer
pow10 forall a. Num a => a -> a -> a
* Integer
pow10) Integer
n0)
      where
        splith :: [Integer] -> [Integer]
splith []     = forall {a}. String -> a
errImpossible String
"splith"
        splith (Integer
n:[Integer]
ns) =
            case Integer
n forall a. Integral a => a -> a -> (a, a)
`quotRem` Integer
pow10 of
                (Integer
q,Integer
r) | Integer
q forall a. Ord a => a -> a -> Bool
> Integer
0     -> Integer
q forall a. a -> [a] -> [a]
: Integer
r forall a. a -> [a] -> [a]
: [Integer] -> [Integer]
splitb [Integer]
ns
                      | Bool
otherwise ->     Integer
r forall a. a -> [a] -> [a]
: [Integer] -> [Integer]
splitb [Integer]
ns

        splitb :: [Integer] -> [Integer]
splitb []     = []
        splitb (Integer
n:[Integer]
ns) = case Integer
n forall a. Integral a => a -> a -> (a, a)
`quotRem` Integer
pow10 of
                            (Integer
q,Integer
r) -> Integer
q forall a. a -> [a] -> [a]
: Integer
r forall a. a -> [a] -> [a]
: [Integer] -> [Integer]
splitb [Integer]
ns

    putH :: [Integer] -> [Int]
    putH :: [Integer] -> [Int]
putH []     = forall {a}. String -> a
errImpossible String
"putH"
    putH (Integer
n:[Integer]
ns) = case Integer
n forall a. Integral a => a -> a -> (a, a)
`quotRem` Integer
maxPow10 of
                    (Integer
x,Integer
y)
                        | Int
q forall a. Ord a => a -> a -> Bool
> Int
0     -> Int
q forall a. a -> [a] -> [a]
: Int
r forall a. a -> [a] -> [a]
: [Integer] -> [Int]
putB [Integer]
ns
                        | Bool
otherwise ->     Int
r forall a. a -> [a] -> [a]
: [Integer] -> [Int]
putB [Integer]
ns
                        where q :: Int
q = forall a. Num a => Integer -> a
fromInteger Integer
x
                              r :: Int
r = forall a. Num a => Integer -> a
fromInteger Integer
y

    putB :: [Integer] -> [Int]
    putB :: [Integer] -> [Int]
putB []     = []
    putB (Integer
n:[Integer]
ns) = case Integer
n forall a. Integral a => a -> a -> (a, a)
`quotRem` Integer
maxPow10 of
                    (Integer
q,Integer
r) -> forall a. Num a => Integer -> a
fromInteger Integer
q forall a. a -> [a] -> [a]
: forall a. Num a => Integer -> a
fromInteger Integer
r forall a. a -> [a] -> [a]
: [Integer] -> [Int]
putB [Integer]
ns
{-# INLINE integerDec #-}

foreign import ccall unsafe "static _hs_bytestring_int_dec_padded9"
    c_int_dec_padded9 :: CInt -> Ptr Word8 -> IO ()

foreign import ccall unsafe "static _hs_bytestring_long_long_int_dec_padded18"
    c_long_long_int_dec_padded18 :: CLLong -> Ptr Word8 -> IO ()

{-# INLINE intDecPadded18 #-}
intDecPadded18 :: P.BoundedPrim Int
intDecPadded18 :: BoundedPrim Int
intDecPadded18 = forall a. FixedPrim a -> BoundedPrim a
P.liftFixedToBounded forall a b. (a -> b) -> a -> b
$ forall a. a -> a -> a
caseWordSize_32_64
    (forall a. Int -> (a -> Ptr Word8 -> IO ()) -> FixedPrim a
P.fixedPrim  Int
9 forall a b. (a -> b) -> a -> b
$ CInt -> Ptr Word8 -> IO ()
c_int_dec_padded9            forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral)
    (forall a. Int -> (a -> Ptr Word8 -> IO ()) -> FixedPrim a
P.fixedPrim Int
18 forall a b. (a -> b) -> a -> b
$ CLLong -> Ptr Word8 -> IO ()
c_long_long_int_dec_padded18 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral)

#if !MIN_VERSION_bytestring(0,10,12)
boundedPrim :: Int -> (a -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim a
boundedPrim = boudedPrim
#endif

-- Variable-length encoding

----


-- | Signed VLQ encoding (the first bit is a sign)

intVLQ :: Int -> Builder
intVLQ :: Int -> Builder
intVLQ Int
x = forall s a. Buildable s => BoundedPrim a -> a -> BuilderFor s
primBounded BoundedPrim Int
intVLQBP Int
x
{-# INLINE intVLQ #-}

intVLQBP :: P.BoundedPrim Int
intVLQBP :: BoundedPrim Int
intVLQBP = forall a.
Int -> (a -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim a
P.boundedPrim Int
10 Int -> Ptr Word8 -> IO (Ptr Word8)
writeIntFinite
{-# INLINE CONLIKE intVLQBP #-}

-- | Unsigned VLQ encoding

wordVLQ :: Word -> Builder
wordVLQ :: Word -> Builder
wordVLQ Word
x = forall s a. Buildable s => BoundedPrim a -> a -> BuilderFor s
primBounded BoundedPrim Word
wordVLQBP Word
x

wordVLQBP :: P.BoundedPrim Word
wordVLQBP :: BoundedPrim Word
wordVLQBP = forall a.
Int -> (a -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim a
P.boundedPrim Int
10 (forall a r.
(Bits a, Integral a) =>
(Ptr Word8 -> IO r) -> a -> Ptr Word8 -> IO r
writeUnsignedFinite forall (f :: * -> *) a. Applicative f => a -> f a
pure)

writeWord8 :: Word8 -> Ptr Word8 -> IO (Ptr Word8)
writeWord8 :: Word8 -> Ptr Word8 -> IO (Ptr Word8)
writeWord8 Word8
w Ptr Word8
p = do
  forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word8
p Word8
w
  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Word8
p Int
1

writeIntFinite :: Int -> Ptr Word8 -> IO (Ptr Word8)
writeIntFinite :: Int -> Ptr Word8 -> IO (Ptr Word8)
writeIntFinite Int
n
  | Int
n forall a. Ord a => a -> a -> Bool
< Int
0 = case forall a. Num a => a -> a
negate Int
n of
    Int
n'
      | Int
n' forall a. Ord a => a -> a -> Bool
< Int
0x40 -> Word8 -> Ptr Word8 -> IO (Ptr Word8)
writeWord8 (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n' forall a. Bits a => a -> Int -> a
`setBit` Int
6)
      | Bool
otherwise ->
          Word8 -> Ptr Word8 -> IO (Ptr Word8)
writeWord8 (Word8
0xc0 forall a. Bits a => a -> a -> a
.|. forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n') forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=>
            forall a r.
(Bits a, Integral a) =>
(Ptr Word8 -> IO r) -> a -> Ptr Word8 -> IO r
writeUnsignedFinite forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Bits a => a -> Int -> a
unsafeShiftR Int
n' Int
6)
  | Int
n forall a. Ord a => a -> a -> Bool
< Int
0x40 = Word8 -> Ptr Word8 -> IO (Ptr Word8)
writeWord8 (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n)
  | Bool
otherwise = Word8 -> Ptr Word8 -> IO (Ptr Word8)
writeWord8 (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n forall a. Bits a => a -> Int -> a
`setBit` Int
7 forall a. Bits a => a -> Int -> a
`clearBit` Int
6) forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=>
      forall a r.
(Bits a, Integral a) =>
(Ptr Word8 -> IO r) -> a -> Ptr Word8 -> IO r
writeUnsignedFinite forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a. Bits a => a -> Int -> a
unsafeShiftR Int
n Int
6)
{-# INLINE writeIntFinite #-}

writeUnsignedFinite :: (Bits a, Integral a) => (Ptr Word8 -> IO r) -> a -> Ptr Word8 -> IO r
writeUnsignedFinite :: forall a r.
(Bits a, Integral a) =>
(Ptr Word8 -> IO r) -> a -> Ptr Word8 -> IO r
writeUnsignedFinite Ptr Word8 -> IO r
k = forall {t}. (Integral t, Bits t) => t -> Ptr Word8 -> IO r
go
  where
    go :: t -> Ptr Word8 -> IO r
go t
m
      | t
m forall a. Ord a => a -> a -> Bool
< t
0x80 = Word8 -> Ptr Word8 -> IO (Ptr Word8)
writeWord8 (forall a b. (Integral a, Num b) => a -> b
fromIntegral t
m) forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Ptr Word8 -> IO r
k
      | Bool
otherwise = Word8 -> Ptr Word8 -> IO (Ptr Word8)
writeWord8 (forall a. Bits a => a -> Int -> a
setBit (forall a b. (Integral a, Num b) => a -> b
fromIntegral t
m) Int
7) forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> t -> Ptr Word8 -> IO r
go (forall a. Bits a => a -> Int -> a
unsafeShiftR t
m Int
7)
{-# INLINE writeUnsignedFinite #-}

-- | Encode a Word in <https://github.com/stoklund/varint#prefixvarint PrefixVarInt>

prefixVarInt :: Word -> Builder
prefixVarInt :: Word -> Builder
prefixVarInt Word
x = forall s a. Buildable s => BoundedPrim a -> a -> BuilderFor s
primBounded BoundedPrim Word
prefixVarIntBP Word
x

prefixVarIntBP :: P.BoundedPrim Word
prefixVarIntBP :: BoundedPrim Word
prefixVarIntBP = forall a.
Int -> (a -> Ptr Word8 -> IO (Ptr Word8)) -> BoundedPrim a
P.boundedPrim Int
9 forall a b. (a -> b) -> a -> b
$ \Word
x Ptr Word8
ptr0 -> do
  let bits :: Int
bits = Int
64 forall a. Num a => a -> a -> a
- forall b. FiniteBits b => b -> Int
countLeadingZeros (Word
x forall a. Bits a => a -> a -> a
.|. Word
1)
  if Int
bits forall a. Ord a => a -> a -> Bool
> Int
56
    then do
      forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word8
ptr0 Word8
0
      forall a. Storable a => Ptr a -> a -> IO ()
poke (forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
ptr0 forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1) Word
x
      forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! Ptr Word8
ptr0 forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
9
    else do
      let bytes :: Int
bytes = Int
1 forall a. Num a => a -> a -> a
+ (Int
bits forall a. Num a => a -> a -> a
- Int
1) forall a. Integral a => a -> a -> a
`div` Int
7
      let end :: Ptr b
end = Ptr Word8
ptr0 forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
bytes
      let go :: Ptr b -> t -> IO (Ptr b)
go Ptr b
ptr t
n
            | Ptr b
ptr forall a. Eq a => a -> a -> Bool
== forall {b}. Ptr b
end = forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr b
ptr
            | Bool
otherwise = do
              forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr b
ptr (forall a b. (Integral a, Num b) => a -> b
fromIntegral t
n forall a. Bits a => a -> a -> a
.&. b
0xff)
              Ptr b -> t -> IO (Ptr b)
go (Ptr b
ptr forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1) (t
n forall a. Bits a => a -> Int -> a
`shiftR` Int
8)
      forall {b} {t}.
(Storable b, Integral t, Bits b, Bits t, Num b) =>
Ptr b -> t -> IO (Ptr b)
go Ptr Word8
ptr0 forall a b. (a -> b) -> a -> b
$! (Word
2 forall a. Num a => a -> a -> a
* Word
x forall a. Num a => a -> a -> a
+ Word
1) forall a. Bits a => a -> Int -> a
`shiftL` (Int
bytes forall a. Num a => a -> a -> a
- Int
1)
{-# INLINE CONLIKE prefixVarIntBP #-}

intersperse :: (Foldable f, Buildable e) => BuilderFor e -> f (BuilderFor e) -> BuilderFor e
intersperse :: forall (f :: * -> *) e.
(Foldable f, Buildable e) =>
BuilderFor e -> f (BuilderFor e) -> BuilderFor e
intersperse BuilderFor e
d = [BuilderFor e] -> BuilderFor e
go forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
toList where
  go :: [BuilderFor e] -> BuilderFor e
go (BuilderFor e
x0 : [BuilderFor e]
xs) = BuilderFor e
x0 forall a. Semigroup a => a -> a -> a
<> forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\BuilderFor e
x BuilderFor e
r -> BuilderFor e
d forall a. Semigroup a => a -> a -> a
<> BuilderFor e
x forall a. Semigroup a => a -> a -> a
<> BuilderFor e
r) forall a. Monoid a => a
mempty [BuilderFor e]
xs
  go [] = forall a. Monoid a => a
mempty
{-# INLINE intersperse #-}

unwords :: (Foldable f, Buildable e) => f (BuilderFor e) -> BuilderFor e
unwords :: forall (f :: * -> *) e.
(Foldable f, Buildable e) =>
f (BuilderFor e) -> BuilderFor e
unwords = forall (f :: * -> *) e.
(Foldable f, Buildable e) =>
BuilderFor e -> f (BuilderFor e) -> BuilderFor e
intersperse (Word8 -> Builder
word8 Word8
32)
{-# INLINE unwords #-}

unlines :: (Foldable f, Buildable e) => f (BuilderFor e) -> BuilderFor e
unlines :: forall (f :: * -> *) e.
(Foldable f, Buildable e) =>
f (BuilderFor e) -> BuilderFor e
unlines = forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (forall a. Semigroup a => a -> a -> a
<>Word8 -> Builder
word8 Word8
10)
{-# INLINE unlines #-}

-- | Turn a value into a 'Builder' using the 'Show' instance.

viaShow :: Show a => a -> Builder
viaShow :: forall a. Show a => a -> Builder
viaShow a
x = String -> Builder
string8 (forall a. Show a => a -> String
show a
x)
{-# INLINE viaShow #-}