ouroboros-network-api
Safe HaskellNone
LanguageHaskell2010

Ouroboros.Network.Block

Description

Abstract view over blocks

The network layer does not make any concrete assumptions about what blocks look like.

Synopsis

Documentation

newtype SlotNo #

The 0-based index for the Ourboros time slot.

Constructors

SlotNo 

Fields

Instances

Instances details
FromJSON SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

ToJSON SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

FromCBOR SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

ToCBOR SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toCBOR :: SlotNo -> Encoding #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SlotNo -> Size #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SlotNo] -> Size #

NFData SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

rnf :: SlotNo -> () #

Bounded SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Enum SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Generic SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Associated Types

type Rep SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

type Rep SlotNo = D1 ('MetaData "SlotNo" "Cardano.Slotting.Slot" "cardano-slotting-0.2.0.0-9f9c1d3cf583b4a5a1b94ca6c7aa97d6161ffaa37cd2811c55245f3ba83bfbe2" 'True) (C1 ('MetaCons "SlotNo" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSlotNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

Methods

from :: SlotNo -> Rep SlotNo x #

to :: Rep SlotNo x -> SlotNo #

Num SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Show SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Eq SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

(==) :: SlotNo -> SlotNo -> Bool #

(/=) :: SlotNo -> SlotNo -> Bool #

Ord SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

NoThunks SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Serialise SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

ShowProxy SlotNo Source # 
Instance details

Defined in Ouroboros.Network.Util.ShowProxy

HasHeader block => Anchorable (WithOrigin SlotNo) (Anchor block) block Source # 
Instance details

Defined in Ouroboros.Network.AnchoredFragment

Methods

asAnchor :: block -> Anchor block Source #

getAnchorMeasure :: Proxy block -> Anchor block -> WithOrigin SlotNo Source #

type Rep SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

type Rep SlotNo = D1 ('MetaData "SlotNo" "Cardano.Slotting.Slot" "cardano-slotting-0.2.0.0-9f9c1d3cf583b4a5a1b94ca6c7aa97d6161ffaa37cd2811c55245f3ba83bfbe2" 'True) (C1 ('MetaCons "SlotNo" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSlotNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

newtype BlockNo #

The 0-based index of the block in the blockchain. BlockNo is <= SlotNo and is only equal at slot N if there is a block for every slot where N <= SlotNo.

Constructors

BlockNo 

Fields

Instances

Instances details
FromJSON BlockNo 
Instance details

Defined in Cardano.Slotting.Block

ToJSON BlockNo 
Instance details

Defined in Cardano.Slotting.Block

FromCBOR BlockNo 
Instance details

Defined in Cardano.Slotting.Block

ToCBOR BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Methods

toCBOR :: BlockNo -> Encoding #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy BlockNo -> Size #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [BlockNo] -> Size #

NFData BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Methods

rnf :: BlockNo -> () #

Bounded BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Enum BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Generic BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Associated Types

type Rep BlockNo 
Instance details

Defined in Cardano.Slotting.Block

type Rep BlockNo = D1 ('MetaData "BlockNo" "Cardano.Slotting.Block" "cardano-slotting-0.2.0.0-9f9c1d3cf583b4a5a1b94ca6c7aa97d6161ffaa37cd2811c55245f3ba83bfbe2" 'True) (C1 ('MetaCons "BlockNo" 'PrefixI 'True) (S1 ('MetaSel ('Just "unBlockNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

Methods

from :: BlockNo -> Rep BlockNo x #

to :: Rep BlockNo x -> BlockNo #

Num BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Show BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Eq BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Methods

(==) :: BlockNo -> BlockNo -> Bool #

(/=) :: BlockNo -> BlockNo -> Bool #

Ord BlockNo 
Instance details

Defined in Cardano.Slotting.Block

NoThunks BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Serialise BlockNo 
Instance details

Defined in Cardano.Slotting.Block

type Rep BlockNo 
Instance details

Defined in Cardano.Slotting.Block

type Rep BlockNo = D1 ('MetaData "BlockNo" "Cardano.Slotting.Block" "cardano-slotting-0.2.0.0-9f9c1d3cf583b4a5a1b94ca6c7aa97d6161ffaa37cd2811c55245f3ba83bfbe2" 'True) (C1 ('MetaCons "BlockNo" 'PrefixI 'True) (S1 ('MetaSel ('Just "unBlockNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

type family HeaderHash (b :: k) Source #

Header hash

Instances

Instances details
type HeaderHash (HeaderFields b :: Type) Source # 
Instance details

Defined in Ouroboros.Network.Block

type HeaderHash (Serialised block :: Type) Source # 
Instance details

Defined in Ouroboros.Network.Block

type HeaderHash (Serialised block :: Type) = HeaderHash block

data HeaderFields (b :: k) Source #

Header fields we expect to be present in a block

These fields are lazy because they are extracted from a block or block header; this type is not intended for storage.

Constructors

HeaderFields 

Fields

Instances

Instances details
StandardHash b => StandardHash (HeaderFields b :: Type) Source # 
Instance details

Defined in Ouroboros.Network.Block

Generic (HeaderFields b) Source # 
Instance details

Defined in Ouroboros.Network.Block

Associated Types

type Rep (HeaderFields b) 
Instance details

Defined in Ouroboros.Network.Block

type Rep (HeaderFields b) = D1 ('MetaData "HeaderFields" "Ouroboros.Network.Block" "ouroboros-network-api-0.11.0.0-inplace" 'False) (C1 ('MetaCons "HeaderFields" 'PrefixI 'True) (S1 ('MetaSel ('Just "headerFieldSlot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SlotNo) :*: (S1 ('MetaSel ('Just "headerFieldBlockNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockNo) :*: S1 ('MetaSel ('Just "headerFieldHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HeaderHash b)))))

Methods

from :: HeaderFields b -> Rep (HeaderFields b) x #

to :: Rep (HeaderFields b) x -> HeaderFields b #

StandardHash b => Show (HeaderFields b) Source # 
Instance details

Defined in Ouroboros.Network.Block

StandardHash b => Eq (HeaderFields b) Source # 
Instance details

Defined in Ouroboros.Network.Block

StandardHash b => Ord (HeaderFields b) Source # 
Instance details

Defined in Ouroboros.Network.Block

(StandardHash b, Typeable b, Typeable k) => HasHeader (HeaderFields b) Source # 
Instance details

Defined in Ouroboros.Network.Block

Serialise (HeaderHash b) => Serialise (HeaderFields b) Source # 
Instance details

Defined in Ouroboros.Network.Block

type HeaderHash (HeaderFields b :: Type) Source # 
Instance details

Defined in Ouroboros.Network.Block

type Rep (HeaderFields b) Source # 
Instance details

Defined in Ouroboros.Network.Block

type Rep (HeaderFields b) = D1 ('MetaData "HeaderFields" "Ouroboros.Network.Block" "ouroboros-network-api-0.11.0.0-inplace" 'False) (C1 ('MetaCons "HeaderFields" 'PrefixI 'True) (S1 ('MetaSel ('Just "headerFieldSlot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SlotNo) :*: (S1 ('MetaSel ('Just "headerFieldBlockNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockNo) :*: S1 ('MetaSel ('Just "headerFieldHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HeaderHash b)))))

castHeaderFields :: forall {k1} {k2} (b :: k1) (b' :: k2). HeaderHash b ~ HeaderHash b' => HeaderFields b -> HeaderFields b' Source #

class (StandardHash b, Typeable b) => HasHeader b where Source #

Abstract over the shape of blocks (or indeed just block headers)

Instances

Instances details
(StandardHash b, Typeable b, Typeable k) => HasHeader (HeaderFields b) Source # 
Instance details

Defined in Ouroboros.Network.Block

class HasHeader b => HasFullHeader b where Source #

Extension of HasHeader with some additional information

Used in tests and assertions only.

class (Eq (HeaderHash b), Ord (HeaderHash b), Show (HeaderHash b), Typeable (HeaderHash b), NoThunks (HeaderHash b)) => StandardHash (b :: k) Source #

StandardHash summarises the constraints we want header hashes to have

Without this class we would need to write

deriving instance Eq (HeaderHash block) => Eq (ChainHash block)

That requires UndecidableInstances; not a problem by itself, but it also means that we can then not use deriving Eq anywhere else for datatypes that reference Hash, which is very frustrating; see

https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/exts/deriving_inferred.html

Introducing the StandardHash class avoids this problem.

Having these constraints directly as part of the HasHeader class is possible but libraries that use the networking layer may wish to be able to talk about StandardHash independently of HasHeader since the latter may impose yet further constraints.

Instances

Instances details
StandardHash b => StandardHash (HeaderFields b :: Type) Source # 
Instance details

Defined in Ouroboros.Network.Block

StandardHash block => StandardHash (Serialised block :: Type) Source # 
Instance details

Defined in Ouroboros.Network.Block

data ChainHash (b :: k) Source #

Constructors

GenesisHash 
BlockHash !(HeaderHash b) 

Instances

Instances details
Generic (ChainHash b) Source # 
Instance details

Defined in Ouroboros.Network.Block

Associated Types

type Rep (ChainHash b) 
Instance details

Defined in Ouroboros.Network.Block

type Rep (ChainHash b) = D1 ('MetaData "ChainHash" "Ouroboros.Network.Block" "ouroboros-network-api-0.11.0.0-inplace" 'False) (C1 ('MetaCons "GenesisHash" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlockHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HeaderHash b))))

Methods

from :: ChainHash b -> Rep (ChainHash b) x #

to :: Rep (ChainHash b) x -> ChainHash b #

StandardHash block => Show (ChainHash block) Source # 
Instance details

Defined in Ouroboros.Network.Block

Methods

showsPrec :: Int -> ChainHash block -> ShowS #

show :: ChainHash block -> String #

showList :: [ChainHash block] -> ShowS #

StandardHash block => Eq (ChainHash block) Source # 
Instance details

Defined in Ouroboros.Network.Block

Methods

(==) :: ChainHash block -> ChainHash block -> Bool #

(/=) :: ChainHash block -> ChainHash block -> Bool #

StandardHash block => Ord (ChainHash block) Source # 
Instance details

Defined in Ouroboros.Network.Block

Methods

compare :: ChainHash block -> ChainHash block -> Ordering #

(<) :: ChainHash block -> ChainHash block -> Bool #

(<=) :: ChainHash block -> ChainHash block -> Bool #

(>) :: ChainHash block -> ChainHash block -> Bool #

(>=) :: ChainHash block -> ChainHash block -> Bool #

max :: ChainHash block -> ChainHash block -> ChainHash block #

min :: ChainHash block -> ChainHash block -> ChainHash block #

(StandardHash block, Typeable block) => NoThunks (ChainHash block) Source # 
Instance details

Defined in Ouroboros.Network.Block

Serialise (HeaderHash b) => Serialise (ChainHash b) Source # 
Instance details

Defined in Ouroboros.Network.Block

type Rep (ChainHash b) Source # 
Instance details

Defined in Ouroboros.Network.Block

type Rep (ChainHash b) = D1 ('MetaData "ChainHash" "Ouroboros.Network.Block" "ouroboros-network-api-0.11.0.0-inplace" 'False) (C1 ('MetaCons "GenesisHash" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlockHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HeaderHash b))))

castHash :: forall {k1} {k2} (b :: k1) (b' :: k2). Coercible (HeaderHash b) (HeaderHash b') => ChainHash b -> ChainHash b' Source #

newtype Point (block :: k) Source #

A point on the chain is identified by its Slot and HeaderHash.

The Slot tells us where to look and the HeaderHash either simply serves as a check, or in some contexts it disambiguates blocks from different forks that were in the same slot.

It's a newtype rather than a type synonym, because using a type synonym would lead to ambiguity, since HeaderHash is a non-injective type family.

Constructors

Point 

Instances

Instances details
ShowProxy block => ShowProxy (Point block :: Type) Source # 
Instance details

Defined in Ouroboros.Network.Block

Methods

showProxy :: Proxy (Point block) -> String Source #

Generic (Point block) Source # 
Instance details

Defined in Ouroboros.Network.Block

Associated Types

type Rep (Point block) 
Instance details

Defined in Ouroboros.Network.Block

type Rep (Point block) = D1 ('MetaData "Point" "Ouroboros.Network.Block" "ouroboros-network-api-0.11.0.0-inplace" 'True) (C1 ('MetaCons "Point" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPoint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (WithOrigin (Block SlotNo (HeaderHash block))))))

Methods

from :: Point block -> Rep (Point block) x #

to :: Rep (Point block) x -> Point block #

StandardHash block => Show (Point block) Source # 
Instance details

Defined in Ouroboros.Network.Block

Methods

showsPrec :: Int -> Point block -> ShowS #

show :: Point block -> String #

showList :: [Point block] -> ShowS #

StandardHash block => Eq (Point block) Source # 
Instance details

Defined in Ouroboros.Network.Block

Methods

(==) :: Point block -> Point block -> Bool #

(/=) :: Point block -> Point block -> Bool #

StandardHash block => Ord (Point block) Source # 
Instance details

Defined in Ouroboros.Network.Block

Methods

compare :: Point block -> Point block -> Ordering #

(<) :: Point block -> Point block -> Bool #

(<=) :: Point block -> Point block -> Bool #

(>) :: Point block -> Point block -> Bool #

(>=) :: Point block -> Point block -> Bool #

max :: Point block -> Point block -> Point block #

min :: Point block -> Point block -> Point block #

StandardHash block => NoThunks (Point block) Source # 
Instance details

Defined in Ouroboros.Network.Block

Methods

noThunks :: Context -> Point block -> IO (Maybe ThunkInfo) #

wNoThunks :: Context -> Point block -> IO (Maybe ThunkInfo) #

showTypeOf :: Proxy (Point block) -> String #

Serialise (HeaderHash block) => Serialise (Point block) Source # 
Instance details

Defined in Ouroboros.Network.Block

Methods

encode :: Point block -> Encoding #

decode :: Decoder s (Point block) #

encodeList :: [Point block] -> Encoding #

decodeList :: Decoder s [Point block] #

type Rep (Point block) Source # 
Instance details

Defined in Ouroboros.Network.Block

type Rep (Point block) = D1 ('MetaData "Point" "Ouroboros.Network.Block" "ouroboros-network-api-0.11.0.0-inplace" 'True) (C1 ('MetaCons "Point" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPoint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (WithOrigin (Block SlotNo (HeaderHash block))))))

pointSlot :: forall {k} (block :: k). Point block -> WithOrigin SlotNo Source #

pointHash :: forall {k} (block :: k). Point block -> ChainHash block Source #

castPoint :: forall {k1} {k2} (b :: k1) (b' :: k2). Coercible (HeaderHash b) (HeaderHash b') => Point b -> Point b' Source #

blockPoint :: HasHeader block => block -> Point block Source #

pattern GenesisPoint :: Point block Source #

pattern BlockPoint :: SlotNo -> HeaderHash block -> Point block Source #

atSlot :: forall {k} (block :: k). Point block -> SlotNo Source #

withHash :: forall {k} (block :: k). Point block -> HeaderHash block Source #

data Tip (b :: k) Source #

Used in chain-sync protocol to advertise the tip of the server's chain.

Constructors

TipGenesis

The tip is genesis

Tip !SlotNo !(HeaderHash b) !BlockNo

The tip is not genesis

Instances

Instances details
ShowProxy b => ShowProxy (Tip b :: Type) Source # 
Instance details

Defined in Ouroboros.Network.Block

Methods

showProxy :: Proxy (Tip b) -> String Source #

Generic (Tip b) Source # 
Instance details

Defined in Ouroboros.Network.Block

Associated Types

type Rep (Tip b) 
Instance details

Defined in Ouroboros.Network.Block

type Rep (Tip b) = D1 ('MetaData "Tip" "Ouroboros.Network.Block" "ouroboros-network-api-0.11.0.0-inplace" 'False) (C1 ('MetaCons "TipGenesis" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Tip" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotNo) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HeaderHash b)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlockNo))))

Methods

from :: Tip b -> Rep (Tip b) x #

to :: Rep (Tip b) x -> Tip b #

StandardHash b => Show (Tip b) Source # 
Instance details

Defined in Ouroboros.Network.Block

Methods

showsPrec :: Int -> Tip b -> ShowS #

show :: Tip b -> String #

showList :: [Tip b] -> ShowS #

StandardHash b => Eq (Tip b) Source # 
Instance details

Defined in Ouroboros.Network.Block

Methods

(==) :: Tip b -> Tip b -> Bool #

(/=) :: Tip b -> Tip b -> Bool #

StandardHash b => NoThunks (Tip b) Source # 
Instance details

Defined in Ouroboros.Network.Block

type Rep (Tip b) Source # 
Instance details

Defined in Ouroboros.Network.Block

type Rep (Tip b) = D1 ('MetaData "Tip" "Ouroboros.Network.Block" "ouroboros-network-api-0.11.0.0-inplace" 'False) (C1 ('MetaCons "TipGenesis" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Tip" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotNo) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HeaderHash b)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlockNo))))

castTip :: forall {k1} {k2} (a :: k1) (b :: k2). HeaderHash a ~ HeaderHash b => Tip a -> Tip b Source #

The equivalent of castPoint for Tip

getTipPoint :: forall {k} (b :: k). Tip b -> Point b Source #

getTipBlockNo :: forall {k} (b :: k). Tip b -> WithOrigin BlockNo Source #

getTipSlotNo :: forall {k} (b :: k). Tip b -> WithOrigin SlotNo Source #

encodeTip :: forall {k} (blk :: k). (HeaderHash blk -> Encoding) -> Tip blk -> Encoding Source #

decodeTip :: forall {k} (blk :: k). (forall s. Decoder s (HeaderHash blk)) -> forall s. Decoder s (Tip blk) Source #

data ChainUpdate (block :: k) a Source #

A representation of two actions to update a chain: add a block or roll back to a previous point.

The type parameter a is there to allow a Functor instance. Typically, it will be instantiated with block itself.

Constructors

AddBlock a 
RollBack (Point block) 

Instances

Instances details
Functor (ChainUpdate block) Source # 
Instance details

Defined in Ouroboros.Network.Block

Methods

fmap :: (a -> b) -> ChainUpdate block a -> ChainUpdate block b #

(<$) :: a -> ChainUpdate block b -> ChainUpdate block a #

Foldable (ChainUpdate block) Source # 
Instance details

Defined in Ouroboros.Network.Block

Methods

fold :: Monoid m => ChainUpdate block m -> m #

foldMap :: Monoid m => (a -> m) -> ChainUpdate block a -> m #

foldMap' :: Monoid m => (a -> m) -> ChainUpdate block a -> m #

foldr :: (a -> b -> b) -> b -> ChainUpdate block a -> b #

foldr' :: (a -> b -> b) -> b -> ChainUpdate block a -> b #

foldl :: (b -> a -> b) -> b -> ChainUpdate block a -> b #

foldl' :: (b -> a -> b) -> b -> ChainUpdate block a -> b #

foldr1 :: (a -> a -> a) -> ChainUpdate block a -> a #

foldl1 :: (a -> a -> a) -> ChainUpdate block a -> a #

toList :: ChainUpdate block a -> [a] #

null :: ChainUpdate block a -> Bool #

length :: ChainUpdate block a -> Int #

elem :: Eq a => a -> ChainUpdate block a -> Bool #

maximum :: Ord a => ChainUpdate block a -> a #

minimum :: Ord a => ChainUpdate block a -> a #

sum :: Num a => ChainUpdate block a -> a #

product :: Num a => ChainUpdate block a -> a #

Traversable (ChainUpdate block) Source # 
Instance details

Defined in Ouroboros.Network.Block

Methods

traverse :: Applicative f => (a -> f b) -> ChainUpdate block a -> f (ChainUpdate block b) #

sequenceA :: Applicative f => ChainUpdate block (f a) -> f (ChainUpdate block a) #

mapM :: Monad m => (a -> m b) -> ChainUpdate block a -> m (ChainUpdate block b) #

sequence :: Monad m => ChainUpdate block (m a) -> m (ChainUpdate block a) #

(StandardHash block, Show a) => Show (ChainUpdate block a) Source # 
Instance details

Defined in Ouroboros.Network.Block

Methods

showsPrec :: Int -> ChainUpdate block a -> ShowS #

show :: ChainUpdate block a -> String #

showList :: [ChainUpdate block a] -> ShowS #

(StandardHash block, Eq a) => Eq (ChainUpdate block a) Source # 
Instance details

Defined in Ouroboros.Network.Block

Methods

(==) :: ChainUpdate block a -> ChainUpdate block a -> Bool #

(/=) :: ChainUpdate block a -> ChainUpdate block a -> Bool #

data MaxSlotNo Source #

The highest slot number seen.

Constructors

NoMaxSlotNo

No block/header has been seen yet, so we don't have a highest slot number.

MaxSlotNo !SlotNo

The highest slot number seen.

Instances

Instances details
Monoid MaxSlotNo Source # 
Instance details

Defined in Ouroboros.Network.Block

Semigroup MaxSlotNo Source # 
Instance details

Defined in Ouroboros.Network.Block

Generic MaxSlotNo Source # 
Instance details

Defined in Ouroboros.Network.Block

Associated Types

type Rep MaxSlotNo 
Instance details

Defined in Ouroboros.Network.Block

type Rep MaxSlotNo = D1 ('MetaData "MaxSlotNo" "Ouroboros.Network.Block" "ouroboros-network-api-0.11.0.0-inplace" 'False) (C1 ('MetaCons "NoMaxSlotNo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MaxSlotNo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotNo)))
Show MaxSlotNo Source # 
Instance details

Defined in Ouroboros.Network.Block

Eq MaxSlotNo Source # 
Instance details

Defined in Ouroboros.Network.Block

Ord MaxSlotNo Source # 
Instance details

Defined in Ouroboros.Network.Block

NoThunks MaxSlotNo Source # 
Instance details

Defined in Ouroboros.Network.Block

type Rep MaxSlotNo Source # 
Instance details

Defined in Ouroboros.Network.Block

type Rep MaxSlotNo = D1 ('MetaData "MaxSlotNo" "Ouroboros.Network.Block" "ouroboros-network-api-0.11.0.0-inplace" 'False) (C1 ('MetaCons "NoMaxSlotNo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MaxSlotNo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotNo)))

genesisPoint :: forall {k} (block :: k). Point block Source #

Serialisation

encodePoint :: forall {k} (block :: k). (HeaderHash block -> Encoding) -> Point block -> Encoding Source #

encodeChainHash :: forall {k} (block :: k). (HeaderHash block -> Encoding) -> ChainHash block -> Encoding Source #

decodePoint :: forall {k} (block :: k). (forall s. Decoder s (HeaderHash block)) -> forall s. Decoder s (Point block) Source #

decodeChainHash :: forall {k} (block :: k). (forall s. Decoder s (HeaderHash block)) -> forall s. Decoder s (ChainHash block) Source #

Serialised block/header

newtype Serialised (a :: k) Source #

An already serialised value

When streaming blocks/header from disk to the network, there is often no need to deserialise them, as we'll just end up serialising them again when putting them on the wire.

Constructors

Serialised 

Instances

Instances details
StandardHash block => StandardHash (Serialised block :: Type) Source # 
Instance details

Defined in Ouroboros.Network.Block

ShowProxy a => ShowProxy (Serialised a :: Type) Source # 
Instance details

Defined in Ouroboros.Network.Block

Show (Serialised a) Source # 
Instance details

Defined in Ouroboros.Network.Block

Eq (Serialised a) Source # 
Instance details

Defined in Ouroboros.Network.Block

Methods

(==) :: Serialised a -> Serialised a -> Bool #

(/=) :: Serialised a -> Serialised a -> Bool #

Serialise (Serialised a) Source #

CBOR-in-CBOR

TODO: replace with encodeEmbeddedCBOR from cborg-0.2.4 once it is available, since that will be faster.

TODO: Avoid converting to a strict ByteString, as that requires copying O(n) in case the lazy ByteString consists of more than one chunks.

Instance details

Defined in Ouroboros.Network.Block

type HeaderHash (Serialised block :: Type) Source # 
Instance details

Defined in Ouroboros.Network.Block

type HeaderHash (Serialised block :: Type) = HeaderHash block

wrapCBORinCBOR :: (a -> Encoding) -> a -> Encoding Source #

Wrap CBOR-in-CBOR

This is primarily useful for the decoder; see unwrapCBORinCBOR

unwrapCBORinCBOR :: (forall s. Decoder s (ByteString -> a)) -> forall s. Decoder s a Source #

Unwrap CBOR-in-CBOR

The CBOR-in-CBOR encoding gives us the ByteString we need in order to to construct annotations.

mkSerialised :: (a -> Encoding) -> a -> Serialised a Source #

Construct Serialised value from an unserialised value

fromSerialised :: (forall s. Decoder s (ByteString -> a)) -> Serialised a -> forall s. Decoder s a Source #

Decode a Serialised value

Unlike a regular Decoder, which has an implicit input stream, fromSerialised takes the Serialised value as an argument.