{-# language BangPatterns #-}
{-# language DataKinds #-}
{-# language DuplicateRecordFields #-}
{-# language LambdaCase #-}
{-# language MagicHash #-}
{-# language NumericUnderscores #-}
{-# language RankNTypes #-}
{-# language ScopedTypeVariables #-}
{-# language TypeApplications #-}
{-# language UnboxedTuples #-}
module Data.Bytes.Builder
(
Builder
, fromBounded
, run
, runOnto
, reversedOnto
, putMany
, putManyConsLength
, bytes
, copy
, copy2
, insert
, byteArray
, shortByteString
, shortTextUtf8
, shortTextJsonString
, cstring
, cstring#
, cstringLen
, stringUtf8
, word64Dec
, word32Dec
, word16Dec
, word8Dec
, wordDec
, naturalDec
, int64Dec
, int32Dec
, int16Dec
, int8Dec
, intDec
, integerDec
, word64PaddedUpperHex
, word32PaddedUpperHex
, word16PaddedUpperHex
, word16PaddedLowerHex
, word16LowerHex
, word16UpperHex
, word8PaddedUpperHex
, word8LowerHex
, ascii
, ascii2
, ascii3
, ascii4
, ascii5
, ascii6
, ascii7
, ascii8
, char
, word8
, word256BE
, word128BE
, word64BE
, word32BE
, word16BE
, int64BE
, int32BE
, int16BE
, word256LE
, word128LE
, word64LE
, word32LE
, word16LE
, int64LE
, int32LE
, int16LE
, intLEB128
, wordLEB128
, word64LEB128
, word8Array
, word16ArrayBE
, word32ArrayBE
, word64ArrayBE
, word128ArrayBE
, word256ArrayBE
, int64ArrayBE
, int32ArrayBE
, int16ArrayBE
, word16ArrayLE
, word32ArrayLE
, word64ArrayLE
, word128ArrayLE
, word256ArrayLE
, int64ArrayLE
, int32ArrayLE
, int16ArrayLE
, consLength
, consLength32LE
, consLength32BE
, consLength64BE
, doubleDec
, replicate
, flush
) where
import Prelude hiding (replicate)
import Control.Exception (SomeException,toException)
import Control.Monad.ST (ST,runST)
import Control.Monad.IO.Class (MonadIO,liftIO)
import Data.Bits (unsafeShiftR,unsafeShiftL,xor,finiteBitSize)
import Data.Bytes.Builder.Unsafe (Builder(Builder),commitDistance1)
import Data.Bytes.Builder.Unsafe (BuilderState(BuilderState),pasteIO)
import Data.Bytes.Builder.Unsafe (Commits(Initial,Mutable,Immutable))
import Data.Bytes.Builder.Unsafe (reverseCommitsOntoChunks)
import Data.Bytes.Builder.Unsafe (commitsOntoChunks)
import Data.Bytes.Builder.Unsafe (stringUtf8,cstring,fromEffect)
import Data.Bytes.Builder.Unsafe (addCommitsLength,copyReverseCommits)
import Data.ByteString.Short.Internal (ShortByteString(SBS))
import Data.Bytes.Chunks (Chunks(ChunksNil))
import Data.Bytes.Types (Bytes(Bytes),MutableBytes(MutableBytes))
import Data.Char (ord)
import Data.Foldable (foldlM)
import Data.Int (Int64,Int32,Int16,Int8)
import Data.Primitive (ByteArray(..),MutableByteArray(..),PrimArray(..))
import Data.Text.Short (ShortText)
import Data.WideWord (Word128,Word256)
import Data.Word (Word64,Word32,Word16,Word8)
import Foreign.C.String (CStringLen)
import GHC.ByteOrder (ByteOrder(BigEndian,LittleEndian),targetByteOrder)
import GHC.Exts (Int(I#),Char(C#),Int#,State#,ByteArray#,(>=#))
import GHC.Exts (RealWorld,(+#),(-#),(<#))
import GHC.Exts (Addr#,(*#))
import GHC.Integer.Logarithms.Compat (integerLog2#)
import GHC.IO (IO(IO),stToIO)
import GHC.Natural (naturalFromInteger,naturalToInteger)
import GHC.ST (ST(ST))
import GHC.Word (Word(W#),Word8(W8#))
import Numeric.Natural (Natural)
import qualified Arithmetic.Nat as Nat
import qualified Arithmetic.Types as Arithmetic
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
run ::
Int
-> Builder
-> Chunks
run :: Int -> Builder -> Chunks
run !Int
hint Builder
bldr = Int -> Builder -> Chunks -> Chunks
runOnto Int
hint Builder
bldr Chunks
ChunksNil
runOnto ::
Int
-> Builder
-> 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
reversedOnto ::
Int
-> 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
putMany :: Foldable f
=> Int
-> (a -> Builder)
-> f a
-> (MutableBytes RealWorld -> IO b)
-> IO ()
{-# inline putMany #-}
putMany :: 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 (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 (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 (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 (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")
putManyConsLength :: (Foldable f, MonadIO m)
=> Arithmetic.Nat n
-> (Int -> Bounded.Builder n)
-> Int
-> (a -> Builder)
-> f a
-> (MutableBytes RealWorld -> m b)
-> m ()
{-# inline putManyConsLength #-}
putManyConsLength :: 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 (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 (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 (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 (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 (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 (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 (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 (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 (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 (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 (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 (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 (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 (f :: * -> *) a. Applicative f => a -> f a
pure ()
fromBounded ::
Arithmetic.Nat n
-> Bounded.Builder n
-> Builder
{-# inline fromBounded #-}
fromBounded :: 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 #)
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 #)
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))
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
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
(\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
Exts.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
Exts.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 #)
)
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
Exts.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
Exts.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
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)
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
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
Exts.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
Exts.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
Exts.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
Exts.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
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) #)
)
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 :: 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 (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 :: 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 (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 :: 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 (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
go :: Int -> Int -> MutableByteArray s -> Int -> ST s Int
go :: 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 (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
go :: Int -> Int -> MutableByteArray s -> Int -> ST s Int
go :: 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 -> ST s ()
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 (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
31 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
i)) Word8
v
Int -> ST s ()
loop (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
| Bool
otherwise = () -> ST s ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Int -> ST s ()
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 (f :: * -> *) a. Applicative f => a -> f a
pure Int
doff
asWord8s :: PrimArray a -> PrimArray Word8
asWord8s :: PrimArray a -> PrimArray Word8
asWord8s (PrimArray ByteArray#
x) = ByteArray# -> PrimArray Word8
forall a. ByteArray# -> PrimArray a
PrimArray ByteArray#
x
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 -> ST s Int) -> Builder
fromFunction Int
reqLen ((forall s. MutableByteArray s -> Int -> ST s Int) -> Builder)
-> (forall s. MutableByteArray s -> Int -> ST s Int) -> Builder
forall a b. (a -> b) -> a -> b
$ \MutableByteArray s
dst Int
doff0 -> 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))
dst Int
doff0 (Char -> Word8
c2w Char
'"')
let go :: Int -> a -> Int -> ST s Int
go !Int
soff !a
slen !Int
doff = if a
slen a -> a -> Bool
forall a. Ord a => a -> a -> Bool
> a
0
then case ByteArray -> Int -> Char
indexChar8Array (ByteArray# -> ByteArray
ByteArray ByteArray#
src#) Int
soff of
Char
'\\' -> MutableByteArray s -> Int -> Char -> Char -> ST s ()
forall s. MutableByteArray s -> Int -> Char -> Char -> ST s ()
write2 MutableByteArray s
dst Int
doff Char
'\\' Char
'\\' ST s () -> ST s Int -> ST s Int
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Int -> a -> Int -> ST s Int
go (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (a
slen a -> a -> a
forall a. Num a => a -> a -> a
- a
1) (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2)
Char
'\"' -> MutableByteArray s -> Int -> Char -> Char -> ST s ()
forall s. MutableByteArray s -> Int -> Char -> Char -> ST s ()
write2 MutableByteArray s
dst Int
doff Char
'\\' Char
'\"' ST s () -> ST s Int -> ST s Int
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Int -> a -> Int -> ST s Int
go (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (a
slen a -> a -> a
forall a. Num a => a -> a -> a
- a
1) (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2)
Char
c -> if Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'\x20'
then 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 (Char -> Word8
c2w Char
c) ST s () -> ST s Int -> ST s Int
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Int -> a -> Int -> ST s Int
go (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (a
slen a -> a -> a
forall a. Num a => a -> a -> a
- a
1) (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
else case Char
c of
Char
'\n' -> MutableByteArray s -> Int -> Char -> Char -> ST s ()
forall s. MutableByteArray s -> Int -> Char -> Char -> ST s ()
write2 MutableByteArray s
dst Int
doff Char
'\\' Char
'n' ST s () -> ST s Int -> ST s Int
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Int -> a -> Int -> ST s Int
go (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (a
slen a -> a -> a
forall a. Num a => a -> a -> a
- a
1) (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2)
Char
'\r' -> MutableByteArray s -> Int -> Char -> Char -> ST s ()
forall s. MutableByteArray s -> Int -> Char -> Char -> ST s ()
write2 MutableByteArray s
dst Int
doff Char
'\\' Char
'r' ST s () -> ST s Int -> ST s Int
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Int -> a -> Int -> ST s Int
go (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (a
slen a -> a -> a
forall a. Num a => a -> a -> a
- a
1) (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2)
Char
'\t' -> MutableByteArray s -> Int -> Char -> Char -> ST s ()
forall s. MutableByteArray s -> Int -> Char -> Char -> ST s ()
write2 MutableByteArray s
dst Int
doff Char
'\\' Char
't' ST s () -> ST s Int -> ST s Int
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Int -> a -> Int -> ST s Int
go (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (a
slen a -> a -> a
forall a. Num a => a -> a -> a
- a
1) (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2)
Char
_ -> do
MutableByteArray s -> Int -> Char -> Char -> ST s ()
forall s. MutableByteArray s -> Int -> Char -> Char -> ST s ()
write2 MutableByteArray s
dst Int
doff Char
'\\' Char
'u'
Int
doff' <- Builder 4 -> MutableByteArray s -> Int -> ST s Int
forall (n :: Nat) s.
Builder n -> MutableByteArray s -> Int -> ST s Int
UnsafeBounded.pasteST
(Word16 -> Builder 4
Bounded.word16PaddedUpperHex (Word8 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Word8
c2w Char
c)))
MutableByteArray s
dst (Int
doff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2)
Int -> a -> Int -> ST s Int
go (Int
soff Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (a
slen a -> a -> a
forall a. Num a => a -> a -> a
- a
1) Int
doff'
else Int -> ST s Int
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
doff
Int
doffRes <- Int -> Int -> Int -> ST s Int
forall a. (Ord a, Num a) => Int -> a -> Int -> ST s Int
go (Int# -> Int
I# Int#
soff0#) (Int# -> Int
I# Int#
slen0#) (Int
doff0 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
doffRes (Char -> Word8
c2w Char
'"')
Int -> ST s Int
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
doffRes Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
where
slen0 :: Int
slen0 = Int# -> Int
I# Int#
slen0#
reqLen :: Int
reqLen = (Int
6 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
slen0) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2
fromFunction :: Int -> (forall s. MutableByteArray s -> Int -> ST s Int) -> Builder
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 #)
write2 :: MutableByteArray s -> Int -> Char -> Char -> ST s ()
write2 :: MutableByteArray s -> Int -> Char -> Char -> ST s ()
write2 MutableByteArray s
marr Int
ix Char
a Char
b = 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
ix (Char -> Word8
c2w Char
a)
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
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Char -> Word8
c2w Char
b)
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))
shortTextJsonString :: ShortText -> Builder
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
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
ascii :: Char -> Builder
ascii :: Char -> Builder
ascii Char
c = Builder 1 -> Builder
fromBoundedOne (Char -> Builder 1
Bounded.ascii Char
c)
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)
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)
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)
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)
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)
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)
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)
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 :: ST s a -> State# s -> (# State# s, a #)
unST (ST State# s -> (# State# s, a #)
f) = State# s -> (# State# s, a #)
f
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
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)
word8 :: Word8 -> Builder
word8 :: Word8 -> Builder
word8 Word8
w = Builder 1 -> Builder
fromBoundedOne (Word8 -> Builder 1
Bounded.word8 Word8
w)
consLength ::
Arithmetic.Nat n
-> (Int -> Bounded.Builder n)
-> Builder
-> Builder
{-# inline consLength #-}
consLength :: 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 ->
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 #)
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))
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))
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))
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
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
indexChar8Array :: ByteArray -> Int -> Char
indexChar8Array :: ByteArray -> Int -> Char
indexChar8Array (ByteArray ByteArray#
b) (I# Int#
i) = Char# -> Char
C# (ByteArray# -> Int# -> Char#
Exts.indexCharArray# ByteArray#
b Int#
i)
c2w :: Char -> Word8
c2w :: Char -> Word8
c2w = Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word8) -> (Char -> Int) -> Char -> Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Int
ord
zigZagNative :: Int -> Word
zigZagNative :: Int -> Word
zigZagNative Int
s = Int -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Int @Word
((Int -> Int -> Int
forall a. Bits a => a -> Int -> a
unsafeShiftL Int
s Int
1) Int -> Int -> Int
forall a. Bits a => a -> a -> a
`xor` (Int -> Int -> Int
forall a. Bits a => a -> Int -> a
unsafeShiftR Int
s (Word -> Int
forall b. FiniteBits b => b -> Int
finiteBitSize (Word
forall a. HasCallStack => a
undefined :: Word) Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)))
intLEB128 :: Int -> Builder
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
zigZagNative
wordLEB128 :: Word -> Builder
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)
word64LEB128 :: Word64 -> Builder
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)
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
<> Natural -> Builder
naturalDec (Integer -> Natural
naturalFromInteger (Integer -> Integer
forall a. Num a => a -> a
negate Integer
i))
| Bool
otherwise = Natural -> Builder
naturalDec (Integer -> Natural
naturalFromInteger Integer
i)
naturalDec :: Natural -> Builder
naturalDec :: Natural -> Builder
naturalDec !Natural
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# (Natural -> Integer
naturalToInteger Natural
n0))))
(\MutableByteArray s
marr Int
off -> case Natural
n0 of
Natural
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 (f :: * -> *) a. Applicative f => a -> f a
pure (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
Natural
_ -> Natural -> MutableByteArray s -> Int -> Int -> ST s Int
forall s. Natural -> MutableByteArray s -> Int -> Int -> ST s Int
go Natural
n0 MutableByteArray s
marr Int
off Int
off
)
where
go :: forall s. Natural -> MutableByteArray s -> Int -> Int -> ST s Int
go :: Natural -> MutableByteArray s -> Int -> Int -> ST s Int
go !Natural
n !MutableByteArray s
buf !Int
off0 !Int
off = case Natural -> Natural -> (Natural, Natural)
forall a. Integral a => a -> a -> (a, a)
quotRem Natural
n Natural
1_000_000_000 of
(Natural
q,Natural
r) -> case Natural
q of
Natural
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 (Natural -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Natural @Word Natural
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 (f :: * -> *) a. Applicative f => a -> f a
pure Int
off'
Natural
_ -> do
Int
off' <- Word -> MutableByteArray s -> Int -> ST s Int
forall s. Word -> MutableByteArray s -> Int -> ST s Int
backwardsPasteWordPaddedDec9
(Natural -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Natural @Word Natural
r) MutableByteArray s
buf Int
off
Natural -> MutableByteArray s -> Int -> Int -> ST s Int
forall s. Natural -> MutableByteArray s -> Int -> Int -> ST s Int
go Natural
q MutableByteArray s
buf Int
off0 Int
off'
reverseBytes :: MutableByteArray s -> Int -> Int -> ST s ()
{-# inline reverseBytes #-}
reverseBytes :: MutableByteArray s -> Int -> Int -> ST s ()
reverseBytes MutableByteArray s
arr Int
begin Int
end = Int -> Int -> ST s ()
go Int
begin Int
end where
go :: Int -> Int -> ST s ()
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 (ST s)) -> Int -> ST s Word8
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> m a
PM.readByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
arr Int
ixA
Word8
b :: Word8 <- MutableByteArray (PrimState (ST s)) -> Int -> ST s Word8
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> m a
PM.readByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
arr Int
ixB
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
ixA Word8
b
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
ixB Word8
a
Int -> Int -> ST s ()
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 () -> ST s ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
backwardsPasteWordPaddedDec9 ::
Word -> MutableByteArray s -> Int -> ST s Int
backwardsPasteWordPaddedDec9 :: 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 (f :: * -> *) a. Applicative f => a -> f a
pure ())
) MutableByteArray s
arr Int
off Word
w
Int -> ST s Int
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 :: (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 :: MutableByteArray s -> Int -> Word -> ST s Int
backwardsWordLoop MutableByteArray s
arr Int
off0 Word
x0 = Int -> Word -> ST s Int
go Int
off0 Word
x0 where
go :: Int -> Word -> ST s 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 (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
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 -> ST s Int
go (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Word
y
else Int -> ST s Int
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
off
replicate ::
Int
-> 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 (f :: * -> *) a. Applicative f => a -> f a
pure (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
len)
)
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
unsafeWordToWord8 :: Word -> Word8
unsafeWordToWord8 :: Word -> Word8
unsafeWordToWord8 (W# Word#
w) = Word# -> Word8
W8# Word#
w