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.
- When building a short strict
Bytes
withbuild
/buildWith
, we double the buffer each time buffer is full. - When building a large lazy
[Bytes]
withbuildChunks
/buildChunksWith
, we insert a new chunk when buffer is full.
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 BuildResult
handling.
Synopsis
- newtype Builder a = Builder {
- runBuilder :: (a -> BuildStep) -> BuildStep
- append :: Builder a -> Builder b -> Builder b
- data Buffer = Buffer !(MutablePrimArray RealWorld Word8) !Int
- freezeBuffer :: Buffer -> IO Bytes
- data BuildResult
- type BuildStep = Buffer -> IO BuildResult
- build :: Builder a -> Bytes
- buildWith :: Int -> Builder a -> Bytes
- buildChunks :: Builder a -> [Bytes]
- buildChunksWith :: Int -> Int -> Builder a -> [Bytes]
- buildText :: HasCallStack => Builder a -> Text
- unsafeBuildText :: Builder a -> Text
- bytes :: Bytes -> Builder ()
- ensureN :: Int -> (MutablePrimArray RealWorld Word8 -> Int -> IO Int) -> Builder ()
- writeN :: Int -> (MutablePrimArray RealWorld Word8 -> Int -> IO ()) -> Builder ()
- encodePrim :: forall a. Unaligned a => a -> Builder ()
- encodePrimLE :: forall a. Unaligned (LE a) => a -> Builder ()
- encodePrimBE :: forall a. Unaligned (BE a) => a -> Builder ()
- stringModifiedUTF8 :: String -> Builder ()
- charModifiedUTF8 :: Char -> Builder ()
- stringUTF8 :: String -> Builder ()
- charUTF8 :: Char -> Builder ()
- string7 :: String -> Builder ()
- char7 :: Char -> Builder ()
- word7 :: Word8 -> Builder ()
- string8 :: String -> Builder ()
- char8 :: Char -> Builder ()
- word8 :: Word8 -> Builder ()
- text :: Text -> Builder ()
- paren :: Builder () -> Builder ()
- curly :: Builder () -> Builder ()
- square :: Builder () -> Builder ()
- angle :: Builder () -> Builder ()
- quotes :: Builder () -> Builder ()
- squotes :: Builder () -> Builder ()
- colon :: Builder ()
- comma :: Builder ()
- intercalateVec :: Vec v a => Builder () -> (a -> Builder ()) -> v a -> Builder ()
- intercalateList :: Builder () -> (a -> Builder ()) -> [a] -> Builder ()
Builder type
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 | |
|
Instances
Monad Builder Source # | |
Functor Builder Source # | |
Applicative Builder Source # | |
Show (Builder a) Source # | |
a ~ () => IsString (Builder a) Source # | This instance simple write literals' bytes into buffer,
which is different from |
Defined in Z.Data.Builder.Base fromString :: String -> Builder a # | |
Semigroup (Builder ()) Source # | |
Monoid (Builder ()) Source # | |
Arbitrary (Builder ()) Source # | |
CoArbitrary (Builder ()) Source # | |
Defined in Z.Data.Builder.Base coarbitrary :: Builder () -> Gen b -> Gen b # |
Helper type to help ghc unpack
Buffer | |
|
freezeBuffer :: Buffer -> IO Bytes Source #
Freeze buffer and return a Bytes
.
Note the mutable buffer array will be shrinked with shrinkMutablePrimArray
, which may not
able to be reused.
data BuildResult Source #
BuildSignal
s abstract signals to the caller of a BuildStep
. There are
three signals: Done
, BufferFull
, or InsertBytes
signals
type BuildStep = Buffer -> IO BuildResult Source #
BuilderStep
is a function that fill buffer under given conditions.
Running a builder
buildWith :: Int -> Builder a -> Bytes Source #
Run Builder with doubling buffer strategy, which is suitable for building short bytes.
buildChunks :: Builder a -> [Bytes] Source #
Shortcut to buildChunksWith
defaultChunkSize
.
buildChunksWith :: Int -> Int -> Builder a -> [Bytes] Source #
Run Builder with inserting chunk strategy, which is suitable for building a list of bytes chunks and processing them in a streaming ways.
Note the building process is lazy, building happens when list chunks are consumed.
buildText :: HasCallStack => Builder a -> Text Source #
Build some bytes and validate if it's UTF8 bytes.
unsafeBuildText :: Builder a -> Text Source #
Basic buiders
Pritimive builders
encodePrim :: forall a. Unaligned a => a -> Builder () Source #
Write a primitive type in host byte order.
encodePrimLE :: forall a. Unaligned (LE a) => a -> Builder () Source #
Write a primitive type with little endianess.
encodePrimBE :: forall a. Unaligned (BE a) => a -> Builder () Source #
Write a primitive type 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.
This is different from writing string literals builders via OverloadedStrings
, because string literals
do not provide UTF8 guarantees.
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.
word8 :: Word8 -> Builder () Source #
Turn Word8
into Builder
with ASCII8 encoding, (alias to encodePrim
).
Note, this encoding is NOT compatible with UTF8 encoding, i.e. bytes written by this builder may not be legal UTF8 encoding bytes.
Builder helpers
:: Vec v a | |
=> Builder () | the seperator |
-> (a -> Builder ()) | value formatter |
-> v a | value vector |
-> Builder () |
Use separator to connect a vector of builders.
import Z.Data.Builder as B import Z.Data.Text as T import Z.Data.Vector as V > T.validate . B.build $ B.intercalateVec "," B.int (V.pack [1,2,3,4] :: V.PrimVector Int) "1,2,3,4"
Use separator to connect list of builders.
import Z.Data.Builder as B import Z.Data.Text as T import Z.Data.Vector as V T.validate . B.build $ B.intercalateList "," B.int ([1,2,3,4] :: [Int]) "1,2,3,4"