Skip to content

Instantly share code, notes, and snippets.

@avieth
Created June 6, 2018 15:02
Show Gist options
  • Save avieth/d4e43b3abca9b44f97b883bffa9d47b5 to your computer and use it in GitHub Desktop.
Save avieth/d4e43b3abca9b44f97b883bffa9d47b5 to your computer and use it in GitHub Desktop.
Inter-node comm
{-# LANGUAGE GADTSyntax #-}
-- # Inter-node messages
-- | A single 'Message' type for all inter-node communication.
data Message where
MessageControl :: Control -> Message
MessageDatum :: Datum -> Message
MessageAnnounce :: Announce -> Message
MessageRequest :: Request -> Message
-- | We want to be able to opt-in to certain topics so that, for instance, an
-- end-user edge node which has delegated all of its stake does not receive
-- transactions, SSC, or delegation data. They can't be slot leader, so they
-- don't need these things.
--
-- Another application we may want is to unsubscribe (or not subscribe to begin
-- with) from everything except blocks while downloading a significant portion
-- of the chain, for the other data can't be used without the full chain.
data Control where
ControlKeepalive :: Control
-- Encoding/decoding a set: length limit is implicit if we use canonical
-- CBOR: 5 valid Topic encodings, must come in ascending order, will not
-- be canonical if there are >= 6 from the 5.
ControlSubscribe :: Set Topic -> Control
ControlUnsubscribe :: Set Topic -> Control
data Topic where
TopicBlock :: Topic
TopicDelegation :: Topic
TopicSsc :: Topic
TopicTxp :: Topic
TopicUpdate :: Topic
-- | All blockchain data.
data Datum where
Block :: Block -> Datum
Txp :: TxAux -> Datum
UpdateProposal :: UpdateProposal -> Datum
UpdateVote :: UpdateVote -> Datum
SscCert :: VssCertificate -> Datum
SscOpening :: Opening -> Datum
SscShares :: InnerSharesMap -> Datum
SscCommitment :: SignedCommitment -> Datum
Delegation :: ProxySKHeavy -> Datum
-- | Announcements of data, for relaying.
-- These contain identifiers of 'Datum' values. When relaying, we won't send
-- the whole datum, because the peer may already have it.
data Announce where
-- We announce block headers, but they are requested by (Epoch, Slot) rather
-- than header hash as is done now. This makes it easy to request the
-- _next_ block in a chain, the header hash of which is unknown.
AnnounceBlockHeader :: BlockHeader -> Announce
AnnounceTxp :: TxId -> Announce
AnnounceUpdateProposal :: UpId -> Announce
AnnounceUpdateVote :: VoteId -> Announce
-- These keys identifier the stakeholder, but not the epoch for which it's
-- relevant.
-- The signed data in each of these variants of course pins them to an
-- epoch... I guess it's OK to let the epoch be determined implicitly by
-- the node's local time...
AnnounceSscCert :: StakeholderId -> Announce
AnnounceSscOpening :: StakeholderId -> Announce
AnnounceSscShares :: StakeholderId -> Announce
AnnounceSscCommitment :: StakeholderId -> Announce
-- No delegation announcement, because that's how it is now.
-- But maybe there ought to be one? How to identify it? Hash of the whole
-- thing?
-- | Requests for data, for relaying and for unsolicited requests.
-- This is just like 'Annuonce' except for 'RequestBlock', which uses a range
-- of slots rather than a 'BlockHeader', which may not be known.
data Request where
-- Request all blocks in some non-empty range of (Epoch, Slot).
-- Probably encode it as an epoch, slot, and non-negative integer.
RequestBlock :: SlotRange -> Request
RequestTxp :: TxId -> Request
RequestUpdateProposal :: UpId -> Request
RequestUpdateVote :: VoteId -> Request
RequestSscCert :: StakeholderId -> Request
RequestSscOpening :: StakeholderId -> Request
RequestSscShares :: StakeholderId -> Request
RequestSscCommitment :: StakeholderId -> Request
-- # Diffusion layer type
--
-- Instead of taking callbacks from a 'Logic' term, which fit well with the
-- architecture at the time, a 'Diffusion' can be a simple source and sink for
-- data, and the 'Logic' type can be removed.
--
-- The dispatcher thread in cardano-sl-networking which consumes the receive
-- queue of a network-transport 'EndPoint' can be ditched and in some sense
-- "moved up" to the application: it will consume the source of a 'Diffusion'
-- and deal with blockchain data.
-- TBD: interface for controlling subscription topics?
-- The application will probably need that; it's not clear whether the full
-- diffusion layer is capable of making such decisions.
data Diffusion m = Diffusion
{ -- | Data coming from the network.
source :: m SourceDatum
-- | Data going to the network.
, sink :: SinkDatum -> m ()
}
-- | No 'Announce', 'Request', or 'Control' will come out of a 'Diffusion'.
-- These things are details of our particular full diffusion layer, which
-- implements our official wire protocol.
type SourceDatum = Datum
-- | The user of a 'Diffusion' cannot put out 'Announce' or 'Control', but it
-- _can_ 'Request': it must be able to ask for more blocks.
data SinkDatum where
Broadcast :: Broadcast -> SinkDatum
Beacon :: Beacon -> SinkDatum
type Broadcast = Datum
-- | TBD: is there anything else that the application must be able to ask for?
data Beacon where
BeaconBlock :: SlotRange -> Beacon
-- # Recovery mode goes away
--
-- Currently blocks and block relaying are handled differently from the other
-- types. There's a block retrieval queue, members of which are block headers,
-- which is filled by the block announcement listener. I believe the raison
-- d'etre of this thing is to linearise block download. With the above
-- 'Diffusion' type that's already done.
--
-- Another feature of recovery mode is that it's driven by header announcements
-- from peers, rather than by the current epoch/slot (local time): only when a
-- header of greater difficulty than the current tip is received will a block
-- download commence. This feature of the system is also an easy attack vector:
-- just repeatedly send the victim a block header of higher difficulty than the
-- real blockchain and it will never do anything useful.
-- With block requests keyed on epoch/slot, we can get rid of this weakness: if
-- the current slot is sufficiently higher than the tip, put out a beacon
-- for the appropriate range.
--
-- When blocks come in from the 'Diffusion' source, they're not expected to be
-- part of a single chain: there could be forks. The current system does not
-- deal with forks at all: it will take the most difficult chain and forget
-- about all others. If asynchronous block download is to work, we'll need to
-- be able to track multiple forks, and judiciously decide when to forget a
-- fork. This leads to the question of block storage (and block cache).
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment