ouroboros-network-framework
Safe HaskellNone
LanguageHaskell2010

Simulation.Network.Snocket

Description

This module provides simulation environment and a snocket implementation suitable for IOSim.

Though this module is designed for simulation / testing, it lives in the library, since it is needed in `ouroboros-network-framework:test` and `ouroboros-network:test' components.

TODO: Create a snocket package, in order to avoid having to have ouroboros-network-testing as a dependency for this cabal library.

Synopsis

Simulated Snocket

withSnocket :: (Alternative (STM m), MonadDelay m, MonadLabelledSTM m, MonadMask m, MonadTimer m, MonadThrow (STM m), GlobalAddressScheme peerAddr, Ord peerAddr, Typeable peerAddr, Show peerAddr) => Tracer m (WithAddr (TestAddress peerAddr) (SnocketTrace m (TestAddress peerAddr))) -> BearerInfo -> Map (NormalisedId (TestAddress peerAddr)) (Script BearerInfo) -> (Snocket m (FD m (TestAddress peerAddr)) (TestAddress peerAddr) -> m (ObservableNetworkState (TestAddress peerAddr)) -> m a) -> m a Source #

A bracket which runs a network simulation. When the simulation terminates it verifies that all listening sockets and all connections are closed. It might throw ResourceException.

newtype ObservableNetworkState addr Source #

Simulation accessible network environment consumed by simSnocket.

Constructors

ObservableNetworkState 

Fields

  • onsConnections :: Map (NormalisedId addr) addr

    Registry of active connections and respective provider

Instances

Instances details
Show addr => Show (ObservableNetworkState addr) Source # 
Instance details

Defined in Simulation.Network.Snocket

data SDUSize #

Instances

Instances details
Enum SDUSize 
Instance details

Defined in Network.Mux.Types

Generic SDUSize 
Instance details

Defined in Network.Mux.Types

Associated Types

type Rep SDUSize 
Instance details

Defined in Network.Mux.Types

type Rep SDUSize = D1 ('MetaData "SDUSize" "Network.Mux.Types" "network-mux-0.5-inplace" 'True) (C1 ('MetaCons "SDUSize" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSDUSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16)))

Methods

from :: SDUSize -> Rep SDUSize x #

to :: Rep SDUSize x -> SDUSize #

Num SDUSize 
Instance details

Defined in Network.Mux.Types

Integral SDUSize 
Instance details

Defined in Network.Mux.Types

Real SDUSize 
Instance details

Defined in Network.Mux.Types

Show SDUSize 
Instance details

Defined in Network.Mux.Types

Eq SDUSize 
Instance details

Defined in Network.Mux.Types

Methods

(==) :: SDUSize -> SDUSize -> Bool #

(/=) :: SDUSize -> SDUSize -> Bool #

Ord SDUSize 
Instance details

Defined in Network.Mux.Types

type Rep SDUSize 
Instance details

Defined in Network.Mux.Types

type Rep SDUSize = D1 ('MetaData "SDUSize" "Network.Mux.Types" "network-mux-0.5-inplace" 'True) (C1 ('MetaCons "SDUSize" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSDUSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16)))

newtype Script a #

Constructors

Script (NonEmpty a) 

Instances

Instances details
Functor Script 
Instance details

Defined in Ouroboros.Network.Testing.Data.Script

Methods

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

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

Foldable Script 
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 
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) 
Instance details

Defined in Ouroboros.Network.Testing.Data.Script

Methods

arbitrary :: Gen (Script a) #

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

Show a => Show (Script a) 
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) 
Instance details

Defined in Ouroboros.Network.Testing.Data.Script

Methods

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

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

type Size = Int64 #

data SnocketTrace (m :: Type -> Type) addr Source #

Constructors

STConnecting (FD_ m addr) addr 
STConnected (FD_ m addr) OpenType 
STBearerInfo BearerInfo 
STConnectError (FD_ m addr) addr IOError 
STConnectTimeout TimeoutDetail 
STBindError (FD_ m addr) addr IOError 
STClosing SockType (Wedge (ConnectionId addr) [addr]) 
STClosed SockType (Maybe (Maybe ConnectionState))

TODO: Document meaning of 'Maybe (Maybe OpenState)'

STClosingQueue Bool 
STClosedQueue Bool 
STAcceptFailure SockType SomeException 
STAccepting 
STAccepted addr 
STAttenuatedChannelTrace (ConnectionId addr) AttenuatedChannelTrace 

Instances

Instances details
Show addr => Show (SnocketTrace m addr) Source # 
Instance details

Defined in Simulation.Network.Snocket

Methods

showsPrec :: Int -> SnocketTrace m addr -> ShowS #

show :: SnocketTrace m addr -> String #

showList :: [SnocketTrace m addr] -> ShowS #

data SockType Source #

Instances

Instances details
Show SockType Source # 
Instance details

Defined in Simulation.Network.Snocket

data OpenType Source #

Either simultaneous open or normal open. Unlike in TCP, only one side will will know that it is doing simultaneous open.

Constructors

SimOpen

Simultaneous open

NormalOpen

Normal open

Instances

Instances details
Show OpenType Source # 
Instance details

Defined in Simulation.Network.Snocket

normaliseId :: Ord addr => ConnectionId addr -> NormalisedId addr Source #

Safe constructor of NormalisedId

data BearerInfo Source #

Each bearer info describes outbound and inbound side of a point to point bearer.

Constructors

BearerInfo 

Fields

Instances

Instances details
Show BearerInfo Source # 
Instance details

Defined in Simulation.Network.Snocket

data IOErrType Source #

Error types.

Instances

Instances details
Show IOErrType Source # 
Instance details

Defined in Simulation.Network.Snocket

Eq IOErrType Source # 
Instance details

Defined in Simulation.Network.Snocket

noAttenuation :: BearerInfo Source #

BearerInfo without attenuation and instantaneous connect delay. It also using the production value of SDUSize.

data FD (m :: Type -> Type) peerAddr Source #

File descriptor type.

makeFDBearer :: forall addr (m :: Type -> Type). (MonadMonotonicTime m, MonadSTM m, MonadThrow m, Show addr) => MakeBearer m (FD m (TestAddress addr)) Source #

class GlobalAddressScheme addr where Source #

A type class for global IP address scheme. Every node in the simulation has an ephemeral address. Every node in the simulation has an implicit ipv4 and ipv6 address (if one is not bound by explicitly).

Instances

Instances details
GlobalAddressScheme Int Source #

All negative addresses are ephemeral. Even address are IPv4, while odd ones are IPv6.

Instance details

Defined in Simulation.Network.Snocket

data AddressType Source #

Connection manager supports IPv4 and IPv6 addresses.

Constructors

IPv4Address 
IPv6Address 

Instances

Instances details
Show AddressType Source # 
Instance details

Defined in Ouroboros.Network.ConnectionManager.Types

data WithAddr addr event Source #

Constructors

WithAddr 

Fields

Instances

Instances details
(Show addr, Show event) => Show (WithAddr addr event) Source # 
Instance details

Defined in Simulation.Network.Snocket

Methods

showsPrec :: Int -> WithAddr addr event -> ShowS #

show :: WithAddr addr event -> String #

showList :: [WithAddr addr event] -> ShowS #