Safe Haskell | None |
---|---|
Language | Haskell2010 |
Abstract view over blocks
The network layer does not make any concrete assumptions about what blocks look like.
Synopsis
- newtype SlotNo = SlotNo {}
- newtype BlockNo = BlockNo {}
- type family HeaderHash (b :: k)
- data HeaderFields (b :: k) = HeaderFields {}
- castHeaderFields :: forall {k1} {k2} (b :: k1) (b' :: k2). HeaderHash b ~ HeaderHash b' => HeaderFields b -> HeaderFields b'
- class (StandardHash b, Typeable b) => HasHeader b where
- getHeaderFields :: b -> HeaderFields b
- blockNo :: HasHeader b => b -> BlockNo
- blockSlot :: HasHeader b => b -> SlotNo
- blockHash :: HasHeader b => b -> HeaderHash b
- class HasHeader b => HasFullHeader b where
- blockPrevHash :: b -> ChainHash b
- blockInvariant :: b -> Bool
- class (Eq (HeaderHash b), Ord (HeaderHash b), Show (HeaderHash b), Typeable (HeaderHash b), NoThunks (HeaderHash b)) => StandardHash (b :: k)
- data ChainHash (b :: k)
- = GenesisHash
- | BlockHash !(HeaderHash b)
- castHash :: forall {k1} {k2} (b :: k1) (b' :: k2). Coercible (HeaderHash b) (HeaderHash b') => ChainHash b -> ChainHash b'
- newtype Point (block :: k) = Point {
- getPoint :: WithOrigin (Block SlotNo (HeaderHash block))
- pointSlot :: forall {k} (block :: k). Point block -> WithOrigin SlotNo
- pointHash :: forall {k} (block :: k). Point block -> ChainHash block
- castPoint :: forall {k1} {k2} (b :: k1) (b' :: k2). Coercible (HeaderHash b) (HeaderHash b') => Point b -> Point b'
- blockPoint :: HasHeader block => block -> Point block
- pattern GenesisPoint :: Point block
- pattern BlockPoint :: SlotNo -> HeaderHash block -> Point block
- atSlot :: forall {k} (block :: k). Point block -> SlotNo
- withHash :: forall {k} (block :: k). Point block -> HeaderHash block
- data Tip (b :: k)
- = TipGenesis
- | Tip !SlotNo !(HeaderHash b) !BlockNo
- castTip :: forall {k1} {k2} (a :: k1) (b :: k2). HeaderHash a ~ HeaderHash b => Tip a -> Tip b
- getTipPoint :: forall {k} (b :: k). Tip b -> Point b
- getTipBlockNo :: forall {k} (b :: k). Tip b -> WithOrigin BlockNo
- getTipSlotNo :: forall {k} (b :: k). Tip b -> WithOrigin SlotNo
- tipFromHeader :: HasHeader a => a -> Tip a
- encodeTip :: forall {k} (blk :: k). (HeaderHash blk -> Encoding) -> Tip blk -> Encoding
- decodeTip :: forall {k} (blk :: k). (forall s. Decoder s (HeaderHash blk)) -> forall s. Decoder s (Tip blk)
- data ChainUpdate (block :: k) a
- data MaxSlotNo
- maxSlotNoFromMaybe :: Maybe SlotNo -> MaxSlotNo
- maxSlotNoToMaybe :: MaxSlotNo -> Maybe SlotNo
- maxSlotNoFromWithOrigin :: WithOrigin SlotNo -> MaxSlotNo
- genesisPoint :: forall {k} (block :: k). Point block
- encodePoint :: forall {k} (block :: k). (HeaderHash block -> Encoding) -> Point block -> Encoding
- encodeChainHash :: forall {k} (block :: k). (HeaderHash block -> Encoding) -> ChainHash block -> Encoding
- decodePoint :: forall {k} (block :: k). (forall s. Decoder s (HeaderHash block)) -> forall s. Decoder s (Point block)
- decodeChainHash :: forall {k} (block :: k). (forall s. Decoder s (HeaderHash block)) -> forall s. Decoder s (ChainHash block)
- newtype Serialised (a :: k) = Serialised {}
- wrapCBORinCBOR :: (a -> Encoding) -> a -> Encoding
- unwrapCBORinCBOR :: (forall s. Decoder s (ByteString -> a)) -> forall s. Decoder s a
- mkSerialised :: (a -> Encoding) -> a -> Serialised a
- fromSerialised :: (forall s. Decoder s (ByteString -> a)) -> Serialised a -> forall s. Decoder s a
Documentation
The 0-based index for the Ourboros time slot.
Instances
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.
Instances
FromJSON BlockNo | |||||
Defined in Cardano.Slotting.Block | |||||
ToJSON BlockNo | |||||
FromCBOR BlockNo | |||||
ToCBOR BlockNo | |||||
NFData BlockNo | |||||
Defined in Cardano.Slotting.Block | |||||
Bounded BlockNo | |||||
Enum BlockNo | |||||
Generic BlockNo | |||||
Defined in Cardano.Slotting.Block
| |||||
Num BlockNo | |||||
Show BlockNo | |||||
Eq BlockNo | |||||
Ord BlockNo | |||||
NoThunks BlockNo | |||||
Serialise BlockNo | |||||
type Rep BlockNo | |||||
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
type HeaderHash (HeaderFields b :: Type) Source # | |
Defined in Ouroboros.Network.Block | |
type HeaderHash (Serialised block :: Type) Source # | |
Defined in Ouroboros.Network.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.
Instances
StandardHash b => StandardHash (HeaderFields b :: Type) Source # | |||||
Defined in Ouroboros.Network.Block | |||||
Generic (HeaderFields b) Source # | |||||
Defined in Ouroboros.Network.Block
from :: HeaderFields b -> Rep (HeaderFields b) x # to :: Rep (HeaderFields b) x -> HeaderFields b # | |||||
StandardHash b => Show (HeaderFields b) Source # | |||||
Defined in Ouroboros.Network.Block showsPrec :: Int -> HeaderFields b -> ShowS # show :: HeaderFields b -> String # showList :: [HeaderFields b] -> ShowS # | |||||
StandardHash b => Eq (HeaderFields b) Source # | |||||
Defined in Ouroboros.Network.Block (==) :: HeaderFields b -> HeaderFields b -> Bool # (/=) :: HeaderFields b -> HeaderFields b -> Bool # | |||||
StandardHash b => Ord (HeaderFields b) Source # | |||||
Defined in Ouroboros.Network.Block compare :: HeaderFields b -> HeaderFields b -> Ordering # (<) :: HeaderFields b -> HeaderFields b -> Bool # (<=) :: HeaderFields b -> HeaderFields b -> Bool # (>) :: HeaderFields b -> HeaderFields b -> Bool # (>=) :: HeaderFields b -> HeaderFields b -> Bool # max :: HeaderFields b -> HeaderFields b -> HeaderFields b # min :: HeaderFields b -> HeaderFields b -> HeaderFields b # | |||||
(StandardHash b, Typeable b, Typeable k) => HasHeader (HeaderFields b) Source # | |||||
Defined in Ouroboros.Network.Block getHeaderFields :: HeaderFields b -> HeaderFields (HeaderFields b) Source # | |||||
Serialise (HeaderHash b) => Serialise (HeaderFields b) Source # | |||||
Defined in Ouroboros.Network.Block encode :: HeaderFields b -> Encoding # decode :: Decoder s (HeaderFields b) # encodeList :: [HeaderFields b] -> Encoding # decodeList :: Decoder s [HeaderFields b] # | |||||
type HeaderHash (HeaderFields b :: Type) Source # | |||||
Defined in Ouroboros.Network.Block | |||||
type Rep (HeaderFields b) Source # | |||||
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)
getHeaderFields :: b -> HeaderFields b Source #
Instances
(StandardHash b, Typeable b, Typeable k) => HasHeader (HeaderFields b) Source # | |
Defined in Ouroboros.Network.Block getHeaderFields :: HeaderFields b -> HeaderFields (HeaderFields b) Source # |
blockHash :: HasHeader b => b -> HeaderHash b Source #
class HasHeader b => HasFullHeader b where Source #
Extension of HasHeader
with some additional information
Used in tests and assertions only.
blockPrevHash :: b -> ChainHash b Source #
blockInvariant :: b -> Bool Source #
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
StandardHash b => StandardHash (HeaderFields b :: Type) Source # | |
Defined in Ouroboros.Network.Block | |
StandardHash block => StandardHash (Serialised block :: Type) Source # | |
Defined in Ouroboros.Network.Block |
data ChainHash (b :: k) Source #
Instances
Generic (ChainHash b) Source # | |||||
Defined in Ouroboros.Network.Block
| |||||
StandardHash block => Show (ChainHash block) Source # | |||||
StandardHash block => Eq (ChainHash block) Source # | |||||
StandardHash block => Ord (ChainHash block) Source # | |||||
Defined in Ouroboros.Network.Block 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 # | |||||
Serialise (HeaderHash b) => Serialise (ChainHash b) Source # | |||||
type Rep (ChainHash b) Source # | |||||
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.
Point | |
|
Instances
ShowProxy block => ShowProxy (Point block :: Type) Source # | |||||
Generic (Point block) Source # | |||||
Defined in Ouroboros.Network.Block
| |||||
StandardHash block => Show (Point block) Source # | |||||
StandardHash block => Eq (Point block) Source # | |||||
StandardHash block => Ord (Point block) Source # | |||||
Defined in Ouroboros.Network.Block | |||||
StandardHash block => NoThunks (Point block) Source # | |||||
Serialise (HeaderHash block) => Serialise (Point block) Source # | |||||
type Rep (Point block) Source # | |||||
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)))))) |
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 #
withHash :: forall {k} (block :: k). Point block -> HeaderHash block Source #
Used in chain-sync protocol to advertise the tip of the server's chain.
TipGenesis | The tip is genesis |
Tip !SlotNo !(HeaderHash b) !BlockNo | The tip is not genesis |
Instances
ShowProxy b => ShowProxy (Tip b :: Type) Source # | |||||
Generic (Tip b) Source # | |||||
Defined in Ouroboros.Network.Block
| |||||
StandardHash b => Show (Tip b) Source # | |||||
StandardHash b => Eq (Tip b) Source # | |||||
StandardHash b => NoThunks (Tip b) Source # | |||||
type Rep (Tip b) Source # | |||||
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 #
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 #
tipFromHeader :: HasHeader a => a -> Tip a 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.
Instances
Functor (ChainUpdate block) Source # | |
Defined in Ouroboros.Network.Block fmap :: (a -> b) -> ChainUpdate block a -> ChainUpdate block b # (<$) :: a -> ChainUpdate block b -> ChainUpdate block a # | |
Foldable (ChainUpdate block) Source # | |
Defined in Ouroboros.Network.Block 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 # | |
Defined in Ouroboros.Network.Block 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 # | |
Defined in Ouroboros.Network.Block 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 # | |
Defined in Ouroboros.Network.Block (==) :: ChainUpdate block a -> ChainUpdate block a -> Bool # (/=) :: ChainUpdate block a -> ChainUpdate block a -> Bool # |
The highest slot number seen.
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
Monoid MaxSlotNo Source # | |||||
Semigroup MaxSlotNo Source # | |||||
Generic MaxSlotNo Source # | |||||
Defined in Ouroboros.Network.Block
| |||||
Show MaxSlotNo Source # | |||||
Eq MaxSlotNo Source # | |||||
Ord MaxSlotNo Source # | |||||
Defined in Ouroboros.Network.Block | |||||
NoThunks MaxSlotNo Source # | |||||
type Rep MaxSlotNo Source # | |||||
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.
Instances
StandardHash block => StandardHash (Serialised block :: Type) Source # | |
Defined in Ouroboros.Network.Block | |
ShowProxy a => ShowProxy (Serialised a :: Type) Source # | |
Defined in Ouroboros.Network.Block | |
Show (Serialised a) Source # | |
Defined in Ouroboros.Network.Block showsPrec :: Int -> Serialised a -> ShowS # show :: Serialised a -> String # showList :: [Serialised a] -> ShowS # | |
Eq (Serialised a) Source # | |
Defined in Ouroboros.Network.Block (==) :: 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. |
Defined in Ouroboros.Network.Block encode :: Serialised a -> Encoding # decode :: Decoder s (Serialised a) # encodeList :: [Serialised a] -> Encoding # decodeList :: Decoder s [Serialised a] # | |
type HeaderHash (Serialised block :: Type) Source # | |
Defined in Ouroboros.Network.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.