cardano-ledger-binary-1.3.2.0: Binary serialization library used throughout ledger
Safe HaskellSafe-Inferred
LanguageHaskell2010

Cardano.Ledger.Binary.Decoding.Annotated

Synopsis

Documentation

data Annotated b a Source #

Constructors

Annotated 

Fields

Instances

Instances details
Bifunctor Annotated Source # 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Methods

bimap ∷ (a → b) → (c → d) → Annotated a c → Annotated b d Source #

first ∷ (a → b) → Annotated a c → Annotated b c Source #

second ∷ (b → c) → Annotated a b → Annotated a c Source #

Functor (Annotated b) Source # 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Methods

fmap ∷ (a → b0) → Annotated b a → Annotated b b0 Source #

(<$) ∷ a → Annotated b b0 → Annotated b a Source #

FromJSON b ⇒ FromJSON (Annotated b ()) Source # 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

ToJSON b ⇒ ToJSON (Annotated b a) Source # 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Generic (Annotated b a) Source # 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Associated Types

type Rep (Annotated b a) ∷ TypeType Source #

Methods

fromAnnotated b a → Rep (Annotated b a) x Source #

toRep (Annotated b a) x → Annotated b a Source #

(Show b, Show a) ⇒ Show (Annotated b a) Source # 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Methods

showsPrecIntAnnotated b a → ShowS Source #

showAnnotated b a → String Source #

showList ∷ [Annotated b a] → ShowS Source #

Decoded (Annotated b ByteString) Source # 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Associated Types

type BaseType (Annotated b ByteString) Source #

(NFData b, NFData a) ⇒ NFData (Annotated b a) Source # 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Methods

rnfAnnotated b a → () Source #

(Eq b, Eq a) ⇒ Eq (Annotated b a) Source # 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Methods

(==)Annotated b a → Annotated b a → Bool Source #

(/=)Annotated b a → Annotated b a → Bool Source #

(Eq a, Ord b) ⇒ Ord (Annotated b a) Source # 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Methods

compareAnnotated b a → Annotated b a → Ordering Source #

(<)Annotated b a → Annotated b a → Bool Source #

(<=)Annotated b a → Annotated b a → Bool Source #

(>)Annotated b a → Annotated b a → Bool Source #

(>=)Annotated b a → Annotated b a → Bool Source #

maxAnnotated b a → Annotated b a → Annotated b a Source #

minAnnotated b a → Annotated b a → Annotated b a Source #

(NoThunks b, NoThunks a) ⇒ NoThunks (Annotated b a) Source # 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

type Rep (Annotated b a) Source # 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

type Rep (Annotated b a) = D1 ('MetaData "Annotated" "Cardano.Ledger.Binary.Decoding.Annotated" "cardano-ledger-binary-1.3.2.0-inplace" 'False) (C1 ('MetaCons "Annotated" 'PrefixI 'True) (S1 ('MetaSel ('Just "unAnnotated") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "annotation") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))
type BaseType (Annotated b ByteString) Source # 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

data ByteSpan Source #

A pair of offsets delimiting the beginning and end of a substring of a ByteString

Instances

Instances details
ToJSON ByteSpan Source # 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Generic ByteSpan Source # 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Associated Types

type Rep ByteSpanTypeType Source #

Show ByteSpan Source # 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

type Rep ByteSpan Source # 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

type Rep ByteSpan = D1 ('MetaData "ByteSpan" "Cardano.Ledger.Binary.Decoding.Annotated" "cardano-ledger-binary-1.3.2.0-inplace" 'False) (C1 ('MetaCons "ByteSpan" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteOffset) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteOffset)))

class Decoded t where Source #

Associated Types

type BaseType t ∷ Type Source #

Methods

recoverBytes ∷ t → ByteString Source #

Instances

Instances details
Decoded (Annotated b ByteString) Source # 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Associated Types

type BaseType (Annotated b ByteString) Source #

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

sliceByteStringByteSpanByteString Source #

Extract a substring of a given ByteString corresponding to the offsets.

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

reAnnotateEncCBOR a ⇒ VersionAnnotated a b → Annotated a ByteString Source #

Reconstruct an annotation by re-serialising the payload to a ByteString.

newtype Annotator a Source #

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

Constructors

Annotator 

Fields

Instances

Instances details
Applicative Annotator Source # 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Methods

pure ∷ a → Annotator a Source #

(<*>)Annotator (a → b) → Annotator a → Annotator b Source #

liftA2 ∷ (a → b → c) → Annotator a → Annotator b → Annotator c Source #

(*>)Annotator a → Annotator b → Annotator b Source #

(<*)Annotator a → Annotator b → Annotator a Source #

Functor Annotator Source # 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Methods

fmap ∷ (a → b) → Annotator a → Annotator b Source #

(<$) ∷ a → Annotator b → Annotator a Source #

Monad Annotator Source # 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Methods

(>>=)Annotator a → (a → Annotator b) → Annotator b Source #

(>>)Annotator a → Annotator b → Annotator b Source #

return ∷ a → Annotator a Source #

DecCBOR (Annotator Data) Source # 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

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

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

Constructors

Full ByteString