Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Implementation details of the Data.ByteString.Reverse module. Breaking changes will be more frequent in this module; use with caution.
Synopsis
- newtype BuildR = BuildR (Addr# -> Int# -> State# RealWorld -> (# Addr#, Int#, State# RealWorld #))
- data BuildRState = BuildRState {}
- appendBuildR :: BuildR -> BuildR -> BuildR
- foldlRVector :: Vector v a => (b -> a -> b) -> b -> v a -> b
- toBuildR :: (Ptr Word8 -> Int -> IO (Ptr Word8, Int)) -> BuildR
- fromBuildR :: BuildR -> Ptr Word8 -> Int -> IO (Ptr Word8, Int)
- etaBuildR :: (a -> BuildR) -> a -> BuildR
- runBuildR :: BuildR -> (Int, ByteString)
- data SealedState = SealedState {
- sealedSB :: ByteString
- totalSB :: !Int
- stateVarSB :: !(IORef BuildRState)
- statePtrSB :: !(StablePtr (IORef BuildRState))
- recycledSB :: Maybe (MutableByteArray RealWorld)
- sealBuffer :: Ptr Word8 -> Int -> IO SealedState
- smallChunkSize :: Int
- readState :: Ptr MetaData -> IO (StablePtr (IORef BuildRState))
- readSpace :: Ptr MetaData -> IO Int
- writeState :: Ptr MetaData -> StablePtr (IORef BuildRState) -> IO ()
- writeSpace :: Ptr MetaData -> Int -> IO ()
- metaDataSize :: Int
- metaDataAlign :: Int
- withUnused :: (Int -> BuildR) -> BuildR
- withTotal :: (Int -> BuildR) -> BuildR
- readTotal :: Ptr Word8 -> Int -> IO Int
- withLengthOf :: (Int -> BuildR) -> BuildR -> BuildR
- withLengthOf# :: (Int# -> BuildR) -> BuildR -> BuildR
- reallocate :: Int -> BuildR
- prependChunk :: ByteString -> BuildR
- newtype ReverseChunks = ReverseChunks {}
- prependReverseChunks :: ReverseChunks -> BuildR
- ensure :: Int -> BuildR -> BuildR
- ensure# :: Int# -> BuildR -> BuildR
- unsafeConsume :: Int -> (Ptr Word8 -> IO ()) -> BuildR
- floatToWord32 :: Ptr Word8 -> Int -> Float -> IO Word32
- doubleToWord64 :: Ptr Word8 -> Int -> Double -> IO Word64
Documentation
Writes bytes in reverse order, updating the current state.
It is the responsibility of the execution context and buffer
management primitives to ensure that the current buffer remains
reachable during builder execution, though completed buffers
may be copied to new storage at any time. Aside from those
primitives, BuildR
implementations may ignore that issue.
When combining BuildR
s with <>
we expect the best performance
when associating to the left. For example
,
though unless your foldl
(<>
) mempty
foldl
iteration starts from the right there may
still be issues. Consider using vectorBuildR
instead of foldMap
.
BuildR (Addr# -> Int# -> State# RealWorld -> (# Addr#, Int#, State# RealWorld #)) | Both the builder arguments and the returned values are:
It seems we cannot preserve register allocation between the arguments
and the returned components, even by including padding. If GHC were to
allocate registers right-to-left (instead of the current left-to-right),
and if it made sure to allocate the register that it uses for closure
arguments *last* when allocating return registers, then we would stand
a chance of not having to move the state components between registers.
That way But in many cases register movements combine with increments. Also, we have arranged to put only the most frequently-used state components into registers, which reduces the costs of both moves and of save/reload pairs. For example, our tracking of the total bytes written involves metadata at the start of the current buffer rather than an additional state register. |
data BuildRState Source #
The current state of execution of a builder
is a
.StablePtr
(IORef
BuildRState
)
Current Buffer Layout:
We devote the first few octets of the current buffer to metadata that does not change very frequently:
Addr#
: cast to 'StablePtr# (IORef BuildRState)'; indirect acceses to the full builder state, which is used relatively infrequently.Int#
: the total number of non-metadata bytes originally available within the current buffer before we started consuming them,- plus* the number of bytes actually written to previous buffers. We subtract the current unused figure to get the total bytes written.
Double#
: suitably-aligned scratch space for serialization ofDouble
andFloat
values.
Though this choice imposes a small memory overhead in every buffer, it reduces the time and space required to save and restore metadata around the many non-inline calls that typically occur while writing data into the buffer.
BuildRState | |
|
appendBuildR :: BuildR -> BuildR -> BuildR Source #
Needed for rewrite rules; normally you would use <>
.
foldlRVector :: Vector v a => (b -> a -> b) -> b -> v a -> b Source #
Like foldl
but iterates right-to-left, which
is often useful when creating reverse builders.
etaBuildR :: (a -> BuildR) -> a -> BuildR Source #
Eta-expands a function that produces a BuildR
, so that
its input is not evaluated until the builder state is presented.
This odd combinator seems to help performance at times, though
it may change behavior on nonterminating values of type a
.
runBuildR :: BuildR -> (Int, ByteString) Source #
Like toLazyByteString
but also
returns the total length of the lazy ByteString
,
which is computed as a side effect of encoding.
data SealedState Source #
The result of a call to sealBuffer
.
SealedState | |
|
:: Ptr Word8 | Pointer to the used portion of the current buffer. |
-> Int | The number of bytes still unused in the current buffer. |
-> IO SealedState |
Takes ownership of the current buffer, but sometimes hands it back for reuse.
If more building is required then please allocate a new current buffer and update the builder state variable accordingly.
(This is a manual wrapper around sealBuffer#
.)
smallChunkSize :: Int Source #
writeState :: Ptr MetaData -> StablePtr (IORef BuildRState) -> IO () Source #
metaDataSize :: Int Source #
metaDataAlign :: Int Source #
withUnused :: (Int -> BuildR) -> BuildR Source #
First reads the number of unused bytes in the current buffer.
withLengthOf :: (Int -> BuildR) -> BuildR -> BuildR Source #
Executes the right builder, measuring how many bytes it writes, then provides that figure to the left builder.
withLengthOf# :: (Int# -> BuildR) -> BuildR -> BuildR Source #
Executes the right builder, measuring how many bytes it writes, then provides that figure to the left builder.
reallocate :: Int -> BuildR Source #
Seals the current buffer and creates a new one with at least the given number of bytes.
prependChunk :: ByteString -> BuildR Source #
Prepends a ByteString
to the output.
NOTE: This is a relatively heavyweight operation. For small strings it may be faster to copy them to the current buffer.
newtype ReverseChunks Source #
Like ByteString
, but with the chunks in reverse order,
even though the bytes within each chunk are in forward order.
prependReverseChunks :: ReverseChunks -> BuildR Source #
Equivalent to the following, but faster:
foldMap prependChunk . reverse . getReverseChunks
NOTE: This is a relatively heavyweight operation. For small strings it may be faster to copy them to the current buffer.
ensure :: Int -> BuildR -> BuildR Source #
Ensures that the current buffer has at least the given number of bytes before executing the given builder.
unsafeConsume :: Int -> (Ptr Word8 -> IO ()) -> BuildR Source #
ASSUMES that the specified number of bytes is both nonnegative and less than or equal to the number of unused bytes in the current buffer, consumes that number of unused bytes, and provides their starting address.