Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Cardano.Ledger.Binary
Synopsis
- module Cardano.Ledger.Binary.Decoding
- module Cardano.Ledger.Binary.Encoding
- module Cardano.Ledger.Binary.Group
- module Cardano.Ledger.Binary.Version
- type Size = Fix SizeF
- class Typeable a ⇒ FromCBOR a where
- data SizeOverride
- = SizeConstant Size
- | SizeExpression ((∀ a. ToCBOR a ⇒ Proxy a → Size) → Size)
- | SelectCases [Text]
- data Range b = Range {}
- data Case t = Case Text t
- newtype LengthOf xs = LengthOf xs
- class Typeable a ⇒ ToCBOR a where
- szCases ∷ [Case Size] → Size
- caseValue ∷ Case t → t
- szEval ∷ (∀ t. ToCBOR t ⇒ (Proxy t → Size) → Proxy t → Range Natural) → Size → Range Natural
- szLazy ∷ ToCBOR a ⇒ Proxy a → Size
- szGreedy ∷ ToCBOR a ⇒ Proxy a → Size
- isTodo ∷ Size → Bool
- apMono ∷ Text → (Natural → Natural) → Size → Size
- szWithCtx ∷ ToCBOR a ⇒ Map TypeRep SizeOverride → Proxy a → Size
- szSimplify ∷ Size → Either Size (Range Natural)
- szForce ∷ Size → Size
- szBounds ∷ ToCBOR a ⇒ a → Either Size (Range Natural)
- withWordSize ∷ (Integral s, Integral a) ⇒ s → a
- toCBORMaybe ∷ (a → Encoding) → Maybe a → Encoding
- data Term
- data DeserialiseFailure = DeserialiseFailure ByteOffset String
- translateViaCBORAnnotator ∷ (ToCBOR a, DecCBOR (Annotator b)) ⇒ Version → Text → a → Except DecoderError b
Documentation
module Cardano.Ledger.Binary.Group
type Size = Fix SizeF Source #
Expressions describing the statically-computed size bounds on a type's possible values.
class Typeable a ⇒ FromCBOR a where Source #
Instances
data SizeOverride Source #
Override mechanisms to be used with szWithCtx
.
Constructors
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 |
A range of values. Should satisfy the invariant forall x. lo x <= hi x
.
An individual labeled case.
A type used to represent the length of a value in Size
computations.
Constructors
LengthOf xs |
Instances
class Typeable a ⇒ ToCBOR a where Source #
Minimal complete definition
Methods
toCBOR ∷ a → Encoding Source #
encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy a → Size Source #
encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [a] → Size Source #
Instances
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.
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)
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))) })
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
.
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.
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.
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))) })
withWordSize ∷ (Integral s, Integral a) ⇒ s → a Source #
Compute encoded size of an integer
A general CBOR term, which can be used to serialise or deserialise arbitrary CBOR terms for interoperability or debugging. This type is essentially a direct reflection of the CBOR abstract syntax tree as a Haskell data type.
The Term
type also comes with a Serialise
instance, so you can
easily use
to directly decode any arbitrary
CBOR value into Haskell with ease, and likewise with decode
:: Decoder
Term
encode
.
Since: cborg-0.2.0.0
Constructors
TInt !Int | |
TInteger !Integer | |
TBytes !ByteString | |
TBytesI !ByteString | |
TString !Text | |
TStringI !Text | |
TList ![Term] | |
TListI ![Term] | |
TMap ![(Term, Term)] | |
TMapI ![(Term, Term)] | |
TTagged !Word64 !Term | |
TBool !Bool | |
TNull | |
TSimple !Word8 | |
THalf !Float | |
TFloat !Float | |
TDouble !Double |
data DeserialiseFailure Source #
An exception type that may be returned (by pure functions) or thrown (by IO actions) that fail to deserialise a given input.
Since: cborg-0.2.0.0
Constructors
DeserialiseFailure ByteOffset String |
Instances
Exception DeserialiseFailure | |
Defined in Codec.CBOR.Read | |
Show DeserialiseFailure | |
Defined in Codec.CBOR.Read Methods showsPrec ∷ Int → DeserialiseFailure → ShowS # show ∷ DeserialiseFailure → String # showList ∷ [DeserialiseFailure] → ShowS # | |
NFData DeserialiseFailure | |
Defined in Codec.CBOR.Read Methods rnf ∷ DeserialiseFailure → () # | |
Eq DeserialiseFailure | |
Defined in Codec.CBOR.Read Methods |
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.