Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype PeerGraph = PeerGraph [(PeerAddr, [PeerAddr], PeerInfo)]
- data GovernorMockEnvironment = GovernorMockEnvironment {
- peerGraph :: !PeerGraph
- localRootPeers :: !(LocalRootPeers PeerAddr)
- publicRootPeers :: !(PublicRootPeers PeerAddr)
- targets :: !(TimedScript ConsensusModePeerTargets)
- pickKnownPeersForPeerShare :: !(PickScript PeerAddr)
- pickColdPeersToPromote :: !(PickScript PeerAddr)
- pickWarmPeersToPromote :: !(PickScript PeerAddr)
- pickHotPeersToDemote :: !(PickScript PeerAddr)
- pickWarmPeersToDemote :: !(PickScript PeerAddr)
- pickColdPeersToForget :: !(PickScript PeerAddr)
- pickInboundPeers :: !(PickScript PeerAddr)
- peerSharingFlag :: !PeerSharing
- useBootstrapPeers :: !(TimedScript UseBootstrapPeers)
- consensusMode :: !ConsensusMode
- useLedgerPeers :: !(TimedScript UseLedgerPeers)
- ledgerStateJudgement :: !(TimedScript LedgerStateJudgement)
- newtype GovernorPraosMockEnvironment = GovernorPraosMockEnvironment {}
- newtype GovernorMockEnvironmentWithoutAsyncDemotion = GovernorMockEnvironmentWAD GovernorMockEnvironment
- runGovernorInMockEnvironment :: GovernorMockEnvironment -> SimTrace Void
- exploreGovernorInMockEnvironment :: Testable test => (ExplorationOptions -> ExplorationOptions) -> GovernorMockEnvironment -> (Maybe (SimTrace Void) -> SimTrace Void -> test) -> Property
- data TraceMockEnv
- = TraceEnvAddPeers !PeerGraph
- | TraceEnvSetLocalRoots !(LocalRootPeers PeerAddr)
- | TraceEnvRequestPublicRootPeers
- | TraceEnvRequestBigLedgerPeers
- | TraceEnvSetPublicRoots !(PublicRootPeers PeerAddr)
- | TraceEnvPublicRootTTL
- | TraceEnvBigLedgerPeersTTL
- | TraceEnvPeerShareTTL !PeerAddr
- | TraceEnvSetTargets !PeerSelectionTargets
- | TraceEnvPeersDemote !AsyncDemotion !PeerAddr
- | TraceEnvEstablishConn !PeerAddr
- | TraceEnvActivatePeer !PeerAddr
- | TraceEnvDeactivatePeer !PeerAddr
- | TraceEnvCloseConn !PeerAddr
- | TraceEnvRootsResult ![PeerAddr]
- | TraceEnvBigLedgerPeersResult !(Set PeerAddr)
- | TraceEnvPeerShareRequest !PeerAddr !(Maybe ([PeerAddr], PeerShareTime))
- | TraceEnvPeerShareResult !PeerAddr ![PeerAddr]
- | TraceEnvPeersStatus !(Map PeerAddr PeerStatus)
- | TraceEnvSetUseBootstrapPeers !UseBootstrapPeers
- | TraceEnvSetLedgerStateJudgement !LedgerStateJudgement
- | TraceEnvUseLedgerPeers !UseLedgerPeers
- | TraceEnvGenesisLsjAndTargets !(LedgerStateJudgement, PeerSelectionTargets)
- data TestTraceEvent
- selectGovernorEvents :: [(Time, TestTraceEvent)] -> [(Time, TracePeerSelection PeerAddr)]
- selectGovernorStateEvents :: [(Time, TestTraceEvent)] -> [(Time, DebugPeerSelection PeerAddr)]
- selectPeerSelectionTraceEvents :: SimTrace a -> [(Time, TestTraceEvent)]
- selectPeerSelectionTraceEventsUntil :: Time -> SimTrace a -> [(Time, TestTraceEvent)]
- peerShareReachablePeers :: PeerGraph -> Set PeerAddr -> Set PeerAddr
- data ScriptDelay
- newtype Script a = Script (NonEmpty a)
- arbitraryPickScript :: Gen (Set peeraddr) -> Gen (PickScript peeraddr)
- arbitraryScriptOf :: Int -> Gen a -> Gen (Script a)
- initScript :: MonadSTM m => Script a -> m (TVar m (Script a))
- initScript' :: MonadSTM m => Script a -> m (StrictTVar m (Script a))
- interpretPickScript :: forall (m :: Type -> Type) peeraddr. (MonadSTM m, Ord peeraddr) => StrictTVar m (PickScript peeraddr) -> Set peeraddr -> Int -> STM m (Set peeraddr)
- playTimedScript :: (MonadAsync m, MonadDelay m) => Tracer m a -> TimedScript a -> m (TVar m a)
- prop_shrink_Script :: ShrinkCarefully (Script Int) -> Property
- shrinkScriptWith :: (a -> [a]) -> Script a -> [Script a]
- singletonScript :: a -> Script a
- singletonTimedScript :: a -> TimedScript a
- stepScript :: MonadSTM m => TVar m (Script a) -> m a
- stepScriptSTM :: forall (m :: Type -> Type) a. MonadSTM m => TVar m (Script a) -> STM m a
- stepScriptSTM' :: forall (m :: Type -> Type) a. MonadSTM m => StrictTVar m (Script a) -> STM m a
- type PickScript peeraddr = Script (PickMembers peeraddr)
- type TimedScript a = Script (a, ScriptDelay)
- data PeerStatus
- tests :: TestTree
- prop_shrink_nonequal_GovernorMockEnvironment :: ShrinkCarefully GovernorMockEnvironment -> Property
- config_REPROMOTE_DELAY :: RepromoteDelay
Documentation
The peer graph is the graph of all the peers in the mock p2p network, in traditional adjacency representation.
data GovernorMockEnvironment Source #
The data needed to execute the peer selection governor in a test with a
mock network environment. It contains the data needed to provide the
PeerSelectionActions
and PeerSelectionPolicy
to run the governor.
The representations are chosen to be easily shrinkable. See the Arbitrary
instances.
Instances
newtype GovernorPraosMockEnvironment Source #
This instance is used to generate test cases for properties which rely on peer selection prior to introduction of Genesis
Instances
newtype GovernorMockEnvironmentWithoutAsyncDemotion Source #
GovernorMockEnvironment
which does not do any asynchronous demotions.
runGovernorInMockEnvironment :: GovernorMockEnvironment -> SimTrace Void Source #
Run the peerSelectionGovernor
in the mock environment dictated by the
data in the GovernorMockEnvironment
.
The result is an execution trace.
exploreGovernorInMockEnvironment :: Testable test => (ExplorationOptions -> ExplorationOptions) -> GovernorMockEnvironment -> (Maybe (SimTrace Void) -> SimTrace Void -> test) -> Property Source #
data TraceMockEnv Source #
Instances
Show TraceMockEnv Source # | |
Defined in Test.Ouroboros.Network.PeerSelection.MockEnvironment showsPrec :: Int -> TraceMockEnv -> ShowS # show :: TraceMockEnv -> String # showList :: [TraceMockEnv] -> ShowS # |
data TestTraceEvent Source #
GovernorDebug !(DebugPeerSelection PeerAddr) | |
GovernorEvent !(TracePeerSelection PeerAddr) | |
GovernorCounters !PeerSelectionCounters | |
GovernorAssociationMode !AssociationMode | |
MockEnvEvent !TraceMockEnv |
Instances
Show TestTraceEvent Source # | |
Defined in Test.Ouroboros.Network.PeerSelection.MockEnvironment showsPrec :: Int -> TestTraceEvent -> ShowS # show :: TestTraceEvent -> String # showList :: [TestTraceEvent] -> ShowS # |
selectGovernorEvents :: [(Time, TestTraceEvent)] -> [(Time, TracePeerSelection PeerAddr)] Source #
selectGovernorStateEvents :: [(Time, TestTraceEvent)] -> [(Time, DebugPeerSelection PeerAddr)] Source #
selectPeerSelectionTraceEvents :: SimTrace a -> [(Time, TestTraceEvent)] Source #
selectPeerSelectionTraceEventsUntil :: Time -> SimTrace a -> [(Time, TestTraceEvent)] Source #
data ScriptDelay #
Instances
Arbitrary ScriptDelay | |
Defined in Ouroboros.Network.Testing.Data.Script arbitrary :: Gen ScriptDelay # shrink :: ScriptDelay -> [ScriptDelay] # | |
Show ScriptDelay | |
Defined in Ouroboros.Network.Testing.Data.Script showsPrec :: Int -> ScriptDelay -> ShowS # show :: ScriptDelay -> String # showList :: [ScriptDelay] -> ShowS # | |
Eq ScriptDelay | |
Defined in Ouroboros.Network.Testing.Data.Script (==) :: ScriptDelay -> ScriptDelay -> Bool # (/=) :: ScriptDelay -> ScriptDelay -> Bool # |
Instances
Functor Script | |
Foldable Script | |
Defined in Ouroboros.Network.Testing.Data.Script fold :: Monoid m => Script m -> m # foldMap :: Monoid m => (a -> m) -> Script a -> m # foldMap' :: Monoid m => (a -> m) -> Script a -> m # foldr :: (a -> b -> b) -> b -> Script a -> b # foldr' :: (a -> b -> b) -> b -> Script a -> b # foldl :: (b -> a -> b) -> b -> Script a -> b # foldl' :: (b -> a -> b) -> b -> Script a -> b # foldr1 :: (a -> a -> a) -> Script a -> a # foldl1 :: (a -> a -> a) -> Script a -> a # elem :: Eq a => a -> Script a -> Bool # maximum :: Ord a => Script a -> a # minimum :: Ord a => Script a -> a # | |
Traversable Script | |
Arbitrary a => Arbitrary (Script a) | |
Show a => Show (Script a) | |
Eq a => Eq (Script a) | |
arbitraryPickScript :: Gen (Set peeraddr) -> Gen (PickScript peeraddr) #
initScript' :: MonadSTM m => Script a -> m (StrictTVar m (Script a)) #
interpretPickScript :: forall (m :: Type -> Type) peeraddr. (MonadSTM m, Ord peeraddr) => StrictTVar m (PickScript peeraddr) -> Set peeraddr -> Int -> STM m (Set peeraddr) #
playTimedScript :: (MonadAsync m, MonadDelay m) => Tracer m a -> TimedScript a -> m (TVar m a) #
prop_shrink_Script :: ShrinkCarefully (Script Int) -> Property #
shrinkScriptWith :: (a -> [a]) -> Script a -> [Script a] #
singletonScript :: a -> Script a #
singletonTimedScript :: a -> TimedScript a #
Timed script which consists of a single element.
stepScript :: MonadSTM m => TVar m (Script a) -> m a #
stepScriptSTM' :: forall (m :: Type -> Type) a. MonadSTM m => StrictTVar m (Script a) -> STM m a #
type PickScript peeraddr = Script (PickMembers peeraddr) #
A pick script is used to interpret the policyPickKnownPeersForPeerShare
and
the policyPickColdPeersToForget
. It selects elements from the given
choices by their index (modulo the number of choices). This representation
was chosen because it allows easy shrinking.
type TimedScript a = Script (a, ScriptDelay) #
data PeerStatus #
PeerCold | Peer is in true cold which means no connection to exists and the outbound governor is safe to promote it. |
PeerCooling | Peer is in cold state but its connection still lingers. I.e. it is still in progress to be fully demoted. Note:
The `PeerCooling -> PeerCold` state transition is an `outbound-governor`
reflection of the connection-manager's `TerminatingSt -> TerminatedSt`
state transition (our version of tcp's |
PeerWarm | |
PeerHot |
Instances
Show PeerStatus | |
Defined in Ouroboros.Network.PeerSelection.Types showsPrec :: Int -> PeerStatus -> ShowS # show :: PeerStatus -> String # showList :: [PeerStatus] -> ShowS # | |
Eq PeerStatus | |
Defined in Ouroboros.Network.PeerSelection.Types (==) :: PeerStatus -> PeerStatus -> Bool # (/=) :: PeerStatus -> PeerStatus -> Bool # | |
Ord PeerStatus | |
Defined in Ouroboros.Network.PeerSelection.Types compare :: PeerStatus -> PeerStatus -> Ordering # (<) :: PeerStatus -> PeerStatus -> Bool # (<=) :: PeerStatus -> PeerStatus -> Bool # (>) :: PeerStatus -> PeerStatus -> Bool # (>=) :: PeerStatus -> PeerStatus -> Bool # max :: PeerStatus -> PeerStatus -> PeerStatus # min :: PeerStatus -> PeerStatus -> PeerStatus # |