cardano-diffusion:cardano-diffusion-tests-lib
Safe HaskellNone
LanguageHaskell2010

Test.Cardano.Network.PeerSelection.MockEnvironment

Synopsis

Documentation

newtype PeerGraph #

Constructors

PeerGraph [(PeerAddr, [PeerAddr], PeerInfo)] 

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.

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.

data TestTraceEvent extraState extraFlags extraPeers extraCounters extraTrace Source #

Constructors

GovernorDebug !(DebugPeerSelection extraState extraFlags extraPeers PeerAddr) 
GovernorEvent !(TracePeerSelection extraState extraFlags extraPeers extraTrace PeerAddr) 
GovernorCounters !(PeerSelectionCounters extraCounters) 
GovernorAssociationMode !AssociationMode 
MockEnvEvent !TraceMockEnv 

Instances

Instances details
(Show extraState, Show extraFlags, Show extraPeers, Show extraTrace, Show extraCounters) => Show (TestTraceEvent extraState extraFlags extraPeers extraCounters extraTrace) Source # 
Instance details

Defined in Test.Cardano.Network.PeerSelection.MockEnvironment

Methods

showsPrec :: Int -> TestTraceEvent extraState extraFlags extraPeers extraCounters extraTrace -> ShowS #

show :: TestTraceEvent extraState extraFlags extraPeers extraCounters extraTrace -> String #

showList :: [TestTraceEvent extraState extraFlags extraPeers extraCounters extraTrace] -> ShowS #

selectGovernorEvents :: [(Time, TestTraceEvent extraState extraFlags extraPeers extraCounters extraTrace)] -> [(Time, TracePeerSelection extraState extraFlags extraPeers extraTrace PeerAddr)] Source #

selectGovernorStateEvents :: [(Time, TestTraceEvent extraState extraFlags extraPeers extraCounters extraTrace)] -> [(Time, DebugPeerSelection extraState extraFlags extraPeers PeerAddr)] Source #

selectPeerSelectionTraceEvents :: (Typeable extraState, Typeable extraFlags, Typeable extraPeers, Typeable extraCounters, Typeable extraTrace) => SimTrace a -> [(Time, TestTraceEvent extraState extraFlags extraPeers extraCounters extraTrace)] Source #

selectPeerSelectionTraceEventsUntil :: (Typeable extraState, Typeable extraFlags, Typeable extraPeers, Typeable extraCounters, Typeable extraTrace) => Time -> SimTrace a -> [(Time, TestTraceEvent extraState extraFlags extraPeers extraCounters extraTrace)] Source #

newtype Script a #

Constructors

Script (NonEmpty a) 

Instances

Instances details
Functor Script 
Instance details

Defined in Test.Ouroboros.Network.Data.Script

Methods

fmap :: (a -> b) -> Script a -> Script b #

(<$) :: a -> Script b -> Script a #

Foldable Script 
Instance details

Defined in Test.Ouroboros.Network.Data.Script

Methods

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 #

toList :: Script a -> [a] #

null :: Script a -> Bool #

length :: Script a -> Int #

elem :: Eq a => a -> Script a -> Bool #

maximum :: Ord a => Script a -> a #

minimum :: Ord a => Script a -> a #

sum :: Num a => Script a -> a #

product :: Num a => Script a -> a #

Traversable Script 
Instance details

Defined in Test.Ouroboros.Network.Data.Script

Methods

traverse :: Applicative f => (a -> f b) -> Script a -> f (Script b) #

sequenceA :: Applicative f => Script (f a) -> f (Script a) #

mapM :: Monad m => (a -> m b) -> Script a -> m (Script b) #

sequence :: Monad m => Script (m a) -> m (Script a) #

Arbitrary a => Arbitrary (Script a) 
Instance details

Defined in Test.Ouroboros.Network.Data.Script

Methods

arbitrary :: Gen (Script a) #

shrink :: Script a -> [Script a] #

NFData a => NFData (Script a) 
Instance details

Defined in Test.Ouroboros.Network.Data.Script

Methods

rnf :: Script a -> () #

Show a => Show (Script a) 
Instance details

Defined in Test.Ouroboros.Network.Data.Script

Methods

showsPrec :: Int -> Script a -> ShowS #

show :: Script a -> String #

showList :: [Script a] -> ShowS #

Eq a => Eq (Script a) 
Instance details

Defined in Test.Ouroboros.Network.Data.Script

Methods

(==) :: Script a -> Script a -> Bool #

(/=) :: Script a -> Script a -> Bool #

type PickScript peeraddr = Script (PickMembers peeraddr) #

arbitraryPickScript :: Gen (Set peeraddr) -> Gen (PickScript peeraddr) #

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] #

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 #