Z-Data-0.1.0.0: array, vector and text
Copyright(c) Dong Han 2017-2019
(c) Tao He 2018-2019
LicenseBSD
Maintainerwinterland1989@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Z.Data.Builder.Base

Description

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 a DoubleBuffer.
  • When building a large lazy [Bytes] with 'buildBytesList/buildBytesListwith', we do an InsertChunk.
  • 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

Builder type

data AllocateStrategy s Source #

AllocateStrategy will decide how each BuildStep proceed when previous buffer is not enough.

Constructors

DoubleBuffer 
InsertChunk !Int 
OneShotAction (Bytes -> ST s ()) 

data Buffer s Source #

Helper type to help ghc unpack

Constructors

Buffer 

Fields

type BuildStep s = Buffer s -> ST s [Bytes] Source #

BuilderStep is a function that fill buffer under given conditions.

newtype Builder a Source #

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 as xC0 x80.
  • xD800 ~ xDFFF will be encoded in three bytes as normal UTF-8 codepoints.

Constructors

Builder 

Fields

Instances

Instances details
Monad Builder Source # 
Instance details

Defined in Z.Data.Builder.Base

Methods

(>>=) :: Builder a -> (a -> Builder b) -> Builder b #

(>>) :: Builder a -> Builder b -> Builder b #

return :: a -> Builder a #

Functor Builder Source # 
Instance details

Defined in Z.Data.Builder.Base

Methods

fmap :: (a -> b) -> Builder a -> Builder b #

(<$) :: a -> Builder b -> Builder a #

Applicative Builder Source # 
Instance details

Defined in Z.Data.Builder.Base

Methods

pure :: a -> Builder a #

(<*>) :: Builder (a -> b) -> Builder a -> Builder b #

liftA2 :: (a -> b -> c) -> Builder a -> Builder b -> Builder c #

(*>) :: Builder a -> Builder b -> Builder b #

(<*) :: Builder a -> Builder b -> Builder a #

Show (Builder a) Source # 
Instance details

Defined in Z.Data.Builder.Base

Methods

showsPrec :: Int -> Builder a -> ShowS #

show :: Builder a -> String #

showList :: [Builder a] -> ShowS #

a ~ () => IsString (Builder a) Source # 
Instance details

Defined in Z.Data.Builder.Base

Methods

fromString :: String -> Builder a #

Semigroup (Builder ()) Source # 
Instance details

Defined in Z.Data.Builder.Base

Methods

(<>) :: Builder () -> Builder () -> Builder () #

sconcat :: NonEmpty (Builder ()) -> Builder () #

stimes :: Integral b => b -> Builder () -> Builder () #

Monoid (Builder ()) Source # 
Instance details

Defined in Z.Data.Builder.Base

Methods

mempty :: Builder () #

mappend :: Builder () -> Builder () -> Builder () #

mconcat :: [Builder ()] -> Builder () #

Arbitrary (Builder ()) Source # 
Instance details

Defined in Z.Data.Builder.Base

Methods

arbitrary :: Gen (Builder ())

shrink :: Builder () -> [Builder ()]

CoArbitrary (Builder ()) Source # 
Instance details

Defined in Z.Data.Builder.Base

Methods

coarbitrary :: Builder () -> Gen b -> Gen b

Running a builder

buildBytesWith :: Int -> Builder a -> Bytes Source #

run Builder with DoubleBuffer strategy, which is suitable for building short bytes.

buildBytesListWith :: Int -> Int -> Builder a -> [Bytes] Source #

run Builder with InsertChunk strategy, which is suitable for building lazy bytes chunks.

buildAndRunWith :: Int -> (Bytes -> IO ()) -> Builder a -> IO () Source #

run Builder with OneShotAction strategy, which is suitable for doing effects while building.

Basic buiders

bytes :: Bytes -> Builder () Source #

Write a Bytes.

ensureN :: Int -> Builder () Source #

Ensure that there are at least n many elements available.

atMost Source #

Arguments

:: Int

size bound

-> (forall s. MutablePrimArray s Word8 -> Int -> ST s Int)

the writer which pure a new offset for next write

-> Builder () 

writeN Source #

Arguments

:: Int

size bound

-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())

the writer which pure a new offset for next write

-> Builder () 

Boundary handling

oneShotAction :: (Bytes -> ST s ()) -> Int -> BuildStep s -> BuildStep s Source #

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 #

Turn Char into Builder with Modified UTF8 encoding

'NUL' is encoded as two bytes C0 80 , 'xD800' ~ 'xDFFF' is encoded as a three bytes normal UTF-8 codepoint.

stringUTF8 :: String -> Builder () Source #

Turn String into Builder with UTF8 encoding

Illegal codepoints will be written as replacementChars.

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 replacementChars.

string7 :: String -> Builder () Source #

Turn String into Builder with ASCII7 encoding

Codepoints beyond 'x7F' will be chopped.

char7 :: Char -> Builder () Source #

Turn Char into Builder with ASCII7 encoding

Codepoints beyond 'x7F' will be chopped.

string8 :: String -> Builder () Source #

Turn String into Builder with ASCII8 encoding

Codepoints beyond 'xFF' will be chopped. Note, this encoding is NOT compatible with UTF8 encoding, i.e. bytes written by this builder may not be legal UTF8 encoding bytes.

char8 :: Char -> Builder () Source #

Turn Char into Builder with ASCII8 encoding

Codepoints beyond 'xFF' will be chopped. Note, this encoding is NOT compatible with UTF8 encoding, i.e. bytes written by this builder may not be legal UTF8 encoding bytes.

text :: Text -> Builder () Source #

Write UTF8 encoded Text using Builder.

Note, if you're trying to write string literals builders, please open OverloadedStrings and use Builders IsString instance, it will be rewritten into a memcpy.

Builder helpers

paren :: Builder () -> Builder () Source #

add {...} to original builder.

curly :: Builder () -> Builder () Source #

add {...} to original builder.

square :: Builder () -> Builder () Source #

add [...] to original builder.

angle :: Builder () -> Builder () Source #

add ... to original builder.

quotes :: Builder () -> Builder () Source #

add "..." to original builder.

squotes :: Builder () -> Builder () Source #

add ... to original builder.

colon :: Builder () Source #

write an ASCII :

comma :: Builder () Source #

write an ASCII ,

intercalateVec Source #

Arguments

:: Vec v a 
=> Builder ()

the seperator

-> (a -> Builder ())

value formatter

-> v a

value vector

-> Builder () 

Use separator to connect a vector of builders.

intercalateList Source #

Arguments

:: Builder ()

the seperator

-> (a -> Builder ())

value formatter

-> [a]

value list

-> Builder () 

Use separator to connect list of builders.