Copyright | (c) Dong Han 2017-2018 |
---|---|
License | BSD |
Maintainer | winterland1989@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Z.Data.Builder
Description
Synopsis
- data Builder a
- append :: Builder a -> Builder b -> Builder b
- buildBytes :: Builder a -> Bytes
- buildBytesWith :: Int -> Builder a -> Bytes
- buildBytesList :: Builder a -> [Bytes]
- buildBytesListWith :: Int -> Int -> Builder a -> [Bytes]
- buildAndRun :: (Bytes -> IO ()) -> Builder a -> IO ()
- buildAndRunWith :: Int -> (Bytes -> IO ()) -> Builder a -> IO ()
- bytes :: Bytes -> Builder ()
- ensureN :: Int -> Builder ()
- atMost :: Int -> (forall s. MutablePrimArray s Word8 -> Int -> ST s Int) -> Builder ()
- writeN :: Int -> (forall s. MutablePrimArray s Word8 -> Int -> ST s ()) -> Builder ()
- encodePrim :: forall a. UnalignedAccess a => a -> Builder ()
- encodePrimLE :: forall a. UnalignedAccess (LE a) => a -> Builder ()
- encodePrimBE :: forall a. UnalignedAccess (BE a) => a -> Builder ()
- stringModifiedUTF8 :: String -> Builder ()
- charModifiedUTF8 :: Char -> Builder ()
- stringUTF8 :: String -> Builder ()
- charUTF8 :: Char -> Builder ()
- string7 :: String -> Builder ()
- char7 :: Char -> Builder ()
- string8 :: String -> Builder ()
- char8 :: Char -> Builder ()
- text :: Text -> Builder ()
- data IFormat = IFormat {}
- defaultIFormat :: IFormat
- data Padding
- int :: (Integral a, Bounded a) => a -> Builder ()
- intWith :: (Integral a, Bounded a) => IFormat -> a -> Builder ()
- integer :: Integer -> Builder ()
- hex :: forall a. (FiniteBits a, Integral a) => a -> Builder ()
- heX :: forall a. (FiniteBits a, Integral a) => a -> Builder ()
- data FFormat
- double :: Double -> Builder ()
- doubleWith :: FFormat -> Maybe Int -> Double -> Builder ()
- float :: Float -> Builder ()
- floatWith :: FFormat -> Maybe Int -> Float -> Builder ()
- scientific :: Scientific -> Builder ()
- scientificWith :: FFormat -> Maybe Int -> Scientific -> Builder ()
- paren :: Builder () -> Builder ()
- curly :: Builder () -> Builder ()
- square :: Builder () -> Builder ()
- angle :: Builder () -> Builder ()
- quotes :: Builder () -> Builder ()
- squotes :: Builder () -> Builder ()
- colon :: Builder ()
- comma :: Builder ()
- intercalateVec :: Vec v a => Builder () -> (a -> Builder ()) -> v a -> Builder ()
- intercalateList :: Builder () -> (a -> Builder ()) -> [a] -> Builder ()
Builder type
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 asxC0 x80
.xD800
~xDFFF
will be encoded in three bytes as normal UTF-8 codepoints.
Instances
Monad Builder Source # | |
Functor Builder Source # | |
Applicative Builder Source # | |
Show (Builder a) Source # | |
a ~ () => IsString (Builder a) Source # | |
Defined in Z.Data.Builder.Base Methods fromString :: String -> Builder a # | |
Semigroup (Builder ()) Source # | |
Monoid (Builder ()) Source # | |
Arbitrary (Builder ()) Source # | |
CoArbitrary (Builder ()) Source # | |
Defined in Z.Data.Builder.Base Methods coarbitrary :: Builder () -> Gen b -> Gen b |
Running builders
buildBytes :: Builder a -> Bytes Source #
shortcut to buildBytesWith
defaultInitSize
.
buildBytesWith :: Int -> Builder a -> Bytes Source #
run Builder with DoubleBuffer
strategy, which is suitable
for building short bytes.
buildBytesList :: Builder a -> [Bytes] Source #
shortcut to buildBytesListWith
defaultChunkSize
.
buildBytesListWith :: Int -> Int -> Builder a -> [Bytes] Source #
run Builder with InsertChunk
strategy, which is suitable
for building lazy bytes chunks.
buildAndRun :: (Bytes -> IO ()) -> Builder a -> IO () Source #
shortcut to buildAndRunWith
defaultChunkSize
.
buildAndRunWith :: Int -> (Bytes -> IO ()) -> Builder a -> IO () Source #
run Builder with OneShotAction
strategy, which is suitable
for doing effects while building.
Basic buiders
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 #
stringUTF8 :: String -> Builder () Source #
Turn String
into Builder
with UTF8 encoding
Illegal codepoints will be written as replacementChar
s.
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 replacementChar
s.
Numeric builders
Integral type formatting
Integral formatting options.
Constructors
IFormat | |
defaultIFormat :: IFormat Source #
defaultIFormat = IFormat 0 NoPadding False
Constructors
NoPadding | |
RightSpacePadding | |
LeftSpacePadding | |
ZeroPadding |
Instances
Enum Padding Source # | |
Eq Padding Source # | |
Ord Padding Source # | |
Defined in Z.Data.Builder.Numeric | |
Show Padding Source # | |
Arbitrary Padding Source # | |
CoArbitrary Padding Source # | |
Defined in Z.Data.Builder.Numeric Methods coarbitrary :: Padding -> Gen b -> Gen b |
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
Control the rendering of floating point numbers.
Constructors
Exponent | Scientific notation (e.g. |
Fixed | Standard decimal notation. |
Generic | Use decimal notation for values between |
Instances
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.
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.
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.
Like scientific
but provides rendering options.