Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- decodeFull ∷ ∀ a. DecCBOR a ⇒ Version → ByteString → Either DecoderError a
- decodeFull' ∷ ∀ a. DecCBOR a ⇒ Version → ByteString → Either DecoderError a
- decodeFullDecoder ∷ Version → Text → (∀ s. Decoder s a) → ByteString → Either DecoderError a
- decodeFullDecoder' ∷ Version → Text → (∀ s. Decoder s a) → ByteString → Either DecoderError a
- decodeFullAnnotator ∷ Version → Text → (∀ s. Decoder s (Annotator a)) → ByteString → Either DecoderError a
- decodeFullAnnotatedBytes ∷ Functor f ⇒ Version → Text → (∀ s. Decoder s (f ByteSpan)) → ByteString → Either DecoderError (f ByteString)
- decodeFullAnnotatorFromHexText ∷ Version → Text → (∀ s. Decoder s (Annotator a)) → Text → Either DecoderError a
- module Cardano.Ledger.Binary.Version
- class Typeable a ⇒ DecCBOR a where
- fromByronCBOR ∷ DecCBOR a ⇒ Decoder s a
- decodeScriptContextFromData ∷ (FromData a, MonadFail m) ⇒ Data → m a
- class Monoid (Share a) ⇒ DecShareCBOR a where
- newtype Interns a = Interns [Intern a]
- data Intern a = Intern {
- internMaybe ∷ a → Maybe a
- internWeight ∷ !Int
- decShareLensCBOR ∷ DecShareCBOR b ⇒ SimpleGetter bs (Share b) → StateT bs (Decoder s) b
- decSharePlusLensCBOR ∷ DecShareCBOR b ⇒ Lens' bs (Share b) → StateT bs (Decoder s) b
- decNoShareCBOR ∷ DecShareCBOR a ⇒ Decoder s a
- interns ∷ Interns k → k → k
- internsFromMap ∷ Ord k ⇒ Map k a → Interns k
- internsFromVMap ∷ Ord k ⇒ VMap VB kv k a → Interns k
- toMemptyLens ∷ Monoid a ⇒ Lens' a b → Lens' c b → Lens' c a
- decShareMonadCBOR ∷ (DecCBOR (f b), Monad f) ⇒ Interns b → Decoder s (f b)
- 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
- cborError ∷ (MonadFail m, Buildable e) ⇒ e → m a
- toCborError ∷ (MonadFail m, Buildable e) ⇒ Either e a → m a
- data DecoderError
- showDecoderError ∷ Buildable e ⇒ e → String
- invalidKey ∷ MonadFail m ⇒ Word → m a
- data Decoder s a
- fromPlainDecoder ∷ Decoder s a → Decoder s a
- toPlainDecoder ∷ Maybe ByteString → Version → Decoder s a → Decoder s a
- withPlainDecoder ∷ Decoder s a → (Decoder s a → Decoder s b) → Decoder s b
- enforceDecoderVersion ∷ Version → Decoder s a → Decoder s a
- getDecoderVersion ∷ Decoder s Version
- ifDecoderVersionAtLeast ∷ Version → Decoder s a → Decoder s a → Decoder s a
- whenDecoderVersionAtLeast ∷ Version → Decoder s a → Decoder s ()
- unlessDecoderVersionAtLeast ∷ Version → Decoder s a → Decoder s ()
- decodeVersion ∷ Decoder s Version
- decodeRational ∷ Decoder s Rational
- decodeRationalWithTag ∷ Decoder s Rational
- decodeList ∷ Decoder s a → Decoder s [a]
- decodeNonEmptyList ∷ Decoder s a → Decoder s (NonEmpty a)
- decodeMaybe ∷ Decoder s a → Decoder s (Maybe a)
- decodeNullMaybe ∷ Decoder s a → Decoder s (Maybe a)
- decodeStrictMaybe ∷ Decoder s a → Decoder s (StrictMaybe a)
- decodeNullStrictMaybe ∷ Decoder s a → Decoder s (StrictMaybe a)
- decodeEither ∷ Decoder s a → Decoder s b → Decoder s (Either a b)
- 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
- decodeListLike ∷ Text → Decoder s a → (a → Int → Decoder s ()) → Decoder s a
- decodeListLikeT ∷ (MonadTrans m, Monad (m (Decoder s))) ⇒ Text → m (Decoder s) a → (a → Int → m (Decoder s) ()) → m (Decoder s) a
- decodeEnumBounded ∷ ∀ a s. (Enum a, Bounded a, Typeable a) ⇒ Decoder s a
- decodeWithOrigin ∷ Decoder s a → Decoder s (WithOrigin a)
- decodeMap ∷ Ord k ⇒ Decoder s k → Decoder s v → Decoder s (Map k v)
- decodeMapByKey ∷ Ord k ⇒ Decoder s k → (k → Decoder s v) → Decoder s (Map k v)
- decodeMapLikeEnforceNoDuplicates ∷ Ord k ⇒ Decoder s (Maybe Int) → Decoder s (k, v) → Decoder s (Map k v)
- decodeVMap ∷ (Vector kv k, Vector vv v, Ord k) ⇒ Decoder s k → Decoder s v → Decoder s (VMap kv vv k v)
- setTag ∷ Word
- decodeSetTag ∷ Decoder s ()
- decodeSet ∷ Ord a ⇒ Decoder s a → Decoder s (Set a)
- decodeListLikeWithCount ∷ ∀ s a b. Monoid b ⇒ Decoder s (Maybe Int) → (a → b → b) → (b → Decoder s a) → Decoder s (Int, b)
- decodeListLikeEnforceNoDuplicates ∷ ∀ s a b c. Monoid b ⇒ Decoder s (Maybe Int) → (a → b → b) → (b → (Int, c)) → Decoder s a → Decoder s c
- decodeSetLikeEnforceNoDuplicates ∷ ∀ s a b c. Monoid b ⇒ (a → b → b) → (b → (Int, c)) → Decoder s a → Decoder s c
- decodeVector ∷ Vector vec a ⇒ Decoder s a → Decoder s (vec a)
- decodeSeq ∷ Decoder s a → Decoder s (Seq a)
- decodeStrictSeq ∷ Decoder s a → Decoder s (StrictSeq a)
- decodeMapContents ∷ Decoder s a → Decoder s [a]
- decodeMapTraverse ∷ (Ord a, Applicative t) ⇒ Decoder s (t a) → Decoder s (t b) → Decoder s (t (Map a b))
- decodeMapContentsTraverse ∷ Applicative t ⇒ Decoder s (t a) → Decoder s (t b) → Decoder s (t [(a, b)])
- decodeUTCTime ∷ Decoder s UTCTime
- binaryGetDecoder ∷ Bool → Text → Get a → Decoder s a
- decodeIPv4 ∷ Decoder s IPv4
- decodeIPv6 ∷ Decoder s IPv6
- allowTag ∷ Word → Decoder s ()
- assertTag ∷ Word → Decoder s ()
- enforceSize ∷ Text → Int → Decoder s ()
- matchSize ∷ Text → Int → Int → Decoder s ()
- decodeBool ∷ Decoder s Bool
- decodeBreakOr ∷ Decoder s Bool
- decodeByteArray ∷ Decoder s ByteArray
- decodeByteArrayCanonical ∷ Decoder s ByteArray
- decodeBytes ∷ Decoder s ByteString
- decodeBytesCanonical ∷ Decoder s ByteString
- decodeBytesIndef ∷ Decoder s ()
- decodeDouble ∷ Decoder s Double
- decodeDoubleCanonical ∷ Decoder s Double
- decodeFloat ∷ Decoder s Float
- decodeFloat16Canonical ∷ Decoder s Float
- decodeFloatCanonical ∷ Decoder s Float
- decodeInt ∷ Decoder s Int
- decodeInt16 ∷ Decoder s Int16
- decodeInt16Canonical ∷ Decoder s Int16
- decodeInt32 ∷ Decoder s Int32
- decodeInt32Canonical ∷ Decoder s Int32
- decodeInt64 ∷ Decoder s Int64
- decodeInt64Canonical ∷ Decoder s Int64
- decodeInt8 ∷ Decoder s Int8
- decodeInt8Canonical ∷ Decoder s Int8
- decodeIntCanonical ∷ Decoder s Int
- decodeInteger ∷ Decoder s Integer
- decodeNatural ∷ Decoder s Natural
- decodeIntegerCanonical ∷ Decoder s Integer
- decodeListLen ∷ Decoder s Int
- decodeListLenCanonical ∷ Decoder s Int
- decodeListLenCanonicalOf ∷ Int → Decoder s ()
- decodeListLenIndef ∷ Decoder s ()
- decodeListLenOf ∷ Int → Decoder s ()
- decodeListLenOrIndef ∷ Decoder s (Maybe Int)
- decodeMapLen ∷ Decoder s Int
- decodeMapLenCanonical ∷ Decoder s Int
- decodeMapLenIndef ∷ Decoder s ()
- decodeMapLenOrIndef ∷ Decoder s (Maybe Int)
- decodeNegWord ∷ Decoder s Word
- decodeNegWord64 ∷ Decoder s Word64
- decodeNegWord64Canonical ∷ Decoder s Word64
- decodeNegWordCanonical ∷ Decoder s Word
- decodeNull ∷ Decoder s ()
- decodeSequenceLenIndef ∷ (r → a → r) → r → (r → b) → Decoder s a → Decoder s b
- decodeSequenceLenN ∷ (r → a → r) → r → (r → b) → Int → Decoder s a → Decoder s b
- decodeSimple ∷ Decoder s Word8
- decodeSimpleCanonical ∷ Decoder s Word8
- decodeString ∷ Decoder s Text
- decodeStringCanonical ∷ Decoder s Text
- decodeStringIndef ∷ Decoder s ()
- decodeTag ∷ Decoder s Word
- decodeTag64 ∷ Decoder s Word64
- decodeTag64Canonical ∷ Decoder s Word64
- decodeTagCanonical ∷ Decoder s Word
- decodeUtf8ByteArray ∷ Decoder s ByteArray
- decodeUtf8ByteArrayCanonical ∷ Decoder s ByteArray
- decodeWithByteSpan ∷ Decoder s a → Decoder s (a, ByteOffset, ByteOffset)
- decodeWord ∷ Decoder s Word
- decodeWord16 ∷ Decoder s Word16
- decodeWord16Canonical ∷ Decoder s Word16
- decodeWord32 ∷ Decoder s Word32
- decodeWord32Canonical ∷ Decoder s Word32
- decodeWord64 ∷ Decoder s Word64
- decodeWord64Canonical ∷ Decoder s Word64
- decodeWord8 ∷ Decoder s Word8
- decodeWord8Canonical ∷ Decoder s Word8
- decodeWordCanonical ∷ Decoder s Word
- decodeWordCanonicalOf ∷ Word → Decoder s ()
- decodeWordOf ∷ Word → Decoder s ()
- decodeTerm ∷ Decoder s Term
- peekAvailable ∷ Decoder s Int
- peekByteOffset ∷ Decoder s ByteOffset
- peekTokenType ∷ Decoder s TokenType
- data Sized a = Sized {
- sizedValue ∷ !a
- sizedSize ∷ Int64
- mkSized ∷ EncCBOR a ⇒ Version → a → Sized a
- decodeSized ∷ Decoder s a → Decoder s (Sized a)
- toSizedL ∷ EncCBOR s ⇒ Version → Lens' s a → Lens' (Sized s) a
- type Dropper s = Decoder s ()
- dropBytes ∷ Dropper s
- dropInt32 ∷ Dropper s
- dropList ∷ Dropper s → Dropper s
- dropMap ∷ Dropper s → Dropper s → Dropper s
- dropSet ∷ Dropper s → Dropper s
- dropTuple ∷ Dropper s → Dropper s → Dropper s
- dropTriple ∷ Dropper s → Dropper s → Dropper s → Dropper s
- dropWord8 ∷ Dropper s
- dropWord64 ∷ Dropper s
- data Annotated b a = Annotated {
- unAnnotated ∷ !b
- annotation ∷ !a
- decodeAnnotated ∷ Decoder s a → Decoder s (Annotated a ByteString)
- data ByteSpan = ByteSpan !ByteOffset !ByteOffset
- class Decoded t where
- type BaseType t ∷ Type
- recoverBytes ∷ t → ByteString
- annotationBytes ∷ Functor f ⇒ ByteString → f ByteSpan → f ByteString
- annotatedDecoder ∷ Decoder s a → Decoder s (Annotated a ByteSpan)
- slice ∷ ByteString → ByteSpan → ByteString
- decCBORAnnotated ∷ DecCBOR a ⇒ Decoder s (Annotated a ByteSpan)
- reAnnotate ∷ EncCBOR a ⇒ Version → Annotated a b → Annotated a ByteString
- newtype Annotator a = Annotator {
- runAnnotator ∷ FullByteString → a
- annotatorSlice ∷ Decoder s (Annotator (ByteString → a)) → Decoder s (Annotator a)
- withSlice ∷ Decoder s a → Decoder s (a, Annotator ByteString)
- newtype FullByteString = Full ByteString
- decodeAnnSet ∷ Ord t ⇒ Decoder s (Annotator t) → Decoder s (Annotator (Set t))
- decodeNestedCbor ∷ DecCBOR a ⇒ Decoder s a
- decodeNestedCborBytes ∷ Decoder s ByteString
- unsafeDeserialize ∷ DecCBOR a ⇒ Version → ByteString → a
- unsafeDeserialize' ∷ DecCBOR a ⇒ Version → ByteString → a
- toStrictByteString ∷ Encoding → ByteString
Running decoders
decodeFull ∷ ∀ a. DecCBOR a ⇒ Version → ByteString → Either DecoderError a Source #
Deserialize a Haskell value from a binary CBOR representation, failing if
there are leftovers. In other words, the Full here implies the contract
on this function that the input must be consumed in its entirety by the
decoder specified in DecCBOR
.
decodeFull' ∷ ∀ a. DecCBOR a ⇒ Version → ByteString → Either DecoderError a Source #
Same as decodeFull
, except accepts a strict ByteString
as input
instead of the lazy one.
∷ Version | Protocol version to be used during decoding. |
→ Text | Label for error reporting |
→ (∀ s. Decoder s a) | The parser for the |
→ ByteString | The |
→ Either DecoderError a |
Same as decodeFull
, except instead of relying on the DecCBOR
instance
the Decoder
must be suplied manually.
decodeFullDecoder' ∷ Version → Text → (∀ s. Decoder s a) → ByteString → Either DecoderError a Source #
Same as decodeFullDecoder
, except works on strict ByteString
decodeFullAnnotator ∷ Version → Text → (∀ s. Decoder s (Annotator a)) → ByteString → Either DecoderError a Source #
Same as decodeFullDecoder
, except it provdes the means of passing portion or all
of the ByteString
input argument to the decoding Annotator
.
decodeFullAnnotatedBytes ∷ Functor f ⇒ Version → Text → (∀ s. Decoder s (f ByteSpan)) → ByteString → Either DecoderError (f ByteString) Source #
Same as decodeFullDecoder
, decodes a Haskell value from a lazy
ByteString
, requiring that the full ByteString is consumed, and
replaces ByteSpan
annotations with the corresponding slice of the input as
a strict ByteString
.
decodeFullAnnotatorFromHexText ∷ Version → Text → (∀ s. Decoder s (Annotator a)) → Text → Either DecoderError a Source #
class Typeable a ⇒ DecCBOR a where Source #
Nothing
decCBOR ∷ Decoder s a Source #
dropCBOR ∷ Proxy a → Decoder s () Source #
Validate decoding of a Haskell value, without the need to actually construct
it. Could be slightly faster than decCBOR
, however it should respect this law:
dropCBOR (proxy :: Proxy a) = () <$ (decCBOR :: Decoder s a)
Instances
fromByronCBOR ∷ DecCBOR a ⇒ Decoder s a Source #
Convert a versioned DecCBOR
instance to a plain Decoder
using Byron protocol
version and empty ByteString
.
class Monoid (Share a) ⇒ DecShareCBOR a where Source #
getShare ∷ a → Share a Source #
Whenever fromShareCBOR
is being used for defining the instance this
function should return the state that can be added whenever user invokes
decSharePlusCBOR
. mempty
is returned by default.
decShareCBOR ∷ Share a → Decoder s a Source #
Utilize sharing when decoding, but do not add anything to the state for future sharing.
decSharePlusCBOR ∷ StateT (Share a) (Decoder s) a Source #
Deserialize with sharing and add to the state that is used for sharing. Default
implementation will add value returned by getShare
for adding to the
state.
Instances
This is an abstract interface that does the interning. In other words it
does the actual sharing by looking up the supplied value in some existing
data structure and uses that value instead. Relying on this interface gives us
the benefit of ignoring the type of underlying data structure and allows us
to compose many Intern
s with the monoidal interface provided by Interns
wrapper. In order to create an Intern
see the internsFromMap
or
internsFromVMap
functions.
Intern | |
|
decShareLensCBOR ∷ DecShareCBOR b ⇒ SimpleGetter bs (Share b) → StateT bs (Decoder s) b Source #
decSharePlusLensCBOR ∷ DecShareCBOR b ⇒ Lens' bs (Share b) → StateT bs (Decoder s) b Source #
Just like decSharePlusCBOR
, except allows to transform the shared state
with a lens.
decNoShareCBOR ∷ DecShareCBOR a ⇒ Decoder s a Source #
Use DecShareCBOR
class while ignoring sharing
toMemptyLens ∷ Monoid a ⇒ Lens' a b → Lens' c b → Lens' c a Source #
Using this function it is possible to compose two lenses. One will extract a value and another will used it for placing it into a empty monoid. Here is an example of how a second element of a tuple can be projected on the third element of a 3-tuple.
toMemptyLens _3 _2 == lens (\(_, b) -> (mempty, mempty, b)) (\(a, _) (_, _, b) -> (a, b))
Here is an example where we extract a second element of a tuple and insert it at
third position of a three tuple while all other elements are set to mempty
:
>>>
import Lens.Micro
>>>
("foo","bar") ^. toMemptyLens _3 _2 :: (Maybe String, (), String)
(Nothing,(),"bar")
In the opposite direction of extracting the third element of a 3-tuple and replacing the second element of the tuple the setter is being applied to
>>>
("foo","bar") & toMemptyLens _3 _2 .~ (Just "baz", (), "booyah") :: (String, String)
("foo","booyah")
decShareMonadCBOR ∷ (DecCBOR (f b), Monad f) ⇒ Interns b → Decoder s (f b) Source #
Share every item in a functor, have deserializing it
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
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 # |
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.
fromPlainDecoder ∷ Decoder s a → Decoder s a Source #
Promote a regular Decoder
to a versioned one. Which means it will work for all
versions.
∷ Maybe ByteString | Some decoders require the original bytes to be supplied as well. Such decoders will
fail whenever |
→ Version | |
→ Decoder s a | |
→ Decoder s a |
Extract the underlying Decoder
by optionally supplying the original bytes and
specifying the concrete version to be used.
withPlainDecoder ∷ Decoder s a → (Decoder s a → Decoder s b) → Decoder s b Source #
Use the supplied decoder as a plain decoder with current version.
enforceDecoderVersion ∷ Version → Decoder s a → Decoder s a Source #
Ignore the current version of the decoder and enforce the supplied one instead.
getDecoderVersion ∷ Decoder s Version Source #
Extract current version of the decoder
>>>
import Cardano.Ledger.Decoding
>>>
decodeFullDecoder 3 "Version" getDecoderVersion ""
Right 3
ifDecoderVersionAtLeast Source #
∷ Version | |
→ Decoder s a | Use this decoder if current decoder version is larger or equal to the supplied
|
→ Decoder s a | Use this decoder if current decoder version is lower than the supplied |
→ Decoder s a |
Conditionally choose the newer or older decoder, depending on the current version. Version in the context of encoders/decoders is the major protocol version. Supplied version acts as a pivot.
Example
Let's say prior to the version 2 some type Foo
was backed by Word16
, but at the 2nd
version onwards it was switched to Word32
instead. In order to support both versions,
we change the type, but we also use this condition to keep backwards compatibility of
the decoder:
>>>
newtype Foo = Foo Word32
>>>
decFoo = Foo <$> ifDecoderVersionAtLeast 2 decodeWord32 (fromIntegral <$> decodeWord16)
whenDecoderVersionAtLeast Source #
∷ Version | |
→ Decoder s a | Run this decoder whenever current decoder version is larger or equal to the supplied
|
→ Decoder s () |
Optionally run a decoder depending on the current version and the supplied one.
unlessDecoderVersionAtLeast Source #
∷ Version | |
→ Decoder s a | Run this decoder whenever current decoder version is smaller to the supplied |
→ Decoder s () |
Optionally run a decoder depending on the current version and the supplied one.
decodeRationalWithTag ∷ Decoder s Rational Source #
Enforces tag 30 to indicate a rational number, as per tag assignment: https://www.iana.org/assignments/cbor-tags/cbor-tags.xhtml
decodeList ∷ Decoder s a → Decoder s [a] Source #
for list.Decoder
- [>= 2] - Allows variable as well as exact list length encoding.
- [< 2] - Expects variable list length encoding
decodeNullMaybe ∷ Decoder s a → Decoder s (Maybe a) Source #
Alternative way to decode a Maybe type.
Note - this is not the default method for decoding Maybe
, use decodeMaybe
instead.
decodeStrictMaybe ∷ Decoder s a → Decoder s (StrictMaybe a) Source #
Unlike decodeMaybe
this allows variable as well as exact list length encoding for
all versions, because Byron never used StrictMaybe
type.
decodeNullStrictMaybe ∷ Decoder s a → Decoder s (StrictMaybe a) Source #
Alternative way to decode a StrictMaybe
type.
Note - this is not the default method for decoding StrictMaybe
, use
decodeStrictMaybe
instead.
decodeRecordNamedT ∷ (MonadTrans m, Monad (m (Decoder s))) ⇒ Text → (a → Int) → m (Decoder s) a → m (Decoder s) a Source #
∷ Text | Name for error reporting |
→ Decoder s a | Decoder for the datastructure itself |
→ (a → Int → Decoder s ()) | In case when length was encoded, act upon it. |
→ Decoder s a |
Use this decoder for any list like structure that accepts fixed or variable list length encoding.
decodeWithOrigin ∷ Decoder s a → Decoder s (WithOrigin a) Source #
decodeMap ∷ Ord k ⇒ Decoder s k → Decoder s v → Decoder s (Map k v) Source #
Decoder
for Map
. Versions variance:
- [>= 9] - Allows variable as well as exact list length encoding. Duplicate keys will result in a deserialization failure
- [>= 2] - Allows variable as well as exact list length encoding. Duplicate keys are silently ignored
- [< 2] - Expects exact list length encoding and enforces strict order without any duplicates.
An example of how to use versioning
>>>
:set -XOverloadedStrings
>>>
import Codec.CBOR.FlatTerm
>>>
fromFlatTerm (toPlainDecoder 1 (decodeMap decodeInt decodeBytes)) [TkMapLen 2,TkInt 1,TkBytes "Foo",TkInt 2,TkBytes "Bar"]
Right (fromList [(1,"Foo"),(2,"Bar")])>>>
fromFlatTerm (toPlainDecoder 1 (decodeMap decodeInt decodeBytes)) [TkMapBegin,TkInt 1,TkBytes "Foo",TkInt 2,TkBytes "Bar"]
Left "decodeMapLen: unexpected token TkMapBegin">>>
fromFlatTerm (toPlainDecoder 2 (decodeMap decodeInt decodeBytes)) [TkMapBegin,TkInt 1,TkBytes "Foo",TkInt 2,TkBytes "Bar",TkBreak]
Right (fromList [(1,"Foo"),(2,"Bar")])
decodeMapByKey ∷ Ord k ⇒ Decoder s k → (k → Decoder s v) → Decoder s (Map k v) Source #
Just like decodeMap
, but also gives access to the key for the value decoder.
decodeMapLikeEnforceNoDuplicates ∷ Ord k ⇒ Decoder s (Maybe Int) → Decoder s (k, v) → Decoder s (Map k v) Source #
Similar to decodeMapByKey
, except it gives access to the key value
decoder as a pair and allows for different type of length encoding
decodeVMap ∷ (Vector kv k, Vector vv v, Ord k) ⇒ Decoder s k → Decoder s v → Decoder s (VMap kv vv k v) Source #
Decode VMap
. Unlike decodeMap
it does not behavee differently for
version prior to 2.
We stitch a `258` in from of a (Hash)Set, so that tools which programmatically check for canonicity can recognise it from a normal array. Why 258? This will be formalised pretty soon, but IANA allocated 256...18446744073709551615 to "First come, first served": https://www.iana.org/assignments/cbor-tags/cbor-tags.xhtml Currently `258` is the first unassigned tag and as it requires 2 bytes to be encoded, it sounds like the best fit.
https://github.com/input-output-hk/cbor-sets-spec/blob/master/CBOR_SETS.md
decodeSetTag ∷ Decoder s () Source #
decodeSet ∷ Ord a ⇒ Decoder s a → Decoder s (Set a) Source #
Decoder
for Set
. Versions variance:
- [>= 9] - Allows variable as well as exact list length encoding. Duplicates are not allowed. Set tag 258 is permitted, but not enforced.
- [>= 2, < 9] - Allows variable as well as exact list length encoding. Duplicates are silently ignored, set tag 258 is not permitted.
- [< 2] - Expects exact list length encoding and enforces strict order without any duplicates. Also enforces special set tag 258, which was abandoned starting with version 2
decodeListLikeWithCount Source #
∷ ∀ s a b. Monoid b | |
⇒ Decoder s (Maybe Int) | Length decoder that produces the expected number of elements. When |
→ (a → b → b) | Add an element into the decoded List like data structure |
→ (b → Decoder s a) | Decoder for the values. Current accumulator is supplied as an argument |
→ Decoder s (Int, b) |
Decode a collection of values with ability to supply length decoder. Number of decoded elements will be returned together with the data structure
decodeListLikeEnforceNoDuplicates Source #
∷ ∀ s a b c. Monoid b | |
⇒ Decoder s (Maybe Int) | |
→ (a → b → b) | Add an element into the decoded List like data structure |
→ (b → (Int, c)) | Get the final data structure and the number of elements it has. |
→ Decoder s a | |
→ Decoder s c |
Decode a collection of values with ability to supply length decoder. Duplicates are not allowed.
decodeSetLikeEnforceNoDuplicates Source #
∷ ∀ s a b c. Monoid b | |
⇒ (a → b → b) | Add an element into the decoded Set like data structure |
→ (b → (Int, c)) | Get the final data structure from the decoded sequence of values and the number of
elements it contains. This is useful when a sequence on the wire is represented by a
|
→ Decoder s a | |
→ Decoder s c |
Decode a Set as a either a definite or indefinite list. Duplicates are not allowed. Set tag 258 is permitted, but not enforced.
decodeVector ∷ Vector vec a ⇒ Decoder s a → Decoder s (vec a) Source #
Generic decoder for vectors. Its intended use is to allow easy
definition of Serialise
instances for custom vector
decodeSeq ∷ Decoder s a → Decoder s (Seq a) Source #
Decoder for Seq
. Same behavior for all versions, allows variable as
well as exact list length encoding
decodeStrictSeq ∷ Decoder s a → Decoder s (StrictSeq a) Source #
Decoder for StrictSeq
. Same behavior for all versions, allows variable as
well as exact list length encoding.
decodeMapContents ∷ Decoder s a → Decoder s [a] Source #
decodeMapTraverse ∷ (Ord a, Applicative t) ⇒ Decoder s (t a) → Decoder s (t b) → Decoder s (t (Map a b)) Source #
decodeMapContentsTraverse ∷ Applicative t ⇒ Decoder s (t a) → Decoder s (t b) → Decoder s (t [(a, b)]) Source #
decodeIPv4 ∷ Decoder s IPv4 Source #
decodeIPv6 ∷ Decoder s IPv6 Source #
enforceSize ∷ Text → Int → Decoder s () Source #
Enforces that the input size is the same as the decoded one, failing in case it's not
matchSize ∷ Text → Int → Int → Decoder s () Source #
Compare two sizes, failing if they are not equal
decodeBool ∷ Decoder s Bool Source #
decodeBreakOr ∷ Decoder s Bool Source #
decodeBytesIndef ∷ Decoder s () Source #
decodeDouble ∷ Decoder s Double Source #
decodeFloat ∷ Decoder s Float Source #
decodeInt16 ∷ Decoder s Int16 Source #
decodeInt32 ∷ Decoder s Int32 Source #
decodeInt64 ∷ Decoder s Int64 Source #
decodeInt8 ∷ Decoder s Int8 Source #
decodeListLen ∷ Decoder s Int Source #
decodeListLenCanonicalOf ∷ Int → Decoder s () Source #
decodeListLenIndef ∷ Decoder s () Source #
decodeListLenOf ∷ Int → Decoder s () Source #
decodeMapLen ∷ Decoder s Int Source #
decodeMapLenIndef ∷ Decoder s () Source #
decodeNegWord ∷ Decoder s Word Source #
decodeNull ∷ Decoder s () Source #
decodeSequenceLenIndef ∷ (r → a → r) → r → (r → b) → Decoder s a → Decoder s b Source #
decodeSimple ∷ Decoder s Word8 Source #
decodeString ∷ Decoder s Text Source #
decodeStringIndef ∷ Decoder s () Source #
decodeTag64 ∷ Decoder s Word64 Source #
decodeWithByteSpan ∷ Decoder s a → Decoder s (a, ByteOffset, ByteOffset) Source #
decodeWord ∷ Decoder s Word Source #
decodeWord16 ∷ Decoder s Word16 Source #
decodeWord32 ∷ Decoder s Word32 Source #
decodeWord64 ∷ Decoder s Word64 Source #
decodeWord8 ∷ Decoder s Word8 Source #
decodeWordCanonicalOf ∷ Word → Decoder s () Source #
decodeWordOf ∷ Word → Decoder s () Source #
decodeTerm ∷ Decoder s Term Source #
peekAvailable ∷ Decoder s Int Source #
A CBOR deserialized value together with its size. When deserializing use
either decodeSized
or its DecCBOR
instance.
Use mkSized
to construct such value.
Sized | |
|
Instances
Generic (Sized a) Source # | |
Show a ⇒ Show (Sized a) Source # | |
DecCBOR a ⇒ DecCBOR (Sized a) Source # | |
EncCBOR a ⇒ EncCBOR (Sized a) Source # | Discards the size. |
NFData a ⇒ NFData (Sized a) Source # | |
Defined in Cardano.Ledger.Binary.Decoding.Sized | |
Eq a ⇒ Eq (Sized a) Source # | |
NoThunks a ⇒ NoThunks (Sized a) Source # | |
type Rep (Sized a) Source # | |
Defined in Cardano.Ledger.Binary.Decoding.Sized type Rep (Sized a) = D1 ('MetaData "Sized" "Cardano.Ledger.Binary.Decoding.Sized" "cardano-ledger-binary-1.5.0.0-inplace" 'False) (C1 ('MetaCons "Sized" 'PrefixI 'True) (S1 ('MetaSel ('Just "sizedValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "sizedSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64))) |
mkSized ∷ EncCBOR a ⇒ Version → a → Sized a Source #
Construct a Sized
value by serializing it first and recording the amount
of bytes it requires. Note, however, CBOR serialization is not canonical,
therefore it is *NOT* a requirement that this property holds:
sizedSize (mkSized a) === sizedSize (unsafeDeserialize (serialize a) :: a)
toSizedL ∷ EncCBOR s ⇒ Version → Lens' s a → Lens' (Sized s) a Source #
Take a lens that operates on a particular type and convert it into a lens
that operates on the Sized
version of the type.
dropList ∷ Dropper s → Dropper s Source #
Drop a list of values using the supplied Dropper
for each element
dropWord64 ∷ Dropper s Source #
Annotated
The regular CBOR Decoder
does not support access to the original ByteString
that is
being read during deserialization. The Annotator
and Annotated
recover this ability.
ByteSpan
A pair of indexes into a bytestring, indicating a substring.Annotated
Used in practice to pair a value with aByteSpan
. Mostly used in Byron codebase.FullByteString
A newtype (around a bytestring) used to store the original bytestring being deserialized.Annotator
An explict reader monad whose environment is aFullByteString
The basic idea is, for a given type t
, where we need the original ByteString
, either
- To complete the deserialization, or
- To combine the deserialized answer with the original
ByteString
.
We should proceed as follows: Define instances (
instead
of DecCBOR
(Annotator
t))(
. When making this instance we may freely use that both DecCBOR
t)Decoder
and Annotator
are both monads, and that functions withSlice
and annotatorSlice
provide access to the original bytes, or portions thereof, inside of decoders. Then,
to actually decode a value of type t
, we use something similar to the following code
fragment.
howToUseFullBytes bytes = do Annotator f <- decodeFullDecoder "DecodingAnnotator" (decCBOR :: forall s. Decoder s (Annotator t)) bytes pure (f (Full bytes))
Decode the bytes to get an (
where f is a function that when given
original bytes produces a value of type Annotator
f)t
, then apply f
to (
to get
the answer.Full
bytes)
Annotated | |
|
Instances
decodeAnnotated ∷ Decoder s a → Decoder s (Annotated a ByteString) Source #
A pair of offsets delimiting the beginning and end of a substring of a ByteString
Instances
ToJSON ByteSpan Source # | |
Generic ByteSpan Source # | |
Show ByteSpan Source # | |
type Rep ByteSpan Source # | |
Defined in Cardano.Ledger.Binary.Decoding.Annotated type Rep ByteSpan = D1 ('MetaData "ByteSpan" "Cardano.Ledger.Binary.Decoding.Annotated" "cardano-ledger-binary-1.5.0.0-inplace" 'False) (C1 ('MetaCons "ByteSpan" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteOffset) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteOffset))) |
class Decoded t where Source #
recoverBytes ∷ t → ByteString Source #
Instances
Decoded (Annotated b ByteString) Source # | |
Defined in Cardano.Ledger.Binary.Decoding.Annotated type BaseType (Annotated b ByteString) Source # |
annotationBytes ∷ Functor f ⇒ ByteString → f ByteSpan → f ByteString Source #
annotatedDecoder ∷ Decoder s a → Decoder s (Annotated a ByteSpan) Source #
A decoder for a value paired with an annotation specifying the start and end of the consumed bytes.
slice ∷ ByteString → ByteSpan → ByteString Source #
Extract a substring of a given ByteString corresponding to the offsets.
decCBORAnnotated ∷ DecCBOR a ⇒ Decoder s (Annotated a ByteSpan) Source #
A decoder for a value paired with an annotation specifying the start and end of the consumed bytes.
reAnnotate ∷ EncCBOR a ⇒ Version → Annotated a b → Annotated a ByteString Source #
Reconstruct an annotation by re-serialising the payload to a ByteString.
A value of type (Annotator a)
is one that needs access to the entire bytestring
used during decoding to finish construction of a vaue of type a
. A typical use is
some type that stores the bytes that were used to deserialize it. For example the
type Inner
below is constructed using the helper function makeInner
which
serializes and stores its bytes (using serialize
). Note how we build the
Annotator
by abstracting over the full bytes, and using those original bytes to
fill the bytes field of the constructor Inner
. The EncCBOR
instance just reuses
the stored bytes to produce an encoding (using encodePreEncoded
).
data Inner = Inner Int Bool LByteString makeInner :: Int -> Bool -> Inner makeInner i b = Inner i b (serialize (encCBOR i <> encCBOR b)) instance EncCBOR Inner where encCBOR (Inner _ _ bytes) = encodePreEncoded bytes instance DecCBOR (Annotator Inner) where decCBOR = do int <- decCBOR trueOrFalse <- decCBOR pure (Annotator ((Full bytes) -> Inner int trueOrFalse bytes))
if an Outer
type has a field of type Inner
, with a (EncCBOR (Annotator Inner))
instance, the Outer
type must also have a (EncCBOR (Annotator Outer))
instance. The
key to writing that instance is to use the operation withSlice
which returns a pair.
The first component is an Annotator
that can build Inner
, the second is an
Annotator
that given the full bytes, extracts just the bytes needed to decode
Inner
.
data Outer = Outer Text Inner instance EncCBOR Outer where encCBOR (Outer t i) = encCBOR t <> encCBOR i instance DecCBOR (Annotator Outer) where decCBOR = do t <- decCBOR (Annotator mkInner, Annotator extractInnerBytes) <- withSlice decCBOR pure (Annotator ( full -> Outer t (mkInner (Full (extractInnerBytes full)))))
annotatorSlice ∷ Decoder s (Annotator (ByteString → a)) → Decoder s (Annotator a) Source #
The argument is a decoder for a annotator that needs access to the bytes that | were decoded. This function constructs and supplies the relevant piece.
withSlice ∷ Decoder s a → Decoder s (a, Annotator ByteString) Source #
Pairs the decoder result with an annotator that can be used to construct the exact bytes used to decode the result.
newtype FullByteString Source #
This marks the entire bytestring used during decoding, rather than the piece we need to finish constructing our value.
Nested CBOR in CBOR
decodeNestedCbor ∷ DecCBOR 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.
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.
Unsafe deserialization
unsafeDeserialize ∷ DecCBOR a ⇒ Version → ByteString → a Source #
Deserialize a Haskell value from the external binary representation, which
have been made using serialize
or a matching serialization functionilty in
another language that uses CBOR format. Accepts lazy ByteString
as
input, for strict variant use unsafeDeserialize
` instead.
This deserializaer is not safe for these reasons:
- Throws:
if the given external representation is invalid or does not correspond to a value of the expected type.DeserialiseFailure
- Decoding will not fail when the binary input is not consumed in full.
unsafeDeserialize' ∷ DecCBOR a ⇒ Version → ByteString → a Source #
Variant of unsafeDeserialize
that accepts a strict ByteString
as
input.
Helpers
∷ Encoding | The |
→ ByteString | The encoded value. |
Turn an Encoding
into a strict ByteString
in CBOR binary
format.
Since: cborg-0.2.0.0