Copyright | (c) Duncan Coutts 2015-2017 |
---|---|
License | BSD3-style (see LICENSE.txt) |
Maintainer | duncan@community.haskell.org |
Stability | experimental |
Portability | non-portable (GHC extensions) |
Safe Haskell | None |
Language | Haskell2010 |
High level API for encoding values, for later serialization into
CBOR binary format, using a
based interface.Monoid
Synopsis
- newtype Encoding = Encoding (Tokens -> Tokens)
- data Tokens
- = TkWord !Word Tokens
- | TkWord64 !Word64 Tokens
- | TkInt !Int Tokens
- | TkInt64 !Int64 Tokens
- | TkBytes !ByteString Tokens
- | TkBytesBegin Tokens
- | TkByteArray !SlicedByteArray Tokens
- | TkString !Text Tokens
- | TkUtf8ByteArray !SlicedByteArray Tokens
- | TkStringBegin Tokens
- | TkListLen !Word Tokens
- | TkListBegin Tokens
- | TkMapLen !Word Tokens
- | TkMapBegin Tokens
- | TkTag !Word Tokens
- | TkTag64 !Word64 Tokens
- | TkInteger !Integer Tokens
- | TkNull Tokens
- | TkUndef Tokens
- | TkBool !Bool Tokens
- | TkSimple !Word8 Tokens
- | TkFloat16 !Float Tokens
- | TkFloat32 !Float Tokens
- | TkFloat64 !Double Tokens
- | TkBreak Tokens
- | TkEnd
- encodeWord :: Word -> Encoding
- encodeWord8 :: Word8 -> Encoding
- encodeWord16 :: Word16 -> Encoding
- encodeWord32 :: Word32 -> Encoding
- encodeWord64 :: Word64 -> Encoding
- encodeInt :: Int -> Encoding
- encodeInt8 :: Int8 -> Encoding
- encodeInt16 :: Int16 -> Encoding
- encodeInt32 :: Int32 -> Encoding
- encodeInt64 :: Int64 -> Encoding
- encodeInteger :: Integer -> Encoding
- encodeBytes :: ByteString -> Encoding
- encodeBytesIndef :: Encoding
- encodeByteArray :: SlicedByteArray -> Encoding
- encodeString :: Text -> Encoding
- encodeStringIndef :: Encoding
- encodeUtf8ByteArray :: SlicedByteArray -> Encoding
- encodeListLen :: Word -> Encoding
- encodeListLenIndef :: Encoding
- encodeMapLen :: Word -> Encoding
- encodeMapLenIndef :: Encoding
- encodeBreak :: Encoding
- encodeTag :: Word -> Encoding
- encodeTag64 :: Word64 -> Encoding
- encodeBool :: Bool -> Encoding
- encodeUndef :: Encoding
- encodeNull :: Encoding
- encodeSimple :: Word8 -> Encoding
- encodeFloat16 :: Float -> Encoding
- encodeFloat :: Float -> Encoding
- encodeDouble :: Double -> Encoding
Encoding implementation
An intermediate form used during serialisation, specified as a
. It supports efficient concatenation, and is equivalent
to a specialised Monoid
type.Endo
Tokens
It is used for the stage in serialisation where we flatten out the Haskell data structure but it is independent of any specific external binary or text format.
Traditionally, to build any arbitrary
value, you specify
larger structures from smaller ones and append the small ones together
using Encoding
.mconcat
Since: cborg-0.2.0.0
A flattened representation of a term, which is independent of any underlying binary representation, but which we later serialise into CBOR format.
Since: cborg-0.2.0.0
Encoding
API for serialisation
Encoding
encodeWord16 :: Word16 -> Encoding Source #
Encode a
in a flattened format.Word16
Since: cborg-0.2.0.0
encodeWord32 :: Word32 -> Encoding Source #
Encode a
in a flattened format.Word32
Since: cborg-0.2.0.0
encodeWord64 :: Word64 -> Encoding Source #
Encode a
in a flattened format.Word64
Since: cborg-0.2.0.0
encodeInt64 :: Int64 -> Encoding Source #
Encode an @Int64
in a flattened format.
Since: cborg-0.2.0.0
encodeInteger :: Integer -> Encoding Source #
Encode an arbitrarily large @Integer
in a
flattened format.
Since: cborg-0.2.0.0
encodeBytes :: ByteString -> Encoding Source #
Encode an arbitrary strict
in
a flattened format.ByteString
Since: cborg-0.2.0.0
encodeBytesIndef :: Encoding Source #
Encode a token specifying the beginning of a string of bytes of
indefinite length. In reality, this specifies a stream of many
occurrences of encodeBytes
, each specifying a single chunk of the
overall string. After all the bytes desired have been encoded, you
should follow it with a break token (see
).encodeBreak
Since: cborg-0.2.0.0
encodeByteArray :: SlicedByteArray -> Encoding Source #
Encode a bytestring in a flattened format.
Since: cborg-0.2.0.0
encodeStringIndef :: Encoding Source #
Encode the beginning of an indefinite string.
Since: cborg-0.2.0.0
encodeUtf8ByteArray :: SlicedByteArray -> Encoding Source #
Encode a UTF-8 string in a flattened format. Note that the contents is not validated to be well-formed UTF-8.
Since: cborg-0.2.0.0
encodeListLen :: Word -> Encoding Source #
Encode the length of a list, used to indicate that the following tokens represent the list values.
Since: cborg-0.2.0.0
encodeListLenIndef :: Encoding Source #
Encode a token specifying that this is the beginning of an
indefinite list of unknown size. Tokens representing the list are
expected afterwords, followed by a break token (see
) when the list has ended.encodeBreak
Since: cborg-0.2.0.0
encodeMapLen :: Word -> Encoding Source #
Encode the length of a Map, used to indicate that the following tokens represent the map values.
Since: cborg-0.2.0.0
encodeMapLenIndef :: Encoding Source #
Encode a token specifying that this is the beginning of an
indefinite map of unknown size. Tokens representing the map are
expected afterwords, followed by a break token (see
) when the map has ended.encodeBreak
Since: cborg-0.2.0.0
encodeBreak :: Encoding Source #
Encode a 'break', used to specify the end of indefinite length objects like maps or lists.
Since: cborg-0.2.0.0
encodeTag64 :: Word64 -> Encoding Source #
Encode an arbitrary 64-bit
tag.Word64
Since: cborg-0.2.0.0
encodeUndef :: Encoding Source #
Encode an Undef
value.
Since: cborg-0.2.0.0
encodeNull :: Encoding Source #
Encode a Null
value.
Since: cborg-0.2.0.0
encodeSimple :: Word8 -> Encoding Source #
Encode a 'simple' CBOR token that can be represented with an 8-bit word. You probably don't ever need this.
Since: cborg-0.2.0.0
encodeFloat16 :: Float -> Encoding Source #
Encode a small 16-bit
in a flattened format.Float
Since: cborg-0.2.0.0