ouroboros-network-testing
Safe HaskellNone
LanguageHaskell2010

Ouroboros.Network.Testing.Data.Script

Synopsis

Test scripts

newtype Script a Source #

Constructors

Script (NonEmpty a) 

Instances

Instances details
Functor Script Source # 
Instance details

Defined in Ouroboros.Network.Testing.Data.Script

Methods

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

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

Foldable Script Source # 
Instance details

Defined in Ouroboros.Network.Testing.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 Source # 
Instance details

Defined in Ouroboros.Network.Testing.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) Source # 
Instance details

Defined in Ouroboros.Network.Testing.Data.Script

Methods

arbitrary :: Gen (Script a) #

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

Show a => Show (Script a) Source # 
Instance details

Defined in Ouroboros.Network.Testing.Data.Script

Methods

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

show :: Script a -> String #

showList :: [Script a] -> ShowS #

Eq a => Eq (Script a) Source # 
Instance details

Defined in Ouroboros.Network.Testing.Data.Script

Methods

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

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

data NonEmpty a #

Non-empty (and non-strict) list type.

@since base-4.9.0.0

Constructors

a :| [a] infixr 5 

Instances

Instances details
MonadZip NonEmpty

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Zip

Methods

mzip :: NonEmpty a -> NonEmpty b -> NonEmpty (a, b) #

mzipWith :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c #

munzip :: NonEmpty (a, b) -> (NonEmpty a, NonEmpty b) #

Foldable1 NonEmpty

Since: base-4.18.0.0

Instance details

Defined in Data.Foldable1

Methods

fold1 :: Semigroup m => NonEmpty m -> m #

foldMap1 :: Semigroup m => (a -> m) -> NonEmpty a -> m #

foldMap1' :: Semigroup m => (a -> m) -> NonEmpty a -> m #

toNonEmpty :: NonEmpty a -> NonEmpty a #

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

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

head :: NonEmpty a -> a #

last :: NonEmpty a -> a #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> NonEmpty a -> b #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> NonEmpty a -> b #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> NonEmpty a -> b #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> NonEmpty a -> b #

Eq1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> NonEmpty a -> NonEmpty b -> Bool #

Ord1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> NonEmpty a -> NonEmpty b -> Ordering #

Read1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (NonEmpty a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [NonEmpty a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (NonEmpty a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [NonEmpty a] #

Show1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NonEmpty a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [NonEmpty a] -> ShowS #

NFData1 NonEmpty

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> NonEmpty a -> () #

Applicative NonEmpty

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

pure :: a -> NonEmpty a #

(<*>) :: NonEmpty (a -> b) -> NonEmpty a -> NonEmpty b #

liftA2 :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c #

(*>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

(<*) :: NonEmpty a -> NonEmpty b -> NonEmpty a #

Functor NonEmpty

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

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

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

Monad NonEmpty

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(>>=) :: NonEmpty a -> (a -> NonEmpty b) -> NonEmpty b #

(>>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

return :: a -> NonEmpty a #

Foldable NonEmpty

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Foldable

Methods

fold :: Monoid m => NonEmpty m -> m #

foldMap :: Monoid m => (a -> m) -> NonEmpty a -> m #

foldMap' :: Monoid m => (a -> m) -> NonEmpty a -> m #

foldr :: (a -> b -> b) -> b -> NonEmpty a -> b #

foldr' :: (a -> b -> b) -> b -> NonEmpty a -> b #

foldl :: (b -> a -> b) -> b -> NonEmpty a -> b #

foldl' :: (b -> a -> b) -> b -> NonEmpty a -> b #

foldr1 :: (a -> a -> a) -> NonEmpty a -> a #

foldl1 :: (a -> a -> a) -> NonEmpty a -> a #

toList :: NonEmpty a -> [a] #

null :: NonEmpty a -> Bool #

length :: NonEmpty a -> Int #

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

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

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

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

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

Traversable NonEmpty

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

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

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

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

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

Hashable1 NonEmpty

Since: hashable-1.3.1.0

Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> NonEmpty a -> Int #

Generic1 NonEmpty 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 NonEmpty

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

from1 :: NonEmpty a -> Rep1 NonEmpty a #

to1 :: Rep1 NonEmpty a -> NonEmpty a #

Lift a => Lift (NonEmpty a :: Type)

Since: template-haskell-2.15.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => NonEmpty a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => NonEmpty a -> Code m (NonEmpty a) #

NFData a => NFData (NonEmpty a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: NonEmpty a -> () #

Semigroup (NonEmpty a)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(<>) :: NonEmpty a -> NonEmpty a -> NonEmpty a #

sconcat :: NonEmpty (NonEmpty a) -> NonEmpty a #

stimes :: Integral b => b -> NonEmpty a -> NonEmpty a #

Generic (NonEmpty a) 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep (NonEmpty a)

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

from :: NonEmpty a -> Rep (NonEmpty a) x #

to :: Rep (NonEmpty a) x -> NonEmpty a #

IsList (NonEmpty a)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.IsList

Associated Types

type Item (NonEmpty a) 
Instance details

Defined in GHC.Internal.IsList

type Item (NonEmpty a) = a

Methods

fromList :: [Item (NonEmpty a)] -> NonEmpty a #

fromListN :: Int -> [Item (NonEmpty a)] -> NonEmpty a #

toList :: NonEmpty a -> [Item (NonEmpty a)] #

Show a => Show (NonEmpty a)

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Show

Methods

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

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

Eq a => Eq (NonEmpty a)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

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

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

Ord a => Ord (NonEmpty a)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

compare :: NonEmpty a -> NonEmpty a -> Ordering #

(<) :: NonEmpty a -> NonEmpty a -> Bool #

(<=) :: NonEmpty a -> NonEmpty a -> Bool #

(>) :: NonEmpty a -> NonEmpty a -> Bool #

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

max :: NonEmpty a -> NonEmpty a -> NonEmpty a #

min :: NonEmpty a -> NonEmpty a -> NonEmpty a #

Hashable a => Hashable (NonEmpty a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> NonEmpty a -> Int #

hash :: NonEmpty a -> Int #

Pretty a => Pretty (NonEmpty a) 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: NonEmpty a -> Doc ann #

prettyList :: [NonEmpty a] -> Doc ann #

Serialise a => Serialise (NonEmpty a)

Since: serialise-0.2.0.0

Instance details

Defined in Codec.Serialise.Class

type Rep1 NonEmpty

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (NonEmpty a)

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Item (NonEmpty a) 
Instance details

Defined in GHC.Internal.IsList

type Item (NonEmpty a) = a

initScript :: MonadSTM m => Script a -> m (TVar m (Script a)) Source #

stepScript :: MonadSTM m => TVar m (Script a) -> m a Source #

stepScriptSTM :: forall (m :: Type -> Type) a. MonadSTM m => TVar m (Script a) -> STM m a Source #

stepScriptOrFinish :: MonadSTM m => TVar m (Script a) -> m (Either a a) Source #

Return Left if it was the last step, return Right if the script can continue.

stepScriptOrFinishSTM :: forall (m :: Type -> Type) a. MonadSTM m => TVar m (Script a) -> STM m (Either a a) Source #

stepScriptSTM' :: forall (m :: Type -> Type) a. MonadSTM m => StrictTVar m (Script a) -> STM m a Source #

shrinkScriptWith :: (a -> [a]) -> Script a -> [Script a] Source #

Timed scripts

singletonTimedScript :: a -> TimedScript a Source #

Timed script which consists of a single element.

Pick scripts

type PickScript peeraddr = Script (PickMembers peeraddr) Source #

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.

data PickMembers peeraddr Source #

Constructors

PickFirst 
PickAll 
PickSome (Set peeraddr) 

Instances

Instances details
(Arbitrary peeraddr, Ord peeraddr) => Arbitrary (PickMembers peeraddr) Source # 
Instance details

Defined in Ouroboros.Network.Testing.Data.Script

Methods

arbitrary :: Gen (PickMembers peeraddr) #

shrink :: PickMembers peeraddr -> [PickMembers peeraddr] #

Show peeraddr => Show (PickMembers peeraddr) Source # 
Instance details

Defined in Ouroboros.Network.Testing.Data.Script

Methods

showsPrec :: Int -> PickMembers peeraddr -> ShowS #

show :: PickMembers peeraddr -> String #

showList :: [PickMembers peeraddr] -> ShowS #

Eq peeraddr => Eq (PickMembers peeraddr) Source # 
Instance details

Defined in Ouroboros.Network.Testing.Data.Script

Methods

(==) :: PickMembers peeraddr -> PickMembers peeraddr -> Bool #

(/=) :: PickMembers peeraddr -> PickMembers peeraddr -> Bool #

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

interpretPickScript :: forall (m :: Type -> Type) peeraddr. (MonadSTM m, Ord peeraddr) => StrictTVar m (PickScript peeraddr) -> Set peeraddr -> Int -> STM m (Set peeraddr) Source #