{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE UnboxedTuples #-}

module Data.Bytes.Builder
  ( -- * Bounded Primitives
    Builder
  , fromBounded

    -- * Evaluation
  , run
  , runOnto
  , runOntoLength
  , reversedOnto
  , putMany
  , putManyConsLength

    -- * Materialized Byte Sequences
  , bytes
  , chunks
  , copy
  , copyCons
  , copy2
  , insert
  , byteArray
  , shortByteString
  , textUtf8
  , textJsonString
  , shortTextUtf8
  , shortTextJsonString
  , cstring
  , cstring#
  , cstringLen
  , stringUtf8

    -- * Byte Sequence Encodings
  , sevenEightRight
  , sevenEightSmile

    -- * Encode Integral Types

    -- ** Human-Readable
  , word64Dec
  , word32Dec
  , word16Dec
  , word8Dec
  , wordDec
  , naturalDec
  , int64Dec
  , int32Dec
  , int16Dec
  , int8Dec
  , intDec
  , integerDec

    -- * Unsigned Words

    -- ** 64-bit
  , word64PaddedUpperHex

    -- ** 32-bit
  , word32PaddedUpperHex

    -- ** 16-bit
  , word16PaddedUpperHex
  , word16PaddedLowerHex
  , word16LowerHex
  , word16UpperHex

    -- ** 8-bit
  , word8PaddedUpperHex
  , word8LowerHex
  , ascii
  , ascii2
  , ascii3
  , ascii4
  , ascii5
  , ascii6
  , ascii7
  , ascii8
  , char

    -- ** Machine-Readable

    -- *** One
  , word8

    -- **** Big Endian
  , word256BE
  , word128BE
  , word64BE
  , word32BE
  , word16BE
  , int64BE
  , int32BE
  , int16BE

    -- **** Little Endian
  , word256LE
  , word128LE
  , word64LE
  , word32LE
  , word16LE
  , int64LE
  , int32LE
  , int16LE

    -- **** LEB128
  , intLEB128
  , int32LEB128
  , int64LEB128
  , wordLEB128
  , word16LEB128
  , word32LEB128
  , word64LEB128

    -- **** VLQ
  , wordVlq
  , word32Vlq
  , word64Vlq

    -- *** Many
  , word8Array

    -- **** Big Endian
  , word16ArrayBE
  , word32ArrayBE
  , word64ArrayBE
  , word128ArrayBE
  , word256ArrayBE
  , int64ArrayBE
  , int32ArrayBE
  , int16ArrayBE

    -- **** Little Endian
  , word16ArrayLE
  , word32ArrayLE
  , word64ArrayLE
  , word128ArrayLE
  , word256ArrayLE
  , int64ArrayLE
  , int32ArrayLE
  , int16ArrayLE

    -- ** Prefixing with Length
  , consLength
  , consLength32LE
  , consLength32BE
  , consLength64BE

    -- * Encode Floating-Point Types

    -- ** Human-Readable
  , doubleDec

    -- * Replication
  , replicate

    -- * Control
  , flush

    -- * Rebuild
  , rebuild
  ) where

import Prelude hiding (replicate)

import Control.Exception (SomeException, toException)
import Control.Monad.IO.Class (MonadIO, liftIO)
import Control.Monad.ST (ST, runST)
import Data.Bits (unsafeShiftL, unsafeShiftR, (.&.), (.|.))
import Data.ByteString.Short.Internal (ShortByteString (SBS))
import Data.Bytes.Builder.Unsafe
  ( Builder (Builder)
  , BuilderState (BuilderState)
  , Commits (Immutable, Initial, Mutable)
  , addCommitsLength
  , commitDistance1
  , commitsOntoChunks
  , copyReverseCommits
  , cstring
  , fromEffect
  , pasteIO
  , pasteUtf8TextJson#
  , reverseCommitsOntoChunks
  , stringUtf8
  )
import Data.Bytes.Chunks (Chunks (ChunksCons, ChunksNil))
import Data.Bytes.Types (Bytes (Bytes), MutableBytes (MutableBytes))
import Data.Foldable (foldlM)
import Data.Int (Int16, Int32, Int64, Int8)
import Data.Primitive (ByteArray (..), MutableByteArray (..), PrimArray (..))
import Data.Text.Short (ShortText)
import Data.WideWord (Word128, Word256)
import Data.Word (Word16, Word32, Word64, Word8)
import Data.Word.Zigzag (toZigzag32, toZigzag64, toZigzagNative)
import Foreign.C.String (CStringLen)
import GHC.ByteOrder (ByteOrder (BigEndian, LittleEndian), targetByteOrder)
import GHC.Exts (Addr#, ByteArray#, Int (I#), Int#, MutableByteArray#, RealWorld, State#, oneShot, (*#), (+#), (-#), (<#), (>=#))
import GHC.IO (IO (IO), stToIO)
import GHC.Integer.Logarithms.Compat (integerLog2#)
import GHC.Natural (naturalFromInteger, naturalToInteger)
import GHC.ST (ST (ST))
import GHC.Word (Word (W#), Word8 (W8#))
import Numeric.Natural (Natural)

import qualified Compat as C

import qualified Arithmetic.Nat as Nat
import qualified Arithmetic.Types as Arithmetic
import qualified Data.Bytes as Bytes
import qualified Data.Bytes.Builder.Bounded as Bounded
import qualified Data.Bytes.Builder.Bounded.Unsafe as UnsafeBounded
import qualified Data.Primitive as PM
import qualified Data.Text.Short as TS
import qualified GHC.Exts as Exts
import qualified Op as Op

import Data.Text (Text)
import qualified Data.Text.Array as A
import qualified Data.Text.Internal as I

-- | Run a builder.
run ::
  -- | Size of initial chunk (use 4080 if uncertain)
  Int ->
  -- | Builder
  Builder ->
  Chunks
run :: Int -> Builder -> Chunks
run !Int
hint Builder
bldr = Int -> Builder -> Chunks -> Chunks
runOnto Int
hint Builder
bldr Chunks
ChunksNil

{- | Run a builder. The resulting chunks are consed onto the
beginning of an existing sequence of chunks.
-}
runOnto ::
  -- | Size of initial chunk (use 4080 if uncertain)
  Int ->
  -- | Builder
  Builder ->
  -- | Suffix
  Chunks ->
  Chunks
runOnto :: Int -> Builder -> Chunks -> Chunks
runOnto hint :: Int
hint@(I# Int#
hint#) (Builder forall s.
MutableByteArray# s
-> Int#
-> Int#
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
f) Chunks
cs0 = (forall s. ST s Chunks) -> Chunks
forall a. (forall s. ST s a) -> a
runST ((forall s. ST s Chunks) -> Chunks)
-> (forall s. ST s Chunks) -> Chunks
forall a b. (a -> b) -> a -> b
$ do
  MutableByteArray MutableByteArray# s
buf0 <- Int -> ST s (MutableByteArray (PrimState (ST s)))
forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
hint
  Commits s
cs <- STRep s (Commits s) -> ST s (Commits s)
forall s a. STRep s a -> ST s a
ST (STRep s (Commits s) -> ST s (Commits s))
-> STRep s (Commits s) -> ST s (Commits s)
forall a b. (a -> b) -> a -> b
$ \State# s
s0 -> case MutableByteArray# s
-> Int#
-> Int#
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
forall s.
MutableByteArray# s
-> Int#
-> Int#
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
f MutableByteArray# s
buf0 Int#
0# Int#
hint# Commits s
forall s. Commits s
Initial State# s
s0 of
    (# State# s
s1, MutableByteArray# s
bufX, Int#
offX, Int#
_, Commits s
csX #) ->
      (# State# s
s1, MutableByteArray# s -> Int# -> Commits s -> Commits s
forall s. MutableByteArray# s -> Int# -> Commits s -> Commits s
Mutable MutableByteArray# s
bufX Int#
offX Commits s
csX #)
  Chunks -> Commits s -> ST s Chunks
forall s. Chunks -> Commits s -> ST s Chunks
reverseCommitsOntoChunks Chunks
cs0 Commits s
cs

{- | Variant of 'runOnto' that additionally returns the number of bytes
consed onto the suffix.
-}
runOntoLength ::
  -- | Size of initial chunk (use 4080 if uncertain)
  Int ->
  -- | Builder
  Builder ->
  -- | Suffix
  Chunks ->
  (Int, Chunks)
runOntoLength :: Int -> Builder -> Chunks -> (Int, Chunks)
runOntoLength hint :: Int
hint@(I# Int#
hint#) (Builder forall s.
MutableByteArray# s
-> Int#
-> Int#
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
f) Chunks
cs0 = (forall s. ST s (Int, Chunks)) -> (Int, Chunks)
forall a. (forall s. ST s a) -> a
runST ((forall s. ST s (Int, Chunks)) -> (Int, Chunks))
-> (forall s. ST s (Int, Chunks)) -> (Int, Chunks)
forall a b. (a -> b) -> a -> b
$ do
  MutableByteArray MutableByteArray# s
buf0 <- Int -> ST s (MutableByteArray (PrimState (ST s)))
forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
hint
  Commits s
cs <- STRep s (Commits s) -> ST s (Commits s)
forall s a. STRep s a -> ST s a
ST (STRep s (Commits s) -> ST s (Commits s))
-> STRep s (Commits s) -> ST s (Commits s)
forall a b. (a -> b) -> a -> b
$ \State# s
s0 -> case MutableByteArray# s
-> Int#
-> Int#
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
forall s.
MutableByteArray# s
-> Int#
-> Int#
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
f MutableByteArray# s
buf0 Int#
0# Int#
hint# Commits s
forall s. Commits s
Initial State# s
s0 of
    (# State# s
s1, MutableByteArray# s
bufX, Int#
offX, Int#
_, Commits s
csX #) ->
      (# State# s
s1, MutableByteArray# s -> Int# -> Commits s -> Commits s
forall s. MutableByteArray# s -> Int# -> Commits s -> Commits s
Mutable MutableByteArray# s
bufX Int#
offX Commits s
csX #)
  let !n :: Int
n = Int -> Commits s -> Int
forall s. Int -> Commits s -> Int
addCommitsLength Int
0 Commits s
cs
  Chunks
ch <- Chunks -> Commits s -> ST s Chunks
forall s. Chunks -> Commits s -> ST s Chunks
reverseCommitsOntoChunks Chunks
cs0 Commits s
cs
  (Int, Chunks) -> ST s (Int, Chunks)
forall a. a -> ST s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
n, Chunks
ch)

{- | Variant of 'runOnto' that conses the additional chunks
in reverse order.
-}
reversedOnto ::
  -- | Size of initial chunk (use 4080 if uncertain)
  Int ->
  -- | Builder
  Builder ->
  Chunks ->
  Chunks
reversedOnto :: Int -> Builder -> Chunks -> Chunks
reversedOnto hint :: Int
hint@(I# Int#
hint#) (Builder forall s.
MutableByteArray# s
-> Int#
-> Int#
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
f) Chunks
cs0 = (forall s. ST s Chunks) -> Chunks
forall a. (forall s. ST s a) -> a
runST ((forall s. ST s Chunks) -> Chunks)
-> (forall s. ST s Chunks) -> Chunks
forall a b. (a -> b) -> a -> b
$ do
  MutableByteArray MutableByteArray# s
buf0 <- Int -> ST s (MutableByteArray (PrimState (ST s)))
forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
hint
  Commits s
cs <- STRep s (Commits s) -> ST s (Commits s)
forall s a. STRep s a -> ST s a
ST (STRep s (Commits s) -> ST s (Commits s))
-> STRep s (Commits s) -> ST s (Commits s)
forall a b. (a -> b) -> a -> b
$ \State# s
s0 -> case MutableByteArray# s
-> Int#
-> Int#
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
forall s.
MutableByteArray# s
-> Int#
-> Int#
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
f MutableByteArray# s
buf0 Int#
0# Int#
hint# Commits s
forall s. Commits s
Initial State# s
s0 of
    (# State# s
s1, MutableByteArray# s
bufX, Int#
offX, Int#
_, Commits s
csX #) ->
      (# State# s
s1, MutableByteArray# s -> Int# -> Commits s -> Commits s
forall s. MutableByteArray# s -> Int# -> Commits s -> Commits s
Mutable MutableByteArray# s
bufX Int#
offX Commits s
csX #)
  Chunks -> Commits s -> ST s Chunks
forall s. Chunks -> Commits s -> ST s Chunks
commitsOntoChunks Chunks
cs0 Commits s
cs

{- | Run a builder against lots of elements. This fills the same
underlying buffer over and over again. Do not let the argument to
the callback escape from the callback (i.e. do not write it to an
@IORef@). Also, do not @unsafeFreezeByteArray@ any of the mutable
byte arrays in the callback. The intent is that the callback will
write the buffer out.
-}
putMany ::
  (Foldable f) =>
  -- | Size of shared chunk (use 8176 if uncertain)
  Int ->
  -- | Value builder
  (a -> Builder) ->
  -- | Collection of values
  f a ->
  -- | Consume chunks.
  (MutableBytes RealWorld -> IO b) ->
  IO ()
{-# INLINE putMany #-}
putMany :: forall (f :: * -> *) a b.
Foldable f =>
Int
-> (a -> Builder)
-> f a
-> (MutableBytes RealWorld -> IO b)
-> IO ()
putMany Int
hint0 a -> Builder
g f a
xs MutableBytes RealWorld -> IO b
cb = do
  MutableByteArray MutableByteArray# RealWorld
buf0 <- Int -> IO (MutableByteArray (PrimState IO))
forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
hint
  BuilderState MutableByteArray# RealWorld
bufZ Int#
offZ Int#
_ Commits RealWorld
cmtsZ <-
    (BuilderState RealWorld -> a -> IO (BuilderState RealWorld))
-> BuilderState RealWorld -> f a -> IO (BuilderState RealWorld)
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldlM
      ( \BuilderState RealWorld
st0 a
a -> do
          st1 :: BuilderState RealWorld
st1@(BuilderState MutableByteArray# RealWorld
buf Int#
off Int#
_ Commits RealWorld
cmts) <- Builder -> BuilderState RealWorld -> IO (BuilderState RealWorld)
pasteIO (a -> Builder
g a
a) BuilderState RealWorld
st0
          case Commits RealWorld
cmts of
            Commits RealWorld
Initial ->
              if Int# -> Int
I# Int#
off Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
threshold
                then BuilderState RealWorld -> IO (BuilderState RealWorld)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure BuilderState RealWorld
st1
                else do
                  b
_ <- MutableBytes RealWorld -> IO b
cb (MutableByteArray RealWorld -> Int -> Int -> MutableBytes RealWorld
forall s. MutableByteArray s -> Int -> Int -> MutableBytes s
MutableBytes (MutableByteArray# RealWorld -> MutableByteArray RealWorld
forall s. MutableByteArray# s -> MutableByteArray s
MutableByteArray MutableByteArray# RealWorld
buf) Int
0 (Int# -> Int
I# Int#
off))
                  BuilderState RealWorld -> IO (BuilderState RealWorld)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MutableByteArray# RealWorld
-> Int# -> Int# -> Commits RealWorld -> BuilderState RealWorld
forall s.
MutableByteArray# s -> Int# -> Int# -> Commits s -> BuilderState s
BuilderState MutableByteArray# RealWorld
buf0 Int#
0# Int#
hint# Commits RealWorld
forall s. Commits s
Initial)
            Commits RealWorld
_ -> do
              let total :: Int
total = Int -> Commits RealWorld -> Int
forall s. Int -> Commits s -> Int
addCommitsLength (Int# -> Int
I# Int#
off) Commits RealWorld
cmts
                  doff0 :: Int
doff0 = Int
total Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int# -> Int
I# Int#
off
              MutableByteArray RealWorld
large <- Int -> IO (MutableByteArray (PrimState IO))
forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
total
              ST RealWorld () -> IO ()
forall a. ST RealWorld a -> IO a
stToIO (MutableByteArray (PrimState (ST RealWorld))
-> Int
-> MutableByteArray (PrimState (ST RealWorld))
-> Int
-> Int
-> ST RealWorld ()
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> MutableByteArray (PrimState m) -> Int -> Int -> m ()
PM.copyMutableByteArray MutableByteArray RealWorld
MutableByteArray (PrimState (ST RealWorld))
large Int
doff0 (MutableByteArray# RealWorld -> MutableByteArray RealWorld
forall s. MutableByteArray# s -> MutableByteArray s
MutableByteArray MutableByteArray# RealWorld
buf) Int
0 (Int# -> Int
I# Int#
off))
              Int
r <- ST RealWorld Int -> IO Int
forall a. ST RealWorld a -> IO a
stToIO (MutableByteArray RealWorld
-> Int -> Commits RealWorld -> ST RealWorld Int
forall s. MutableByteArray s -> Int -> Commits s -> ST s Int
copyReverseCommits MutableByteArray RealWorld
large Int
doff0 Commits RealWorld
cmts)
              case Int
r of
                Int
0 -> do
                  b
_ <- MutableBytes RealWorld -> IO b
cb (MutableByteArray RealWorld -> Int -> Int -> MutableBytes RealWorld
forall s. MutableByteArray s -> Int -> Int -> MutableBytes s
MutableBytes MutableByteArray RealWorld
large Int
0 Int
total)
                  BuilderState RealWorld -> IO (BuilderState RealWorld)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MutableByteArray# RealWorld
-> Int# -> Int# -> Commits RealWorld -> BuilderState RealWorld
forall s.
MutableByteArray# s -> Int# -> Int# -> Commits s -> BuilderState s
BuilderState MutableByteArray# RealWorld
buf0 Int#
0# Int#
hint# Commits RealWorld
forall s. Commits s
Initial)
                Int
_ -> (State# RealWorld
 -> (# State# RealWorld, BuilderState RealWorld #))
-> IO (BuilderState RealWorld)
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO (\State# RealWorld
s0 -> SomeException
-> State# RealWorld
-> (# State# RealWorld, BuilderState RealWorld #)
forall a b. a -> State# RealWorld -> (# State# RealWorld, b #)
Exts.raiseIO# SomeException
putManyError State# RealWorld
s0)
      )
      (MutableByteArray# RealWorld
-> Int# -> Int# -> Commits RealWorld -> BuilderState RealWorld
forall s.
MutableByteArray# s -> Int# -> Int# -> Commits s -> BuilderState s
BuilderState MutableByteArray# RealWorld
buf0 Int#
0# Int#
hint# Commits RealWorld
forall s. Commits s
Initial)
      f a
xs
  b
_ <- case Commits RealWorld
cmtsZ of
    Commits RealWorld
Initial -> MutableBytes RealWorld -> IO b
cb (MutableByteArray RealWorld -> Int -> Int -> MutableBytes RealWorld
forall s. MutableByteArray s -> Int -> Int -> MutableBytes s
MutableBytes (MutableByteArray# RealWorld -> MutableByteArray RealWorld
forall s. MutableByteArray# s -> MutableByteArray s
MutableByteArray MutableByteArray# RealWorld
bufZ) Int
0 (Int# -> Int
I# Int#
offZ))
    Commits RealWorld
_ -> (State# RealWorld -> (# State# RealWorld, b #)) -> IO b
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO (\State# RealWorld
s0 -> SomeException -> State# RealWorld -> (# State# RealWorld, b #)
forall a b. a -> State# RealWorld -> (# State# RealWorld, b #)
Exts.raiseIO# SomeException
putManyError State# RealWorld
s0)
  () -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
 where
  !hint :: Int
hint@(I# Int#
hint#) = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
hint0 Int
8
  !threshold :: Int
threshold = Int -> Int -> Int
forall a. Integral a => a -> a -> a
div (Int
hint Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
3) Int
4

putManyError :: SomeException
{-# NOINLINE putManyError #-}
putManyError :: SomeException
putManyError =
  IOError -> SomeException
forall e. Exception e => e -> SomeException
toException
    (String -> IOError
userError String
"bytebuild: putMany implementation error")

{- | Variant of 'putMany' that prefixes each pushed array of chunks
with the number of bytes that the chunks in each batch required.
(This excludes the bytes required to encode the length itself.)
This is useful for chunked HTTP encoding.
-}
putManyConsLength ::
  (Foldable f, MonadIO m) =>
  -- | Number of bytes used by the serialization of the length
  Arithmetic.Nat n ->
  -- | Length serialization function
  (Int -> Bounded.Builder n) ->
  -- | Size of shared chunk (use 8176 if uncertain)
  Int ->
  -- | Value builder
  (a -> Builder) ->
  -- | Collection of values
  f a ->
  -- | Consume chunks.
  (MutableBytes RealWorld -> m b) ->
  m ()
{-# INLINE putManyConsLength #-}
putManyConsLength :: forall (f :: * -> *) (m :: * -> *) (n :: Nat) a b.
(Foldable f, MonadIO m) =>
Nat n
-> (Int -> Builder n)
-> Int
-> (a -> Builder)
-> f a
-> (MutableBytes RealWorld -> m b)
-> m ()
putManyConsLength Nat n
n Int -> Builder n
buildSize Int
hint a -> Builder
g f a
xs MutableBytes RealWorld -> m b
cb = do
  let !(I# Int#
n#) = Nat n -> Int
forall (n :: Nat). Nat n -> Int
Nat.demote Nat n
n
  let !(I# Int#
actual#) = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
hint (Int# -> Int
I# Int#
n#)
  let !threshold :: Int
threshold = Int -> Int -> Int
forall a. Integral a => a -> a -> a
div (Int# -> Int
I# Int#
actual# Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
3) Int
4
  MutableByteArray MutableByteArray# RealWorld
buf0 <- IO (MutableByteArray RealWorld) -> m (MutableByteArray RealWorld)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Int -> IO (MutableByteArray (PrimState IO))
forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray (Int# -> Int
I# Int#
actual#))
  BuilderState MutableByteArray# RealWorld
bufZ Int#
offZ Int#
_ Commits RealWorld
cmtsZ <-
    (BuilderState RealWorld -> a -> m (BuilderState RealWorld))
-> BuilderState RealWorld -> f a -> m (BuilderState RealWorld)
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldlM
      ( \BuilderState RealWorld
st0 a
a -> do
          st1 :: BuilderState RealWorld
st1@(BuilderState MutableByteArray# RealWorld
buf Int#
off Int#
_ Commits RealWorld
cmts) <- IO (BuilderState RealWorld) -> m (BuilderState RealWorld)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Builder -> BuilderState RealWorld -> IO (BuilderState RealWorld)
pasteIO (a -> Builder
g a
a) BuilderState RealWorld
st0)
          case Commits RealWorld
cmts of
            Commits RealWorld
Initial ->
              if Int# -> Int
I# Int#
off Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
threshold
                then BuilderState RealWorld -> m (BuilderState RealWorld)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure BuilderState RealWorld
st1
                else do
                  let !dist :: Int#
dist = Int#
off Int# -> Int# -> Int#
-# Int#
n#
                  Int
_ <-
                    IO Int -> m Int
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int -> m Int) -> IO Int -> m Int
forall a b. (a -> b) -> a -> b
$
                      ST RealWorld Int -> IO Int
forall a. ST RealWorld a -> IO a
stToIO (ST RealWorld Int -> IO Int) -> ST RealWorld Int -> IO Int
forall a b. (a -> b) -> a -> b
$
                        Builder n -> MutableByteArray RealWorld -> Int -> ST RealWorld Int
forall (n :: Nat) s.
Builder n -> MutableByteArray s -> Int -> ST s Int
UnsafeBounded.pasteST
                          (Int -> Builder n
buildSize (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int# -> Int
I# Int#
dist)))
                          (MutableByteArray# RealWorld -> MutableByteArray RealWorld
forall s. MutableByteArray# s -> MutableByteArray s
MutableByteArray MutableByteArray# RealWorld
buf0)
                          Int
0
                  b
_ <- MutableBytes RealWorld -> m b
cb (MutableByteArray RealWorld -> Int -> Int -> MutableBytes RealWorld
forall s. MutableByteArray s -> Int -> Int -> MutableBytes s
MutableBytes (MutableByteArray# RealWorld -> MutableByteArray RealWorld
forall s. MutableByteArray# s -> MutableByteArray s
MutableByteArray MutableByteArray# RealWorld
buf) Int
0 (Int# -> Int
I# Int#
off))
                  BuilderState RealWorld -> m (BuilderState RealWorld)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MutableByteArray# RealWorld
-> Int# -> Int# -> Commits RealWorld -> BuilderState RealWorld
forall s.
MutableByteArray# s -> Int# -> Int# -> Commits s -> BuilderState s
BuilderState MutableByteArray# RealWorld
buf0 Int#
n# (Int#
actual# Int# -> Int# -> Int#
-# Int#
n#) Commits RealWorld
forall s. Commits s
Initial)
            Commits RealWorld
_ -> do
              let !dist :: Int#
dist = MutableByteArray# RealWorld
-> Int#
-> MutableByteArray# RealWorld
-> Int#
-> Commits RealWorld
-> Int#
forall s.
MutableByteArray# s
-> Int# -> MutableByteArray# s -> Int# -> Commits s -> Int#
commitDistance1 MutableByteArray# RealWorld
buf0 Int#
n# MutableByteArray# RealWorld
buf Int#
off Commits RealWorld
cmts
              Int
_ <-
                IO Int -> m Int
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int -> m Int) -> IO Int -> m Int
forall a b. (a -> b) -> a -> b
$
                  ST RealWorld Int -> IO Int
forall a. ST RealWorld a -> IO a
stToIO (ST RealWorld Int -> IO Int) -> ST RealWorld Int -> IO Int
forall a b. (a -> b) -> a -> b
$
                    Builder n -> MutableByteArray RealWorld -> Int -> ST RealWorld Int
forall (n :: Nat) s.
Builder n -> MutableByteArray s -> Int -> ST s Int
UnsafeBounded.pasteST
                      (Int -> Builder n
buildSize (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int# -> Int
I# Int#
dist)))
                      (MutableByteArray# RealWorld -> MutableByteArray RealWorld
forall s. MutableByteArray# s -> MutableByteArray s
MutableByteArray MutableByteArray# RealWorld
buf0)
                      Int
0
              let total :: Int
total = Int -> Commits RealWorld -> Int
forall s. Int -> Commits s -> Int
addCommitsLength (Int# -> Int
I# Int#
off) Commits RealWorld
cmts
                  doff0 :: Int
doff0 = Int
total Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int# -> Int
I# Int#
off
              MutableByteArray RealWorld
large <- IO (MutableByteArray RealWorld) -> m (MutableByteArray RealWorld)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Int -> IO (MutableByteArray (PrimState IO))
forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
PM.newByteArray Int
total)
              IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (ST RealWorld () -> IO ()
forall a. ST RealWorld a -> IO a
stToIO (MutableByteArray (PrimState (ST RealWorld))
-> Int
-> MutableByteArray (PrimState (ST RealWorld))
-> Int
-> Int
-> ST RealWorld ()
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> MutableByteArray (PrimState m) -> Int -> Int -> m ()
PM.copyMutableByteArray MutableByteArray RealWorld
MutableByteArray (PrimState (ST RealWorld))
large Int
doff0 (MutableByteArray# RealWorld -> MutableByteArray RealWorld
forall s. MutableByteArray# s -> MutableByteArray s
MutableByteArray MutableByteArray# RealWorld
buf) Int
0 (Int# -> Int
I# Int#
off)))
              Int
r <- IO Int -> m Int
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (ST RealWorld Int -> IO Int
forall a. ST RealWorld a -> IO a
stToIO (MutableByteArray RealWorld
-> Int -> Commits RealWorld -> ST RealWorld Int
forall s. MutableByteArray s -> Int -> Commits s -> ST s Int
copyReverseCommits MutableByteArray RealWorld
large Int
doff0 Commits RealWorld
cmts))
              case Int
r of
                Int
0 -> do
                  b
_ <- MutableBytes RealWorld -> m b
cb (MutableByteArray RealWorld -> Int -> Int -> MutableBytes RealWorld
forall s. MutableByteArray s -> Int -> Int -> MutableBytes s
MutableBytes MutableByteArray RealWorld
large Int
0 Int
total)
                  BuilderState RealWorld -> m (BuilderState RealWorld)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MutableByteArray# RealWorld
-> Int# -> Int# -> Commits RealWorld -> BuilderState RealWorld
forall s.
MutableByteArray# s -> Int# -> Int# -> Commits s -> BuilderState s
BuilderState MutableByteArray# RealWorld
buf0 Int#
n# (Int#
actual# Int# -> Int# -> Int#
-# Int#
n#) Commits RealWorld
forall s. Commits s
Initial)
                Int
_ -> IO (BuilderState RealWorld) -> m (BuilderState RealWorld)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO ((State# RealWorld
 -> (# State# RealWorld, BuilderState RealWorld #))
-> IO (BuilderState RealWorld)
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO (\State# RealWorld
s0 -> SomeException
-> State# RealWorld
-> (# State# RealWorld, BuilderState RealWorld #)
forall a b. a -> State# RealWorld -> (# State# RealWorld, b #)
Exts.raiseIO# SomeException
putManyError State# RealWorld
s0))
      )
      (MutableByteArray# RealWorld
-> Int# -> Int# -> Commits RealWorld -> BuilderState RealWorld
forall s.
MutableByteArray# s -> Int# -> Int# -> Commits s -> BuilderState s
BuilderState MutableByteArray# RealWorld
buf0 Int#
n# (Int#
actual# Int# -> Int# -> Int#
-# Int#
n#) Commits RealWorld
forall s. Commits s
Initial)
      f a
xs
  b
_ <- case Commits RealWorld
cmtsZ of
    Commits RealWorld
Initial -> do
      let !distZ :: Int#
distZ = Int#
offZ Int# -> Int# -> Int#
-# Int#
n#
      Int
_ <-
        IO Int -> m Int
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int -> m Int) -> IO Int -> m Int
forall a b. (a -> b) -> a -> b
$
          ST RealWorld Int -> IO Int
forall a. ST RealWorld a -> IO a
stToIO (ST RealWorld Int -> IO Int) -> ST RealWorld Int -> IO Int
forall a b. (a -> b) -> a -> b
$
            Builder n -> MutableByteArray RealWorld -> Int -> ST RealWorld Int
forall (n :: Nat) s.
Builder n -> MutableByteArray s -> Int -> ST s Int
UnsafeBounded.pasteST
              (Int -> Builder n
buildSize (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int# -> Int
I# Int#
distZ)))
              (MutableByteArray# RealWorld -> MutableByteArray RealWorld
forall s. MutableByteArray# s -> MutableByteArray s
MutableByteArray MutableByteArray# RealWorld
buf0)
              Int
0
      MutableBytes RealWorld -> m b
cb (MutableByteArray RealWorld -> Int -> Int -> MutableBytes RealWorld
forall s. MutableByteArray s -> Int -> Int -> MutableBytes s
MutableBytes (MutableByteArray# RealWorld -> MutableByteArray RealWorld
forall s. MutableByteArray# s -> MutableByteArray s
MutableByteArray MutableByteArray# RealWorld
bufZ) Int
0 (Int# -> Int
I# Int#
offZ))
    Commits RealWorld
_ -> IO b -> m b
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO ((State# RealWorld -> (# State# RealWorld, b #)) -> IO b
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO (\State# RealWorld
s0 -> SomeException -> State# RealWorld -> (# State# RealWorld, b #)
forall a b. a -> State# RealWorld -> (# State# RealWorld, b #)
Exts.raiseIO# SomeException
putManyError State# RealWorld
s0))
  () -> m ()
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()

{- | Convert a bounded builder to an unbounded one. If the size
is a constant, use @Arithmetic.Nat.constant@ as the first argument
to let GHC conjure up this value for you.
-}
fromBounded ::
  Arithmetic.Nat n ->
  Bounded.Builder n ->
  Builder
{-# INLINE fromBounded #-}
fromBounded :: forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat n
n (UnsafeBounded.Builder forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #)
f) = (forall s.
 MutableByteArray# s
 -> Int#
 -> Int#
 -> Commits s
 -> State# s
 -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Builder
Builder ((forall s.
  MutableByteArray# s
  -> Int#
  -> Int#
  -> Commits s
  -> State# s
  -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
 -> Builder)
-> (forall s.
    MutableByteArray# s
    -> Int#
    -> Int#
    -> Commits s
    -> State# s
    -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Builder
forall a b. (a -> b) -> a -> b
$ \MutableByteArray# s
buf0 Int#
off0 Int#
len0 Commits s
cs0 State# s
s0 ->
  let !(I# Int#
req) = Nat n -> Int
forall (n :: Nat). Nat n -> Int
Nat.demote Nat n
n
      !(# State# s
s1, MutableByteArray# s
buf1, Int#
off1, Int#
len1, Commits s
cs1 #) = case Int#
len0 Int# -> Int# -> Int#
>=# Int#
req of
        Int#
1# -> (# State# s
s0, MutableByteArray# s
buf0, Int#
off0, Int#
len0, Commits s
cs0 #)
        Int#
_ ->
          let !(I# Int#
lenX) = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
4080 (Int# -> Int
I# Int#
req)
           in case Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
Exts.newByteArray# Int#
lenX State# s
s0 of
                (# State# s
sX, MutableByteArray# s
bufX #) ->
                  (# State# s
sX, MutableByteArray# s
bufX, Int#
0#, Int#
lenX, MutableByteArray# s -> Int# -> Commits s -> Commits s
forall s. MutableByteArray# s -> Int# -> Commits s -> Commits s
Mutable MutableByteArray# s
buf0 Int#
off0 Commits s
cs0 #)
   in case MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #)
f MutableByteArray# s
buf1 Int#
off1 State# s
s1 of
        (# State# s
s2, Int#
off2 #) -> (# State# s
s2, MutableByteArray# s
buf1, Int#
off2, Int#
len1 Int# -> Int# -> Int#
-# (Int#
off2 Int# -> Int# -> Int#
-# Int#
off1), Commits s
cs1 #)

-- This is a micro-optimization that uses an equality check instead
-- of an inequality check when the required number of bytes is one.
-- Use this instead of fromBounded (where possible) leads to marginally
-- better results in benchmarks.
fromBoundedOne ::
  Bounded.Builder 1 ->
  Builder
{-# INLINE fromBoundedOne #-}
fromBoundedOne :: Builder 1 -> Builder
fromBoundedOne (UnsafeBounded.Builder forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #)
f) = (forall s.
 MutableByteArray# s
 -> Int#
 -> Int#
 -> Commits s
 -> State# s
 -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Builder
Builder ((forall s.
  MutableByteArray# s
  -> Int#
  -> Int#
  -> Commits s
  -> State# s
  -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
 -> Builder)
-> (forall s.
    MutableByteArray# s
    -> Int#
    -> Int#
    -> Commits s
    -> State# s
    -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Builder
forall a b. (a -> b) -> a -> b
$ \MutableByteArray# s
buf0 Int#
off0 Int#
len0 Commits s
cs0 State# s
s0 ->
  let !(# State# s
s1, MutableByteArray# s
buf1, Int#
off1, Int#
len1, Commits s
cs1 #) = case Int#
len0 of
        Int#
0# -> case Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
Exts.newByteArray# Int#
4080# State# s
s0 of
          (# State# s
sX, MutableByteArray# s
bufX #) ->
            (# State# s
sX, MutableByteArray# s
bufX, Int#
0#, Int#
4080#, MutableByteArray# s -> Int# -> Commits s -> Commits s
forall s. MutableByteArray# s -> Int# -> Commits s -> Commits s
Mutable MutableByteArray# s
buf0 Int#
off0 Commits s
cs0 #)
        Int#
_ -> (# State# s
s0, MutableByteArray# s
buf0, Int#
off0, Int#
len0, Commits s
cs0 #)
   in case MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #)
f MutableByteArray# s
buf1 Int#
off1 State# s
s1 of
        (# State# s
s2, Int#
_ #) -> (# State# s
s2, MutableByteArray# s
buf1, Int#
off1 Int# -> Int# -> Int#
+# Int#
1#, Int#
len1 Int# -> Int# -> Int#
-# Int#
1#, Commits s
cs1 #)

-- | Create a builder from an unsliced byte sequence. Implemented with 'bytes'.
byteArray :: ByteArray -> Builder
byteArray :: ByteArray -> Builder
byteArray ByteArray
a = Bytes -> Builder
bytes (ByteArray -> Int -> Int -> Bytes
Bytes ByteArray
a Int
0 (ByteArray -> Int
PM.sizeofByteArray ByteArray
a))

-- | Create a builder from a short bytestring. Implemented with 'bytes'.
shortByteString :: ShortByteString -> Builder
shortByteString :: ShortByteString -> Builder
shortByteString (SBS ByteArray#
x) = Bytes -> Builder
bytes (ByteArray -> Int -> Int -> Bytes
Bytes ByteArray
a Int
0 (ByteArray -> Int
PM.sizeofByteArray ByteArray
a))
 where
  a :: ByteArray
a = ByteArray# -> ByteArray
ByteArray ByteArray#
x

{- | Create a builder from a sliced byte sequence. The variants
'copy' and 'insert' provide more control over whether or not
the byte sequence is copied or aliased. This function is preferred
when the user does not know the size of the byte sequence.
-}
bytes :: Bytes -> Builder
bytes :: Bytes -> Builder
bytes (Bytes (ByteArray ByteArray#
src#) (I# Int#
soff#) (I# Int#
slen#)) =
  (forall s.
 MutableByteArray# s
 -> Int#
 -> Int#
 -> Commits s
 -> State# s
 -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Builder
Builder
    -- There are three cases to consider: (1) there is not enough
    -- space and (1a) the chunk is not small or (1b) the chunk is
    -- small; (2) There is enough space for a copy.
    ( \MutableByteArray# s
buf0 Int#
off0 Int#
len0 Commits s
cs0 State# s
s0 -> case Int#
len0 Int# -> Int# -> Int#
<# Int#
slen# of
        Int#
1# -> case Int#
slen# Int# -> Int# -> Int#
>=# Int#
256# of
          Int#
1# -> case Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
Exts.newByteArray# Int#
0# State# s
s0 of
            (# State# s
s1, MutableByteArray# s
buf1 #) -> (# State# s
s1, MutableByteArray# s
buf1, Int#
0#, Int#
0#, ByteArray# -> Int# -> Int# -> Commits s -> Commits s
forall s. ByteArray# -> Int# -> Int# -> Commits s -> Commits s
Immutable ByteArray#
src# Int#
soff# Int#
slen# (MutableByteArray# s -> Int# -> Commits s -> Commits s
forall s. MutableByteArray# s -> Int# -> Commits s -> Commits s
Mutable MutableByteArray# s
buf0 Int#
off0 Commits s
cs0) #)
          Int#
_ -> case Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
Exts.newByteArray# Int#
4080# State# s
s0 of
            (# State# s
s1, MutableByteArray# s
buf1 #) -> case ByteArray#
-> Int#
-> MutableByteArray# s
-> Int#
-> Int#
-> State# s
-> State# s
forall d.
ByteArray#
-> Int#
-> MutableByteArray# d
-> Int#
-> Int#
-> State# d
-> State# d
Op.copyByteArray# ByteArray#
src# Int#
soff# MutableByteArray# s
buf1 Int#
0# Int#
slen# State# s
s1 of
              State# s
s2 -> (# State# s
s2, MutableByteArray# s
buf1, Int#
slen#, Int#
4080# Int# -> Int# -> Int#
-# Int#
slen#, MutableByteArray# s -> Int# -> Commits s -> Commits s
forall s. MutableByteArray# s -> Int# -> Commits s -> Commits s
Mutable MutableByteArray# s
buf0 Int#
off0 Commits s
cs0 #)
        Int#
_ ->
          let s1 :: State# s
s1 = ByteArray#
-> Int#
-> MutableByteArray# s
-> Int#
-> Int#
-> State# s
-> State# s
forall d.
ByteArray#
-> Int#
-> MutableByteArray# d
-> Int#
-> Int#
-> State# d
-> State# d
Op.copyByteArray# ByteArray#
src# Int#
soff# MutableByteArray# s
buf0 Int#
off0 Int#
slen# State# s
s0
           in (# State# s
s1, MutableByteArray# s
buf0, Int#
off0 Int# -> Int# -> Int#
+# Int#
slen#, Int#
len0 Int# -> Int# -> Int#
-# Int#
slen#, Commits s
cs0 #)
    )

-- | Paste byte chunks into a builder.
chunks :: Chunks -> Builder
{-# NOINLINE chunks #-}
chunks :: Chunks -> Builder
chunks Chunks
xs0 =
  -- Implementation note: It would probably be good to begin with a
  -- goCopying phase before switching to goInserting. If the total
  -- size of the chunks is small, we could end up just copying
  -- everything into the existing buffer, which would be nice.
  -- Note: This function needs a test in the test suite.
  (forall s.
 MutableByteArray# s
 -> Int#
 -> Int#
 -> Commits s
 -> State# s
 -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Builder
Builder ((forall s.
  MutableByteArray# s
  -> Int#
  -> Int#
  -> Commits s
  -> State# s
  -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
 -> Builder)
-> (forall s.
    MutableByteArray# s
    -> Int#
    -> Int#
    -> Commits s
    -> State# s
    -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Builder
forall a b. (a -> b) -> a -> b
$ \MutableByteArray# s
buf0 Int#
off0 Int#
len0 Commits s
cs0 State# s
s0 -> case Chunks
xs0 of
    Chunks
ChunksNil -> (# State# s
s0, MutableByteArray# s
buf0, Int#
off0, Int#
len0, Commits s
cs0 #)
    ChunksCons {} -> Chunks
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
forall s.
Chunks
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
goInserting Chunks
xs0 (MutableByteArray# s -> Int# -> Commits s -> Commits s
forall s. MutableByteArray# s -> Int# -> Commits s -> Commits s
Mutable MutableByteArray# s
buf0 Int#
off0 Commits s
cs0) State# s
s0
 where
  -- Notice that goNoncopying does not take a buffer as an argument. At the
  -- very end, we create a 128-byte buffer with nothing in it and present
  -- that as the new buffer. We *cannot* simply reuse the old buffer with
  -- the length set to zero because commitDistance1 would get confused.
  goInserting :: Chunks -> Commits s -> State# s -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
  goInserting :: forall s.
Chunks
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
goInserting Chunks
ChunksNil !Commits s
cs State# s
s0 = case Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
Exts.newByteArray# Int#
128# State# s
s0 of
    (# State# s
s1, MutableByteArray# s
buf1 #) -> (# State# s
s1, MutableByteArray# s
buf1, Int#
0#, Int#
128#, Commits s
cs #)
  goInserting (ChunksCons (Bytes (ByteArray ByteArray#
b) (I# Int#
off) (I# Int#
len)) Chunks
ys) !Commits s
cs State# s
s0 =
    Chunks
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
forall s.
Chunks
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
goInserting Chunks
ys (ByteArray# -> Int# -> Int# -> Commits s -> Commits s
forall s. ByteArray# -> Int# -> Int# -> Commits s -> Commits s
Immutable ByteArray#
b Int#
off Int#
len Commits s
cs) State# s
s0

{- | Create a builder from a byte sequence. This always results in a
call to @memcpy@. This is beneficial when the byte sequence is
known to be small (less than 256 bytes).
-}
copy :: Bytes -> Builder
copy :: Bytes -> Builder
copy (Bytes (ByteArray ByteArray#
src#) (I# Int#
soff#) (I# Int#
slen#)) =
  (forall s.
 MutableByteArray# s
 -> Int#
 -> Int#
 -> Commits s
 -> State# s
 -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Builder
Builder
    ( \MutableByteArray# s
buf0 Int#
off0 Int#
len0 Commits s
cs0 State# s
s0 -> case Int#
len0 Int# -> Int# -> Int#
<# Int#
slen# of
        Int#
1# -> case Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
Exts.newByteArray# Int#
newSz State# s
s0 of
          (# State# s
s1, MutableByteArray# s
buf1 #) -> case ByteArray#
-> Int#
-> MutableByteArray# s
-> Int#
-> Int#
-> State# s
-> State# s
forall d.
ByteArray#
-> Int#
-> MutableByteArray# d
-> Int#
-> Int#
-> State# d
-> State# d
Op.copyByteArray# ByteArray#
src# Int#
soff# MutableByteArray# s
buf1 Int#
0# Int#
slen# State# s
s1 of
            State# s
s2 -> (# State# s
s2, MutableByteArray# s
buf1, Int#
slen#, Int#
newSz Int# -> Int# -> Int#
-# Int#
slen#, MutableByteArray# s -> Int# -> Commits s -> Commits s
forall s. MutableByteArray# s -> Int# -> Commits s -> Commits s
Mutable MutableByteArray# s
buf0 Int#
off0 Commits s
cs0 #)
        Int#
_ ->
          let !s1 :: State# s
s1 = ByteArray#
-> Int#
-> MutableByteArray# s
-> Int#
-> Int#
-> State# s
-> State# s
forall d.
ByteArray#
-> Int#
-> MutableByteArray# d
-> Int#
-> Int#
-> State# d
-> State# d
Op.copyByteArray# ByteArray#
src# Int#
soff# MutableByteArray# s
buf0 Int#
off0 Int#
slen# State# s
s0
           in (# State# s
s1, MutableByteArray# s
buf0, Int#
off0 Int# -> Int# -> Int#
+# Int#
slen#, Int#
len0 Int# -> Int# -> Int#
-# Int#
slen#, Commits s
cs0 #)
    )
 where
  !(I# Int#
newSz) = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max (Int# -> Int
I# Int#
slen#) Int
4080

{- | Variant of 'copy' that additionally pastes an extra byte in
front of the bytes.
-}
copyCons :: Word8 -> Bytes -> Builder
copyCons :: Word8 -> Bytes -> Builder
copyCons (W8# Word8#
w0) (Bytes (ByteArray ByteArray#
src#) (I# Int#
soff#) (I# Int#
slen#)) =
  (forall s.
 MutableByteArray# s
 -> Int#
 -> Int#
 -> Commits s
 -> State# s
 -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Builder
Builder
    ( \MutableByteArray# s
buf0 Int#
off0 Int#
len0 Commits s
cs0 State# s
s0 -> case Int#
len0 Int# -> Int# -> Int#
<# (Int#
slen# Int# -> Int# -> Int#
+# Int#
1#) of
        Int#
1# -> case Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
Exts.newByteArray# Int#
newSz State# s
s0 of
          (# State# s
s1, MutableByteArray# s
buf1 #) -> case ByteArray#
-> Int#
-> MutableByteArray# s
-> Int#
-> Int#
-> State# s
-> State# s
forall d.
ByteArray#
-> Int#
-> MutableByteArray# d
-> Int#
-> Int#
-> State# d
-> State# d
Op.copyByteArray# ByteArray#
src# Int#
soff# MutableByteArray# s
buf1 Int#
1# Int#
slen# State# s
s1 of
            State# s
s2 -> case MutableByteArray# s -> Int# -> Word8# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Word8# -> State# d -> State# d
Exts.writeWord8Array# MutableByteArray# s
buf1 Int#
0# Word8#
w0 State# s
s2 of
              State# s
s3 -> (# State# s
s3, MutableByteArray# s
buf1, Int#
slen# Int# -> Int# -> Int#
+# Int#
1#, Int#
newSz Int# -> Int# -> Int#
-# (Int#
slen# Int# -> Int# -> Int#
+# Int#
1#), MutableByteArray# s -> Int# -> Commits s -> Commits s
forall s. MutableByteArray# s -> Int# -> Commits s -> Commits s
Mutable MutableByteArray# s
buf0 Int#
off0 Commits s
cs0 #)
        Int#
_ ->
          let !s1 :: State# s
s1 = ByteArray#
-> Int#
-> MutableByteArray# s
-> Int#
-> Int#
-> State# s
-> State# s
forall d.
ByteArray#
-> Int#
-> MutableByteArray# d
-> Int#
-> Int#
-> State# d
-> State# d
Op.copyByteArray# ByteArray#
src# Int#
soff# MutableByteArray# s
buf0 (Int#
off0 Int# -> Int# -> Int#
+# Int#
1#) Int#
slen# State# s
s0
              !s2 :: State# s
s2 = MutableByteArray# s -> Int# -> Word8# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Word8# -> State# d -> State# d
Exts.writeWord8Array# MutableByteArray# s
buf0 Int#
off0 Word8#
w0 State# s
s1
           in (# State# s
s2, MutableByteArray# s
buf0, Int#
off0 Int# -> Int# -> Int#
+# (Int#
slen# Int# -> Int# -> Int#
+# Int#
1#), Int#
len0 Int# -> Int# -> Int#
-# (Int#
slen# Int# -> Int# -> Int#
+# Int#
1#), Commits s
cs0 #)
    )
 where
  !(I# Int#
newSz) = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max ((Int# -> Int
I# Int#
slen#) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Int
4080

cstring# :: Addr# -> Builder
{-# INLINE cstring# #-}
cstring# :: Addr# -> Builder
cstring# Addr#
x = CString -> Builder
cstring (Addr# -> CString
forall a. Addr# -> Ptr a
Exts.Ptr Addr#
x)

{- | Create a builder from a C string with explicit length. The builder
must be executed before the C string is freed.
-}
cstringLen :: CStringLen -> Builder
cstringLen :: CStringLen -> Builder
cstringLen (Exts.Ptr Addr#
src#, I# Int#
slen#) =
  (forall s.
 MutableByteArray# s
 -> Int#
 -> Int#
 -> Commits s
 -> State# s
 -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Builder
Builder
    ( \MutableByteArray# s
buf0 Int#
off0 Int#
len0 Commits s
cs0 State# s
s0 -> case Int#
len0 Int# -> Int# -> Int#
<# Int#
slen# of
        Int#
1# -> case Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
Exts.newByteArray# Int#
newSz State# s
s0 of
          (# State# s
s1, MutableByteArray# s
buf1 #) -> case Addr#
-> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
forall d.
Addr#
-> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
Exts.copyAddrToByteArray# Addr#
src# MutableByteArray# s
buf1 Int#
0# Int#
slen# State# s
s1 of
            State# s
s2 -> (# State# s
s2, MutableByteArray# s
buf1, Int#
slen#, Int#
newSz Int# -> Int# -> Int#
-# Int#
slen#, MutableByteArray# s -> Int# -> Commits s -> Commits s
forall s. MutableByteArray# s -> Int# -> Commits s -> Commits s
Mutable MutableByteArray# s
buf0 Int#
off0 Commits s
cs0 #)
        Int#
_ ->
          let !s1 :: State# s
s1 = Addr#
-> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
forall d.
Addr#
-> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
Exts.copyAddrToByteArray# Addr#
src# MutableByteArray# s
buf0 Int#
off0 Int#
slen# State# s
s0
           in (# State# s
s1, MutableByteArray# s
buf0, Int#
off0 Int# -> Int# -> Int#
+# Int#
slen#, Int#
len0 Int# -> Int# -> Int#
-# Int#
slen#, Commits s
cs0 #)
    )
 where
  !(I# Int#
newSz) = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max (Int# -> Int
I# Int#
slen#) Int
4080

{- | Encode seven bytes into eight so that the encoded form is eight-bit clean.
Specifically segment the input bytes inot 7-bit groups (lowest-to-highest
index byte, most-to-least significant bit within a byte), pads the last group
with trailing zeros, and forms octects by prepending a zero to each group.

The name was chosen because this pads the input bits with zeros on the right,
and also because this was likely the originally-indended behavior of the
SMILE standard (see 'sevenEightSmile'). Right padding the input bits to a
multiple of seven, as in this variant, is consistent with base64 encodings
(which encodes 3 bytes in 4) and base85 (which encodes 4 bytes in 5).
-}
sevenEightRight :: Bytes -> Builder
sevenEightRight :: Bytes -> Builder
sevenEightRight Bytes
bs0 = case Int -> Word64 -> Bytes -> (Int, Word64)
toWord Int
0 Word64
0 Bytes
bs0 of
  (Int
0, Word64
_) -> Builder
forall a. Monoid a => a
mempty
  (Int
len, Word64
w) -> Int -> Word64 -> Builder
go (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8) Word64
w Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Bytes -> Builder
sevenEightSmile (Int -> Bytes -> Bytes
Bytes.unsafeDrop Int
len Bytes
bs0)
 where
  go :: Int -> Word64 -> Builder
  go :: Int -> Word64 -> Builder
go !Int
nBits !Word64
_ | Int
nBits Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = Builder
forall a. Monoid a => a
mempty
  go !Int
nBits !Word64
w =
    let octet :: Word8
octet = (Word64 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Word8) -> Word64 -> Word8
forall a b. (a -> b) -> a -> b
$ Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
w (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
7 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)) Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x7f
     in Word8 -> Builder
word8 Word8
octet Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Int -> Word64 -> Builder
go (Int
nBits Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
7) (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
w Int
7)
  toWord :: Int -> Word64 -> Bytes -> (Int, Word64)
  toWord :: Int -> Word64 -> Bytes -> (Int, Word64)
toWord !Int
i !Word64
acc !Bytes
bs
    | Bytes -> Int
Bytes.length Bytes
bs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = (Int
i, Word64
acc)
    | Bool
otherwise =
        let b :: Word64
b = forall a b. (Integral a, Num b) => a -> b
fromIntegral @Word8 @Word64 (Word8 -> Word64) -> Word8 -> Word64
forall a b. (a -> b) -> a -> b
$ Bytes -> Int -> Word8
Bytes.unsafeIndex Bytes
bs Int
0
            acc' :: Word64
acc' = Word64
acc Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|. Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
b (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
7 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
i))
         in if Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
7
              then Int -> Word64 -> Bytes -> (Int, Word64)
toWord (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Word64
acc' (Int -> Bytes -> Bytes
Bytes.unsafeDrop Int
1 Bytes
bs)
              else (Int
i, Word64
acc)

{- | Encode seven bytes into eight so that the encoded form is eight-bit clean.
Specifically segment the input bytes inot 7-bit groups (lowest-to-highest
index byte, most-to-least significant bit within a byte), then pad each group
with zeros on the left until each group is an octet.

The name was chosen because this is the implementation that is used (probably
unintentionally) in the reference SMILE implementation, and so is expected tp
be accepted by existing SMILE consumers.
-}
sevenEightSmile :: Bytes -> Builder
sevenEightSmile :: Bytes -> Builder
sevenEightSmile Bytes
bs0 = case Int -> Word64 -> Bytes -> (Int, Word64)
toWord Int
0 Word64
0 Bytes
bs0 of
  (Int
0, Word64
_) -> Builder
forall a. Monoid a => a
mempty
  (Int
len, Word64
w) -> Int -> Word64 -> Builder
go (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8) Word64
w Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Bytes -> Builder
sevenEightSmile (Int -> Bytes -> Bytes
Bytes.unsafeDrop Int
len Bytes
bs0)
 where
  go :: Int -> Word64 -> Builder
  go :: Int -> Word64 -> Builder
go !Int
nBits !Word64
w
    | Int
nBits Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = Builder
forall a. Monoid a => a
mempty
    | Int
nBits Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
7 = Int -> Word64 -> Builder
go Int
7 (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
w (Int
7 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
nBits))
  go !Int
nBits !Word64
w =
    let octet :: Word8
octet = (Word64 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Word8) -> Word64 -> Word8
forall a b. (a -> b) -> a -> b
$ Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftR Word64
w (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
7 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)) Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x7f
     in Word8 -> Builder
word8 Word8
octet Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Int -> Word64 -> Builder
go (Int
nBits Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
7) (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
w Int
7)
  toWord :: Int -> Word64 -> Bytes -> (Int, Word64)
  toWord :: Int -> Word64 -> Bytes -> (Int, Word64)
toWord !Int
i !Word64
acc !Bytes
bs
    | Bytes -> Int
Bytes.length Bytes
bs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = (Int
i, Word64
acc)
    | Bool
otherwise =
        let b :: Word64
b = forall a b. (Integral a, Num b) => a -> b
fromIntegral @Word8 @Word64 (Word8 -> Word64) -> Word8 -> Word64
forall a b. (a -> b) -> a -> b
$ Bytes -> Int -> Word8
Bytes.unsafeIndex Bytes
bs Int
0
            acc' :: Word64
acc' = Word64
acc Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|. Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
b (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
7 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
i))
         in if Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
7
              then Int -> Word64 -> Bytes -> (Int, Word64)
toWord (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Word64
acc' (Int -> Bytes -> Bytes
Bytes.unsafeDrop Int
1 Bytes
bs)
              else (Int
i, Word64
acc)

{- | Create a builder from two byte sequences. This always results in two
calls to @memcpy@. This is beneficial when the byte sequences are
known to be small (less than 256 bytes).
-}
copy2 :: Bytes -> Bytes -> Builder
copy2 :: Bytes -> Bytes -> Builder
copy2
  (Bytes (ByteArray ByteArray#
srcA#) (I# Int#
soffA#) (I# Int#
slenA#))
  (Bytes (ByteArray ByteArray#
srcB#) (I# Int#
soffB#) (I# Int#
slenB#)) =
    (forall s.
 MutableByteArray# s
 -> Int#
 -> Int#
 -> Commits s
 -> State# s
 -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Builder
Builder
      ( \MutableByteArray# s
buf0 Int#
off0 Int#
len0 Commits s
cs0 State# s
s0 -> case Int#
len0 Int# -> Int# -> Int#
<# Int#
slen# of
          Int#
1# -> case Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
Exts.newByteArray# Int#
newSz State# s
s0 of
            (# State# s
s1, MutableByteArray# s
buf1 #) -> case ByteArray#
-> Int#
-> MutableByteArray# s
-> Int#
-> Int#
-> State# s
-> State# s
forall d.
ByteArray#
-> Int#
-> MutableByteArray# d
-> Int#
-> Int#
-> State# d
-> State# d
Op.copyByteArray# ByteArray#
srcA# Int#
soffA# MutableByteArray# s
buf1 Int#
0# Int#
slenA# State# s
s1 of
              State# s
s2 -> case ByteArray#
-> Int#
-> MutableByteArray# s
-> Int#
-> Int#
-> State# s
-> State# s
forall d.
ByteArray#
-> Int#
-> MutableByteArray# d
-> Int#
-> Int#
-> State# d
-> State# d
Op.copyByteArray# ByteArray#
srcB# Int#
soffB# MutableByteArray# s
buf1 Int#
slenA# Int#
slenB# State# s
s2 of
                State# s
s3 -> (# State# s
s3, MutableByteArray# s
buf1, Int#
slen#, Int#
newSz Int# -> Int# -> Int#
-# Int#
slen#, MutableByteArray# s -> Int# -> Commits s -> Commits s
forall s. MutableByteArray# s -> Int# -> Commits s -> Commits s
Mutable MutableByteArray# s
buf0 Int#
off0 Commits s
cs0 #)
          Int#
_ ->
            let !s1 :: State# s
s1 = ByteArray#
-> Int#
-> MutableByteArray# s
-> Int#
-> Int#
-> State# s
-> State# s
forall d.
ByteArray#
-> Int#
-> MutableByteArray# d
-> Int#
-> Int#
-> State# d
-> State# d
Op.copyByteArray# ByteArray#
srcA# Int#
soffA# MutableByteArray# s
buf0 Int#
off0 Int#
slenA# State# s
s0
                !s2 :: State# s
s2 = ByteArray#
-> Int#
-> MutableByteArray# s
-> Int#
-> Int#
-> State# s
-> State# s
forall d.
ByteArray#
-> Int#
-> MutableByteArray# d
-> Int#
-> Int#
-> State# d
-> State# d
Op.copyByteArray# ByteArray#
srcB# Int#
soffB# MutableByteArray# s
buf0 (Int#
off0 Int# -> Int# -> Int#
+# Int#
slenA#) Int#
slenB# State# s
s1
             in (# State# s
s2, MutableByteArray# s
buf0, Int#
off0 Int# -> Int# -> Int#
+# Int#
slen#, Int#
len0 Int# -> Int# -> Int#
-# Int#
slen#, Commits s
cs0 #)
      )
   where
    !slen# :: Int#
slen# = Int#
slenA# Int# -> Int# -> Int#
+# Int#
slenB#
    !(I# Int#
newSz) = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max (Int# -> Int
I# Int#
slen#) Int
4080

{- | Create a builder from a byte sequence. This never calls @memcpy@.
Instead, it pushes a chunk that references the argument byte sequence.
This wastes the remaining space in the active chunk, so it may adversely
affect performance if used carelessly. See 'flush' for a way to mitigate
this problem. This functions is most beneficial when the byte sequence
is known to be large (more than 8192 bytes).
-}
insert :: Bytes -> Builder
insert :: Bytes -> Builder
insert (Bytes (ByteArray ByteArray#
src#) (I# Int#
soff#) (I# Int#
slen#)) =
  (forall s.
 MutableByteArray# s
 -> Int#
 -> Int#
 -> Commits s
 -> State# s
 -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Builder
Builder
    ( \MutableByteArray# s
buf0 Int#
off0 Int#
_ Commits s
cs0 State# s
s0 -> case Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
Exts.newByteArray# Int#
0# State# s
s0 of
        (# State# s
s1, MutableByteArray# s
buf1 #) ->
          (# State# s
s1, MutableByteArray# s
buf1, Int#
0#, Int#
0#, ByteArray# -> Int# -> Int# -> Commits s -> Commits s
forall s. ByteArray# -> Int# -> Int# -> Commits s -> Commits s
Immutable ByteArray#
src# Int#
soff# Int#
slen# (MutableByteArray# s -> Int# -> Commits s -> Commits s
forall s. MutableByteArray# s -> Int# -> Commits s -> Commits s
Mutable MutableByteArray# s
buf0 Int#
off0 Commits s
cs0) #)
    )

{- | Create a builder from a slice of an array of 'Word8'. There is the same
as 'bytes' but is provided as a convenience for users working with different
types.
-}
word8Array :: PrimArray Word8 -> Int -> Int -> Builder
word8Array :: PrimArray Word8 -> Int -> Int -> Builder
word8Array (PrimArray ByteArray#
arr) Int
off Int
len = Bytes -> Builder
bytes (ByteArray -> Int -> Int -> Bytes
Bytes (ByteArray# -> ByteArray
ByteArray ByteArray#
arr) Int
off Int
len)

int64ArrayLE :: PrimArray Int64 -> Int -> Int -> Builder
int64ArrayLE :: PrimArray Int64 -> Int -> Int -> Builder
int64ArrayLE (PrimArray ByteArray#
x) = PrimArray Word64 -> Int -> Int -> Builder
word64ArrayLE (ByteArray# -> PrimArray Word64
forall a. ByteArray# -> PrimArray a
PrimArray ByteArray#
x)

int64ArrayBE :: PrimArray Int64 -> Int -> Int -> Builder
int64ArrayBE :: PrimArray Int64 -> Int -> Int -> Builder
int64ArrayBE (PrimArray ByteArray#
x) = PrimArray Word64 -> Int -> Int -> Builder
word64ArrayBE (ByteArray# -> PrimArray Word64
forall a. ByteArray# -> PrimArray a
PrimArray ByteArray#
x)

int32ArrayLE :: PrimArray Int32 -> Int -> Int -> Builder
int32ArrayLE :: PrimArray Int32 -> Int -> Int -> Builder
int32ArrayLE (PrimArray ByteArray#
x) = PrimArray Word32 -> Int -> Int -> Builder
word32ArrayLE (ByteArray# -> PrimArray Word32
forall a. ByteArray# -> PrimArray a
PrimArray ByteArray#
x)

int32ArrayBE :: PrimArray Int32 -> Int -> Int -> Builder
int32ArrayBE :: PrimArray Int32 -> Int -> Int -> Builder
int32ArrayBE (PrimArray ByteArray#
x) = PrimArray Word32 -> Int -> Int -> Builder
word32ArrayBE (ByteArray# -> PrimArray Word32
forall a. ByteArray# -> PrimArray a
PrimArray ByteArray#
x)

int16ArrayLE :: PrimArray Int16 -> Int -> Int -> Builder
int16ArrayLE :: PrimArray Int16 -> Int -> Int -> Builder
int16ArrayLE (PrimArray ByteArray#
x) = PrimArray Word16 -> Int -> Int -> Builder
word16ArrayLE (ByteArray# -> PrimArray Word16
forall a. ByteArray# -> PrimArray a
PrimArray ByteArray#
x)

int16ArrayBE :: PrimArray Int16 -> Int -> Int -> Builder
int16ArrayBE :: PrimArray Int16 -> Int -> Int -> Builder
int16ArrayBE (PrimArray ByteArray#
x) = PrimArray Word16 -> Int -> Int -> Builder
word16ArrayBE (ByteArray# -> PrimArray Word16
forall a. ByteArray# -> PrimArray a
PrimArray ByteArray#
x)

word128ArrayLE :: PrimArray Word128 -> Int -> Int -> Builder
word128ArrayLE :: PrimArray Word128 -> Int -> Int -> Builder
word128ArrayLE src :: PrimArray Word128
src@(PrimArray ByteArray#
arr) Int
soff0 Int
slen0 = case ByteOrder
targetByteOrder of
  ByteOrder
LittleEndian -> Bytes -> Builder
bytes (ByteArray -> Int -> Int -> Bytes
Bytes (ByteArray# -> ByteArray
ByteArray ByteArray#
arr) (Int
soff0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
16) (Int
slen0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
16))
  ByteOrder
BigEndian -> PrimArray Word128 -> Int -> Int -> Builder
word128ArraySwap PrimArray Word128
src Int
soff0 Int
slen0

word128ArrayBE :: PrimArray Word128 -> Int -> Int -> Builder
word128ArrayBE :: PrimArray Word128 -> Int -> Int -> Builder
word128ArrayBE src :: PrimArray Word128
src@(PrimArray ByteArray#
arr) Int
soff0 Int
slen0 = case ByteOrder
targetByteOrder of
  ByteOrder
BigEndian -> Bytes -> Builder
bytes (ByteArray -> Int -> Int -> Bytes
Bytes (ByteArray# -> ByteArray
ByteArray ByteArray#
arr) (Int
soff0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
16) (Int
slen0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
16))
  ByteOrder
LittleEndian -> PrimArray Word128 -> Int -> Int -> Builder
word128ArraySwap PrimArray Word128
src Int
soff0 Int
slen0

word256ArrayLE :: PrimArray Word256 -> Int -> Int -> Builder
word256ArrayLE :: PrimArray Word256 -> Int -> Int -> Builder
word256ArrayLE src :: PrimArray Word256
src@(PrimArray ByteArray#
arr) Int
soff0 Int
slen0 = case ByteOrder
targetByteOrder of
  ByteOrder
LittleEndian -> Bytes -> Builder
bytes (ByteArray -> Int -> Int -> Bytes
Bytes (ByteArray# -> ByteArray
ByteArray ByteArray#
arr) (Int
soff0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
32) (Int
slen0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
32))
  ByteOrder
BigEndian -> PrimArray Word256 -> Int -> Int -> Builder
word256ArraySwap PrimArray Word256
src Int
soff0 Int
slen0

word256ArrayBE :: PrimArray Word256 -> Int -> Int -> Builder
word256ArrayBE :: PrimArray Word256 -> Int -> Int -> Builder
word256ArrayBE src :: PrimArray Word256
src@(PrimArray ByteArray#
arr) Int
soff0 Int
slen0 = case ByteOrder
targetByteOrder of
  ByteOrder
BigEndian -> Bytes -> Builder
bytes (ByteArray -> Int -> Int -> Bytes
Bytes (ByteArray# -> ByteArray
ByteArray ByteArray#
arr) (Int
soff0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
32) (Int
slen0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
32))
  ByteOrder
LittleEndian -> PrimArray Word256 -> Int -> Int -> Builder
word256ArraySwap PrimArray Word256
src Int
soff0 Int
slen0

word64ArrayLE :: PrimArray Word64 -> Int -> Int -> Builder
word64ArrayLE :: PrimArray Word64 -> Int -> Int -> Builder
word64ArrayLE src :: PrimArray Word64
src@(PrimArray ByteArray#
arr) Int
soff0 Int
slen0 = case ByteOrder
targetByteOrder of
  ByteOrder
LittleEndian -> Bytes -> Builder
bytes (ByteArray -> Int -> Int -> Bytes
Bytes (ByteArray# -> ByteArray
ByteArray ByteArray#
arr) (Int
soff0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8) (Int
slen0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8))
  ByteOrder
BigEndian -> PrimArray Word64 -> Int -> Int -> Builder
word64ArraySwap PrimArray Word64
src Int
soff0 Int
slen0

word64ArrayBE :: PrimArray Word64 -> Int -> Int -> Builder
word64ArrayBE :: PrimArray Word64 -> Int -> Int -> Builder
word64ArrayBE src :: PrimArray Word64
src@(PrimArray ByteArray#
arr) Int
soff0 Int
slen0 = case ByteOrder
targetByteOrder of
  ByteOrder
BigEndian -> Bytes -> Builder
bytes (ByteArray -> Int -> Int -> Bytes
Bytes (ByteArray# -> ByteArray
ByteArray ByteArray#
arr) (Int
soff0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8) (Int
slen0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8))
  ByteOrder
LittleEndian -> PrimArray Word64 -> Int -> Int -> Builder
word64ArraySwap PrimArray Word64
src Int
soff0 Int
slen0

word32ArrayLE :: PrimArray Word32 -> Int -> Int -> Builder
word32ArrayLE :: PrimArray Word32 -> Int -> Int -> Builder
word32ArrayLE src :: PrimArray Word32
src@(PrimArray ByteArray#
arr) Int
soff0 Int
slen0 = case ByteOrder
targetByteOrder of
  ByteOrder
LittleEndian -> Bytes -> Builder
bytes (ByteArray -> Int -> Int -> Bytes
Bytes (ByteArray# -> ByteArray
ByteArray ByteArray#
arr) (Int
soff0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
4) (Int
slen0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
4))
  ByteOrder
BigEndian -> PrimArray Word32 -> Int -> Int -> Builder
word32ArraySwap PrimArray Word32
src Int
soff0 Int
slen0

word32ArrayBE :: PrimArray Word32 -> Int -> Int -> Builder
word32ArrayBE :: PrimArray Word32 -> Int -> Int -> Builder
word32ArrayBE src :: PrimArray Word32
src@(PrimArray ByteArray#
arr) Int
soff0 Int
slen0 = case ByteOrder
targetByteOrder of
  ByteOrder
BigEndian -> Bytes -> Builder
bytes (ByteArray -> Int -> Int -> Bytes
Bytes (ByteArray# -> ByteArray
ByteArray ByteArray#
arr) (Int
soff0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
4) (Int
slen0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
4))
  ByteOrder
LittleEndian -> PrimArray Word32 -> Int -> Int -> Builder
word32ArraySwap PrimArray Word32
src Int
soff0 Int
slen0

word16ArrayLE :: PrimArray Word16 -> Int -> Int -> Builder
word16ArrayLE :: PrimArray Word16 -> Int -> Int -> Builder
word16ArrayLE src :: PrimArray Word16
src@(PrimArray ByteArray#
arr) Int
soff0 Int
slen0 = case ByteOrder
targetByteOrder of
  ByteOrder
LittleEndian -> Bytes -> Builder
bytes (ByteArray -> Int -> Int -> Bytes
Bytes (ByteArray# -> ByteArray
ByteArray ByteArray#
arr) (Int
soff0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
2) (Int
slen0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
2))
  ByteOrder
BigEndian -> PrimArray Word16 -> Int -> Int -> Builder
word16ArraySwap PrimArray Word16
src Int
soff0 Int
slen0

word16ArrayBE :: PrimArray Word16 -> Int -> Int -> Builder
word16ArrayBE :: PrimArray Word16 -> Int -> Int -> Builder
word16ArrayBE src :: PrimArray Word16
src@(PrimArray ByteArray#
arr) Int
soff0 Int
slen0 = case ByteOrder
targetByteOrder of
  ByteOrder
BigEndian -> Bytes -> Builder
bytes (ByteArray -> Int -> Int -> Bytes
Bytes (ByteArray# -> ByteArray
ByteArray ByteArray#
arr) (Int
soff0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
2) (Int
slen0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
2))
  ByteOrder
LittleEndian -> PrimArray Word16 -> Int -> Int -> Builder
word16ArraySwap PrimArray Word16
src Int
soff0 Int
slen0

word16ArraySwap :: PrimArray Word16 -> Int -> Int -> Builder
word16ArraySwap :: PrimArray Word16 -> Int -> Int -> Builder
word16ArraySwap PrimArray Word16
src Int
soff0 Int
slen0 =
  Int -> (forall s. MutableByteArray s -> Int -> ST s Int) -> Builder
fromFunction (Int
slen0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
2) (Int -> Int -> MutableByteArray s -> Int -> ST s Int
forall s. Int -> Int -> MutableByteArray s -> Int -> ST s Int
go (Int
soff0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
2) ((Int
soff0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
slen0) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
2))
 where
  go :: Int -> Int -> MutableByteArray s -> Int -> ST s Int
  go :: forall s. Int -> Int -> MutableByteArray s -> Int -> ST s Int
go !Int
soff !Int
send !MutableByteArray s
dst !Int
doff =
    if Int
soff Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
send
      then do
        let v0 :: Word8
v0 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word16 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word16
src) Int
soff
            v1 :: Word8
v1 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word16 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word16
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst Int
doff Word8
v1
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Word8
v0
        Int -> Int -> MutableByteArray s -> Int -> ST s Int
forall s. Int -> Int -> MutableByteArray s -> Int -> ST s Int
go (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) Int
send MutableByteArray s
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2)
      else Int -> ST s Int
forall a. a -> ST s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
doff

word32ArraySwap :: PrimArray Word32 -> Int -> Int -> Builder
word32ArraySwap :: PrimArray Word32 -> Int -> Int -> Builder
word32ArraySwap PrimArray Word32
src Int
soff0 Int
slen0 =
  Int -> (forall s. MutableByteArray s -> Int -> ST s Int) -> Builder
fromFunction (Int
slen0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
4) (Int -> Int -> MutableByteArray s -> Int -> ST s Int
forall s. Int -> Int -> MutableByteArray s -> Int -> ST s Int
go (Int
soff0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
4) ((Int
soff0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
slen0) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
4))
 where
  go :: Int -> Int -> MutableByteArray s -> Int -> ST s Int
  go :: forall s. Int -> Int -> MutableByteArray s -> Int -> ST s Int
go !Int
soff !Int
send !MutableByteArray s
dst !Int
doff =
    if Int
soff Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
send
      then do
        let v0 :: Word8
v0 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word32 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word32
src) Int
soff
            v1 :: Word8
v1 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word32 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word32
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
            v2 :: Word8
v2 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word32 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word32
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2)
            v3 :: Word8
v3 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word32 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word32
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3)
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst Int
doff Word8
v3
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Word8
v2
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) Word8
v1
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3) Word8
v0
        Int -> Int -> MutableByteArray s -> Int -> ST s Int
forall s. Int -> Int -> MutableByteArray s -> Int -> ST s Int
go (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4) Int
send MutableByteArray s
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4)
      else Int -> ST s Int
forall a. a -> ST s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
doff

word64ArraySwap :: PrimArray Word64 -> Int -> Int -> Builder
word64ArraySwap :: PrimArray Word64 -> Int -> Int -> Builder
word64ArraySwap PrimArray Word64
src Int
soff0 Int
slen0 =
  Int -> (forall s. MutableByteArray s -> Int -> ST s Int) -> Builder
fromFunction (Int
slen0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8) (Int -> Int -> MutableByteArray s -> Int -> ST s Int
forall s. Int -> Int -> MutableByteArray s -> Int -> ST s Int
go (Int
soff0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8) ((Int
soff0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
slen0) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8))
 where
  go :: Int -> Int -> MutableByteArray s -> Int -> ST s Int
  go :: forall s. Int -> Int -> MutableByteArray s -> Int -> ST s Int
go !Int
soff !Int
send !MutableByteArray s
dst !Int
doff =
    if Int
soff Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
send
      then do
        let v0 :: Word8
v0 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word64 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word64
src) Int
soff
            v1 :: Word8
v1 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word64 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word64
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
            v2 :: Word8
v2 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word64 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word64
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2)
            v3 :: Word8
v3 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word64 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word64
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3)
            v4 :: Word8
v4 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word64 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word64
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4)
            v5 :: Word8
v5 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word64 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word64
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
5)
            v6 :: Word8
v6 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word64 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word64
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
6)
            v7 :: Word8
v7 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word64 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word64
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
7)
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst Int
doff Word8
v7
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Word8
v6
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) Word8
v5
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3) Word8
v4
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4) Word8
v3
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
5) Word8
v2
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
6) Word8
v1
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
7) Word8
v0
        Int -> Int -> MutableByteArray s -> Int -> ST s Int
forall s. Int -> Int -> MutableByteArray s -> Int -> ST s Int
go (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
8) Int
send MutableByteArray s
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
8)
      else Int -> ST s Int
forall a. a -> ST s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
doff

word128ArraySwap :: PrimArray Word128 -> Int -> Int -> Builder
word128ArraySwap :: PrimArray Word128 -> Int -> Int -> Builder
word128ArraySwap PrimArray Word128
src Int
soff0 Int
slen0 =
  Int -> (forall s. MutableByteArray s -> Int -> ST s Int) -> Builder
fromFunction (Int
slen0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
16) (Int -> Int -> MutableByteArray s -> Int -> ST s Int
forall s. Int -> Int -> MutableByteArray s -> Int -> ST s Int
go (Int
soff0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
16) ((Int
soff0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
slen0) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
16))
 where
  -- TODO: Perhaps we could put byteswapping functions to use
  -- rather than indexing tons of Word8s. This could be done
  -- both here and in the other swap functions. There are a
  -- decent number of tests for these array-swapping functions,
  -- which makes changing this less scary.
  go :: Int -> Int -> MutableByteArray s -> Int -> ST s Int
  go :: forall s. Int -> Int -> MutableByteArray s -> Int -> ST s Int
go !Int
soff !Int
send !MutableByteArray s
dst !Int
doff =
    if Int
soff Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
send
      then do
        let v0 :: Word8
v0 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word128 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word128
src) Int
soff
            v1 :: Word8
v1 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word128 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word128
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
            v2 :: Word8
v2 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word128 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word128
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2)
            v3 :: Word8
v3 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word128 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word128
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3)
            v4 :: Word8
v4 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word128 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word128
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4)
            v5 :: Word8
v5 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word128 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word128
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
5)
            v6 :: Word8
v6 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word128 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word128
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
6)
            v7 :: Word8
v7 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word128 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word128
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
7)
            v8 :: Word8
v8 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word128 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word128
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
8)
            v9 :: Word8
v9 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word128 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word128
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
9)
            v10 :: Word8
v10 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word128 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word128
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
10)
            v11 :: Word8
v11 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word128 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word128
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
11)
            v12 :: Word8
v12 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word128 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word128
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
12)
            v13 :: Word8
v13 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word128 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word128
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
13)
            v14 :: Word8
v14 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word128 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word128
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
14)
            v15 :: Word8
v15 = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word128 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word128
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
15)
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst Int
doff Word8
v15
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Word8
v14
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) Word8
v13
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3) Word8
v12
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4) Word8
v11
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
5) Word8
v10
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
6) Word8
v9
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
7) Word8
v8
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
8) Word8
v7
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
9) Word8
v6
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
10) Word8
v5
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
11) Word8
v4
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
12) Word8
v3
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
13) Word8
v2
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
14) Word8
v1
        MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
15) Word8
v0
        Int -> Int -> MutableByteArray s -> Int -> ST s Int
forall s. Int -> Int -> MutableByteArray s -> Int -> ST s Int
go (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
16) Int
send MutableByteArray s
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
16)
      else Int -> ST s Int
forall a. a -> ST s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
doff

word256ArraySwap :: PrimArray Word256 -> Int -> Int -> Builder
word256ArraySwap :: PrimArray Word256 -> Int -> Int -> Builder
word256ArraySwap PrimArray Word256
src Int
soff0 Int
slen0 =
  Int -> (forall s. MutableByteArray s -> Int -> ST s Int) -> Builder
fromFunction (Int
slen0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
32) (Int -> Int -> MutableByteArray s -> Int -> ST s Int
forall s. Int -> Int -> MutableByteArray s -> Int -> ST s Int
go (Int
soff0 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
32) ((Int
soff0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
slen0) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
32))
 where
  -- TODO: Perhaps we could put byteswapping functions to use
  -- rather than indexing tons of Word8s. This could be done
  -- both here and in the other swap functions. There are a
  -- decent number of tests for these array-swapping functions,
  -- which makes changing this less scary.
  go :: Int -> Int -> MutableByteArray s -> Int -> ST s Int
  go :: forall s. Int -> Int -> MutableByteArray s -> Int -> ST s Int
go !Int
soff !Int
send !MutableByteArray s
dst !Int
doff =
    if Int
soff Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
send
      then do
        let loop :: Int -> m ()
loop !Int
i
              | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
32 = do
                  let v :: Word8
v = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
PM.indexPrimArray (PrimArray Word256 -> PrimArray Word8
forall a. PrimArray a -> PrimArray Word8
asWord8s PrimArray Word256
src) (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
i)
                  MutableByteArray (PrimState m) -> Int -> Word8 -> m ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState m)
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
31 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
i)) Word8
v
                  Int -> m ()
loop (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
              | Bool
otherwise = () -> m ()
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
        Int -> ST s ()
forall {m :: * -> *}. (PrimState m ~ s, PrimMonad m) => Int -> m ()
loop Int
0
        Int -> Int -> MutableByteArray s -> Int -> ST s Int
forall s. Int -> Int -> MutableByteArray s -> Int -> ST s Int
go (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
32) Int
send MutableByteArray s
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
32)
      else Int -> ST s Int
forall a. a -> ST s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
doff

asWord8s :: PrimArray a -> PrimArray Word8
asWord8s :: forall a. PrimArray a -> PrimArray Word8
asWord8s (PrimArray ByteArray#
x) = ByteArray# -> PrimArray Word8
forall a. ByteArray# -> PrimArray a
PrimArray ByteArray#
x

-- Internal function. Precondition, the referenced slice of the
-- byte sequence is UTF-8 encoded text.
slicedUtf8TextJson :: ByteArray# -> Int# -> Int# -> Builder
{-# NOINLINE slicedUtf8TextJson #-}
slicedUtf8TextJson :: ByteArray# -> Int# -> Int# -> Builder
slicedUtf8TextJson !ByteArray#
src# !Int#
soff0# !Int#
slen0# =
  Int#
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #))
-> Builder
fromFunction#
    Int#
reqLen#
    (\MutableByteArray# s
dst# Int#
doff0# State# s
s0# -> ByteArray#
-> Int#
-> Int#
-> MutableByteArray# s
-> Int#
-> State# s
-> (# State# s, Int# #)
forall s.
ByteArray#
-> Int#
-> Int#
-> MutableByteArray# s
-> Int#
-> State# s
-> (# State# s, Int# #)
pasteUtf8TextJson# ByteArray#
src# Int#
soff0# Int#
slen0# MutableByteArray# s
dst# Int#
doff0# State# s
s0#)
 where
  -- We multiply by 6 because, in the worst case, everything might be in the
  -- unprintable ASCII range. The plus 2 is for the quotes on the ends.
  !reqLen# :: Int#
reqLen# = (Int#
6# Int# -> Int# -> Int#
*# Int#
slen0#) Int# -> Int# -> Int#
+# Int#
2#

{- | Constructor for 'Builder' that works on a function with lifted
arguments instead of unlifted ones. This is just as unsafe as the
actual constructor.
-}
fromFunction :: Int -> (forall s. MutableByteArray s -> Int -> ST s Int) -> Builder
{-# INLINE fromFunction #-}
fromFunction :: Int -> (forall s. MutableByteArray s -> Int -> ST s Int) -> Builder
fromFunction (I# Int#
req) forall s. MutableByteArray s -> Int -> ST s Int
f = (forall s.
 MutableByteArray# s
 -> Int#
 -> Int#
 -> Commits s
 -> State# s
 -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Builder
Builder ((forall s.
  MutableByteArray# s
  -> Int#
  -> Int#
  -> Commits s
  -> State# s
  -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
 -> Builder)
-> (forall s.
    MutableByteArray# s
    -> Int#
    -> Int#
    -> Commits s
    -> State# s
    -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Builder
forall a b. (a -> b) -> a -> b
$ \MutableByteArray# s
buf0 Int#
off0 Int#
len0 Commits s
cs0 State# s
s0 ->
  let !(# State# s
s1, MutableByteArray# s
buf1, Int#
off1, Int#
len1, Commits s
cs1 #) = case Int#
len0 Int# -> Int# -> Int#
>=# Int#
req of
        Int#
1# -> (# State# s
s0, MutableByteArray# s
buf0, Int#
off0, Int#
len0, Commits s
cs0 #)
        Int#
_ ->
          let !(I# Int#
lenX) = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
4080 (Int# -> Int
I# Int#
req)
           in case Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
Exts.newByteArray# Int#
lenX State# s
s0 of
                (# State# s
sX, MutableByteArray# s
bufX #) ->
                  (# State# s
sX, MutableByteArray# s
bufX, Int#
0#, Int#
lenX, MutableByteArray# s -> Int# -> Commits s -> Commits s
forall s. MutableByteArray# s -> Int# -> Commits s -> Commits s
Mutable MutableByteArray# s
buf0 Int#
off0 Commits s
cs0 #)
   in case ST s Int -> State# s -> (# State# s, Int #)
forall s a. ST s a -> State# s -> (# State# s, a #)
unST (MutableByteArray s -> Int -> ST s Int
forall s. MutableByteArray s -> Int -> ST s Int
f (MutableByteArray# s -> MutableByteArray s
forall s. MutableByteArray# s -> MutableByteArray s
MutableByteArray MutableByteArray# s
buf1) (Int# -> Int
I# Int#
off1)) State# s
s1 of
        (# State# s
s2, I# Int#
off2 #) -> (# State# s
s2, MutableByteArray# s
buf1, Int#
off2, Int#
len1 Int# -> Int# -> Int#
-# (Int#
off2 Int# -> Int# -> Int#
-# Int#
off1), Commits s
cs1 #)

fromFunction# :: Int# -> (forall s. MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #)) -> Builder
{-# INLINE fromFunction# #-}
fromFunction# :: Int#
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #))
-> Builder
fromFunction# Int#
req forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #)
f = (forall s.
 MutableByteArray# s
 -> Int#
 -> Int#
 -> Commits s
 -> State# s
 -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Builder
Builder ((forall s.
  MutableByteArray# s
  -> Int#
  -> Int#
  -> Commits s
  -> State# s
  -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
 -> Builder)
-> (forall s.
    MutableByteArray# s
    -> Int#
    -> Int#
    -> Commits s
    -> State# s
    -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Builder
forall a b. (a -> b) -> a -> b
$ \MutableByteArray# s
buf0 Int#
off0 Int#
len0 Commits s
cs0 State# s
s0 ->
  let !(# State# s
s1, MutableByteArray# s
buf1, Int#
off1, Int#
len1, Commits s
cs1 #) = case Int#
len0 Int# -> Int# -> Int#
>=# Int#
req of
        Int#
1# -> (# State# s
s0, MutableByteArray# s
buf0, Int#
off0, Int#
len0, Commits s
cs0 #)
        Int#
_ ->
          let !(I# Int#
lenX) = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
4080 (Int# -> Int
I# Int#
req)
           in case Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
Exts.newByteArray# Int#
lenX State# s
s0 of
                (# State# s
sX, MutableByteArray# s
bufX #) ->
                  (# State# s
sX, MutableByteArray# s
bufX, Int#
0#, Int#
lenX, MutableByteArray# s -> Int# -> Commits s -> Commits s
forall s. MutableByteArray# s -> Int# -> Commits s -> Commits s
Mutable MutableByteArray# s
buf0 Int#
off0 Commits s
cs0 #)
   in case MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #)
f MutableByteArray# s
buf1 Int#
off1 State# s
s1 of
        (# State# s
s2, Int#
off2 #) -> (# State# s
s2, MutableByteArray# s
buf1, Int#
off2, Int#
len1 Int# -> Int# -> Int#
-# (Int#
off2 Int# -> Int# -> Int#
-# Int#
off1), Commits s
cs1 #)

-- | Create a builder from text. The text will be UTF-8 encoded.
shortTextUtf8 :: ShortText -> Builder
shortTextUtf8 :: ShortText -> Builder
shortTextUtf8 ShortText
a =
  let ba :: ByteArray
ba = ShortText -> ByteArray
shortTextToByteArray ShortText
a
   in Bytes -> Builder
bytes (ByteArray -> Int -> Int -> Bytes
Bytes ByteArray
ba Int
0 (ByteArray -> Int
PM.sizeofByteArray ByteArray
ba))

-- | Create a builder from text. The text will be UTF-8 encoded.
textUtf8 :: Text -> Builder
textUtf8 :: Text -> Builder
textUtf8 (I.Text (A.ByteArray ByteArray#
b) Int
off Int
len) =
  Bytes -> Builder
bytes (ByteArray -> Int -> Int -> Bytes
Bytes (ByteArray# -> ByteArray
ByteArray ByteArray#
b) Int
off Int
len)

{- | Create a builder from text. The text will be UTF-8 encoded,
and JSON special characters will be escaped. Additionally, the
result is surrounded by double quotes. For example:

* @foo ==\> "foo"@ (no escape sequences)
* @\\_"_\/ ==\> "\\\\_\\"_\/"@ (escapes backslashes and quotes)
* @hello\<ESC\>world ==> "hello\\u001Bworld"@ (where @\<ESC\>@ is code point 0x1B)
-}
shortTextJsonString :: ShortText -> Builder
{-# INLINE shortTextJsonString #-}
shortTextJsonString :: ShortText -> Builder
shortTextJsonString ShortText
a =
  let !(ByteArray ByteArray#
ba) = ShortText -> ByteArray
shortTextToByteArray ShortText
a
      !(I# Int#
len) = ByteArray -> Int
PM.sizeofByteArray (ByteArray# -> ByteArray
ByteArray ByteArray#
ba)
   in ByteArray# -> Int# -> Int# -> Builder
slicedUtf8TextJson ByteArray#
ba Int#
0# Int#
len

textJsonString :: Text -> Builder
{-# INLINE textJsonString #-}
textJsonString :: Text -> Builder
textJsonString (I.Text (A.ByteArray ByteArray#
ba) (I# Int#
off) (I# Int#
len)) = ByteArray# -> Int# -> Int# -> Builder
slicedUtf8TextJson ByteArray#
ba Int#
off Int#
len

{- | Encodes an unsigned 64-bit integer as decimal.
This encoding never starts with a zero unless the
argument was zero.
-}
word64Dec :: Word64 -> Builder
word64Dec :: Word64 -> Builder
word64Dec Word64
w = Nat 19 -> Builder 19 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 19
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word64 -> Builder 19
Bounded.word64Dec Word64
w)

{- | Encodes an unsigned 16-bit integer as decimal.
This encoding never starts with a zero unless the
argument was zero.
-}
word32Dec :: Word32 -> Builder
word32Dec :: Word32 -> Builder
word32Dec Word32
w = Nat 10 -> Builder 10 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 10
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word32 -> Builder 10
Bounded.word32Dec Word32
w)

{- | Encodes an unsigned 16-bit integer as decimal.
This encoding never starts with a zero unless the
argument was zero.
-}
word16Dec :: Word16 -> Builder
word16Dec :: Word16 -> Builder
word16Dec Word16
w = Nat 5 -> Builder 5 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 5
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word16 -> Builder 5
Bounded.word16Dec Word16
w)

{- | Encodes an unsigned 8-bit integer as decimal.
This encoding never starts with a zero unless the
argument was zero.
-}
word8Dec :: Word8 -> Builder
word8Dec :: Word8 -> Builder
word8Dec Word8
w = Nat 3 -> Builder 3 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 3
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word8 -> Builder 3
Bounded.word8Dec Word8
w)

{- | Encodes an unsigned machine-sized integer as decimal.
This encoding never starts with a zero unless the
argument was zero.
-}
wordDec :: Word -> Builder
wordDec :: Word -> Builder
wordDec Word
w = Nat 19 -> Builder 19 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 19
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word -> Builder 19
Bounded.wordDec Word
w)

{- | Encode a double-floating-point number, using decimal notation or
scientific notation depending on the magnitude. This has undefined
behavior when representing @+inf@, @-inf@, and @NaN@. It will not
crash, but the generated numbers will be nonsense.
-}
doubleDec :: Double -> Builder
doubleDec :: Double -> Builder
doubleDec Double
w = Nat 32 -> Builder 32 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 32
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Double -> Builder 32
Bounded.doubleDec Double
w)

{- | Encodes a signed 64-bit integer as decimal.
This encoding never starts with a zero unless the argument was zero.
Negative numbers are preceded by a minus sign. Positive numbers
are not preceded by anything.
-}
int64Dec :: Int64 -> Builder
int64Dec :: Int64 -> Builder
int64Dec Int64
w = Nat 20 -> Builder 20 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 20
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Int64 -> Builder 20
Bounded.int64Dec Int64
w)

{- | Encodes a signed 32-bit integer as decimal.
This encoding never starts with a zero unless the argument was zero.
Negative numbers are preceded by a minus sign. Positive numbers
are not preceded by anything.
-}
int32Dec :: Int32 -> Builder
int32Dec :: Int32 -> Builder
int32Dec Int32
w = Nat 11 -> Builder 11 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 11
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Int32 -> Builder 11
Bounded.int32Dec Int32
w)

{- | Encodes a signed 16-bit integer as decimal.
This encoding never starts with a zero unless the argument was zero.
Negative numbers are preceded by a minus sign. Positive numbers
are not preceded by anything.
-}
int16Dec :: Int16 -> Builder
int16Dec :: Int16 -> Builder
int16Dec Int16
w = Nat 6 -> Builder 6 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 6
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Int16 -> Builder 6
Bounded.int16Dec Int16
w)

{- | Encodes a signed 8-bit integer as decimal.
This encoding never starts with a zero unless the argument was zero.
Negative numbers are preceded by a minus sign. Positive numbers
are not preceded by anything.
-}
int8Dec :: Int8 -> Builder
int8Dec :: Int8 -> Builder
int8Dec Int8
w = Nat 4 -> Builder 4 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 4
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Int8 -> Builder 4
Bounded.int8Dec Int8
w)

{- | Encodes a signed machine-sized integer as decimal.
This encoding never starts with a zero unless the argument was zero.
Negative numbers are preceded by a minus sign. Positive numbers
are not preceded by anything.
-}
intDec :: Int -> Builder
intDec :: Int -> Builder
intDec Int
w = Nat 20 -> Builder 20 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 20
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Int -> Builder 20
Bounded.intDec Int
w)

{- | Encode a 64-bit unsigned integer as hexadecimal, zero-padding
the encoding to 16 digits. This uses uppercase for the alphabetical
digits. For example, this encodes the number 1022 as @00000000000003FE@.
-}
word64PaddedUpperHex :: Word64 -> Builder
word64PaddedUpperHex :: Word64 -> Builder
word64PaddedUpperHex Word64
w =
  Nat 16 -> Builder 16 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 16
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word64 -> Builder 16
Bounded.word64PaddedUpperHex Word64
w)

{- | Encode a 32-bit unsigned integer as hexadecimal, zero-padding
the encoding to 8 digits. This uses uppercase for the alphabetical
digits. For example, this encodes the number 1022 as @000003FE@.
-}
word32PaddedUpperHex :: Word32 -> Builder
word32PaddedUpperHex :: Word32 -> Builder
word32PaddedUpperHex Word32
w =
  Nat 8 -> Builder 8 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 8
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word32 -> Builder 8
Bounded.word32PaddedUpperHex Word32
w)

{- | Encode a 16-bit unsigned integer as hexadecimal, zero-padding
the encoding to 4 digits. This uses uppercase for the alphabetical
digits. For example, this encodes the number 1022 as @03FE@.
-}
word16PaddedUpperHex :: Word16 -> Builder
word16PaddedUpperHex :: Word16 -> Builder
word16PaddedUpperHex Word16
w =
  Nat 4 -> Builder 4 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 4
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word16 -> Builder 4
Bounded.word16PaddedUpperHex Word16
w)

{- | Encode a 16-bit unsigned integer as hexadecimal, zero-padding
the encoding to 4 digits. This uses lowercase for the alphabetical
digits. For example, this encodes the number 1022 as @03fe@.
-}
word16PaddedLowerHex :: Word16 -> Builder
word16PaddedLowerHex :: Word16 -> Builder
word16PaddedLowerHex Word16
w =
  Nat 4 -> Builder 4 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 4
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word16 -> Builder 4
Bounded.word16PaddedLowerHex Word16
w)

{- | Encode a 16-bit unsigned integer as hexadecimal without leading
zeroes. This uses lowercase for the alphabetical digits. For
example, this encodes the number 1022 as @3fe@.
-}
word16LowerHex :: Word16 -> Builder
word16LowerHex :: Word16 -> Builder
word16LowerHex Word16
w =
  Nat 4 -> Builder 4 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 4
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word16 -> Builder 4
Bounded.word16LowerHex Word16
w)

{- | Encode a 16-bit unsigned integer as hexadecimal without leading
zeroes. This uses uppercase for the alphabetical digits. For
example, this encodes the number 1022 as @3FE@.
-}
word16UpperHex :: Word16 -> Builder
word16UpperHex :: Word16 -> Builder
word16UpperHex Word16
w =
  Nat 4 -> Builder 4 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 4
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word16 -> Builder 4
Bounded.word16UpperHex Word16
w)

{- | Encode a 16-bit unsigned integer as hexadecimal without leading
zeroes. This uses lowercase for the alphabetical digits. For
example, this encodes the number 1022 as @3FE@.
-}
word8LowerHex :: Word8 -> Builder
word8LowerHex :: Word8 -> Builder
word8LowerHex Word8
w =
  Nat 2 -> Builder 2 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 2
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word8 -> Builder 2
Bounded.word8LowerHex Word8
w)

{- | Encode a 8-bit unsigned integer as hexadecimal, zero-padding
the encoding to 2 digits. This uses uppercase for the alphabetical
digits. For example, this encodes the number 11 as @0B@.
-}
word8PaddedUpperHex :: Word8 -> Builder
word8PaddedUpperHex :: Word8 -> Builder
word8PaddedUpperHex Word8
w =
  Nat 2 -> Builder 2 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 2
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word8 -> Builder 2
Bounded.word8PaddedUpperHex Word8
w)

{- | Encode an ASCII char.
Precondition: Input must be an ASCII character. This is not checked.
-}
ascii :: Char -> Builder
ascii :: Char -> Builder
ascii Char
c = Builder 1 -> Builder
fromBoundedOne (Char -> Builder 1
Bounded.ascii Char
c)

{- | Encode two ASCII characters.
Precondition: Must be an ASCII characters. This is not checked.
-}
ascii2 :: Char -> Char -> Builder
ascii2 :: Char -> Char -> Builder
ascii2 Char
a Char
b = Nat 2 -> Builder 2 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 2
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Char -> Char -> Builder 2
Bounded.ascii2 Char
a Char
b)

{- | Encode three ASCII characters.
Precondition: Must be an ASCII characters. This is not checked.
-}
ascii3 :: Char -> Char -> Char -> Builder
ascii3 :: Char -> Char -> Char -> Builder
ascii3 Char
a Char
b Char
c = Nat 3 -> Builder 3 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 3
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Char -> Char -> Char -> Builder 3
Bounded.ascii3 Char
a Char
b Char
c)

{- | Encode four ASCII characters.
Precondition: Must be an ASCII characters. This is not checked.
-}
ascii4 :: Char -> Char -> Char -> Char -> Builder
ascii4 :: Char -> Char -> Char -> Char -> Builder
ascii4 Char
a Char
b Char
c Char
d = Nat 4 -> Builder 4 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 4
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Char -> Char -> Char -> Char -> Builder 4
Bounded.ascii4 Char
a Char
b Char
c Char
d)

{- | Encode five ASCII characters.
Precondition: Must be an ASCII characters. This is not checked.
-}
ascii5 :: Char -> Char -> Char -> Char -> Char -> Builder
ascii5 :: Char -> Char -> Char -> Char -> Char -> Builder
ascii5 Char
a Char
b Char
c Char
d Char
e = Nat 5 -> Builder 5 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 5
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Char -> Char -> Char -> Char -> Char -> Builder 5
Bounded.ascii5 Char
a Char
b Char
c Char
d Char
e)

{- | Encode six ASCII characters.
Precondition: Must be an ASCII characters. This is not checked.
-}
ascii6 :: Char -> Char -> Char -> Char -> Char -> Char -> Builder
ascii6 :: Char -> Char -> Char -> Char -> Char -> Char -> Builder
ascii6 Char
a Char
b Char
c Char
d Char
e Char
f = Nat 6 -> Builder 6 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 6
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Char -> Char -> Char -> Char -> Char -> Char -> Builder 6
Bounded.ascii6 Char
a Char
b Char
c Char
d Char
e Char
f)

{- | Encode seven ASCII characters.
Precondition: Must be an ASCII characters. This is not checked.
-}
ascii7 :: Char -> Char -> Char -> Char -> Char -> Char -> Char -> Builder
ascii7 :: Char -> Char -> Char -> Char -> Char -> Char -> Char -> Builder
ascii7 Char
a Char
b Char
c Char
d Char
e Char
f Char
g = Nat 7 -> Builder 7 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 7
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Char -> Char -> Char -> Char -> Char -> Char -> Char -> Builder 7
Bounded.ascii7 Char
a Char
b Char
c Char
d Char
e Char
f Char
g)

{- | Encode eight ASCII characters.
Precondition: Must be an ASCII characters. This is not checked.
-}
ascii8 :: Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Builder
ascii8 :: Char
-> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Builder
ascii8 Char
a Char
b Char
c Char
d Char
e Char
f Char
g Char
h = Nat 8 -> Builder 8 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 8
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Builder 8
Bounded.ascii8 Char
a Char
b Char
c Char
d Char
e Char
f Char
g Char
h)

-- | Encode a UTF-8 char. This only uses as much space as is required.
char :: Char -> Builder
char :: Char -> Builder
char Char
c = Nat 4 -> Builder 4 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 4
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Char -> Builder 4
Bounded.char Char
c)

unST :: ST s a -> State# s -> (# State# s, a #)
unST :: forall s a. ST s a -> State# s -> (# State# s, a #)
unST (ST STRep s a
f) = STRep s a
f

{- | Requires exactly 8 bytes. Dump the octets of a 64-bit
signed integer in a little-endian fashion.
-}
int64LE :: Int64 -> Builder
int64LE :: Int64 -> Builder
int64LE Int64
w = Nat 8 -> Builder 8 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 8
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Int64 -> Builder 8
Bounded.int64LE Int64
w)

{- | Requires exactly 4 bytes. Dump the octets of a 32-bit
signed integer in a little-endian fashion.
-}
int32LE :: Int32 -> Builder
int32LE :: Int32 -> Builder
int32LE Int32
w = Nat 4 -> Builder 4 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 4
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Int32 -> Builder 4
Bounded.int32LE Int32
w)

{- | Requires exactly 2 bytes. Dump the octets of a 16-bit
signed integer in a little-endian fashion.
-}
int16LE :: Int16 -> Builder
int16LE :: Int16 -> Builder
int16LE Int16
w = Nat 2 -> Builder 2 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 2
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Int16 -> Builder 2
Bounded.int16LE Int16
w)

{- | Requires exactly 8 bytes. Dump the octets of a 64-bit
signed integer in a big-endian fashion.
-}
int64BE :: Int64 -> Builder
int64BE :: Int64 -> Builder
int64BE Int64
w = Nat 8 -> Builder 8 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 8
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Int64 -> Builder 8
Bounded.int64BE Int64
w)

{- | Requires exactly 4 bytes. Dump the octets of a 32-bit
signed integer in a big-endian fashion.
-}
int32BE :: Int32 -> Builder
int32BE :: Int32 -> Builder
int32BE Int32
w = Nat 4 -> Builder 4 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 4
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Int32 -> Builder 4
Bounded.int32BE Int32
w)

{- | Requires exactly 2 bytes. Dump the octets of a 16-bit
signed integer in a big-endian fashion.
-}
int16BE :: Int16 -> Builder
int16BE :: Int16 -> Builder
int16BE Int16
w = Nat 2 -> Builder 2 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 2
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Int16 -> Builder 2
Bounded.int16BE Int16
w)

{- | Requires exactly 32 bytes. Dump the octets of a 256-bit
word in a little-endian fashion.
-}
word256LE :: Word256 -> Builder
word256LE :: Word256 -> Builder
word256LE Word256
w = Nat 32 -> Builder 32 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 32
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word256 -> Builder 32
Bounded.word256LE Word256
w)

{- | Requires exactly 16 bytes. Dump the octets of a 128-bit
word in a little-endian fashion.
-}
word128LE :: Word128 -> Builder
word128LE :: Word128 -> Builder
word128LE Word128
w = Nat 16 -> Builder 16 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 16
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word128 -> Builder 16
Bounded.word128LE Word128
w)

{- | Requires exactly 8 bytes. Dump the octets of a 64-bit
word in a little-endian fashion.
-}
word64LE :: Word64 -> Builder
word64LE :: Word64 -> Builder
word64LE Word64
w = Nat 8 -> Builder 8 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 8
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word64 -> Builder 8
Bounded.word64LE Word64
w)

{- | Requires exactly 4 bytes. Dump the octets of a 32-bit
word in a little-endian fashion.
-}
word32LE :: Word32 -> Builder
word32LE :: Word32 -> Builder
word32LE Word32
w = Nat 4 -> Builder 4 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 4
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word32 -> Builder 4
Bounded.word32LE Word32
w)

{- | Requires exactly 2 bytes. Dump the octets of a 16-bit
word in a little-endian fashion.
-}
word16LE :: Word16 -> Builder
word16LE :: Word16 -> Builder
word16LE Word16
w = Nat 2 -> Builder 2 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 2
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word16 -> Builder 2
Bounded.word16LE Word16
w)

{- | Requires exactly 32 bytes. Dump the octets of a 256-bit
word in a big-endian fashion.
-}
word256BE :: Word256 -> Builder
word256BE :: Word256 -> Builder
word256BE Word256
w = Nat 32 -> Builder 32 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 32
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word256 -> Builder 32
Bounded.word256BE Word256
w)

{- | Requires exactly 16 bytes. Dump the octets of a 128-bit
word in a big-endian fashion.
-}
word128BE :: Word128 -> Builder
word128BE :: Word128 -> Builder
word128BE Word128
w = Nat 16 -> Builder 16 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 16
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word128 -> Builder 16
Bounded.word128BE Word128
w)

{- | Requires exactly 8 bytes. Dump the octets of a 64-bit
word in a big-endian fashion.
-}
word64BE :: Word64 -> Builder
word64BE :: Word64 -> Builder
word64BE Word64
w = Nat 8 -> Builder 8 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 8
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word64 -> Builder 8
Bounded.word64BE Word64
w)

{- | Requires exactly 4 bytes. Dump the octets of a 32-bit
word in a big-endian fashion.
-}
word32BE :: Word32 -> Builder
word32BE :: Word32 -> Builder
word32BE Word32
w = Nat 4 -> Builder 4 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 4
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word32 -> Builder 4
Bounded.word32BE Word32
w)

{- | Requires exactly 2 bytes. Dump the octets of a 16-bit
word in a big-endian fashion.
-}
word16BE :: Word16 -> Builder
word16BE :: Word16 -> Builder
word16BE Word16
w = Nat 2 -> Builder 2 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 2
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word16 -> Builder 2
Bounded.word16BE Word16
w)

-- | Requires exactly 1 byte.
word8 :: Word8 -> Builder
word8 :: Word8 -> Builder
word8 Word8
w = Builder 1 -> Builder
fromBoundedOne (Word8 -> Builder 1
Bounded.word8 Word8
w)

-- | Prefix a builder with the number of bytes that it requires.
consLength ::
  -- | Number of bytes used by the serialization of the length
  Arithmetic.Nat n ->
  -- | Length serialization function
  (Int -> Bounded.Builder n) ->
  -- | Builder whose length is measured
  Builder ->
  Builder
{-# INLINE consLength #-}
consLength :: forall (n :: Nat).
Nat n -> (Int -> Builder n) -> Builder -> Builder
consLength !Nat n
n Int -> Builder n
buildSize (Builder forall s.
MutableByteArray# s
-> Int#
-> Int#
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
f) = (forall s.
 MutableByteArray# s
 -> Int#
 -> Int#
 -> Commits s
 -> State# s
 -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Builder
Builder ((forall s.
  MutableByteArray# s
  -> Int#
  -> Int#
  -> Commits s
  -> State# s
  -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
 -> Builder)
-> (forall s.
    MutableByteArray# s
    -> Int#
    -> Int#
    -> Commits s
    -> State# s
    -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Builder
forall a b. (a -> b) -> a -> b
$ \MutableByteArray# s
buf0 Int#
off0 Int#
len0 Commits s
cs0 State# s
s0 ->
  -- There is actually a little bit of unsoundness here. If the number of
  -- bytes required to encode the length is greater than 4080, this will
  -- write outside the array, leading to a crash.
  let !(I# Int#
lenSz) = Nat n -> Int
forall (n :: Nat). Nat n -> Int
Nat.demote Nat n
n
      !(# State# s
s1, MutableByteArray# s
buf1, Int#
off1, Int#
len1, Commits s
cs1 #) = case Int#
len0 Int# -> Int# -> Int#
>=# Int#
lenSz of
        Int#
1# -> (# State# s
s0, MutableByteArray# s
buf0, Int#
off0, Int#
len0, Commits s
cs0 #)
        Int#
_ -> case Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
Exts.newByteArray# Int#
4080# State# s
s0 of
          (# State# s
sX, MutableByteArray# s
bufX #) ->
            (# State# s
sX, MutableByteArray# s
bufX, Int#
0#, Int#
4080#, MutableByteArray# s -> Int# -> Commits s -> Commits s
forall s. MutableByteArray# s -> Int# -> Commits s -> Commits s
Mutable MutableByteArray# s
buf0 Int#
off0 Commits s
cs0 #)
   in case MutableByteArray# s
-> Int#
-> Int#
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
forall s.
MutableByteArray# s
-> Int#
-> Int#
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
f MutableByteArray# s
buf1 (Int#
off1 Int# -> Int# -> Int#
+# Int#
lenSz) (Int#
len1 Int# -> Int# -> Int#
-# Int#
lenSz) Commits s
cs1 State# s
s1 of
        (# State# s
s2, MutableByteArray# s
buf2, Int#
off2, Int#
len2, Commits s
cs2 #) ->
          let !dist :: Int#
dist = MutableByteArray# s
-> Int# -> MutableByteArray# s -> Int# -> Commits s -> Int#
forall s.
MutableByteArray# s
-> Int# -> MutableByteArray# s -> Int# -> Commits s -> Int#
commitDistance1 MutableByteArray# s
buf1 (Int#
off1 Int# -> Int# -> Int#
+# Int#
lenSz) MutableByteArray# s
buf2 Int#
off2 Commits s
cs2
              ST STRep s Int
g =
                Builder n -> MutableByteArray s -> Int -> ST s Int
forall (n :: Nat) s.
Builder n -> MutableByteArray s -> Int -> ST s Int
UnsafeBounded.pasteST
                  (Int -> Builder n
buildSize (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int# -> Int
I# Int#
dist)))
                  (MutableByteArray# s -> MutableByteArray s
forall s. MutableByteArray# s -> MutableByteArray s
MutableByteArray MutableByteArray# s
buf1)
                  (Int# -> Int
I# Int#
off1)
           in case STRep s Int
g State# s
s2 of
                (# State# s
s3, Int
_ #) -> (# State# s
s3, MutableByteArray# s
buf2, Int#
off2, Int#
len2, Commits s
cs2 #)

{- | Variant of 'consLength32BE' the encodes the length in
a little-endian fashion.
-}
consLength32LE :: Builder -> Builder
consLength32LE :: Builder -> Builder
consLength32LE = Nat 4 -> (Int -> Builder 4) -> Builder -> Builder
forall (n :: Nat).
Nat n -> (Int -> Builder n) -> Builder -> Builder
consLength Nat 4
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (\Int
x -> Word32 -> Builder 4
Bounded.word32LE (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x))

{- | Prefix a builder with its size in bytes. This size is
presented as a big-endian 32-bit word. The need to prefix
a builder with its length shows up a numbers of wire protocols
including those of PostgreSQL and Apache Kafka. Note the
equivalence:

> forall (n :: Int) (x :: Builder).
>   let sz = sizeofByteArray (run n (consLength32BE x))
>   consLength32BE x === word32BE (fromIntegral sz) <> x

However, using 'consLength32BE' is much more efficient here
since it only materializes the 'ByteArray' once.
-}
consLength32BE :: Builder -> Builder
consLength32BE :: Builder -> Builder
consLength32BE = Nat 4 -> (Int -> Builder 4) -> Builder -> Builder
forall (n :: Nat).
Nat n -> (Int -> Builder n) -> Builder -> Builder
consLength Nat 4
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (\Int
x -> Word32 -> Builder 4
Bounded.word32BE (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x))

{- | Prefix a builder with its size in bytes. This size is
presented as a big-endian 64-bit word. See 'consLength32BE'.
-}
consLength64BE :: Builder -> Builder
consLength64BE :: Builder -> Builder
consLength64BE = Nat 8 -> (Int -> Builder 8) -> Builder -> Builder
forall (n :: Nat).
Nat n -> (Int -> Builder n) -> Builder -> Builder
consLength Nat 8
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (\Int
x -> Word64 -> Builder 8
Bounded.word64BE (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x))

{- | Push the buffer currently being filled onto the chunk list,
allocating a new active buffer of the requested size. This is
helpful when a small builder is sandwhiched between two large
zero-copy builders:

> insert bigA <> flush 1 <> word8 0x42 <> insert bigB

Without @flush 1@, @word8 0x42@ would see the zero-byte active
buffer that 'insert' returned, decide that it needed more space,
and allocate a 4080-byte buffer to which only a single byte
would be written.
-}
flush :: Int -> Builder
flush :: Int -> Builder
flush !Int
reqSz = (forall s.
 MutableByteArray# s
 -> Int#
 -> Int#
 -> Commits s
 -> State# s
 -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Builder
Builder ((forall s.
  MutableByteArray# s
  -> Int#
  -> Int#
  -> Commits s
  -> State# s
  -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
 -> Builder)
-> (forall s.
    MutableByteArray# s
    -> Int#
    -> Int#
    -> Commits s
    -> State# s
    -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Builder
forall a b. (a -> b) -> a -> b
$ \MutableByteArray# s
buf0 Int#
off0 Int#
_ Commits s
cs0 State# s
s0 ->
  case Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
Exts.newByteArray# Int#
sz# State# s
s0 of
    (# State# s
sX, MutableByteArray# s
bufX #) ->
      (# State# s
sX, MutableByteArray# s
bufX, Int#
0#, Int#
sz#, MutableByteArray# s -> Int# -> Commits s -> Commits s
forall s. MutableByteArray# s -> Int# -> Commits s -> Commits s
Mutable MutableByteArray# s
buf0 Int#
off0 Commits s
cs0 #)
 where
  !(I# Int#
sz#) = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
reqSz Int
0

-- ShortText is already UTF-8 encoded. This is a no-op.
shortTextToByteArray :: ShortText -> ByteArray
shortTextToByteArray :: ShortText -> ByteArray
shortTextToByteArray ShortText
x = case ShortText -> ShortByteString
TS.toShortByteString ShortText
x of
  SBS ByteArray#
a -> ByteArray# -> ByteArray
ByteArray ByteArray#
a

{- | Encode a signed machine-sized integer with LEB-128. This uses
zig-zag encoding.
-}
intLEB128 :: Int -> Builder
{-# INLINE intLEB128 #-}
intLEB128 :: Int -> Builder
intLEB128 = Word -> Builder
wordLEB128 (Word -> Builder) -> (Int -> Word) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Word
toZigzagNative

-- | Encode a 32-bit signed integer with LEB-128. This uses zig-zag encoding.
int32LEB128 :: Int32 -> Builder
{-# INLINE int32LEB128 #-}
int32LEB128 :: Int32 -> Builder
int32LEB128 = Word32 -> Builder
word32LEB128 (Word32 -> Builder) -> (Int32 -> Word32) -> Int32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32 -> Word32
toZigzag32

-- | Encode a 64-bit signed integer with LEB-128. This uses zig-zag encoding.
int64LEB128 :: Int64 -> Builder
{-# INLINE int64LEB128 #-}
int64LEB128 :: Int64 -> Builder
int64LEB128 = Word64 -> Builder
word64LEB128 (Word64 -> Builder) -> (Int64 -> Word64) -> Int64 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Word64
toZigzag64

-- | Encode a machine-sized word with LEB-128.
wordLEB128 :: Word -> Builder
{-# INLINE wordLEB128 #-}
wordLEB128 :: Word -> Builder
wordLEB128 Word
w = Nat 10 -> Builder 10 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 10
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word -> Builder 10
Bounded.wordLEB128 Word
w)

-- | Encode a 16-bit word with LEB-128.
word16LEB128 :: Word16 -> Builder
{-# INLINE word16LEB128 #-}
word16LEB128 :: Word16 -> Builder
word16LEB128 Word16
w = Nat 3 -> Builder 3 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 3
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word16 -> Builder 3
Bounded.word16LEB128 Word16
w)

-- | Encode a 32-bit word with LEB-128.
word32LEB128 :: Word32 -> Builder
{-# INLINE word32LEB128 #-}
word32LEB128 :: Word32 -> Builder
word32LEB128 Word32
w = Nat 5 -> Builder 5 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 5
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word32 -> Builder 5
Bounded.word32LEB128 Word32
w)

-- | Encode a 64-bit word with LEB-128.
word64LEB128 :: Word64 -> Builder
{-# INLINE word64LEB128 #-}
word64LEB128 :: Word64 -> Builder
word64LEB128 Word64
w = Nat 10 -> Builder 10 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 10
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word64 -> Builder 10
Bounded.word64LEB128 Word64
w)

-- | Encode a machine-sized word with VLQ.
wordVlq :: Word -> Builder
{-# INLINE wordVlq #-}
wordVlq :: Word -> Builder
wordVlq Word
w = Nat 10 -> Builder 10 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 10
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word -> Builder 10
Bounded.wordVlq Word
w)

-- | Encode a 32-bit word with VLQ.
word32Vlq :: Word32 -> Builder
{-# INLINE word32Vlq #-}
word32Vlq :: Word32 -> Builder
word32Vlq Word32
w = Nat 5 -> Builder 5 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 5
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word32 -> Builder 5
Bounded.word32Vlq Word32
w)

-- | Encode a 64-bit word with VLQ.
word64Vlq :: Word64 -> Builder
{-# INLINE word64Vlq #-}
word64Vlq :: Word64 -> Builder
word64Vlq Word64
w = Nat 10 -> Builder 10 -> Builder
forall (n :: Nat). Nat n -> Builder n -> Builder
fromBounded Nat 10
forall (n :: Nat). KnownNat n => Nat n
Nat.constant (Word64 -> Builder 10
Bounded.word64Vlq Word64
w)

{- | Encode a signed arbitrary-precision integer as decimal.
This encoding never starts with a zero unless the argument was zero.
Negative numbers are preceded by a minus sign. Positive numbers
are not preceded by anything.
-}
integerDec :: Integer -> Builder
integerDec :: Integer -> Builder
integerDec !Integer
i
  | Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
0 = Char -> Builder
ascii Char
'-' Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Nat -> Builder
naturalDec (Integer -> Nat
naturalFromInteger (Integer -> Integer
forall a. Num a => a -> a
negate Integer
i))
  | Bool
otherwise = Nat -> Builder
naturalDec (Integer -> Nat
naturalFromInteger Integer
i)

{- | Encodes an unsigned arbitrary-precision integer as decimal.
This encoding never starts with a zero unless the argument was zero.
-}
naturalDec :: Natural -> Builder
naturalDec :: Nat -> Builder
naturalDec !Nat
n0 =
  Int -> (forall s. MutableByteArray s -> Int -> ST s Int) -> Builder
fromEffect
    (Int# -> Int
I# (Int#
11# Int# -> Int# -> Int#
+# (Int#
3# Int# -> Int# -> Int#
*# Integer -> Int#
integerLog2# (Nat -> Integer
naturalToInteger Nat
n0))))
    ( \MutableByteArray s
marr Int
off -> case Nat
n0 of
        Nat
0 -> do
          MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
marr Int
off (Word8
0x30 :: Word8)
          Int -> ST s Int
forall a. a -> ST s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
        Nat
_ -> Nat -> MutableByteArray s -> Int -> Int -> ST s Int
forall s. Nat -> MutableByteArray s -> Int -> Int -> ST s Int
go Nat
n0 MutableByteArray s
marr Int
off Int
off
    )
 where
  go :: forall s. Natural -> MutableByteArray s -> Int -> Int -> ST s Int
  go :: forall s. Nat -> MutableByteArray s -> Int -> Int -> ST s Int
go !Nat
n !MutableByteArray s
buf !Int
off0 !Int
off = case Nat -> Nat -> (Nat, Nat)
forall a. Integral a => a -> a -> (a, a)
quotRem Nat
n Nat
1_000_000_000 of
    (Nat
q, Nat
r) -> case Nat
q of
      Nat
0 -> do
        Int
off' <- MutableByteArray s -> Int -> Word -> ST s Int
forall s. MutableByteArray s -> Int -> Word -> ST s Int
backwardsWordLoop MutableByteArray s
buf Int
off (forall a b. (Integral a, Num b) => a -> b
fromIntegral @Natural @Word Nat
r)
        MutableByteArray s -> Int -> Int -> ST s ()
forall s. MutableByteArray s -> Int -> Int -> ST s ()
reverseBytes MutableByteArray s
buf Int
off0 (Int
off' Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
        Int -> ST s Int
forall a. a -> ST s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
off'
      Nat
_ -> do
        Int
off' <-
          Word -> MutableByteArray s -> Int -> ST s Int
forall s. Word -> MutableByteArray s -> Int -> ST s Int
backwardsPasteWordPaddedDec9
            (forall a b. (Integral a, Num b) => a -> b
fromIntegral @Natural @Word Nat
r)
            MutableByteArray s
buf
            Int
off
        Nat -> MutableByteArray s -> Int -> Int -> ST s Int
forall s. Nat -> MutableByteArray s -> Int -> Int -> ST s Int
go Nat
q MutableByteArray s
buf Int
off0 Int
off'

-- Reverse the bytes in the designated slice. This takes
-- an inclusive start offset and an inclusive end offset.
reverseBytes :: MutableByteArray s -> Int -> Int -> ST s ()
{-# INLINE reverseBytes #-}
reverseBytes :: forall s. MutableByteArray s -> Int -> Int -> ST s ()
reverseBytes MutableByteArray s
arr Int
begin Int
end = Int -> Int -> ST s ()
forall {m :: * -> *}.
(PrimState m ~ s, PrimMonad m) =>
Int -> Int -> m ()
go Int
begin Int
end
 where
  go :: Int -> Int -> m ()
go Int
ixA Int
ixB =
    if Int
ixA Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
ixB
      then do
        Word8
a :: Word8 <- MutableByteArray (PrimState m) -> Int -> m Word8
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> m a
PM.readByteArray MutableByteArray s
MutableByteArray (PrimState m)
arr Int
ixA
        Word8
b :: Word8 <- MutableByteArray (PrimState m) -> Int -> m Word8
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> m a
PM.readByteArray MutableByteArray s
MutableByteArray (PrimState m)
arr Int
ixB
        MutableByteArray (PrimState m) -> Int -> Word8 -> m ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState m)
arr Int
ixA Word8
b
        MutableByteArray (PrimState m) -> Int -> Word8 -> m ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState m)
arr Int
ixB Word8
a
        Int -> Int -> m ()
go (Int
ixA Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Int
ixB Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
      else () -> m ()
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()

backwardsPasteWordPaddedDec9 ::
  Word -> MutableByteArray s -> Int -> ST s Int
backwardsPasteWordPaddedDec9 :: forall s. Word -> MutableByteArray s -> Int -> ST s Int
backwardsPasteWordPaddedDec9 !Word
w !MutableByteArray s
arr !Int
off = do
  (MutableByteArray s -> Int -> Word -> ST s ())
-> MutableByteArray s -> Int -> Word -> ST s ()
forall s a.
(MutableByteArray s -> Int -> Word -> ST s a)
-> MutableByteArray s -> Int -> Word -> ST s a
backwardsPutRem10
    ( (MutableByteArray s -> Int -> Word -> ST s ())
-> MutableByteArray s -> Int -> Word -> ST s ()
forall s a.
(MutableByteArray s -> Int -> Word -> ST s a)
-> MutableByteArray s -> Int -> Word -> ST s a
backwardsPutRem10 ((MutableByteArray s -> Int -> Word -> ST s ())
 -> MutableByteArray s -> Int -> Word -> ST s ())
-> (MutableByteArray s -> Int -> Word -> ST s ())
-> MutableByteArray s
-> Int
-> Word
-> ST s ()
forall a b. (a -> b) -> a -> b
$
        (MutableByteArray s -> Int -> Word -> ST s ())
-> MutableByteArray s -> Int -> Word -> ST s ()
forall s a.
(MutableByteArray s -> Int -> Word -> ST s a)
-> MutableByteArray s -> Int -> Word -> ST s a
backwardsPutRem10 ((MutableByteArray s -> Int -> Word -> ST s ())
 -> MutableByteArray s -> Int -> Word -> ST s ())
-> (MutableByteArray s -> Int -> Word -> ST s ())
-> MutableByteArray s
-> Int
-> Word
-> ST s ()
forall a b. (a -> b) -> a -> b
$
          (MutableByteArray s -> Int -> Word -> ST s ())
-> MutableByteArray s -> Int -> Word -> ST s ()
forall s a.
(MutableByteArray s -> Int -> Word -> ST s a)
-> MutableByteArray s -> Int -> Word -> ST s a
backwardsPutRem10 ((MutableByteArray s -> Int -> Word -> ST s ())
 -> MutableByteArray s -> Int -> Word -> ST s ())
-> (MutableByteArray s -> Int -> Word -> ST s ())
-> MutableByteArray s
-> Int
-> Word
-> ST s ()
forall a b. (a -> b) -> a -> b
$
            (MutableByteArray s -> Int -> Word -> ST s ())
-> MutableByteArray s -> Int -> Word -> ST s ()
forall s a.
(MutableByteArray s -> Int -> Word -> ST s a)
-> MutableByteArray s -> Int -> Word -> ST s a
backwardsPutRem10 ((MutableByteArray s -> Int -> Word -> ST s ())
 -> MutableByteArray s -> Int -> Word -> ST s ())
-> (MutableByteArray s -> Int -> Word -> ST s ())
-> MutableByteArray s
-> Int
-> Word
-> ST s ()
forall a b. (a -> b) -> a -> b
$
              (MutableByteArray s -> Int -> Word -> ST s ())
-> MutableByteArray s -> Int -> Word -> ST s ()
forall s a.
(MutableByteArray s -> Int -> Word -> ST s a)
-> MutableByteArray s -> Int -> Word -> ST s a
backwardsPutRem10 ((MutableByteArray s -> Int -> Word -> ST s ())
 -> MutableByteArray s -> Int -> Word -> ST s ())
-> (MutableByteArray s -> Int -> Word -> ST s ())
-> MutableByteArray s
-> Int
-> Word
-> ST s ()
forall a b. (a -> b) -> a -> b
$
                (MutableByteArray s -> Int -> Word -> ST s ())
-> MutableByteArray s -> Int -> Word -> ST s ()
forall s a.
(MutableByteArray s -> Int -> Word -> ST s a)
-> MutableByteArray s -> Int -> Word -> ST s a
backwardsPutRem10 ((MutableByteArray s -> Int -> Word -> ST s ())
 -> MutableByteArray s -> Int -> Word -> ST s ())
-> (MutableByteArray s -> Int -> Word -> ST s ())
-> MutableByteArray s
-> Int
-> Word
-> ST s ()
forall a b. (a -> b) -> a -> b
$
                  (MutableByteArray s -> Int -> Word -> ST s ())
-> MutableByteArray s -> Int -> Word -> ST s ()
forall s a.
(MutableByteArray s -> Int -> Word -> ST s a)
-> MutableByteArray s -> Int -> Word -> ST s a
backwardsPutRem10 ((MutableByteArray s -> Int -> Word -> ST s ())
 -> MutableByteArray s -> Int -> Word -> ST s ())
-> (MutableByteArray s -> Int -> Word -> ST s ())
-> MutableByteArray s
-> Int
-> Word
-> ST s ()
forall a b. (a -> b) -> a -> b
$
                    (MutableByteArray s -> Int -> Word -> ST s ())
-> MutableByteArray s -> Int -> Word -> ST s ()
forall s a.
(MutableByteArray s -> Int -> Word -> ST s a)
-> MutableByteArray s -> Int -> Word -> ST s a
backwardsPutRem10
                      (\MutableByteArray s
_ Int
_ Word
_ -> () -> ST s ()
forall a. a -> ST s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
    )
    MutableByteArray s
arr
    Int
off
    Word
w
  Int -> ST s Int
forall a. a -> ST s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
9)

backwardsPutRem10 ::
  (MutableByteArray s -> Int -> Word -> ST s a) ->
  MutableByteArray s ->
  Int ->
  Word ->
  ST s a
{-# INLINE backwardsPutRem10 #-}
backwardsPutRem10 :: forall s a.
(MutableByteArray s -> Int -> Word -> ST s a)
-> MutableByteArray s -> Int -> Word -> ST s a
backwardsPutRem10 MutableByteArray s -> Int -> Word -> ST s a
andThen MutableByteArray s
arr Int
off Word
dividend = do
  let quotient :: Word
quotient = Word -> Word
approxDiv10 Word
dividend
      remainder :: Word
remainder = Word
dividend Word -> Word -> Word
forall a. Num a => a -> a -> a
- (Word
10 Word -> Word -> Word
forall a. Num a => a -> a -> a
* Word
quotient)
  MutableByteArray (PrimState (ST s)) -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
arr Int
off (Word -> Word8
unsafeWordToWord8 (Word
remainder Word -> Word -> Word
forall a. Num a => a -> a -> a
+ Word
48))
  MutableByteArray s -> Int -> Word -> ST s a
andThen MutableByteArray s
arr (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Word
quotient

backwardsWordLoop :: MutableByteArray s -> Int -> Word -> ST s Int
{-# INLINE backwardsWordLoop #-}
backwardsWordLoop :: forall s. MutableByteArray s -> Int -> Word -> ST s Int
backwardsWordLoop MutableByteArray s
arr Int
off0 Word
x0 = Int -> Word -> ST s Int
forall {m :: * -> *}.
(PrimState m ~ s, PrimMonad m) =>
Int -> Word -> m Int
go Int
off0 Word
x0
 where
  go :: Int -> Word -> m Int
go !Int
off !(Word
x :: Word) =
    if Word
x Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
> Word
0
      then do
        let (Word
y, Word
z) = Word -> Word -> (Word, Word)
forall a. Integral a => a -> a -> (a, a)
quotRem Word
x Word
10
        MutableByteArray (PrimState m) -> Int -> Word8 -> m ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
PM.writeByteArray MutableByteArray s
MutableByteArray (PrimState m)
arr Int
off (Word -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word
z Word -> Word -> Word
forall a. Num a => a -> a -> a
+ Word
0x30) :: Word8)
        Int -> Word -> m Int
go (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Word
y
      else Int -> m Int
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
off

-- | Replicate a byte the given number of times.
replicate ::
  -- | Number of times to replicate the byte
  Int ->
  -- | Byte to replicate
  Word8 ->
  Builder
replicate :: Int -> Word8 -> Builder
replicate !Int
len !Word8
w =
  Int -> (forall s. MutableByteArray s -> Int -> ST s Int) -> Builder
fromEffect
    Int
len
    ( \MutableByteArray s
marr Int
off -> do
        MutableByteArray (PrimState (ST s))
-> Int -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> Int -> a -> m ()
PM.setByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
marr Int
off Int
len Word8
w
        Int -> ST s Int
forall a. a -> ST s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
len)
    )

-- Based on C code from https://stackoverflow.com/a/5558614
-- For numbers less than 1073741829, this gives a correct answer.
approxDiv10 :: Word -> Word
approxDiv10 :: Word -> Word
approxDiv10 !Word
n = Word -> Int -> Word
forall a. Bits a => a -> Int -> a
unsafeShiftR (Word
0x1999999A Word -> Word -> Word
forall a. Num a => a -> a -> a
* Word
n) Int
32

-- -- A weird beast useful for rewrite rules. Not yet used. This will
-- -- ultimately replace fromEffect and fromBounded.
-- require :: Int -> Builder
-- require !n = Builder $ \buf0 off0 len0 cs0 s0 ->
--   let !(I# req) = n
--    in case len0 >=# req of
--         1# -> (# s0, buf0, off0, len0, cs0 #)
--         _ -> let !(I# lenX) = max 4080 (I# req) in
--           case Exts.newByteArray# lenX s0 of
--             (# sX, bufX #) ->
--               (# sX, bufX, 0#, lenX, Mutable buf0 off0 cs0 #)

unsafeWordToWord8 :: Word -> Word8
unsafeWordToWord8 :: Word -> Word8
unsafeWordToWord8 (W# Word#
w) = Word8# -> Word8
W8# (Word# -> Word8#
C.wordToWord8# Word#
w)

{- | This function and the documentation for it are copied from
Takano Akio's fast-builder library.

@'rebuild' b@ is equivalent to @b@, but it allows GHC to assume
that @b@ will be run at most once. This can enable various
optimizations that greately improve performance.

There are two types of typical situations where a use of 'rebuild'
is often a win:

* When constructing a builder using a recursive function. e.g.
 @rebuild $ foldr ...@.
* When constructing a builder using a conditional expression. e.g.
 @rebuild $ case x of ... @
-}
rebuild :: Builder -> Builder
{-# INLINE rebuild #-}
rebuild :: Builder -> Builder
rebuild (Builder forall s.
MutableByteArray# s
-> Int#
-> Int#
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
f) = (forall s.
 MutableByteArray# s
 -> Int#
 -> Int#
 -> Commits s
 -> State# s
 -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Builder
Builder ((forall s.
  MutableByteArray# s
  -> Int#
  -> Int#
  -> Commits s
  -> State# s
  -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
 -> Builder)
-> (forall s.
    MutableByteArray# s
    -> Int#
    -> Int#
    -> Commits s
    -> State# s
    -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Builder
forall a b. (a -> b) -> a -> b
$ (MutableByteArray# s
 -> Int#
 -> Int#
 -> Commits s
 -> State# s
 -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> MutableByteArray# s
-> Int#
-> Int#
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
forall a b. (a -> b) -> a -> b
oneShot ((MutableByteArray# s
  -> Int#
  -> Int#
  -> Commits s
  -> State# s
  -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
 -> MutableByteArray# s
 -> Int#
 -> Int#
 -> Commits s
 -> State# s
 -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> (MutableByteArray# s
    -> Int#
    -> Int#
    -> Commits s
    -> State# s
    -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> MutableByteArray# s
-> Int#
-> Int#
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
forall a b. (a -> b) -> a -> b
$ \MutableByteArray# s
a -> (Int#
 -> Int#
 -> Commits s
 -> State# s
 -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Int#
-> Int#
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
forall a b. (a -> b) -> a -> b
oneShot ((Int#
  -> Int#
  -> Commits s
  -> State# s
  -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
 -> Int#
 -> Int#
 -> Commits s
 -> State# s
 -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> (Int#
    -> Int#
    -> Commits s
    -> State# s
    -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Int#
-> Int#
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
forall a b. (a -> b) -> a -> b
$ \Int#
b -> (Int#
 -> Commits s
 -> State# s
 -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Int#
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
forall a b. (a -> b) -> a -> b
oneShot ((Int#
  -> Commits s
  -> State# s
  -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
 -> Int#
 -> Commits s
 -> State# s
 -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> (Int#
    -> Commits s
    -> State# s
    -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Int#
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
forall a b. (a -> b) -> a -> b
$ \Int#
c -> (Commits s
 -> State# s
 -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
forall a b. (a -> b) -> a -> b
oneShot ((Commits s
  -> State# s
  -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
 -> Commits s
 -> State# s
 -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> (Commits s
    -> State# s
    -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
forall a b. (a -> b) -> a -> b
$ \Commits s
d -> (State# s
 -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
forall a b. (a -> b) -> a -> b
oneShot ((State# s
  -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
 -> State# s
 -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> (State# s
    -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
forall a b. (a -> b) -> a -> b
$ \State# s
e ->
  MutableByteArray# s
-> Int#
-> Int#
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
forall s.
MutableByteArray# s
-> Int#
-> Int#
-> Commits s
-> State# s
-> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)
f MutableByteArray# s
a Int#
b Int#
c Commits s
d State# s
e