Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Module that re-exports everythign from `cardano-binary` package.
Everything that gets defined in this module should most likely be migrated to `cardano-binary` package.
Synopsis
- 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
- | TkEncoded !ByteString Tokens
- | TkEnd
- newtype Encoding = Encoding (Tokens → Tokens)
- 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
- encodeByteArray ∷ SlicedByteArray → Encoding
- encodeBytesIndef ∷ 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
- encodePreEncoded ∷ ByteString → Encoding
- type ByteOffset = Int64
- data TokenType
- = TypeUInt
- | TypeUInt64
- | TypeNInt
- | TypeNInt64
- | TypeInteger
- | TypeFloat16
- | TypeFloat32
- | TypeFloat64
- | TypeBytes
- | TypeBytesIndef
- | TypeString
- | TypeStringIndef
- | TypeListLen
- | TypeListLen64
- | TypeListLenIndef
- | TypeMapLen
- | TypeMapLen64
- | TypeMapLenIndef
- | TypeTag
- | TypeTag64
- | TypeBool
- | TypeNull
- | TypeSimple
- | TypeBreak
- | TypeInvalid
- data DecodeAction s a
- = ConsumeWord (Word# → ST s (DecodeAction s a))
- | ConsumeWord8 (Word# → ST s (DecodeAction s a))
- | ConsumeWord16 (Word# → ST s (DecodeAction s a))
- | ConsumeWord32 (Word# → ST s (DecodeAction s a))
- | ConsumeNegWord (Word# → ST s (DecodeAction s a))
- | ConsumeInt (Int# → ST s (DecodeAction s a))
- | ConsumeInt8 (Int# → ST s (DecodeAction s a))
- | ConsumeInt16 (Int# → ST s (DecodeAction s a))
- | ConsumeInt32 (Int# → ST s (DecodeAction s a))
- | ConsumeListLen (Int# → ST s (DecodeAction s a))
- | ConsumeMapLen (Int# → ST s (DecodeAction s a))
- | ConsumeTag (Word# → ST s (DecodeAction s a))
- | ConsumeInteger (Integer → ST s (DecodeAction s a))
- | ConsumeFloat (Float# → ST s (DecodeAction s a))
- | ConsumeDouble (Double# → ST s (DecodeAction s a))
- | ConsumeBytes (ByteString → ST s (DecodeAction s a))
- | ConsumeByteArray (ByteArray → ST s (DecodeAction s a))
- | ConsumeString (Text → ST s (DecodeAction s a))
- | ConsumeUtf8ByteArray (ByteArray → ST s (DecodeAction s a))
- | ConsumeBool (Bool → ST s (DecodeAction s a))
- | ConsumeSimple (Word# → ST s (DecodeAction s a))
- | ConsumeBytesIndef (ST s (DecodeAction s a))
- | ConsumeStringIndef (ST s (DecodeAction s a))
- | ConsumeListLenIndef (ST s (DecodeAction s a))
- | ConsumeMapLenIndef (ST s (DecodeAction s a))
- | ConsumeNull (ST s (DecodeAction s a))
- | ConsumeListLenOrIndef (Int# → ST s (DecodeAction s a))
- | ConsumeMapLenOrIndef (Int# → ST s (DecodeAction s a))
- | ConsumeBreakOr (Bool → ST s (DecodeAction s a))
- | PeekTokenType (TokenType → ST s (DecodeAction s a))
- | PeekAvailable (Int# → ST s (DecodeAction s a))
- | PeekByteOffset (Int# → ST s (DecodeAction s a))
- | ConsumeWordCanonical (Word# → ST s (DecodeAction s a))
- | ConsumeWord8Canonical (Word# → ST s (DecodeAction s a))
- | ConsumeWord16Canonical (Word# → ST s (DecodeAction s a))
- | ConsumeWord32Canonical (Word# → ST s (DecodeAction s a))
- | ConsumeNegWordCanonical (Word# → ST s (DecodeAction s a))
- | ConsumeIntCanonical (Int# → ST s (DecodeAction s a))
- | ConsumeInt8Canonical (Int# → ST s (DecodeAction s a))
- | ConsumeInt16Canonical (Int# → ST s (DecodeAction s a))
- | ConsumeInt32Canonical (Int# → ST s (DecodeAction s a))
- | ConsumeListLenCanonical (Int# → ST s (DecodeAction s a))
- | ConsumeMapLenCanonical (Int# → ST s (DecodeAction s a))
- | ConsumeTagCanonical (Word# → ST s (DecodeAction s a))
- | ConsumeIntegerCanonical (Integer → ST s (DecodeAction s a))
- | ConsumeFloat16Canonical (Float# → ST s (DecodeAction s a))
- | ConsumeFloatCanonical (Float# → ST s (DecodeAction s a))
- | ConsumeDoubleCanonical (Double# → ST s (DecodeAction s a))
- | ConsumeBytesCanonical (ByteString → ST s (DecodeAction s a))
- | ConsumeByteArrayCanonical (ByteArray → ST s (DecodeAction s a))
- | ConsumeStringCanonical (Text → ST s (DecodeAction s a))
- | ConsumeUtf8ByteArrayCanonical (ByteArray → ST s (DecodeAction s a))
- | ConsumeSimpleCanonical (Word# → ST s (DecodeAction s a))
- | Fail String
- | Done a
- liftST ∷ ST s a → Decoder s a
- getDecodeAction ∷ Decoder s a → ST s (DecodeAction s a)
- decodeWord ∷ Decoder s Word
- decodeWord8 ∷ Decoder s Word8
- decodeWord16 ∷ Decoder s Word16
- decodeWord32 ∷ Decoder s Word32
- decodeWord64 ∷ Decoder s Word64
- decodeNegWord ∷ Decoder s Word
- decodeNegWord64 ∷ Decoder s Word64
- decodeInt ∷ Decoder s Int
- decodeInt8 ∷ Decoder s Int8
- decodeInt16 ∷ Decoder s Int16
- decodeInt32 ∷ Decoder s Int32
- decodeInt64 ∷ Decoder s Int64
- decodeWordCanonical ∷ Decoder s Word
- decodeWord8Canonical ∷ Decoder s Word8
- decodeWord16Canonical ∷ Decoder s Word16
- decodeWord32Canonical ∷ Decoder s Word32
- decodeWord64Canonical ∷ Decoder s Word64
- decodeNegWordCanonical ∷ Decoder s Word
- decodeNegWord64Canonical ∷ Decoder s Word64
- decodeIntCanonical ∷ Decoder s Int
- decodeInt8Canonical ∷ Decoder s Int8
- decodeInt16Canonical ∷ Decoder s Int16
- decodeInt32Canonical ∷ Decoder s Int32
- decodeInt64Canonical ∷ Decoder s Int64
- decodeInteger ∷ Decoder s Integer
- decodeFloat ∷ Decoder s Float
- decodeDouble ∷ Decoder s Double
- decodeBytes ∷ Decoder s ByteString
- decodeBytesCanonical ∷ Decoder s ByteString
- decodeBytesIndef ∷ Decoder s ()
- decodeByteArray ∷ Decoder s ByteArray
- decodeByteArrayCanonical ∷ Decoder s ByteArray
- decodeString ∷ Decoder s Text
- decodeStringCanonical ∷ Decoder s Text
- decodeStringIndef ∷ Decoder s ()
- decodeUtf8ByteArray ∷ Decoder s ByteArray
- decodeUtf8ByteArrayCanonical ∷ Decoder s ByteArray
- decodeListLen ∷ Decoder s Int
- decodeListLenCanonical ∷ Decoder s Int
- decodeListLenIndef ∷ Decoder s ()
- decodeMapLen ∷ Decoder s Int
- decodeMapLenCanonical ∷ Decoder s Int
- decodeMapLenIndef ∷ Decoder s ()
- decodeTag ∷ Decoder s Word
- decodeTag64 ∷ Decoder s Word64
- decodeTagCanonical ∷ Decoder s Word
- decodeTag64Canonical ∷ Decoder s Word64
- decodeBool ∷ Decoder s Bool
- decodeNull ∷ Decoder s ()
- decodeSimple ∷ Decoder s Word8
- decodeIntegerCanonical ∷ Decoder s Integer
- decodeFloat16Canonical ∷ Decoder s Float
- decodeFloatCanonical ∷ Decoder s Float
- decodeDoubleCanonical ∷ Decoder s Double
- decodeSimpleCanonical ∷ Decoder s Word8
- decodeWordOf ∷ Word → Decoder s ()
- decodeListLenOf ∷ Int → Decoder s ()
- decodeWordCanonicalOf ∷ Word → Decoder s ()
- decodeListLenCanonicalOf ∷ Int → Decoder s ()
- decodeListLenOrIndef ∷ Decoder s (Maybe Int)
- decodeMapLenOrIndef ∷ Decoder s (Maybe Int)
- decodeBreakOr ∷ Decoder s Bool
- peekTokenType ∷ Decoder s TokenType
- peekAvailable ∷ Decoder s Int
- peekByteOffset ∷ Decoder s ByteOffset
- decodeWithByteSpan ∷ Decoder s a → Decoder s (a, ByteOffset, ByteOffset)
- decodeSequenceLenIndef ∷ (r → a → r) → r → (r → r') → Decoder s a → Decoder s r'
- decodeSequenceLenN ∷ (r → a → r) → r → (r → r') → Int → Decoder s a → Decoder s r'
- data Decoder s a
- nestedCborBytesSizeExpr ∷ Size → Size
- nestedCborSizeExpr ∷ Size → Size
- encodeNestedCborBytes ∷ ByteString → Encoding
- encodeNestedCbor ∷ ToCBOR a ⇒ a → Encoding
- serializeEncoding' ∷ Encoding → ByteString
- serializeEncoding ∷ Encoding → ByteString
- serializeBuilder ∷ ToCBOR a ⇒ a → Builder
- serialize' ∷ ToCBOR a ⇒ a → ByteString
- serialize ∷ ToCBOR a ⇒ a → ByteString
- encodeNullMaybe ∷ (a → Encoding) → Maybe a → Encoding
- toCBORMaybe ∷ (a → Encoding) → Maybe a → Encoding
- encodeMaybe ∷ (a → Encoding) → Maybe a → Encoding
- encodeSeq ∷ (a → Encoding) → Seq a → Encoding
- encodeNominalDiffTimeMicro ∷ NominalDiffTime → Encoding
- encodeNominalDiffTime ∷ NominalDiffTime → Encoding
- withWordSize ∷ (Integral s, Integral a) ⇒ s → a
- szBounds ∷ ToCBOR a ⇒ a → Either Size (Range Natural)
- szForce ∷ Size → Size
- szSimplify ∷ Size → Either Size (Range Natural)
- szWithCtx ∷ ToCBOR a ⇒ Map TypeRep SizeOverride → Proxy a → Size
- apMono ∷ Text → (Natural → Natural) → Size → Size
- isTodo ∷ Size → Bool
- szGreedy ∷ ToCBOR a ⇒ Proxy a → Size
- szLazy ∷ ToCBOR a ⇒ Proxy a → Size
- szEval ∷ (∀ t. ToCBOR t ⇒ (Proxy t → Size) → Proxy t → Range Natural) → Size → Range Natural
- caseValue ∷ Case t → t
- szCases ∷ [Case Size] → Size
- class Typeable a ⇒ ToCBOR a where
- newtype LengthOf xs = LengthOf xs
- type Size = Fix SizeF
- data Case t = Case Text t
- data Range b = Range {}
- data SizeOverride
- = SizeConstant Size
- | SizeExpression ((∀ a. ToCBOR a ⇒ Proxy a → Size) → Size)
- | SelectCases [Text]
- decodeNestedCborBytes ∷ Decoder s ByteString
- decodeNestedCbor ∷ FromCBOR a ⇒ Decoder s a
- decodeFullDecoder' ∷ Text → (∀ s. Decoder s a) → ByteString → Either DecoderError a
- decodeFullDecoder ∷ Text → (∀ s. Decoder s a) → ByteString → Either DecoderError a
- decodeFull' ∷ FromCBOR a ⇒ ByteString → Either DecoderError a
- decodeFull ∷ FromCBOR a ⇒ ByteString → Either DecoderError a
- unsafeDeserialize' ∷ FromCBOR a ⇒ ByteString → a
- unsafeDeserialize ∷ FromCBOR a ⇒ ByteString → a
- cborError ∷ (MonadFail m, Buildable e) ⇒ e → m a
- toCborError ∷ (MonadFail m, Buildable e) ⇒ Either e a → m a
- decodeCollectionWithLen ∷ Decoder s (Maybe Int) → Decoder s v → Decoder s (Int, [v])
- decodeCollection ∷ Decoder s (Maybe Int) → Decoder s a → Decoder s [a]
- decodeSeq ∷ Decoder s a → Decoder s (Seq a)
- decodeMapSkel ∷ (Ord k, FromCBOR k, FromCBOR v) ⇒ ([(k, v)] → m) → Decoder s m
- decodeNullMaybe ∷ Decoder s a → Decoder s (Maybe a)
- decodeMaybe ∷ Decoder s a → Decoder s (Maybe a)
- fromCBORMaybe ∷ Decoder s a → Decoder s (Maybe a)
- decodeNominalDiffTimeMicro ∷ Decoder s NominalDiffTime
- decodeNominalDiffTime ∷ Decoder s NominalDiffTime
- decodeListWith ∷ Decoder s a → Decoder s [a]
- matchSize ∷ Text → Int → Int → Decoder s ()
- enforceSize ∷ Text → Int → Decoder s ()
- class Typeable a ⇒ FromCBOR a where
- data DecoderError
- toStrictByteString ∷ Encoding → ByteString
- module Codec.CBOR.Term
- showDecoderError ∷ Buildable e ⇒ e → String
- invalidKey ∷ MonadFail m ⇒ Word → m a
- decodeRecordNamed ∷ Text → (a → Int) → Decoder s a → Decoder s a
- decodeRecordNamedT ∷ (MonadTrans m, Monad (m (Decoder s))) ⇒ Text → (a → Int) → m (Decoder s) a → m (Decoder s) a
- decodeRecordSum ∷ Text → (Word → Decoder s (Int, a)) → Decoder s a
- decodeListLikeT ∷ (MonadTrans m, Monad (m (Decoder s))) ⇒ Text → m (Decoder s) a → (a → Int → m (Decoder s) ()) → m (Decoder s) a
- serializeAsHexText ∷ ToCBOR a ⇒ a → Text
- decodeFullFromHexText ∷ FromCBOR a ⇒ Text → Either DecoderError a
- encodeEnum ∷ Enum a ⇒ a → Encoding
- decodeEnumBounded ∷ ∀ a s. (Enum a, Bounded a, Typeable a) ⇒ Decoder s a
- withHexText ∷ (ByteString → Either DecoderError b) → Text → Either DecoderError b
- encodeVerKeyDSIGN ∷ DSIGNAlgorithm v ⇒ VerKeyDSIGN v → Encoding
- decodeVerKeyDSIGN ∷ DSIGNAlgorithm v ⇒ Decoder s (VerKeyDSIGN v)
- encodeSignKeyDSIGN ∷ DSIGNAlgorithm v ⇒ SignKeyDSIGN v → Encoding
- decodeSignKeyDSIGN ∷ DSIGNAlgorithm v ⇒ Decoder s (SignKeyDSIGN v)
- encodeSigDSIGN ∷ DSIGNAlgorithm v ⇒ SigDSIGN v → Encoding
- decodeSigDSIGN ∷ DSIGNAlgorithm v ⇒ Decoder s (SigDSIGN v)
- encodeSignedDSIGN ∷ DSIGNAlgorithm v ⇒ SignedDSIGN v a → Encoding
- decodeSignedDSIGN ∷ DSIGNAlgorithm v ⇒ Decoder s (SignedDSIGN v a)
- encodeVerKeyKES ∷ KESAlgorithm v ⇒ VerKeyKES v → Encoding
- decodeVerKeyKES ∷ KESAlgorithm v ⇒ Decoder s (VerKeyKES v)
- encodeSignKeyKES ∷ KESAlgorithm v ⇒ SignKeyKES v → Encoding
- decodeSignKeyKES ∷ KESAlgorithm v ⇒ Decoder s (SignKeyKES v)
- encodeSigKES ∷ KESAlgorithm v ⇒ SigKES v → Encoding
- decodeSigKES ∷ KESAlgorithm v ⇒ Decoder s (SigKES v)
- encodeSignedKES ∷ KESAlgorithm v ⇒ SignedKES v a → Encoding
- decodeSignedKES ∷ KESAlgorithm v ⇒ Decoder s (SignedKES v a)
- encodeVerKeyVRF ∷ VRFAlgorithm v ⇒ VerKeyVRF v → Encoding
- decodeVerKeyVRF ∷ VRFAlgorithm v ⇒ Decoder s (VerKeyVRF v)
- encodeSignKeyVRF ∷ VRFAlgorithm v ⇒ SignKeyVRF v → Encoding
- decodeSignKeyVRF ∷ VRFAlgorithm v ⇒ Decoder s (SignKeyVRF v)
- encodeCertVRF ∷ VRFAlgorithm v ⇒ CertVRF v → Encoding
- decodeCertVRF ∷ VRFAlgorithm v ⇒ Decoder s (CertVRF v)
Documentation
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
An intermediate form used during serialisation, specified as a
Monoid
. It supports efficient concatenation, and is equivalent
to a specialised Endo
Tokens
type.
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 Encoding
value, you specify
larger structures from smaller ones and append the small ones together
using mconcat
.
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 ByteString
in
a flattened format.
Since: cborg-0.2.0.0
encodeByteArray ∷ SlicedByteArray → Encoding Source #
Encode a bytestring in a flattened format.
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
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
encodeBreak
) when the list has ended.
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
encodeBreak
) when the map has ended.
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
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 Float
in a flattened format.
Since: cborg-0.2.0.0
encodeFloat ∷ Float → Encoding Source #
Encode a full precision Float
in a flattened format.
Since: cborg-0.2.0.0
encodePreEncoded ∷ ByteString → Encoding Source #
Include pre-encoded valid CBOR data into the Encoding
.
The data is included into the output as-is without any additional wrapper.
This should be used with care. The data must be a valid CBOR encoding, but this is not checked.
This is useful when you have CBOR data that you know is already valid, e.g. previously validated and stored on disk, and you wish to include it without having to decode and re-encode it.
Since: cborg-0.2.2.0
type ByteOffset = Int64 Source #
The type of a token, which a decoder can ask for at an arbitrary time.
Since: cborg-0.2.0.0
Instances
Bounded TokenType | |
Enum TokenType | |
Defined in Codec.CBOR.Decoding succ ∷ TokenType → TokenType Source # pred ∷ TokenType → TokenType Source # toEnum ∷ Int → TokenType Source # fromEnum ∷ TokenType → Int Source # enumFrom ∷ TokenType → [TokenType] Source # enumFromThen ∷ TokenType → TokenType → [TokenType] Source # enumFromTo ∷ TokenType → TokenType → [TokenType] Source # enumFromThenTo ∷ TokenType → TokenType → TokenType → [TokenType] Source # | |
Show TokenType | |
Eq TokenType | |
Ord TokenType | |
Defined in Codec.CBOR.Decoding |
data DecodeAction s a Source #
An action, representing a step for a decoder to taken and a continuation to invoke with the expected value.
Since: cborg-0.2.0.0
liftST ∷ ST s a → Decoder s a Source #
Lift an ST
action into a Decoder
. Useful for, e.g., leveraging
in-place mutation to efficiently build a deserialised value.
Since: cborg-0.2.0.0
getDecodeAction ∷ Decoder s a → ST s (DecodeAction s a) Source #
Given a Decoder
, give us the DecodeAction
Since: cborg-0.2.0.0
decodeWordCanonical ∷ Decoder s Word Source #
Decode canonical representation of a Word
.
Since: cborg-0.2.0.0
decodeWord8Canonical ∷ Decoder s Word8 Source #
Decode canonical representation of a Word8
.
Since: cborg-0.2.0.0
decodeWord16Canonical ∷ Decoder s Word16 Source #
Decode canonical representation of a Word16
.
Since: cborg-0.2.0.0
decodeWord32Canonical ∷ Decoder s Word32 Source #
Decode canonical representation of a Word32
.
Since: cborg-0.2.0.0
decodeWord64Canonical ∷ Decoder s Word64 Source #
Decode canonical representation of a Word64
.
Since: cborg-0.2.0.0
decodeNegWordCanonical ∷ Decoder s Word Source #
Decode canonical representation of a negative Word
.
Since: cborg-0.2.0.0
decodeNegWord64Canonical ∷ Decoder s Word64 Source #
Decode canonical representation of a negative Word64
.
Since: cborg-0.2.0.0
decodeIntCanonical ∷ Decoder s Int Source #
Decode canonical representation of an Int
.
Since: cborg-0.2.0.0
decodeInt8Canonical ∷ Decoder s Int8 Source #
Decode canonical representation of an Int8
.
Since: cborg-0.2.0.0
decodeInt16Canonical ∷ Decoder s Int16 Source #
Decode canonical representation of an Int16
.
Since: cborg-0.2.0.0
decodeInt32Canonical ∷ Decoder s Int32 Source #
Decode canonical representation of an Int32
.
Since: cborg-0.2.0.0
decodeInt64Canonical ∷ Decoder s Int64 Source #
Decode canonical representation of an Int64
.
Since: cborg-0.2.0.0
decodeBytes ∷ Decoder s ByteString Source #
Decode a string of bytes as a ByteString
.
Since: cborg-0.2.0.0
decodeBytesCanonical ∷ Decoder s ByteString Source #
Decode canonical representation of a string of bytes as a ByteString
.
Since: cborg-0.2.1.0
decodeBytesIndef ∷ Decoder s () Source #
Decode a token marking the beginning of an indefinite length set of bytes.
Since: cborg-0.2.0.0
decodeString ∷ Decoder s Text Source #
Decode a textual string as a piece of Text
.
Since: cborg-0.2.0.0
decodeStringCanonical ∷ Decoder s Text Source #
Decode canonical representation of a textual string as a piece of Text
.
Since: cborg-0.2.1.0
decodeStringIndef ∷ Decoder s () Source #
Decode a token marking the beginning of an indefinite length string.
Since: cborg-0.2.0.0
decodeUtf8ByteArrayCanonical ∷ Decoder s ByteArray Source #
Decode canonical representation of a textual string as UTF-8 encoded
ByteArray
. Note that the result is not validated to be well-formed UTF-8.
Also note that this will eagerly copy the content out of the input
to ensure that the input does not leak in the event that the ByteArray
is
live but not forced.
Since: cborg-0.2.1.0
decodeListLen ∷ Decoder s Int Source #
Decode the length of a list.
Since: cborg-0.2.0.0
decodeListLenCanonical ∷ Decoder s Int Source #
Decode canonical representation of the length of a list.
Since: cborg-0.2.0.0
decodeListLenIndef ∷ Decoder s () Source #
Decode a token marking the beginning of a list of indefinite length.
Since: cborg-0.2.0.0
decodeMapLen ∷ Decoder s Int Source #
Decode the length of a map.
Since: cborg-0.2.0.0
decodeMapLenCanonical ∷ Decoder s Int Source #
Decode canonical representation of the length of a map.
Since: cborg-0.2.0.0
decodeMapLenIndef ∷ Decoder s () Source #
Decode a token marking the beginning of a map of indefinite length.
Since: cborg-0.2.0.0
decodeTag ∷ Decoder s Word Source #
Decode an arbitrary tag and return it as a Word
.
Since: cborg-0.2.0.0
decodeTag64 ∷ Decoder s Word64 Source #
Decode an arbitrary 64-bit tag and return it as a Word64
.
Since: cborg-0.2.0.0
decodeTagCanonical ∷ Decoder s Word Source #
Decode canonical representation of an arbitrary tag and return it as a
Word
.
Since: cborg-0.2.0.0
decodeTag64Canonical ∷ Decoder s Word64 Source #
Decode canonical representation of an arbitrary 64-bit tag and return it as
a Word64
.
Since: cborg-0.2.0.0
decodeBool ∷ Decoder s Bool Source #
Decode a bool.
Since: cborg-0.2.0.0
decodeNull ∷ Decoder s () Source #
Decode a nullary value, and return a unit value.
Since: cborg-0.2.0.0
decodeSimple ∷ Decoder s Word8 Source #
Decode a simple
CBOR value and give back a Word8
. You
probably don't ever need to use this.
Since: cborg-0.2.0.0
decodeIntegerCanonical ∷ Decoder s Integer Source #
Decode canonical representation of an Integer
.
Since: cborg-0.2.0.0
decodeFloat16Canonical ∷ Decoder s Float Source #
Decode canonical representation of a half-precision Float
.
Since: cborg-0.2.0.0
decodeFloatCanonical ∷ Decoder s Float Source #
Decode canonical representation of a Float
.
Since: cborg-0.2.0.0
decodeDoubleCanonical ∷ Decoder s Double Source #
Decode canonical representation of a Double
.
Since: cborg-0.2.0.0
decodeSimpleCanonical ∷ Decoder s Word8 Source #
Decode canonical representation of a simple
CBOR value and give back a
Word8
. You probably don't ever need to use this.
Since: cborg-0.2.0.0
Attempt to decode a word with decodeWord
, and ensure the word
is exactly as expected, or fail.
Since: cborg-0.2.0.0
decodeListLenOf ∷ Int → Decoder s () Source #
Attempt to decode a list length using decodeListLen
, and
ensure it is exactly the specified length, or fail.
Since: cborg-0.2.0.0
decodeWordCanonicalOf Source #
Attempt to decode canonical representation of a word with decodeWordCanonical
,
and ensure the word is exactly as expected, or fail.
Since: cborg-0.2.0.0
decodeListLenCanonicalOf ∷ Int → Decoder s () Source #
Attempt to decode canonical representation of a list length using
decodeListLenCanonical
, and ensure it is exactly the specified length, or
fail.
Since: cborg-0.2.0.0
decodeBreakOr ∷ Decoder s Bool Source #
peekTokenType ∷ Decoder s TokenType Source #
Peek at the current token we're about to decode, and return a
TokenType
specifying what it is.
Since: cborg-0.2.0.0
peekAvailable ∷ Decoder s Int Source #
Peek and return the length of the current buffer that we're running our decoder on.
Since: cborg-0.2.0.0
peekByteOffset ∷ Decoder s ByteOffset Source #
Get the current ByteOffset
in the input byte sequence of the Decoder
.
The Decoder
does not provide any facility to get at the input data
directly (since that is tricky with an incremental decoder). The next best
is this primitive which can be used to keep track of the offset within the
input bytes that makes up the encoded form of a term.
By keeping track of the byte offsets before and after decoding a subterm
(a pattern captured by decodeWithByteSpan
) and if the overall input data
is retained then this is enables later retrieving the span of bytes for the
subterm.
Since: cborg-0.2.2.0
decodeWithByteSpan ∷ Decoder s a → Decoder s (a, ByteOffset, ByteOffset) Source #
This captures the pattern of getting the byte offsets before and after decoding a subterm.
!before <- peekByteOffset x <- decode !after <- peekByteOffset
decodeSequenceLenIndef ∷ (r → a → r) → r → (r → r') → Decoder s a → Decoder s r' Source #
Decode an indefinite sequence length.
Since: cborg-0.2.0.0
decodeSequenceLenN ∷ (r → a → r) → r → (r → r') → Int → Decoder s a → Decoder s r' Source #
Decode a sequence length.
Since: cborg-0.2.0.0
A continuation-based decoder, used for decoding values that were
previously encoded using the Codec.CBOR.Encoding
module. As Decoder
has a Monad
instance, you can easily
write Decoder
s monadically for building your deserialisation
logic.
Since: cborg-0.2.0.0
Instances
MonadFail (Decoder s) | Since: cborg-0.2.0.0 |
Applicative (Decoder s) | Since: cborg-0.2.0.0 |
Defined in Codec.CBOR.Decoding | |
Functor (Decoder s) | Since: cborg-0.2.0.0 |
Monad (Decoder s) | Since: cborg-0.2.0.0 |
encodeNestedCborBytes ∷ ByteString → Encoding Source #
Like encodeNestedCbor
, but assumes nothing about the shape of
input object, so that it must be passed as a binary ByteString
blob. It's
the caller responsibility to ensure the input ByteString
correspond
indeed to valid, previously-serialised CBOR data.
encodeNestedCbor ∷ ToCBOR a ⇒ a → Encoding Source #
Encode and serialise the given a
and sorround it with the semantic tag 24
In CBOR diagnostic notation:
>>> 24(hDEADBEEF
)
serializeEncoding' ∷ Encoding → ByteString Source #
A strict version of serializeEncoding
serializeEncoding ∷ Encoding → ByteString Source #
Serialize a Haskell value to an external binary representation using the
provided CBOR Encoding
The output is represented as an LByteString
and is constructed
incrementally.
serializeBuilder ∷ ToCBOR a ⇒ a → Builder Source #
Serialize into a Builder. Useful if you want to throw other ByteStrings around it.
serialize' ∷ ToCBOR a ⇒ a → ByteString Source #
Serialize a Haskell value to an external binary representation.
The output is represented as a strict ByteString
.
serialize ∷ ToCBOR a ⇒ a → ByteString Source #
Serialize a Haskell value with a ToCBOR
instance to an external binary
representation.
The output is represented as a lazy LByteString
and is constructed
incrementally.
encodeNullMaybe ∷ (a → Encoding) → Maybe a → Encoding Source #
Alternative way to encode a Maybe type.
Note - this is not the default method for encoding Maybe
, use encodeMaybe
instead
encodeNominalDiffTimeMicro ∷ NominalDiffTime → Encoding Source #
Same as encodeNominalDiffTime
, except with loss of precision, because it encoded as
Micro
withWordSize ∷ (Integral s, Integral a) ⇒ s → a Source #
Compute encoded size of an integer
szForce ∷ Size → Size Source #
Force any thunks in the given Size
expression.
ghci> putStrLn $ pretty $ szForce $ szLazy (Proxy @TxAux) (0 + { TxAux=(2 + ((0 + (_ :: Tx)) + (_ :: Vector TxInWitness))) })
szSimplify ∷ Size → Either Size (Range Natural) Source #
Simplify the given Size
, resulting in either the simplified Size
or,
if it was fully simplified, an explicit upper and lower bound.
szWithCtx ∷ ToCBOR a ⇒ Map TypeRep SizeOverride → Proxy a → Size Source #
Greedily compute the size bounds for a type, using the given context to override sizes for specific types.
apMono ∷ Text → (Natural → Natural) → Size → Size Source #
Apply a monotonically increasing function to the expression.
There are three cases when applying f
to a Size
expression:
* When applied to a value x
, compute f x
.
* When applied to cases, apply to each case individually.
* In all other cases, create a deferred application of f
.
szGreedy ∷ ToCBOR a ⇒ Proxy a → Size Source #
Evaluate an expression greedily. There may still be thunks in the
result, for types that did not provide a custom encodedSizeExpr
method
in their ToCBOR
instance.
ghci> putStrLn $ pretty $ szGreedy (Proxy @TxAux) (0 + { TxAux=(2 + ((0 + (((1 + (2 + ((_ :: LengthOf [TxIn]) * (2 + { TxInUtxo=(2 + ((1 + 34) + { minBound=1 maxBound=5 })) })))) + (2 + ((_ :: LengthOf [TxOut]) * (0 + { TxOut=(2 + ((0 + ((2 + ((2 + withWordSize((((1 + 30) + (_ :: Attributes AddrAttributes)) + 1))) + (((1 + 30) + (_ :: Attributes AddrAttributes)) + 1))) + { minBound=1 maxBound=5 })) + { minBound=1 maxBound=9 })) })))) + (_ :: Attributes ()))) + (_ :: Vector TxInWitness))) })
szLazy ∷ ToCBOR a ⇒ Proxy a → Size Source #
Evaluate the expression lazily, by immediately creating a thunk that will evaluate its contents lazily.
ghci> putStrLn $ pretty $ szLazy (Proxy @TxAux) (_ :: TxAux)
szEval ∷ (∀ t. ToCBOR t ⇒ (Proxy t → Size) → Proxy t → Range Natural) → Size → Range Natural Source #
Fully evaluate a size expression by applying the given function to any
suspended computations. szEval g
effectively turns each "thunk"
of the form TodoF f x
into g x
, then evaluates the result.
class Typeable a ⇒ ToCBOR a where Source #
toCBOR ∷ a → Encoding Source #
encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [a] → Size Source #
Instances
type Size = Fix SizeF Source #
Expressions describing the statically-computed size bounds on a type's possible values.
An individual labeled case.
A range of values. Should satisfy the invariant forall x. lo x <= hi x
.
data SizeOverride Source #
Override mechanisms to be used with szWithCtx
.
SizeConstant Size | Replace with a fixed |
SizeExpression ((∀ a. ToCBOR a ⇒ Proxy a → Size) → Size) | Recursively compute the size. |
SelectCases [Text] | Select only a specific case from a |
decodeNestedCborBytes ∷ Decoder s ByteString Source #
Like decodeKnownCborDataItem
, but assumes nothing about the Haskell
type we want to deserialise back, therefore it yields the ByteString
Tag 24 surrounded (stripping such tag away).
In CBOR notation, if the data was serialised as:
>>>
24(h'DEADBEEF')
then decodeNestedCborBytes
yields the inner DEADBEEF
, unchanged.
decodeNestedCbor ∷ FromCBOR a ⇒ Decoder s a Source #
Remove the the semantic tag 24 from the enclosed CBOR data item,
decoding back the inner ByteString
as a proper Haskell type.
Consume its input in full.
∷ Text | Label for error reporting |
→ (∀ s. Decoder s a) | The parser for the |
→ ByteString | The |
→ Either DecoderError a |
∷ Text | Label for error reporting |
→ (∀ s. Decoder s a) | The parser for the |
→ ByteString | The |
→ Either DecoderError a |
decodeFull' ∷ FromCBOR a ⇒ ByteString → Either DecoderError a Source #
decodeFull ∷ FromCBOR a ⇒ ByteString → Either DecoderError a Source #
Deserialize a Haskell value from the external binary representation,
failing if there are leftovers. In a nutshell, the full
here implies
the contract of this function is that what you feed as input needs to
be consumed entirely.
unsafeDeserialize' ∷ FromCBOR a ⇒ ByteString → a Source #
Strict variant of deserialize
.
unsafeDeserialize ∷ FromCBOR a ⇒ ByteString → a Source #
Deserialize a Haskell value from the external binary representation
(which must have been made using serialize
or related function).
Throws:
if the given external
representation is invalid or does not correspond to a value of the
expected type.DeserialiseFailure
decodeMapSkel ∷ (Ord k, FromCBOR k, FromCBOR v) ⇒ ([(k, v)] → m) → Decoder s m Source #
Checks canonicity by comparing the new key being decoded with the previous one, to enfore these are sorted the correct way. See: https://tools.ietf.org/html/rfc7049#section-3.9 "[..]The keys in every map must be sorted lowest value to highest.[...]"
decodeNominalDiffTimeMicro ∷ Decoder s NominalDiffTime Source #
For backwards compatibility we round pico precision to micro
matchSize ∷ Text → Int → Int → Decoder s () Source #
Compare two sizes, failing if they are not equal
enforceSize ∷ Text → Int → Decoder s () Source #
Enforces that the input size is the same as the decoded one, failing in case it's not
class Typeable a ⇒ FromCBOR a where Source #
Instances
data DecoderError Source #
DecoderErrorCanonicityViolation Text | |
DecoderErrorCustom Text Text | Custom decoding error, usually due to some validation failure |
DecoderErrorDeserialiseFailure Text DeserialiseFailure | |
DecoderErrorEmptyList Text | |
DecoderErrorLeftover Text ByteString | |
DecoderErrorSizeMismatch Text Int Int | A size mismatch |
DecoderErrorUnknownTag Text Word8 | |
DecoderErrorVoid |
Instances
Exception DecoderError | |
Show DecoderError | |
Defined in Cardano.Binary.FromCBOR | |
Buildable DecoderError | |
Defined in Cardano.Binary.FromCBOR build ∷ DecoderError → Builder Source # | |
Eq DecoderError | |
Defined in Cardano.Binary.FromCBOR (==) ∷ DecoderError → DecoderError → Bool Source # (/=) ∷ DecoderError → DecoderError → Bool Source # |
∷ Encoding | The |
→ ByteString | The encoded value. |
Turn an Encoding
into a strict ByteString
in CBOR binary
format.
Since: cborg-0.2.0.0
module Codec.CBOR.Term
showDecoderError ∷ Buildable e ⇒ e → String Source #
invalidKey ∷ MonadFail m ⇒ Word → m a Source #
Report an error when a numeric key of the type constructor doesn't match.
decodeRecordNamedT ∷ (MonadTrans m, Monad (m (Decoder s))) ⇒ Text → (a → Int) → m (Decoder s) a → m (Decoder s) a Source #
serializeAsHexText ∷ ToCBOR a ⇒ a → Text Source #
Encode a type as CBOR and encode it as base16
decodeFullFromHexText ∷ FromCBOR a ⇒ Text → Either DecoderError a Source #
Try decoding base16 encode bytes and then try to decoding them as CBOR
encodeEnum ∷ Enum a ⇒ a → Encoding Source #
withHexText ∷ (ByteString → Either DecoderError b) → Text → Either DecoderError b Source #
DSIGN
encodeVerKeyDSIGN ∷ DSIGNAlgorithm v ⇒ VerKeyDSIGN v → Encoding Source #
decodeVerKeyDSIGN ∷ DSIGNAlgorithm v ⇒ Decoder s (VerKeyDSIGN v) Source #
encodeSignKeyDSIGN ∷ DSIGNAlgorithm v ⇒ SignKeyDSIGN v → Encoding Source #
decodeSignKeyDSIGN ∷ DSIGNAlgorithm v ⇒ Decoder s (SignKeyDSIGN v) Source #
encodeSigDSIGN ∷ DSIGNAlgorithm v ⇒ SigDSIGN v → Encoding Source #
decodeSigDSIGN ∷ DSIGNAlgorithm v ⇒ Decoder s (SigDSIGN v) Source #
encodeSignedDSIGN ∷ DSIGNAlgorithm v ⇒ SignedDSIGN v a → Encoding Source #
decodeSignedDSIGN ∷ DSIGNAlgorithm v ⇒ Decoder s (SignedDSIGN v a) Source #
KES
encodeVerKeyKES ∷ KESAlgorithm v ⇒ VerKeyKES v → Encoding Source #
decodeVerKeyKES ∷ KESAlgorithm v ⇒ Decoder s (VerKeyKES v) Source #
encodeSignKeyKES ∷ KESAlgorithm v ⇒ SignKeyKES v → Encoding Source #
decodeSignKeyKES ∷ KESAlgorithm v ⇒ Decoder s (SignKeyKES v) Source #
encodeSigKES ∷ KESAlgorithm v ⇒ SigKES v → Encoding Source #
decodeSigKES ∷ KESAlgorithm v ⇒ Decoder s (SigKES v) Source #
encodeSignedKES ∷ KESAlgorithm v ⇒ SignedKES v a → Encoding Source #
decodeSignedKES ∷ KESAlgorithm v ⇒ Decoder s (SignedKES v a) Source #
VRF
encodeVerKeyVRF ∷ VRFAlgorithm v ⇒ VerKeyVRF v → Encoding Source #
decodeVerKeyVRF ∷ VRFAlgorithm v ⇒ Decoder s (VerKeyVRF v) Source #
encodeSignKeyVRF ∷ VRFAlgorithm v ⇒ SignKeyVRF v → Encoding Source #
decodeSignKeyVRF ∷ VRFAlgorithm v ⇒ Decoder s (SignKeyVRF v) Source #
encodeCertVRF ∷ VRFAlgorithm v ⇒ CertVRF v → Encoding Source #
decodeCertVRF ∷ VRFAlgorithm v ⇒ Decoder s (CertVRF v) Source #