Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- serialize ∷ EncCBOR a ⇒ Version → a → ByteString
- serialize' ∷ EncCBOR a ⇒ Version → a → ByteString
- serializeBuilder ∷ EncCBOR a ⇒ Version → a → Builder
- hashWithEncoder ∷ ∀ h a. HashAlgorithm h ⇒ Version → (a → Encoding) → a → Hash h a
- hashEncCBOR ∷ ∀ h a. (HashAlgorithm h, EncCBOR a) ⇒ Version → a → Hash h a
- module Cardano.Ledger.Binary.Version
- data Encoding
- toBuilder ∷ Version → Encoding → Builder
- 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
- toPlainEncoding ∷ Version → Encoding → Encoding
- fromPlainEncoding ∷ Encoding → Encoding
- fromPlainEncodingWithVersion ∷ (Version → Encoding) → Encoding
- withCurrentEncodingVersion ∷ (Version → Encoding) → Encoding
- enforceEncodingVersion ∷ Version → Encoding → Encoding
- ifEncodingVersionAtLeast ∷ Version → Encoding → Encoding → Encoding
- encodeVersion ∷ Version → Encoding
- encodeMaybe ∷ (a → Encoding) → Maybe a → Encoding
- encodeNullMaybe ∷ (a → Encoding) → Maybe a → Encoding
- encodeStrictMaybe ∷ (a → Encoding) → StrictMaybe a → Encoding
- encodeNullStrictMaybe ∷ (a → Encoding) → StrictMaybe a → Encoding
- encodeTuple ∷ (a → Encoding) → (b → Encoding) → (a, b) → Encoding
- encodeRatio ∷ (t → Encoding) → Ratio t → Encoding
- encodeRatioNoTag ∷ (t → Encoding) → Ratio t → Encoding
- encodeRatioWithTag ∷ (t → Encoding) → Ratio t → Encoding
- encodeEnum ∷ Enum a ⇒ a → Encoding
- encodeWithOrigin ∷ (a → Encoding) → WithOrigin a → Encoding
- encodeList ∷ (a → Encoding) → [a] → Encoding
- encodeSeq ∷ (a → Encoding) → Seq a → Encoding
- encodeStrictSeq ∷ (a → Encoding) → StrictSeq a → Encoding
- encodeSet ∷ (a → Encoding) → Set a → Encoding
- encodeMap ∷ (k → Encoding) → (v → Encoding) → Map k v → Encoding
- encodeVMap ∷ (Vector kv k, Vector vv v) ⇒ (k → Encoding) → (v → Encoding) → VMap kv vv k v → Encoding
- encodeVector ∷ Vector v a ⇒ (a → Encoding) → v a → Encoding
- variableListLenEncoding ∷ Int → Encoding → Encoding
- encodeFoldableEncoder ∷ Foldable f ⇒ (a → Encoding) → f a → Encoding
- encodeFoldableAsDefLenList ∷ Foldable f ⇒ (a → Encoding) → f a → Encoding
- encodeFoldableAsIndefLenList ∷ Foldable f ⇒ (a → Encoding) → f a → Encoding
- encodeFoldableMapEncoder ∷ Foldable f ⇒ (Word → a → Maybe Encoding) → f a → Encoding
- lengthThreshold ∷ Int
- encodeUTCTime ∷ UTCTime → Encoding
- encodeIPv4 ∷ IPv4 → Encoding
- ipv4ToBytes ∷ IPv4 → ByteString
- encodeIPv6 ∷ IPv6 → Encoding
- ipv6ToBytes ∷ IPv6 → ByteString
- 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
- encodePreEncoded ∷ ByteString → Encoding
- encodeTerm ∷ Term → Encoding
- class Typeable a ⇒ EncCBOR a where
- withWordSize ∷ (Integral s, Integral a) ⇒ s → a
- newtype PreEncoded = PreEncoded {}
- toByronCBOR ∷ EncCBOR a ⇒ a → Encoding
- data Range b = Range {}
- szEval ∷ (∀ t. EncCBOR t ⇒ (Proxy t → Size) → Proxy t → Range Natural) → Size → Range Natural
- type Size = Fix SizeF
- data Case t = Case Text t
- caseValue ∷ Case t → t
- newtype LengthOf xs = LengthOf xs
- data SizeOverride
- = SizeConstant Size
- | SizeExpression ((∀ a. EncCBOR a ⇒ Proxy a → Size) → Size)
- | SelectCases [Text]
- isTodo ∷ Size → Bool
- szCases ∷ [Case Size] → Size
- szLazy ∷ EncCBOR a ⇒ Proxy a → Size
- szGreedy ∷ EncCBOR a ⇒ Proxy a → Size
- szForce ∷ Size → Size
- szWithCtx ∷ EncCBOR a ⇒ Map TypeRep SizeOverride → Proxy a → Size
- szSimplify ∷ Size → Either Size (Range Natural)
- apMono ∷ Text → (Natural → Natural) → Size → Size
- szBounds ∷ EncCBOR a ⇒ a → Either Size (Range Natural)
- encodedVerKeyDSIGNSizeExpr ∷ ∀ v. DSIGNAlgorithm v ⇒ Proxy (VerKeyDSIGN v) → Size
- encodedSignKeyDSIGNSizeExpr ∷ ∀ v. DSIGNAlgorithm v ⇒ Proxy (SignKeyDSIGN v) → Size
- encodedSigDSIGNSizeExpr ∷ ∀ v. DSIGNAlgorithm v ⇒ Proxy (SigDSIGN v) → Size
- encodedSignedDSIGNSizeExpr ∷ ∀ v a. DSIGNAlgorithm v ⇒ Proxy (SignedDSIGN v a) → Size
- encodedVerKeyKESSizeExpr ∷ ∀ v. KESAlgorithm v ⇒ Proxy (VerKeyKES v) → Size
- encodedSignKeyKESSizeExpr ∷ ∀ v. KESAlgorithm v ⇒ Proxy (SignKeyKES v) → Size
- encodedSigKESSizeExpr ∷ ∀ v. KESAlgorithm v ⇒ Proxy (SigKES v) → Size
- encodedVerKeyVRFSizeExpr ∷ ∀ v. VRFAlgorithm v ⇒ Proxy (VerKeyVRF v) → Size
- encodedSignKeyVRFSizeExpr ∷ ∀ v. VRFAlgorithm v ⇒ Proxy (SignKeyVRF v) → Size
- encodedCertVRFSizeExpr ∷ ∀ v. VRFAlgorithm v ⇒ Proxy (CertVRF v) → Size
- encodeNestedCbor ∷ EncCBOR a ⇒ a → Encoding
- encodeNestedCborBytes ∷ ByteString → Encoding
- nestedCborSizeExpr ∷ Size → Size
- nestedCborBytesSizeExpr ∷ Size → Size
- runByteBuilder ∷ Int → Builder → ByteString
Running decoders
serialize ∷ EncCBOR a ⇒ Version → a → ByteString Source #
Serialize a Haskell value with a EncCBOR
instance to an external binary
representation.
The output is represented as a lazy ByteString
and is constructed
incrementally.
serialize' ∷ EncCBOR a ⇒ Version → a → ByteString Source #
Serialize a Haskell value to an external binary representation.
The output is represented as a strict ByteString
.
serializeBuilder ∷ EncCBOR a ⇒ Version → a → Builder Source #
Serialize into a Builder. Useful if you want to throw other ByteStrings around it.
Hash
hashWithEncoder ∷ ∀ h a. HashAlgorithm h ⇒ Version → (a → Encoding) → a → Hash h a Source #
hashEncCBOR ∷ ∀ h a. (HashAlgorithm h, EncCBOR a) ⇒ Version → a → Hash h a Source #
Decoders
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
withCurrentEncodingVersion ∷ (Version → Encoding) → Encoding Source #
Get access to the current version being used in the encoder
enforceEncodingVersion ∷ Version → Encoding → Encoding Source #
Ignore the current version of the encoder and enforce the supplied one instead.
ifEncodingVersionAtLeast Source #
∷ Version | |
→ Encoding | Use this encoder if current encoder version is larger or equal to the supplied
|
→ Encoding | Use this encoder if current encoder version is lower than the supplied |
→ Encoding |
Conditionoly choose the encoder newer or older deceder, depending on the current version. Supplied version acts as a pivot.
Example
Custom
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
encodeStrictMaybe ∷ (a → Encoding) → StrictMaybe a → Encoding Source #
encodeNullStrictMaybe ∷ (a → Encoding) → StrictMaybe a → Encoding Source #
Alternative way to encode a Maybe type.
Note - this is not the default method for encoding StrictMaybe
, use
encodeStrictMaybe
instead
encodeRatioWithTag ∷ (t → Encoding) → Ratio t → Encoding Source #
Encode a rational number with tag 30, as per tag assignment: https://www.iana.org/assignments/cbor-tags/cbor-tags.xhtml
encodeEnum ∷ Enum a ⇒ a → Encoding Source #
encodeWithOrigin ∷ (a → Encoding) → WithOrigin a → Encoding Source #
Containers
encodeList ∷ (a → Encoding) → [a] → Encoding Source #
Encode a list. Versions variance:
- [>= 2] - Variable length encoding for lists longer than 23 elements, otherwise exact length encoding
- [< 2] - Variable length encoding
encodeSeq ∷ (a → Encoding) → Seq a → Encoding Source #
Encode a Seq. Variable length encoding for Sequences larger than 23 elements, otherwise exact length encoding
encodeSet ∷ (a → Encoding) → Set a → Encoding Source #
Encode a Set. Versions variance:
- [>= 9] - Variable length encoding for Sets larger than 23 elements, otherwise exact
length encoding. Prefixes with a special 258
setTag
. - [>= 2] - Variable length encoding for Sets larger than 23 elements, otherwise exact length encoding
- [< 2] - Variable length encoding. Prefixes with a special 258
setTag
.
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.
encodeVMap ∷ (Vector kv k, Vector vv v) ⇒ (k → Encoding) → (v → Encoding) → VMap kv vv k v → Encoding Source #
Mimics Map
encoder encodeMap
identically.
encodeVector ∷ Vector v a ⇒ (a → Encoding) → v a → Encoding Source #
Generic encoder for vectors. Its intended use is to allow easy
definition of EncCBOR
instances for custom vector
variableListLenEncoding Source #
∷ Int | Number of elements in the encoded data structure. |
→ Encoding | Encoding for the actual data structure |
→ Encoding |
Conditionally use variable length encoding for list like structures with length larger than 23, otherwise use exact list length encoding.
Helpers
encodeFoldableEncoder ∷ Foldable 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.
encodeFoldableAsIndefLenList ∷ Foldable f ⇒ (a → Encoding) → f a → Encoding Source #
Encode any Foldable with indefinite list length encoding
encodeFoldableMapEncoder Source #
∷ 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.
lengthThreshold ∷ Int Source #
This is the optimal maximum number for encoding exact length. Above that threashold using variable length encoding will result in less bytes on the wire.
Time
Network
encodeIPv4 ∷ IPv4 → Encoding Source #
ipv4ToBytes ∷ IPv4 → ByteString Source #
encodeIPv6 ∷ IPv6 → Encoding Source #
ipv6ToBytes ∷ IPv6 → ByteString Source #
Original
encodeWord ∷ Word → Encoding Source #
encodeWord8 ∷ Word8 → Encoding Source #
encodeInt8 ∷ Int8 → Encoding Source #
encodeInt16 ∷ Int16 → Encoding Source #
encodeInt32 ∷ Int32 → Encoding Source #
encodeInt64 ∷ Int64 → Encoding Source #
encodeString ∷ Text → Encoding Source #
encodeListLen ∷ Word → Encoding Source #
encodeMapLen ∷ Word → Encoding Source #
encodeTag64 ∷ Word64 → Encoding Source #
encodeBool ∷ Bool → Encoding Source #
encodeSimple ∷ Word8 → Encoding Source #
encodeFloat ∷ Float → Encoding Source #
encodeTerm ∷ Term → Encoding Source #
class Typeable a ⇒ EncCBOR a where Source #
Nothing
encCBOR ∷ a → Encoding Source #
encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy a → Size Source #
encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [a] → Size Source #
Instances
withWordSize ∷ (Integral s, Integral a) ⇒ s → a Source #
Compute encoded size of an integer
newtype PreEncoded Source #
Instances
EncCBOR PreEncoded Source # | |
Defined in Cardano.Ledger.Binary.Encoding.EncCBOR encCBOR ∷ PreEncoded → Encoding Source # encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy PreEncoded → Size Source # encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [PreEncoded] → Size Source # |
toByronCBOR ∷ EncCBOR a ⇒ a → Encoding Source #
Size of expressions
A range of values. Should satisfy the invariant forall x. lo x <= hi x
.
Instances
(Ord b, Num b) ⇒ Num (Range b) Source # | The |
Defined in Cardano.Ledger.Binary.Encoding.EncCBOR | |
Buildable (Range Natural) Source # | |
szEval ∷ (∀ t. EncCBOR 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.
type Size = Fix SizeF Source #
Expressions describing the statically-computed size bounds on a type's possible values.
An individual labeled case.
A type used to represent the length of a value in Size
computations.
LengthOf xs |
data SizeOverride Source #
Override mechanisms to be used with szWithCtx
.
SizeConstant Size | Replace with a fixed |
SizeExpression ((∀ a. EncCBOR a ⇒ Proxy a → Size) → Size) | Recursively compute the size. |
SelectCases [Text] | Select only a specific case from a |
szLazy ∷ EncCBOR 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 ∷ EncCBOR 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 EncCBOR
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))) })
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))) })
szWithCtx ∷ EncCBOR 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.
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
.
Crypto
encodedVerKeyDSIGNSizeExpr ∷ ∀ v. DSIGNAlgorithm v ⇒ Proxy (VerKeyDSIGN v) → Size Source #
Size
expression for VerKeyDSIGN
which is using sizeVerKeyDSIGN
encoded as Size
.
encodedSignKeyDSIGNSizeExpr ∷ ∀ v. DSIGNAlgorithm v ⇒ Proxy (SignKeyDSIGN v) → Size Source #
Size
expression for SignKeyDSIGN
which is using sizeSignKeyDSIGN
encoded as Size
.
encodedSigDSIGNSizeExpr ∷ ∀ v. DSIGNAlgorithm v ⇒ Proxy (SigDSIGN v) → Size Source #
Size
expression for SigDSIGN
which is using sizeSigDSIGN
encoded as
Size
.
encodedSignedDSIGNSizeExpr ∷ ∀ v a. DSIGNAlgorithm v ⇒ Proxy (SignedDSIGN v a) → Size Source #
Size
expression for SignedDSIGN
which uses encodedSigDSIGNSizeExpr
encodedVerKeyKESSizeExpr ∷ ∀ v. KESAlgorithm v ⇒ Proxy (VerKeyKES v) → Size Source #
Size
expression for VerKeyKES
which is using sizeVerKeyKES
encoded
as Size
.
encodedSignKeyKESSizeExpr ∷ ∀ v. KESAlgorithm v ⇒ Proxy (SignKeyKES v) → Size Source #
Size
expression for SignKeyKES
which is using sizeSignKeyKES
encoded
as Size
.
encodedSigKESSizeExpr ∷ ∀ v. KESAlgorithm v ⇒ Proxy (SigKES v) → Size Source #
Size
expression for SigKES
which is using sizeSigKES
encoded as
Size
.
encodedVerKeyVRFSizeExpr ∷ ∀ v. VRFAlgorithm v ⇒ Proxy (VerKeyVRF v) → Size Source #
Size
expression for VerKeyVRF
which is using sizeVerKeyVRF
encoded as
Size
.
encodedSignKeyVRFSizeExpr ∷ ∀ v. VRFAlgorithm v ⇒ Proxy (SignKeyVRF v) → Size Source #
Size
expression for SignKeyVRF
which is using sizeSignKeyVRF
encoded
as Size
encodedCertVRFSizeExpr ∷ ∀ v. VRFAlgorithm v ⇒ Proxy (CertVRF v) → Size Source #
Size
expression for CertVRF
which is using sizeCertVRF
encoded as
Size
.
Nested CBOR-in-CBOR
encodeNestedCbor ∷ EncCBOR a ⇒ a → Encoding Source #
Encode and serialise the given a
and sorround it with the semantic tag 24
In CBOR diagnostic notation:
>>> 24(hDEADBEEF
)
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.
Tools
runByteBuilder ∷ Int → Builder → ByteString 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.