Skip to content

Commit

Permalink
documentation: improved genesis haddocs
Browse files Browse the repository at this point in the history
There's no in-line way to make subtitles in haddock :/.
  • Loading branch information
coot committed Dec 10, 2024
1 parent 9937f82 commit c017fee
Show file tree
Hide file tree
Showing 2 changed files with 59 additions and 43 deletions.
101 changes: 58 additions & 43 deletions ouroboros-network/src/Ouroboros/Network/BlockFetch/Decision/Genesis.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,8 +5,56 @@
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module Ouroboros.Network.BlockFetch.Decision.Genesis
( -- * Genesis decision logic
-- $genesis-decision-logic

-- | Genesis decision logic
-- * About the influence of in-flight requests
-- $in-flight-requests

-- * Interactions with ChainSync Jumping (CSJ)
-- $chain-sync-jumping

-- * About the gross request
-- $gross-request

fetchDecisionsGenesisM
) where

import Control.Exception (assert)
import Control.Monad (guard)
import Control.Monad.Class.MonadTime.SI (MonadMonotonicTime (getMonotonicTime),
addTime)
import Control.Monad.Trans.Maybe (MaybeT (MaybeT, runMaybeT))
import Control.Monad.Trans.Writer.CPS (Writer, runWriter, tell)
import Control.Tracer (Tracer, traceWith)
import Data.Bifunctor (Bifunctor (..), first)
import Data.DList (DList)
import Data.DList qualified as DList
import Data.Foldable (find, toList)
import Data.List qualified as List
import Data.Maybe (maybeToList)
import Data.Sequence (Seq (..), (<|), (><), (|>))
import Data.Sequence qualified as Sequence
import Data.Set qualified as Set

import Cardano.Prelude (partitionEithers)

import Ouroboros.Network.AnchoredFragment (AnchoredFragment)
import Ouroboros.Network.AnchoredFragment qualified as AF
import Ouroboros.Network.Block
import Ouroboros.Network.BlockFetch.ClientState (FetchRequest (..),
PeerFetchInFlight (..), PeersOrder (..))
import Ouroboros.Network.BlockFetch.ConsensusInterface (ChainSelStarvation (..),
FetchMode (..))
import Ouroboros.Network.BlockFetch.DeltaQ (calculatePeerFetchInFlightLimits)

import Cardano.Slotting.Slot (WithOrigin)
import Ouroboros.Network.BlockFetch.Decision
import Ouroboros.Network.BlockFetch.Decision.Trace (TraceDecisionEvent (..))


-- $genesis-decision-logic
--
-- This module contains the part of the block fetch decisions process that is
-- specific to the bulk sync mode. This logic reuses parts of the logic for the
Expand Down Expand Up @@ -70,9 +118,9 @@
-- if @inflights(thePeer)@ is empty.
--
-- Terminate this iteration.
--
-- About the influence of in-flight requests
-- -----------------------------------------


-- $in-flight-requests
--
-- One can note that in-flight requests are ignored when finding a new peer, but
-- considered when crafting the actual request to a chosen peer. This is by
Expand All @@ -94,9 +142,9 @@
-- transient. Soon enough, @theCandidate@ should be honest (if the consensus
-- layer does its job correctly), and there should exist an honest peer ready to
-- serve @theCandidate@ promptly.
--
-- Interactions with ChainSync Jumping (CSJ)
-- -----------------------------------------


-- $chain-sync-jumping
--
-- Because we always require our peers to be able to serve a gross request
-- with an old block, peers with longer chains have a better chance to pass
Expand All @@ -109,9 +157,9 @@
-- blocks, it will get multiple opportunities to do so since it will be selected
-- as the current peer more often. We therefore rotate the dynamo every time it
-- is the current peer and it fails to serve blocks promptly.
--
-- About the gross request
-- -----------------------


-- $gross-request
--
-- We want to select a peer that is able to serve us a batch of oldest blocks
-- of @theCandidate@. However, not every peer will be able to deliver these
Expand All @@ -123,39 +171,6 @@
-- If the peer cannot offer any more blocks after that, it will be rotated out
-- soon.
--
module Ouroboros.Network.BlockFetch.Decision.Genesis (fetchDecisionsGenesisM) where

import Control.Exception (assert)
import Control.Monad (guard)
import Control.Monad.Class.MonadTime.SI (MonadMonotonicTime (getMonotonicTime),
addTime)
import Control.Monad.Trans.Maybe (MaybeT (MaybeT, runMaybeT))
import Control.Monad.Trans.Writer.CPS (Writer, runWriter, tell)
import Control.Tracer (Tracer, traceWith)
import Data.Bifunctor (Bifunctor (..), first)
import Data.DList (DList)
import Data.DList qualified as DList
import Data.Foldable (find, toList)
import Data.List qualified as List
import Data.Maybe (maybeToList)
import Data.Sequence (Seq (..), (<|), (><), (|>))
import Data.Sequence qualified as Sequence
import Data.Set qualified as Set

import Cardano.Prelude (partitionEithers)

import Ouroboros.Network.AnchoredFragment (AnchoredFragment)
import Ouroboros.Network.AnchoredFragment qualified as AF
import Ouroboros.Network.Block
import Ouroboros.Network.BlockFetch.ClientState (FetchRequest (..),
PeerFetchInFlight (..), PeersOrder (..))
import Ouroboros.Network.BlockFetch.ConsensusInterface (ChainSelStarvation (..),
FetchMode (..))
import Ouroboros.Network.BlockFetch.DeltaQ (calculatePeerFetchInFlightLimits)

import Cardano.Slotting.Slot (WithOrigin)
import Ouroboros.Network.BlockFetch.Decision
import Ouroboros.Network.BlockFetch.Decision.Trace (TraceDecisionEvent (..))

type WithDeclined peer = Writer (DList (FetchDecline, peer))

Expand Down
1 change: 1 addition & 0 deletions scripts/ci/check-stylish-ignore
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
*/Setup.hs
ouroboros-network-api/src/Ouroboros/Network/Protocol/Type.hs
ouroboros-network/src/Ouroboros/Network/BlockFetch/Decision/Genesis.hs
ouroboros-network/src/Ouroboros/Network/Diffusion/P2P.hs
ouroboros-network/src/Ouroboros/Network/PeerSelection/Governor/Types.hs
network-mux/src/Network/Mux/TCPInfo.hs
Expand Down

0 comments on commit c017fee

Please sign in to comment.