Copyright | (c) Dong Han 2017-2019 (c) Tao He 2018-2019 |
---|---|
License | BSD |
Maintainer | winterland1989@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
A Builder
records a buffer writing function, which can be mappend
in O(1) via composition.
In stdio a Builder
are designed to deal with different AllocateStrategy
, it affects how
Builder
react when writing across buffer boundaries:
- When building a short strict
Bytes
with 'buildBytes/buildByteswith', we do aDoubleBuffer
. - When building a large lazy
[Bytes]
with 'buildBytesList/buildBytesListwith', we do anInsertChunk
. - When building and consuming are interlaced with 'buildAndRun/buildAndRunWith',
we do an
OneShotAction
.
Most of the time using combinators from this module to build Builder
s is enough,
but in case of rolling something shining from the ground, keep an eye on correct
AllocateStrategy
handling.
Synopsis
- data AllocateStrategy s
- = DoubleBuffer
- | InsertChunk !Int
- | OneShotAction (Bytes -> ST s ())
- data Buffer s = Buffer !(MutablePrimArray s Word8) !Int
- type BuildStep s = Buffer s -> ST s [Bytes]
- newtype Builder a = Builder {
- runBuilder :: forall s. AllocateStrategy s -> (a -> BuildStep s) -> BuildStep s
- append :: Builder a -> Builder b -> Builder b
- buildBytes :: Builder a -> Bytes
- buildBytesWith :: Int -> Builder a -> Bytes
- buildBytesList :: Builder a -> [Bytes]
- buildBytesListWith :: Int -> Int -> Builder a -> [Bytes]
- buildAndRun :: (Bytes -> IO ()) -> Builder a -> IO ()
- buildAndRunWith :: Int -> (Bytes -> IO ()) -> Builder a -> IO ()
- bytes :: Bytes -> Builder ()
- ensureN :: Int -> Builder ()
- atMost :: Int -> (forall s. MutablePrimArray s Word8 -> Int -> ST s Int) -> Builder ()
- writeN :: Int -> (forall s. MutablePrimArray s Word8 -> Int -> ST s ()) -> Builder ()
- doubleBuffer :: Int -> BuildStep s -> BuildStep s
- insertChunk :: Int -> Int -> BuildStep s -> BuildStep s
- oneShotAction :: (Bytes -> ST s ()) -> Int -> BuildStep s -> BuildStep s
- encodePrim :: forall a. UnalignedAccess a => a -> Builder ()
- encodePrimLE :: forall a. UnalignedAccess (LE a) => a -> Builder ()
- encodePrimBE :: forall a. UnalignedAccess (BE a) => a -> Builder ()
- stringModifiedUTF8 :: String -> Builder ()
- charModifiedUTF8 :: Char -> Builder ()
- stringUTF8 :: String -> Builder ()
- charUTF8 :: Char -> Builder ()
- string7 :: String -> Builder ()
- char7 :: Char -> Builder ()
- string8 :: String -> Builder ()
- char8 :: Char -> Builder ()
- text :: Text -> Builder ()
Builder type
data AllocateStrategy s Source #
AllocateStrategy
will decide how each BuildStep
proceed when previous buffer is not enough.
DoubleBuffer | |
InsertChunk !Int | |
OneShotAction (Bytes -> ST s ()) |
Helper type to help ghc unpack
Buffer | |
|
type BuildStep s = Buffer s -> ST s [Bytes] Source #
BuilderStep
is a function that fill buffer under given conditions.
Builder
is a monad to help compose BuilderStep
. With next BuilderStep
continuation,
we can do interesting things like perform some action, or interleave the build process.
Notes on IsString
instance: Builder ()
's IsString
instance use stringModifiedUTF8
,
which is different from stringUTF8
in that it DOES NOT PROVIDE UTF8 GUARANTEES! :
NUL
will be written asxC0 x80
.xD800
~xDFFF
will be encoded in three bytes as normal UTF-8 codepoints.
Builder | |
|
Running a builder
buildBytes :: Builder a -> Bytes Source #
shortcut to buildBytesWith
defaultInitSize
.
buildBytesWith :: Int -> Builder a -> Bytes Source #
run Builder with DoubleBuffer
strategy, which is suitable
for building short bytes.
buildBytesList :: Builder a -> [Bytes] Source #
shortcut to buildBytesListWith
defaultChunkSize
.
buildBytesListWith :: Int -> Int -> Builder a -> [Bytes] Source #
run Builder with InsertChunk
strategy, which is suitable
for building lazy bytes chunks.
buildAndRun :: (Bytes -> IO ()) -> Builder a -> IO () Source #
shortcut to buildAndRunWith
defaultChunkSize
.
buildAndRunWith :: Int -> (Bytes -> IO ()) -> Builder a -> IO () Source #
run Builder with OneShotAction
strategy, which is suitable
for doing effects while building.
Basic buiders
Boundary handling
Pritimive builders
encodePrim :: forall a. UnalignedAccess a => a -> Builder () Source #
write primitive types in host byte order.
encodePrimLE :: forall a. UnalignedAccess (LE a) => a -> Builder () Source #
write primitive types with little endianess.
encodePrimBE :: forall a. UnalignedAccess (BE a) => a -> Builder () Source #
write primitive types with big endianess.
More builders
stringModifiedUTF8 :: String -> Builder () Source #
Encode string with modified UTF-8 encoding, will be rewritten to a memcpy if possible.
charModifiedUTF8 :: Char -> Builder () Source #
stringUTF8 :: String -> Builder () Source #
Turn String
into Builder
with UTF8 encoding
Illegal codepoints will be written as replacementChar
s.
Note, if you're trying to write string literals builders, and you know it doen't contain
'\NUL' or surrgate codepoints, then you can open OverloadedStrings
and use Builder'
s
IsString
instance, it can save an extra UTF-8 validation.
This function will be rewritten into a memcpy if possible, (running a fast UTF-8 validation at runtime first).
charUTF8 :: Char -> Builder () Source #
Turn Char
into Builder
with UTF8 encoding
Illegal codepoints will be written as replacementChar
s.