stdio-0.1.0.0: A simple and high performance IO toolkit for Haskell

Copyright(c) Dong Han 2017-2018
LicenseBSD
Maintainerwinterland1989@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Std.Data.Builder

Contents

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
Monad Builder Source # 
Instance details

Defined in Std.Data.Builder.Base

Methods

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

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

return :: a -> Builder a #

fail :: String -> Builder a #

Functor Builder Source # 
Instance details

Defined in Std.Data.Builder.Base

Methods

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

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

Applicative Builder Source # 
Instance details

Defined in Std.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 #

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

Defined in Std.Data.Builder.Base

Methods

fromString :: String -> Builder a #

Semigroup (Builder ()) Source # 
Instance details

Defined in Std.Data.Builder.Base

Methods

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

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

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

Monoid (Builder ()) Source # 
Instance details

Defined in Std.Data.Builder.Base

Methods

mempty :: Builder () #

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

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

Running builders

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 return a new offset for next write

-> Builder () 

writeN Source #

Arguments

:: Int

size bound

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

the writer which return a new offset for next write

-> Builder () 

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

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.

Numeric builders

Integral type formatting

data IFormat Source #

Integral formatting options.

Constructors

IFormat 

Fields

Instances
Eq IFormat Source # 
Instance details

Defined in Std.Data.Builder.Numeric

Methods

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

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

Ord IFormat Source # 
Instance details

Defined in Std.Data.Builder.Numeric

Show IFormat Source # 
Instance details

Defined in Std.Data.Builder.Numeric

defaultIFormat :: IFormat Source #

defaultIFormat = IFormat 0 NoPadding False Decimal

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.

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.

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

scientificWith Source #

Arguments

:: FFormat 
-> Maybe Int

Number of decimal places to render.

-> Scientific 
-> Builder () 

Like scientific but provides rendering options.