Copyright | (c) Dong Han 2017-2018 |
---|---|
License | BSD |
Maintainer | winterland1989@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data Builder a
- append :: Builder a -> Builder b -> Builder b
- build :: Builder a -> Bytes
- buildWith :: Int -> Builder a -> Bytes
- buildChunks :: Builder a -> [Bytes]
- buildChunksWith :: Int -> Int -> Builder a -> [Bytes]
- buildText :: HasCallStack => Builder a -> Text
- unsafeBuildText :: Builder a -> Text
- bytes :: Bytes -> Builder ()
- ensureN :: Int -> (MutablePrimArray RealWorld Word8 -> Int -> IO Int) -> Builder ()
- writeN :: Int -> (MutablePrimArray RealWorld Word8 -> Int -> IO ()) -> Builder ()
- encodePrim :: forall a. Unaligned a => a -> Builder ()
- encodePrimLE :: forall a. Unaligned (LE a) => a -> Builder ()
- encodePrimBE :: forall a. Unaligned (BE a) => a -> Builder ()
- stringModifiedUTF8 :: String -> Builder ()
- charModifiedUTF8 :: Char -> Builder ()
- stringUTF8 :: String -> Builder ()
- charUTF8 :: Char -> Builder ()
- string7 :: String -> Builder ()
- char7 :: Char -> Builder ()
- word7 :: Word8 -> Builder ()
- string8 :: String -> Builder ()
- char8 :: Char -> Builder ()
- word8 :: Word8 -> 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 ()
- hexUpper :: 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 ()
- day :: Day -> Builder ()
- timeOfDay :: TimeOfDay -> Builder ()
- timeZone :: TimeZone -> Builder ()
- utcTime :: UTCTime -> Builder ()
- localTime :: LocalTime -> Builder ()
- zonedTime :: ZonedTime -> 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 # | This instance simple write literals' bytes into buffer,
which is different from |
Defined in Z.Data.Builder.Base fromString :: String -> Builder a # | |
Semigroup (Builder ()) Source # | |
Monoid (Builder ()) Source # | |
Arbitrary (Builder ()) Source # | |
CoArbitrary (Builder ()) Source # | |
Defined in Z.Data.Builder.Base 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.
buildChunks :: Builder a -> [Bytes] Source #
Shortcut to buildChunksWith
defaultChunkSize
.
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 #
Basic buiders
Pritimive builders
encodePrim :: forall a. Unaligned a => a -> Builder () Source #
Write a primitive type in host byte order.
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 #
stringUTF8 :: String -> Builder () Source #
Turn String
into Builder
with UTF8 encoding
Illegal codepoints will be written as replacementChar
s.
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 replacementChar
s.
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.
Numeric builders
Integral type formatting
Integral formatting options.
defaultIFormat :: IFormat Source #
defaultIFormat = IFormat 0 NoPadding False
Instances
Enum Padding Source # | |
Eq Padding Source # | |
Ord Padding Source # | |
Show Padding Source # | |
Arbitrary Padding Source # | |
CoArbitrary Padding Source # | |
Defined in Z.Data.Builder.Numeric coarbitrary :: Padding -> Gen b -> Gen b # |
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 import Z.Data.Text as T > T.validate . B.buildBytes $ B.intWith defaultIFormat (12345 :: Int) "12345" > T.validate . B.buildBytes $ B.intWith defaultIFormat{width=10, padding=RightSpacePadding} (12345 :: Int) "12345 " > T.validate . B.buildBytes $ B.intWith defaultIFormat{width=10, padding=ZeroPadding} (12345 :: Int) "0000012345"
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.buildBytes $ B.hex (125 :: Int8) "7d" > T.validate . B.buildBytes $ B.hex (-1 :: Int8) "ff" > T.validate . B.buildBytes $ B.hex (125 :: Word16) "007d"
hexUpper :: forall a. (FiniteBits a, Integral a) => a -> Builder () Source #
The UPPERCASED version of hex
.
IEEE float formating
Control the rendering of floating point numbers.
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.
:: FFormat | |
-> Maybe Int | Number of decimal places to render. |
-> Scientific | |
-> Builder () |
Like scientific
but provides rendering options.
Builder helpers
:: 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"
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
timeZone :: TimeZone -> Builder () Source #
Timezone format in +HH:MM
, with single letter Z
for +00:00
.