mason-0.2.3: Fast and extensible bytestring builder
Copyright(c) Fumiaki Kinoshita 2019-
LicenseBSD3
MaintainerFumiaki Kinoshita <fumiexcel@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Mason.Builder

Description

 
Synopsis

Documentation

type Builder = forall s. Buildable s => BuilderFor s Source #

The Builder type. Requires RankNTypes extension

data BuilderFor s Source #

Builder specialised for a backend

Instances

Instances details
Buildable s => IsString (BuilderFor s) Source # 
Instance details

Defined in Mason.Builder.Internal

Methods

fromString :: String -> BuilderFor s #

Semigroup (BuilderFor s) Source # 
Instance details

Defined in Mason.Builder.Internal

Monoid (BuilderFor a) Source # 
Instance details

Defined in Mason.Builder.Internal

class Buildable s Source #

This class is used to provide backend-specific operations for running a Builder.

Minimal complete definition

flush, allocate

Runners

toLazyByteString :: BuilderFor LazyByteStringBackend -> ByteString Source #

Create a lazy ByteString. Threaded runtime is required.

hPutBuilderLen :: Handle -> BuilderFor BufferedIOBackend -> IO Int Source #

Write a Builder into a handle and obtain the number of bytes written. flush does not imply actual disk operations. Set NoBuffering if you want it to write the content immediately.

hPutBuilder :: Handle -> BuilderFor PutEnv -> IO () Source #

Put the content of a Builder to a Handle.

sendBuilder :: Socket -> BuilderFor BufferedIOBackend -> IO Int Source #

Write a Builder into a handle and obtain the number of bytes written.

Primitives

flush :: Buildable s => BuilderFor s Source #

Flush the content of the internal buffer.

Bytes

lazyByteString :: ByteString -> Builder Source #

Combine chunks of a lazy ByteString

Text

textUtf8 :: Text -> Builder Source #

Encode Text as a UTF-8 byte stream.

encodeUtf8Builder :: Text -> Builder Source #

Encode Text as a UTF-8 byte stream. Synonym for textUtf8.

encodeUtf8BuilderEscaped :: BoundedPrim Word8 -> Text -> Builder Source #

Encode Text with a custom escaping function

char7 :: Char -> Builder Source #

Char7 encode a Char.

string7 :: String -> Builder Source #

Char7 encode a String.

char8 :: Char -> Builder Source #

Char8 encode a Char.

string8 :: String -> Builder Source #

Char8 encode a String.

charUtf8 :: Char -> Builder Source #

UTF-8 encode a Char.

stringUtf8 :: String -> Builder Source #

UTF-8 encode a String.

Primitive

storable :: Storable a => a -> Builder Source #

Turn a Storable value into a Builder

int8 :: Int8 -> Builder Source #

Encode a single signed byte as-is.

word8 :: Word8 -> Builder Source #

Encode a single unsigned byte as-is.

int16LE :: Int16 -> Builder Source #

Encode an Int16 in little endian format.

int32LE :: Int32 -> Builder Source #

Encode an Int32 in little endian format.

int64LE :: Int64 -> Builder Source #

Encode an Int64 in little endian format.

word16LE :: Word16 -> Builder Source #

Encode a Word16 in little endian format.

word32LE :: Word32 -> Builder Source #

Encode a Word32 in little endian format.

word64LE :: Word64 -> Builder Source #

Encode a Word64 in little endian format.

floatLE :: Float -> Builder Source #

Encode a Float in little endian format.

doubleLE :: Double -> Builder Source #

Encode a Double in little endian format.

int16BE :: Int16 -> Builder Source #

Encode an Int16 in big endian format.

int32BE :: Int32 -> Builder Source #

Encode an Int32 in big endian format.

int64BE :: Int64 -> Builder Source #

Encode an Int64 in big endian format.

word16BE :: Word16 -> Builder Source #

Encode a Word16 in big endian format.

word32BE :: Word32 -> Builder Source #

Encode a Word32 in big endian format.

word64BE :: Word64 -> Builder Source #

Encode a Word64 in big endian format.

floatBE :: Float -> Builder Source #

Encode a Float in big endian format.

doubleBE :: Double -> Builder Source #

Encode a Double in big endian format.

Numeral

floatDec :: Float -> Builder Source #

Currently slow. Decimal encoding of an IEEE Float.

doubleDec :: Double -> Builder Source #

Decimal encoding of an IEEE Double.

doubleSI Source #

Arguments

:: Int

precision: must be equal or greater than 3

-> Double 
-> Builder 

Attach an SI prefix so that abs(mantissa) is within [1, 1000). Omits c, d, da and h.

doubleExp Source #

Arguments

:: Int

number of digits in the mantissa

-> Double 
-> Builder 

Always use exponents

doubleFixed Source #

Arguments

:: Int

decimal points

-> Double 
-> Builder 

Fixed precision

word8Dec :: Word8 -> Builder Source #

Decimal encoding of a Word8 using the ASCII digits.

word16Dec :: Word16 -> Builder Source #

Decimal encoding of a Word16 using the ASCII digits.

word32Dec :: Word32 -> Builder Source #

Decimal encoding of a Word32 using the ASCII digits.

word64Dec :: Word64 -> Builder Source #

Decimal encoding of a Word64 using the ASCII digits.

wordDec :: Word -> Builder Source #

Decimal encoding of a Word using the ASCII digits.

int8Dec :: Int8 -> Builder Source #

Decimal encoding of an Int8 using the ASCII digits.

e.g.

toLazyByteString (int8Dec 42)   = "42"
toLazyByteString (int8Dec (-1)) = "-1"

int16Dec :: Int16 -> Builder Source #

Decimal encoding of an Int16 using the ASCII digits.

int32Dec :: Int32 -> Builder Source #

Decimal encoding of an Int32 using the ASCII digits.

int64Dec :: Int64 -> Builder Source #

Decimal encoding of an Int64 using the ASCII digits.

intDec :: Int -> Builder Source #

Decimal encoding of an Int using the ASCII digits.

intDecPadded :: Int -> Int -> Builder Source #

intDec with 0 padding

integerDec :: Integer -> Builder Source #

Decimal encoding of an Integer using the ASCII digits. Simon Meier's improved implementation from https://github.com/haskell/bytestring/commit/92f19a5d94761042b44a433d7331107611e4d717

word8Hex :: Word8 -> Builder Source #

Shortest hexadecimal encoding of a Word8 using lower-case characters.

word16Hex :: Word16 -> Builder Source #

Shortest hexadecimal encoding of a Word16 using lower-case characters.

word32Hex :: Word32 -> Builder Source #

Shortest hexadecimal encoding of a Word32 using lower-case characters.

word64Hex :: Word64 -> Builder Source #

Shortest hexadecimal encoding of a Word64 using lower-case characters.

wordHex :: Word -> Builder Source #

Shortest hexadecimal encoding of a Word using lower-case characters.

int8HexFixed :: Int8 -> Builder Source #

Encode a Int8 using 2 nibbles (hexadecimal digits).

int16HexFixed :: Int16 -> Builder Source #

Encode a Int16 using 4 nibbles.

int32HexFixed :: Int32 -> Builder Source #

Encode a Int32 using 8 nibbles.

int64HexFixed :: Int64 -> Builder Source #

Encode a Int64 using 16 nibbles.

word8HexFixed :: Word8 -> Builder Source #

Encode a Word8 using 2 nibbles (hexadecimal digits).

word16HexFixed :: Word16 -> Builder Source #

Encode a Word16 using 4 nibbles.

word32HexFixed :: Word32 -> Builder Source #

Encode a Word32 using 8 nibbles.

word64HexFixed :: Word64 -> Builder Source #

Encode a Word64 using 16 nibbles.

floatHexFixed :: Float -> Builder Source #

Encode an IEEE Float using 8 nibbles.

doubleHexFixed :: Double -> Builder Source #

Encode an IEEE Double using 16 nibbles.

byteStringHex :: ByteString -> Builder Source #

Encode each byte of a ByteString using its fixed-width hex encoding.

lazyByteStringHex :: ByteString -> Builder Source #

Encode each byte of a lazy ByteString using its fixed-width hex encoding.

Variable-length encoding

intVLQ :: Int -> Builder Source #

Signed VLQ encoding (the first bit is a sign)

wordVLQ :: Word -> Builder Source #

Unsigned VLQ encoding

Combinators

viaShow :: Show a => a -> Builder Source #

Turn a value into a Builder using the Show instance.

Advanced

paddedBoundedPrim Source #

Arguments

:: Word8

filler

-> Int

pad if shorter than this

-> BoundedPrim a 
-> a 
-> Builder 

lengthPrefixedWithin Source #

Arguments

:: Int

maximum length

-> BoundedPrim Int

prefix encoder

-> BuilderFor () 
-> Builder 

Run a builder within a buffer and prefix it by the length.