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

Z.Data.Builder

Description

A Builder records a buffer writing function, which can be mappend in O(1) via composition. This module provides many functions to turn basic data types into Builders, which can used to build strict Bytes or list of Bytes chunks.

Synopsis

Builder type

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

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 #

This instance simple write literals' bytes into buffer, which is different from stringUTF8 in that it DOES NOT PROVIDE UTF8 GUARANTEES! :

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 builders

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

Run Builder with doubling buffer strategy, which is suitable for building short bytes.

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 #

Build some bytes assuming it's UTF8 encoding.

Be carefully use this function because you could constrcut illegal Text values. Check ShowT for UTF8 encoding builders. This functions is intended to be used in debug only.

Basic buiders

bytes :: Bytes -> Builder () Source #

Write a Bytes.

ensureN Source #

Arguments

:: Int

size bound

-> (MutablePrimArray RealWorld Word8 -> Int -> IO Int)

the writer which return a new offset for next write

-> Builder () 

writeN Source #

Arguments

:: Int

size bound

-> (MutablePrimArray RealWorld Word8 -> Int -> IO ())

the writer should write exactly N bytes

-> Builder () 

Pritimive builders

encodePrim :: forall a. Unaligned a => a -> Builder () Source #

Write a primitive type in host byte order.

> encodePrim (256 :: Word16, BE 256 :: BE Word16)
> [0,1,1,0]

newtype BE a Source #

big endianess wrapper

Constructors

BE 

Fields

Instances

Instances details
Eq a => Eq (BE a) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

Methods

(==) :: BE a -> BE a -> Bool #

(/=) :: BE a -> BE a -> Bool #

Show a => Show (BE a) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

Methods

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

show :: BE a -> String #

showList :: [BE a] -> ShowS #

Unaligned (BE Char) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

Unaligned (BE Double) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

Unaligned (BE Float) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

Unaligned (BE Int) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

Unaligned (BE Int16) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

Unaligned (BE Int32) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

Unaligned (BE Int64) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

Unaligned (BE Word) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

Unaligned (BE Word16) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

Unaligned (BE Word32) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

Unaligned (BE Word64) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

newtype LE a Source #

little endianess wrapper

Constructors

LE 

Fields

Instances

Instances details
Eq a => Eq (LE a) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

Methods

(==) :: LE a -> LE a -> Bool #

(/=) :: LE a -> LE a -> Bool #

Show a => Show (LE a) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

Methods

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

show :: LE a -> String #

showList :: [LE a] -> ShowS #

Unaligned (LE Char) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

Unaligned (LE Double) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

Unaligned (LE Float) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

Unaligned (LE Int) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

Unaligned (LE Int16) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

Unaligned (LE Int32) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

Unaligned (LE Int64) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

Unaligned (LE Word) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

Unaligned (LE Word16) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

Unaligned (LE Word32) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

Unaligned (LE Word64) Source # 
Instance details

Defined in Z.Data.Array.Unaligned

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 #

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.

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

word7 :: Word8 -> Builder () Source #

Turn Word8 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.

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.

word8N :: Int -> Word8 -> Builder () Source #

Faster version of replicateM x . word8 by using memset.

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.

Numeric builders

Integral type formatting

data IFormat Source #

Integral formatting options.

Constructors

IFormat 

Fields

Instances

Instances details
Eq IFormat Source # 
Instance details

Defined in Z.Data.Builder.Numeric

Methods

(==) :: IFormat -> IFormat -> Bool #

(/=) :: IFormat -> IFormat -> Bool #

Ord IFormat Source # 
Instance details

Defined in Z.Data.Builder.Numeric

Show IFormat Source # 
Instance details

Defined in Z.Data.Builder.Numeric

Arbitrary IFormat Source # 
Instance details

Defined in Z.Data.Builder.Numeric

CoArbitrary IFormat Source # 
Instance details

Defined in Z.Data.Builder.Numeric

Methods

coarbitrary :: IFormat -> Gen b -> Gen b #

defaultIFormat :: IFormat Source #

defaultIFormat = IFormat 0 NoPadding False

data Padding Source #

Instances

Instances details
Enum Padding Source # 
Instance details

Defined in Z.Data.Builder.Numeric

Eq Padding Source # 
Instance details

Defined in Z.Data.Builder.Numeric

Methods

(==) :: Padding -> Padding -> Bool #

(/=) :: Padding -> Padding -> Bool #

Ord Padding Source # 
Instance details

Defined in Z.Data.Builder.Numeric

Show Padding Source # 
Instance details

Defined in Z.Data.Builder.Numeric

Arbitrary Padding Source # 
Instance details

Defined in Z.Data.Builder.Numeric

CoArbitrary Padding Source # 
Instance details

Defined in Z.Data.Builder.Numeric

Methods

coarbitrary :: Padding -> Gen b -> Gen b #

int :: (Integral a, Bounded a) => a -> Builder () Source #

int = intWith defaultIFormat

intWith :: (Integral a, Bounded a) => IFormat -> a -> Builder () Source #

Format a Bounded Integral type like Int or Word16 into decimal ASCII digits.

import Z.Data.Builder as B

> B.buildText $ B.intWith defaultIFormat  (12345 :: Int)
"12345"
> B.buildText $ B.intWith defaultIFormat{width=10, padding=RightSpacePadding} (12345 :: Int)
"12345     "
> B.buildText $ B.intWith defaultIFormat{width=10, padding=ZeroPadding} (12345 :: Int)
"0000012345"

integer :: Integer -> Builder () Source #

Format a Integer into decimal ASCII digits.

Fixded size hexidecimal formatting

hex :: forall a. (FiniteBits a, Integral a) => a -> Builder () Source #

Format a FiniteBits Integral type into hex nibbles.

import Z.Data.Builder as B
import Z.Data.Text    as T
import Data.Word
import Data.Int

> T.validate . B.build $ B.hex (125 :: Int8)
"7d"
> T.validate . B.build $ B.hex (-1 :: Int8)
"ff"
> T.validate . B.build $ B.hex (125 :: Word16)
"007d"

hexUpper :: forall a. (FiniteBits a, Integral a) => a -> Builder () Source #

The UPPERCASED version of hex.

IEEE float formating

data FFormat Source #

Control the rendering of floating point numbers.

Constructors

Exponent

Scientific notation (e.g. 2.3e123).

Fixed

Standard decimal notation.

Generic

Use decimal notation for values between 0.1 and 9,999,999, and scientific notation otherwise.

double :: Double -> Builder () Source #

Decimal encoding of an IEEE Double.

Using standard decimal notation for arguments whose absolute value lies between 0.1 and 9,999,999, and scientific notation otherwise.

doubleWith Source #

Arguments

:: FFormat 
-> Maybe Int

Number of decimal places to render.

-> Double 
-> Builder () 

Format double-precision float using drisu3 with dragon4 fallback.

float :: Float -> Builder () Source #

Decimal encoding of an IEEE Float.

Using standard decimal notation for arguments whose absolute value lies between 0.1 and 9,999,999, and scientific notation otherwise.

floatWith Source #

Arguments

:: FFormat 
-> Maybe Int

Number of decimal places to render.

-> Float 
-> Builder () 

Format single-precision float using drisu3 with dragon4 fallback.

scientific :: Scientific -> Builder () Source #

A Builder which renders a scientific number to full precision, using standard decimal notation for arguments whose absolute value lies between 0.1 and 9,999,999, and scientific notation otherwise.

scientific' :: Scientific -> Builder () Source #

This builder try to avoid scientific notation when 0 <= exponent < 16.

scientificWith Source #

Arguments

:: FFormat 
-> Maybe Int

Number of decimal places to render.

-> Scientific 
-> Builder () 

Like scientific but provides rendering options.

Builder helpers

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

add (...) to original builder.

parenWhen :: Bool -> Builder () -> Builder () Source #

Add "(..)" around builders when condition is met, otherwise add nothing.

This is useful when defining Print instances.

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.

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"

intercalateList Source #

Arguments

:: Builder ()

the seperator

-> (a -> Builder ())

value formatter

-> [a]

value list

-> Builder () 

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"

Time

day :: Day -> Builder () Source #

YYYY-mm-dd.

timeOfDay :: TimeOfDay -> Builder () Source #

HH-MM-SS.

timeZone :: TimeZone -> Builder () Source #

Timezone format in +HH:MM, with single letter Z for +00:00.

utcTime :: UTCTime -> Builder () Source #

Write UTCTime in ISO8061 YYYY-MM-DDTHH:MM:SS.SSSZ(time zone will always be Z).

localTime :: LocalTime -> Builder () Source #

Write LocalTime in ISO8061 YYYY-MM-DDTHH:MM:SS.SSS.

zonedTime :: ZonedTime -> Builder () Source #

Write ZonedTime in ISO8061 YYYY-MM-DD HH:MM:SS.SSSZ.