Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data NodeId
- longestChainSelection :: (HasHeader block, MonadSTM m) => [StrictTVar m (Maybe (Chain block))] -> StrictTVar m (ChainProducerState block) -> m ()
- chainValidation :: (HasFullHeader block, MonadSTM m) => StrictTVar m (Chain block) -> StrictTVar m (Maybe (Chain block)) -> m ()
- data NodeChannels (m :: Type -> Type) (block :: k) (tip :: k2) = NodeChannels {
- consumerChans :: [Channel m (AnyMessage (ChainSync block (Point block) tip))]
- producerChans :: [Channel m (AnyMessage (ChainSync block (Point block) tip))]
- createOneWaySubscriptionChannels :: forall {k} {k2} (block :: k) (tip :: k2) m. (MonadSTM m, MonadDelay m) => DiffTime -> DiffTime -> m (NodeChannels m block tip, NodeChannels m block tip)
- createTwoWaySubscriptionChannels :: forall {k} {k2} (block :: k) (tip :: k2) m. (MonadDelay m, MonadLabelledSTM m, MonadTimer m) => DiffTime -> DiffTime -> m (NodeChannels m block tip, NodeChannels m block tip)
- blockGenerator :: (HasHeader block, MonadDelay m, MonadSTM m, MonadFork m) => DiffTime -> [block] -> m (STM m (Maybe block))
- observeChainProducerState :: forall m block. (HasHeader block, MonadSTM m) => NodeId -> StrictTVar m [(NodeId, Chain block)] -> StrictTVar m (ChainProducerState block) -> m ()
- data ConsumerId = ConsumerId NodeId Int
- data ProducerId = ProducerId NodeId Int
- forkRelayKernel :: (HasFullHeader block, MonadSTM m, MonadFork m) => [StrictTVar m (Chain block)] -> StrictTVar m (ChainProducerState block) -> m ()
- relayNode :: (MonadFork m, MonadTimer m, MonadThrow m, MonadSay m, HasFullHeader block, Show block, ShowProxy block) => NodeId -> Chain block -> NodeChannels m block (Tip block) -> m (StrictTVar m (ChainProducerState block))
- forkCoreKernel :: (HasFullHeader block, MonadDelay m, MonadLabelledSTM m, MonadFork m, MonadTimer m) => DiffTime -> [block] -> (Chain block -> block -> block) -> StrictTVar m (ChainProducerState block) -> m ()
- coreNode :: (MonadDelay m, MonadLabelledSTM m, MonadFork m, MonadThrow m, MonadTimer m, MonadSay m) => NodeId -> DiffTime -> [Block] -> NodeChannels m Block (Tip Block) -> m (StrictTVar m (ChainProducerState Block))
Documentation
Instances
longestChainSelection :: (HasHeader block, MonadSTM m) => [StrictTVar m (Maybe (Chain block))] -> StrictTVar m (ChainProducerState block) -> m () Source #
State-full chain selection (
).ChainProducerState
chainValidation :: (HasFullHeader block, MonadSTM m) => StrictTVar m (Chain block) -> StrictTVar m (Maybe (Chain block)) -> m () Source #
data NodeChannels (m :: Type -> Type) (block :: k) (tip :: k2) Source #
Simulated network channels for a given network node.
NodeChannels | |
|
Instances
Monoid (NodeChannels m block tip) Source # | |
Defined in Ouroboros.Network.MockNode mempty :: NodeChannels m block tip # mappend :: NodeChannels m block tip -> NodeChannels m block tip -> NodeChannels m block tip # mconcat :: [NodeChannels m block tip] -> NodeChannels m block tip # | |
Semigroup (NodeChannels m block tip) Source # | |
Defined in Ouroboros.Network.MockNode (<>) :: NodeChannels m block tip -> NodeChannels m block tip -> NodeChannels m block tip # sconcat :: NonEmpty (NodeChannels m block tip) -> NodeChannels m block tip # stimes :: Integral b => b -> NodeChannels m block tip -> NodeChannels m block tip # |
createOneWaySubscriptionChannels :: forall {k} {k2} (block :: k) (tip :: k2) m. (MonadSTM m, MonadDelay m) => DiffTime -> DiffTime -> m (NodeChannels m block tip, NodeChannels m block tip) Source #
Create channels n1 → n2, where n1 is a producer and n2 is the consumer.
createTwoWaySubscriptionChannels :: forall {k} {k2} (block :: k) (tip :: k2) m. (MonadDelay m, MonadLabelledSTM m, MonadTimer m) => DiffTime -> DiffTime -> m (NodeChannels m block tip, NodeChannels m block tip) Source #
Create channels for n1 ↔ n2 where both nodes are a consumer and a producer simultaneously.
:: (HasHeader block, MonadDelay m, MonadSTM m, MonadFork m) | |
=> DiffTime | slot duration |
-> [block] | The list of blocks to generate in increasing slot order. This allows for upstream users to generate "half chains" in case we want to simulate nodes having access to already part of the overall chain. |
-> m (STM m (Maybe block)) | returns an stm transaction which returns block. |
Generate a block from a given chain. Each block
is produced at
slotDuration * blockSlot block
time.
observeChainProducerState :: forall m block. (HasHeader block, MonadSTM m) => NodeId -> StrictTVar m [(NodeId, Chain block)] -> StrictTVar m (ChainProducerState block) -> m () Source #
Observe StrictTVar (
, and whenever the
ChainProducerState
block)StrictTVar
mutates, write the result to the supplied
.Probe
data ConsumerId Source #
Instances
Show ConsumerId Source # | |
Defined in Ouroboros.Network.MockNode showsPrec :: Int -> ConsumerId -> ShowS # show :: ConsumerId -> String # showList :: [ConsumerId] -> ShowS # | |
Eq ConsumerId Source # | |
Defined in Ouroboros.Network.MockNode (==) :: ConsumerId -> ConsumerId -> Bool # (/=) :: ConsumerId -> ConsumerId -> Bool # | |
Ord ConsumerId Source # | |
Defined in Ouroboros.Network.MockNode compare :: ConsumerId -> ConsumerId -> Ordering # (<) :: ConsumerId -> ConsumerId -> Bool # (<=) :: ConsumerId -> ConsumerId -> Bool # (>) :: ConsumerId -> ConsumerId -> Bool # (>=) :: ConsumerId -> ConsumerId -> Bool # max :: ConsumerId -> ConsumerId -> ConsumerId # min :: ConsumerId -> ConsumerId -> ConsumerId # |
data ProducerId Source #
Instances
Show ProducerId Source # | |
Defined in Ouroboros.Network.MockNode showsPrec :: Int -> ProducerId -> ShowS # show :: ProducerId -> String # showList :: [ProducerId] -> ShowS # | |
Eq ProducerId Source # | |
Defined in Ouroboros.Network.MockNode (==) :: ProducerId -> ProducerId -> Bool # (/=) :: ProducerId -> ProducerId -> Bool # | |
Ord ProducerId Source # | |
Defined in Ouroboros.Network.MockNode compare :: ProducerId -> ProducerId -> Ordering # (<) :: ProducerId -> ProducerId -> Bool # (<=) :: ProducerId -> ProducerId -> Bool # (>) :: ProducerId -> ProducerId -> Bool # (>=) :: ProducerId -> ProducerId -> Bool # max :: ProducerId -> ProducerId -> ProducerId # min :: ProducerId -> ProducerId -> ProducerId # |
:: (HasFullHeader block, MonadSTM m, MonadFork m) | |
=> [StrictTVar m (Chain block)] | These will track the upstream producers. |
-> StrictTVar m (ChainProducerState block) | This is tracking the current node and the downstream. |
-> m () |
Relay node, which takes
to communicate with its peers
(upstream and downstream). If it is subscribed to n nodes and has
m subscriptions, it will run n consumer end protocols which listen for
updates; verify chains and select the longest one and feed it to the producer
side which sends updates to its m subscribers.NodeChannels
The main thread of the
is not blocking; it will return
relayNode
StrictTVar (
. This allows to extend the relay
node to a core node.ChainProducerState
block)
relayNode :: (MonadFork m, MonadTimer m, MonadThrow m, MonadSay m, HasFullHeader block, Show block, ShowProxy block) => NodeId -> Chain block -> NodeChannels m block (Tip block) -> m (StrictTVar m (ChainProducerState block)) Source #
Relay node, which takes
to communicate with its peers
(upstream and downstream). If it is subscribed to n nodes and has
m subscriptions, it will run n consumer end protocols which listen for
updates; verify chains and select the longest one and feed it to the producer
side which sends updates to its m subscribers.NodeChannels
The main thread of the
is not blocking; it will return
relayNode
StrictTVar (
. This allows to extend the relay
node to a core node.ChainProducerState
block)
:: (HasFullHeader block, MonadDelay m, MonadLabelledSTM m, MonadFork m, MonadTimer m) | |
=> DiffTime | slot duration |
-> [block] | Blocks to produce (in order they should be produced) |
-> (Chain block -> block -> block) | |
-> StrictTVar m (ChainProducerState block) | |
-> m () |
Core node simulation. Given a chain it will generate a block
at its
slot time (i.e. slotDuration * blockSlot block
). When the node finds out
that the slot for which it was supposed to generate a block was already
occupied, it will replace it with its block.
TODO: This should not take a list of blocks, but rather a monadic action
to generate the blocks. At that point the fixup
argument can go also.
Alternatively, we should move this to the tests, and remove it from the
public network layer altogether.
:: (MonadDelay m, MonadLabelledSTM m, MonadFork m, MonadThrow m, MonadTimer m, MonadSay m) | |
=> NodeId | |
-> DiffTime | slot duration |
-> [Block] | |
-> NodeChannels m Block (Tip Block) | |
-> m (StrictTVar m (ChainProducerState Block)) |
Core node simulation. Given a chain it will generate a block
at its
slot time (i.e. slotDuration * blockSlot block
). When the node finds out
that the slot for which it was supposed to generate a block was already
occupied, it will replace it with its block.