Copyright | (c) 2010 Simon Meier |
---|---|
License | BSD3-style (see LICENSE) |
Maintainer | Simon Meier <iridcode@gmail.com> |
Stability | experimental |
Portability | tested on GHC only |
Safe Haskell | None |
Language | Haskell98 |
- data BufRange = BufRange !(Ptr Word8) !(Ptr Word8)
- data BuildSignal a
- data BuildStep a
- done :: Ptr Word8 -> a -> BuildSignal a
- bufferFull :: Int -> Ptr Word8 -> (BufRange -> IO (BuildSignal a)) -> BuildSignal a
- insertByteString :: Ptr Word8 -> ByteString -> (BufRange -> IO (BuildSignal a)) -> BuildSignal a
- data Builder
- fromBuildStepCont :: (forall r. (BufRange -> IO (BuildSignal r)) -> BufRange -> IO (BuildSignal r)) -> Builder
- fromPut :: Put a -> Builder
- flush :: Builder
- data Put a
- putBuilder :: Builder -> Put ()
- putBuildStepCont :: (forall r. (a -> BufRange -> IO (BuildSignal r)) -> BufRange -> IO (BuildSignal r)) -> Put a
- putLiftIO :: IO a -> Put a
- module Blaze.ByteString.Builder.Internal.Write
- writeToByteString :: Write -> ByteString
- toLazyByteString :: Builder -> ByteString
- toLazyByteStringWith :: Int -> Int -> Int -> Builder -> ByteString -> ByteString
- toByteString :: Builder -> ByteString
- toByteStringIO :: (ByteString -> IO ()) -> Builder -> IO ()
- toByteStringIOWith :: Int -> (ByteString -> IO ()) -> Builder -> IO ()
- defaultFirstBufferSize :: Int
- defaultMinimalBufferSize :: Int
- defaultBufferSize :: Int
- defaultMaximalCopySize :: Int
Build Steps
data BuildSignal a Source
done :: Ptr Word8 -> a -> BuildSignal a Source
bufferFull :: Int -> Ptr Word8 -> (BufRange -> IO (BuildSignal a)) -> BuildSignal a Source
insertByteString :: Ptr Word8 -> ByteString -> (BufRange -> IO (BuildSignal a)) -> BuildSignal a Source
Builder
fromBuildStepCont :: (forall r. (BufRange -> IO (BuildSignal r)) -> BufRange -> IO (BuildSignal r)) -> Builder Source
fromPut :: Put a -> Builder Source
Ignore the value of a put and only exploit its output side effect.
Output all data written in the current buffer and start a new chunk.
The use of this function depends on how the resulting bytestrings are
consumed. flush
is possibly not very useful in non-interactive scenarios.
However, it is kept for compatibility with the builder provided by
Data.Binary.Builder.
When using toLazyByteString
to extract a lazy ByteString
from a
Builder
, this means that a new chunk will be started in the resulting lazy
ByteString
. The remaining part of the buffer is spilled, if the
reamining free space is smaller than the minimal desired buffer size.
Put
putBuilder :: Builder -> Put () Source
Put the given builder.
putBuildStepCont :: (forall r. (a -> BufRange -> IO (BuildSignal r)) -> BufRange -> IO (BuildSignal r)) -> Put a Source
Writes
writeToByteString :: Write -> ByteString Source
Run a Write
to produce a strict ByteString
.
This is equivalent to (
, but is more
efficient because it uses just one appropriately-sized buffer.toByteString
. fromWrite
)
Execution
toLazyByteString :: Builder -> ByteString Source
Extract the lazy ByteString
from the builder by running it with default
buffer sizes. Use this function, if you do not have any special
considerations with respect to buffer sizes.
toLazyByteString
b =toLazyByteStringWith
defaultBufferSize
defaultMinimalBufferSize
defaultFirstBufferSize
b L.empty
Note that
is a toLazyByteString
Monoid
homomorphism.
toLazyByteString mempty == mempty toLazyByteString (x `mappend` y) == toLazyByteString x `mappend` toLazyByteString y
However, in the second equation, the left-hand-side is generally faster to execute.
:: Int | Buffer size (upper-bounds the resulting chunk size). |
-> Int | Minimal free buffer space for continuing filling
the same buffer after a |
-> Int | Size of the first buffer to be used and copied for larger resulting sequences |
-> Builder | Builder to run. |
-> ByteString | Lazy bytestring to output after the builder is finished. |
-> ByteString | Resulting lazy bytestring |
Run a Builder
with the given buffer sizes.
Use this function for integrating the Builder
type with other libraries
that generate lazy bytestrings.
Note that the builders should guarantee that on average the desired chunk size is attained. Builders may decide to start a new buffer and not completely fill the existing buffer, if this is faster. However, they should not spill too much of the buffer, if they cannot compensate for it.
A call toLazyByteStringWith bufSize minBufSize firstBufSize
will generate
a lazy bytestring according to the following strategy. First, we allocate
a buffer of size firstBufSize
and start filling it. If it overflows, we
allocate a buffer of size minBufSize
and copy the first buffer to it in
order to avoid generating a too small chunk. Finally, every next buffer will
be of size bufSize
. This, slow startup strategy is required to achieve
good speed for short (<200 bytes) resulting bytestrings, as for them the
allocation cost is of a large buffer cannot be compensated. Moreover, this
strategy also allows us to avoid spilling too much memory for short
resulting bytestrings.
Note that setting firstBufSize >= minBufSize
implies that the first buffer
is no longer copied but allocated and filled directly. Hence, setting
firstBufSize = bufSize
means that all chunks will use an underlying buffer
of size bufSize
. This is recommended, if you know that you always output
more than minBufSize
bytes.
toByteString :: Builder -> ByteString Source
Run the builder to construct a strict bytestring containing the sequence of bytes denoted by the builder. This is done by first serializing to a lazy bytestring and then packing its chunks to a appropriately sized strict bytestring.
toByteString = packChunks . toLazyByteString
Note that
is a toByteString
Monoid
homomorphism.
toByteString mempty == mempty toByteString (x `mappend` y) == toByteString x `mappend` toByteString y
However, in the second equation, the left-hand-side is generally faster to execute.
toByteStringIO :: (ByteString -> IO ()) -> Builder -> IO () Source
Run the builder with a defaultBufferSize
d buffer and execute the given
IO
action whenever the buffer is full or gets flushed.
toByteStringIO
=toByteStringIOWith
defaultBufferSize
This is a Monoid
homomorphism in the following sense.
toByteStringIO io mempty == return () toByteStringIO io (x `mappend` y) == toByteStringIO io x >> toByteStringIO io y
:: Int | Buffer size (upper bounds
the number of bytes forced
per call to the |
-> (ByteString -> IO ()) |
|
-> Builder |
|
-> IO () | Resulting |
toByteStringIOWith bufSize io b
runs the builder b
with a buffer of
at least the size bufSize
and executes the IO
action io
whenever the
buffer is full.
Compared to toLazyByteStringWith
this function requires less allocation,
as the output buffer is only allocated once at the start of the
serialization and whenever something bigger than the current buffer size has
to be copied into the buffer, which should happen very seldomly for the
default buffer size of 32kb. Hence, the pressure on the garbage collector is
reduced, which can be an advantage when building long sequences of bytes.
Deafult Sizes
defaultFirstBufferSize :: Int Source
The default length (64) for the first buffer to be allocated when
converting a Builder
to a lazy bytestring.
See toLazyByteStringWith
for further explanation.
defaultMinimalBufferSize :: Int Source
The minimal length (~4kb) a buffer must have before filling it and outputting it as a chunk of the output stream.
This size determines when a buffer is spilled after a flush
or a direct
bytestring insertion. It is also the size of the first chunk generated by
toLazyByteString
.
defaultBufferSize :: Int Source
Default size (~32kb) for the buffer that becomes a chunk of the output stream once it is filled.
defaultMaximalCopySize :: Int Source
The maximal number of bytes for that copying is cheaper than direct
insertion into the output stream. This takes into account the fragmentation
that may occur in the output buffer due to the early flush
implied by the
direct bytestring insertion.
defaultMaximalCopySize
= 2 *defaultMinimalBufferSize