Copyright | (c) Fumiaki Kinoshita 2019- |
---|---|
License | BSD3 |
Maintainer | Fumiaki Kinoshita <fumiexcel@gmail.com> |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- type Builder = forall s. Buildable s => BuilderFor s
- data BuilderFor s
- class Buildable s
- type StrictByteStringBackend = GrowingBuffer
- toStrictByteString :: BuilderFor StrictByteStringBackend -> ByteString
- type LazyByteStringBackend = Channel
- toLazyByteString :: BuilderFor LazyByteStringBackend -> ByteString
- type BufferedIOBackend = PutEnv
- hPutBuilderLen :: Handle -> BuilderFor BufferedIOBackend -> IO Int
- hPutBuilder :: Handle -> BuilderFor PutEnv -> IO ()
- sendBuilder :: Socket -> BuilderFor BufferedIOBackend -> IO Int
- withPopper :: BuilderFor LazyByteStringBackend -> (IO ByteString -> IO a) -> IO a
- data StreamingBackend
- toStreamingBody :: BuilderFor StreamingBackend -> (Builder -> IO ()) -> IO () -> IO ()
- flush :: Buildable s => BuilderFor s
- byteString :: Buildable s => ByteString -> BuilderFor s
- lazyByteString :: ByteString -> Builder
- shortByteString :: ShortByteString -> Builder
- textUtf8 :: Text -> Builder
- encodeUtf8Builder :: Text -> Builder
- encodeUtf8BuilderEscaped :: Buildable s => BoundedPrim Word8 -> Text -> BuilderFor s
- char7 :: Char -> Builder
- string7 :: String -> Builder
- char8 :: Char -> Builder
- string8 :: String -> Builder
- charUtf8 :: Char -> Builder
- stringUtf8 :: Buildable s => String -> BuilderFor s
- storable :: Storable a => a -> Builder
- int8 :: Int8 -> Builder
- word8 :: Word8 -> Builder
- int16LE :: Int16 -> Builder
- int32LE :: Int32 -> Builder
- int64LE :: Int64 -> Builder
- word16LE :: Word16 -> Builder
- word32LE :: Word32 -> Builder
- word64LE :: Word64 -> Builder
- floatLE :: Float -> Builder
- doubleLE :: Double -> Builder
- int16BE :: Int16 -> Builder
- int32BE :: Int32 -> Builder
- int64BE :: Int64 -> Builder
- word16BE :: Word16 -> Builder
- word32BE :: Word32 -> Builder
- word64BE :: Word64 -> Builder
- floatBE :: Float -> Builder
- doubleBE :: Double -> Builder
- floatDec :: Float -> Builder
- doubleDec :: Double -> Builder
- doubleSI :: Int -> Double -> Builder
- doubleExp :: Int -> Double -> Builder
- doubleFixed :: Int -> Double -> Builder
- word8Dec :: Word8 -> Builder
- word16Dec :: Word16 -> Builder
- word32Dec :: Word32 -> Builder
- word64Dec :: Word64 -> Builder
- wordDec :: Word -> Builder
- int8Dec :: Int8 -> Builder
- int16Dec :: Int16 -> Builder
- int32Dec :: Int32 -> Builder
- int64Dec :: Int64 -> Builder
- intDec :: Int -> Builder
- intDecPadded :: Int -> Int -> Builder
- integerDec :: Integer -> Builder
- word8Hex :: Word8 -> Builder
- word16Hex :: Word16 -> Builder
- word32Hex :: Word32 -> Builder
- word64Hex :: Word64 -> Builder
- wordHex :: Word -> Builder
- int8HexFixed :: Int8 -> Builder
- int16HexFixed :: Int16 -> Builder
- int32HexFixed :: Int32 -> Builder
- int64HexFixed :: Int64 -> Builder
- word8HexFixed :: Word8 -> Builder
- word16HexFixed :: Word16 -> Builder
- word32HexFixed :: Word32 -> Builder
- word64HexFixed :: Word64 -> Builder
- floatHexFixed :: Float -> Builder
- doubleHexFixed :: Double -> Builder
- byteStringHex :: ByteString -> Builder
- lazyByteStringHex :: ByteString -> Builder
- intVLQ :: Int -> Builder
- intVLQBP :: BoundedPrim Int
- wordVLQ :: Word -> Builder
- wordVLQBP :: BoundedPrim Word
- prefixVarInt :: Word -> Builder
- prefixVarIntBP :: BoundedPrim Word
- intersperse :: (Foldable f, Buildable e) => BuilderFor e -> f (BuilderFor e) -> BuilderFor e
- unwords :: (Foldable f, Buildable e) => f (BuilderFor e) -> BuilderFor e
- unlines :: (Foldable f, Buildable e) => f (BuilderFor e) -> BuilderFor e
- viaShow :: Show a => a -> Builder
- paddedBoundedPrim :: Word8 -> Int -> BoundedPrim a -> a -> Builder
- zeroPaddedBoundedPrim :: Int -> BoundedPrim a -> a -> Builder
- primFixed :: Buildable s => FixedPrim a -> a -> BuilderFor s
- primBounded :: Buildable s => BoundedPrim a -> a -> BuilderFor s
- lengthPrefixedWithin :: Int -> BoundedPrim Int -> BuilderFor () -> Builder
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
Buildable s => IsString (BuilderFor s) Source # | |
Defined in Mason.Builder.Internal fromString :: String -> BuilderFor s # | |
Monoid (BuilderFor a) Source # | |
Defined in Mason.Builder.Internal mempty :: BuilderFor a # mappend :: BuilderFor a -> BuilderFor a -> BuilderFor a # mconcat :: [BuilderFor a] -> BuilderFor a # | |
Semigroup (BuilderFor s) Source # | |
Defined in Mason.Builder.Internal (<>) :: BuilderFor s -> BuilderFor s -> BuilderFor s # sconcat :: NonEmpty (BuilderFor s) -> BuilderFor s # stimes :: Integral b => b -> BuilderFor s -> BuilderFor s # |
This class is used to provide backend-specific operations for running a Builder
.
Instances
Buildable DynamicBackend Source # | |
Defined in Mason.Builder.Dynamic | |
Buildable Channel Source # | |
Defined in Mason.Builder.Internal | |
Buildable GrowingBuffer Source # | |
Defined in Mason.Builder.Internal | |
Buildable PutEnv Source # | |
Defined in Mason.Builder.Internal byteString :: ByteString -> BuilderFor PutEnv Source # flush :: BuilderFor PutEnv Source # | |
Buildable StreamingBackend Source # | |
Defined in Mason.Builder.Internal | |
Buildable () Source # | Work with a constant buffer. |
Defined in Mason.Builder.Internal byteString :: ByteString -> BuilderFor () Source # flush :: BuilderFor () Source # allocate :: Int -> BuilderFor () Source # |
Runners
toStrictByteString :: BuilderFor StrictByteStringBackend -> ByteString Source #
Create a strict ByteString
type LazyByteStringBackend = Channel Source #
toLazyByteString :: BuilderFor LazyByteStringBackend -> ByteString Source #
Create a lazy ByteString
. Threaded runtime is required.
type BufferedIOBackend = PutEnv Source #
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 #
sendBuilder :: Socket -> BuilderFor BufferedIOBackend -> IO Int Source #
Write a Builder
into a handle and obtain the number of bytes written.
withPopper :: BuilderFor LazyByteStringBackend -> (IO ByteString -> IO a) -> IO a Source #
data StreamingBackend Source #
Instances
toStreamingBody :: BuilderFor StreamingBackend -> (Builder -> IO ()) -> IO () -> IO () Source #
Convert a Builder
into a StreamingBody.
Primitives
flush :: Buildable s => BuilderFor s Source #
Flush the content of the internal buffer.
Bytes
byteString :: Buildable s => ByteString -> BuilderFor s Source #
Put a ByteString
.
lazyByteString :: ByteString -> Builder Source #
Combine chunks of a lazy ByteString
shortByteString :: ShortByteString -> Builder Source #
Copy a ShortByteString
to a buffer.
Text
encodeUtf8Builder :: Text -> Builder Source #
encodeUtf8BuilderEscaped :: Buildable s => BoundedPrim Word8 -> Text -> BuilderFor s Source #
Encode Text
with a custom escaping function.
Note that implementation differs between text-1.x
and text-2.x
due to the
package moving from using UTF-16 to UTF-8 for the internal representation.
stringUtf8 :: Buildable s => String -> BuilderFor s Source #
UTF-8 encode a String
.
Primitive
Numeral
Attach an SI prefix so that abs(mantissa) is within [1, 1000). Omits c, d, da and h.
int8Dec :: Int8 -> Builder Source #
Decimal encoding of an Int8
using the ASCII digits.
e.g.
toLazyByteString (int8Dec 42) = "42" toLazyByteString (int8Dec (-1)) = "-1"
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.
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
prefixVarInt :: Word -> Builder Source #
Encode a Word in PrefixVarInt
Combinators
intersperse :: (Foldable f, Buildable e) => BuilderFor e -> f (BuilderFor e) -> BuilderFor e Source #
unwords :: (Foldable f, Buildable e) => f (BuilderFor e) -> BuilderFor e Source #
unlines :: (Foldable f, Buildable e) => f (BuilderFor e) -> BuilderFor e Source #
Advanced
:: Word8 | filler |
-> Int | pad if shorter than this |
-> BoundedPrim a | |
-> a | |
-> Builder |
zeroPaddedBoundedPrim :: Int -> BoundedPrim a -> a -> Builder Source #
primBounded :: Buildable s => BoundedPrim a -> a -> BuilderFor s Source #
Use BoundedPrim
:: Int | maximum length |
-> BoundedPrim Int | prefix encoder |
-> BuilderFor () | |
-> Builder |
Run a builder within a buffer and prefix it by the length.