cardano-ledger-core-1.12.0.0: Core components of Cardano ledgers from the Shelley release on.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Cardano.Ledger.Serialization

Description

Deprecated: Use Binary from 'cardano-ledger-binary' package instead

Synopsis

Documentation

class Typeable a ⇒ EncCBORGroup a where Source #

Methods

encCBORGroup ∷ a → Encoding Source #

encodedGroupSizeExpr ∷ (∀ x. EncCBOR x ⇒ Proxy x → Size) → Proxy a → Size Source #

listLen ∷ a → Word Source #

listLenBoundProxy a → Word Source #

an upper bound for listLen, used in Size expressions.

class Typeable a ⇒ DecCBORGroup a where Source #

Methods

decCBORGroupDecoder s a Source #

Instances

Instances details
DecCBORGroup ProtVer Source # 
Instance details

Defined in Cardano.Ledger.BaseTypes

DecCBORGroup Ptr Source # 
Instance details

Defined in Cardano.Ledger.Credential

Crypto c ⇒ DecCBORGroup (PoolParams c) Source # 
Instance details

Defined in Cardano.Ledger.PoolParams

newtype CBORGroup a Source #

Constructors

CBORGroup 

Fields

Instances

Instances details
Show a ⇒ Show (CBORGroup a) 
Instance details

Defined in Cardano.Ledger.Binary.Group

(DecCBORGroup a, EncCBORGroup a) ⇒ DecCBOR (CBORGroup a) 
Instance details

Defined in Cardano.Ledger.Binary.Group

EncCBORGroup a ⇒ EncCBOR (CBORGroup a) 
Instance details

Defined in Cardano.Ledger.Binary.Group

Methods

encCBORCBORGroup a → Encoding Source #

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy (CBORGroup a) → Size Source #

encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [CBORGroup a] → Size Source #

Eq a ⇒ Eq (CBORGroup a) 
Instance details

Defined in Cardano.Ledger.Binary.Group

Methods

(==)CBORGroup a → CBORGroup a → Bool Source #

(/=)CBORGroup a → CBORGroup a → Bool Source #

decodeListDecoder s a → Decoder s [a] Source #

Decoder for list.

  • [>= 2] - Allows variable as well as exact list length encoding.
  • [< 2] - Expects variable list length encoding

decodeSeqDecoder s a → Decoder s (Seq a) Source #

Decoder for Seq. Same behavior for all versions, allows variable as well as exact list length encoding

decodeStrictSeqDecoder s a → Decoder s (StrictSeq a) Source #

Decoder for StrictSeq. Same behavior for all versions, allows variable as well as exact list length encoding.

decodeSetOrd 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

decodeMapOrd 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")])

decodeMapTraverse ∷ (Ord a, Applicative t) ⇒ Decoder s (t a) → Decoder s (t b) → Decoder s (t (Map a b)) Source #

decodeMaybeDecoder s a → Decoder s (Maybe a) Source #

Decoder for Maybe. Versions variance:

  • [>= 2] - Allows variable as well as exact list length encoding.
  • [< 2] - Expects exact list length encoding

decodeRecordNamedText → (a → Int) → Decoder s a → Decoder s a Source #

decodeRecordNamedT ∷ (MonadTrans m, Monad (m (Decoder s))) ⇒ Text → (a → Int) → m (Decoder s) a → m (Decoder s) a Source #

decodeRecordSumText → (WordDecoder s (Int, a)) → Decoder s a Source #

decodeNullMaybeDecoder 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.

encodeFoldableEncoderFoldable f ⇒ (a → Encoding) → f a → Encoding Source #

Encode any Foldable with the variable list length encoding, which will use indefinite encoding over 23 elements and definite otherwise.

encodeFoldableMapEncoder Source #

Arguments

Foldable f 
⇒ (Word → a → Maybe Encoding)

A function that accepts an index of the value in the foldable data strucure, the actual value and optionally produces the encoding of the value and an index if that value should be encoded.

→ f a 
Encoding 

Encode a data structure as a Map with the 0-based index for a Key to a value. Uses variable map length encoding, which means an indefinite encoding for maps with over 23 elements and definite otherwise.

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

encodeMap ∷ (k → Encoding) → (v → Encoding) → Map k v → Encoding Source #

Encode a Map. Versions variance:

  • [>= 2] - Variable length encoding for Maps larger than 23 key value pairs, otherwise exact length encoding
  • [< 2] - Variable length encoding.

mapEncCBOR ∷ (EncCBOR a, EncCBOR b) ⇒ Map a b → Encoding Source #

mapDecCBOR ∷ (Ord a, DecCBOR a, DecCBOR b) ⇒ Decoder s (Map a b) Source #

translateViaCBORAnnotator Source #

Arguments

∷ (ToCBOR a, DecCBOR (Annotator b)) 
Version

Version that will be used for deserialization

Text 
→ a 
Except DecoderError b 

Translation function between values through a related binary representation. This function allows you to translate one type into another (or the same one) through their common binary format. It is possible for the source type to be encoded with a different version than the version that will be used for decoding. This is useful for types that build upon one another and are "upgradeable" through their binary representation. It is important to note that the deserialization will happen with Annotator, since that is usually the way we deserialize upgradeable types that live on chain. Moreover, encoding does not require a version, because memoized types that were decoded with annotation will have the bytes retained and thus will have the ToCBOR instance.

runByteBuilderIntBuilderByteString Source #

Run a ByteString Builder using a strategy aimed at making smaller things efficiently.

It takes a size hint and produces a strict ByteString. This will be fast when the size hint is the same or slightly bigger than the true size.

data Sized a Source #

A CBOR deserialized value together with its size. When deserializing use either decodeSized or its DecCBOR instance.

Use mkSized to construct such value.

Constructors

Sized 

Fields

  • sizedValue ∷ !a
     
  • sizedSizeInt64

    Overhead in bytes. The field is lazy on purpose, because it might not be needed, but it can be expensive to compute.

Instances

Instances details
Generic (Sized a) 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Sized

Associated Types

type Rep (Sized a) ∷ TypeType Source #

Methods

fromSized a → Rep (Sized a) x Source #

toRep (Sized a) x → Sized a Source #

Show a ⇒ Show (Sized a) 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Sized

Methods

showsPrecIntSized a → ShowS Source #

showSized a → String Source #

showList ∷ [Sized a] → ShowS Source #

DecCBOR a ⇒ DecCBOR (Sized a) 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Sized

Methods

decCBORDecoder s (Sized a) Source #

dropCBORProxy (Sized a) → Decoder s () Source #

labelProxy (Sized a) → Text Source #

EncCBOR a ⇒ EncCBOR (Sized a)

Discards the size.

Instance details

Defined in Cardano.Ledger.Binary.Decoding.Sized

Methods

encCBORSized a → Encoding Source #

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy (Sized a) → Size Source #

encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [Sized a] → Size Source #

NFData a ⇒ NFData (Sized a) 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Sized

Methods

rnfSized a → () Source #

Eq a ⇒ Eq (Sized a) 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Sized

Methods

(==)Sized a → Sized a → Bool Source #

(/=)Sized a → Sized a → Bool Source #

NoThunks a ⇒ NoThunks (Sized a) 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Sized

type Rep (Sized a) 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Sized

type Rep (Sized a) = D1 ('MetaData "Sized" "Cardano.Ledger.Binary.Decoding.Sized" "cardano-ledger-binary-1.3.2.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)))

mkSizedEncCBOR 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)

toSizedLEncCBOR s ⇒ VersionLens' 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.