ouroboros-network-framework
Safe HaskellNone
LanguageHaskell2010

Ouroboros.Network.Mux

Synopsis

Basic notions

data WithProtocolTemperature (pt :: ProtocolTemperature) a where Source #

We keep hot, warm and established application (or their context) distinct. It's only needed for a handy projectBundle map.

Constructors

WithHot :: forall a. !a -> WithProtocolTemperature 'Hot a 
WithWarm :: forall a. !a -> WithProtocolTemperature 'Warm a 
WithEstablished :: forall a. !a -> WithProtocolTemperature 'Established a 

Instances

Instances details
Applicative (WithProtocolTemperature 'Established) Source # 
Instance details

Defined in Ouroboros.Network.Mux

Applicative (WithProtocolTemperature 'Hot) Source # 
Instance details

Defined in Ouroboros.Network.Mux

Applicative (WithProtocolTemperature 'Warm) Source # 
Instance details

Defined in Ouroboros.Network.Mux

Functor (WithProtocolTemperature pt) Source # 
Instance details

Defined in Ouroboros.Network.Mux

Foldable (WithProtocolTemperature pt) Source # 
Instance details

Defined in Ouroboros.Network.Mux

Methods

fold :: Monoid m => WithProtocolTemperature pt m -> m #

foldMap :: Monoid m => (a -> m) -> WithProtocolTemperature pt a -> m #

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

foldr :: (a -> b -> b) -> b -> WithProtocolTemperature pt a -> b #

foldr' :: (a -> b -> b) -> b -> WithProtocolTemperature pt a -> b #

foldl :: (b -> a -> b) -> b -> WithProtocolTemperature pt a -> b #

foldl' :: (b -> a -> b) -> b -> WithProtocolTemperature pt a -> b #

foldr1 :: (a -> a -> a) -> WithProtocolTemperature pt a -> a #

foldl1 :: (a -> a -> a) -> WithProtocolTemperature pt a -> a #

toList :: WithProtocolTemperature pt a -> [a] #

null :: WithProtocolTemperature pt a -> Bool #

length :: WithProtocolTemperature pt a -> Int #

elem :: Eq a => a -> WithProtocolTemperature pt a -> Bool #

maximum :: Ord a => WithProtocolTemperature pt a -> a #

minimum :: Ord a => WithProtocolTemperature pt a -> a #

sum :: Num a => WithProtocolTemperature pt a -> a #

product :: Num a => WithProtocolTemperature pt a -> a #

Traversable (WithProtocolTemperature pt) Source # 
Instance details

Defined in Ouroboros.Network.Mux

Monoid a => Monoid (WithProtocolTemperature 'Established a) Source # 
Instance details

Defined in Ouroboros.Network.Mux

Monoid a => Monoid (WithProtocolTemperature 'Hot a) Source # 
Instance details

Defined in Ouroboros.Network.Mux

Monoid a => Monoid (WithProtocolTemperature 'Warm a) Source # 
Instance details

Defined in Ouroboros.Network.Mux

Semigroup a => Semigroup (WithProtocolTemperature 'Established a) Source # 
Instance details

Defined in Ouroboros.Network.Mux

Semigroup a => Semigroup (WithProtocolTemperature 'Hot a) Source # 
Instance details

Defined in Ouroboros.Network.Mux

Semigroup a => Semigroup (WithProtocolTemperature 'Warm a) Source # 
Instance details

Defined in Ouroboros.Network.Mux

Show a => Show (WithProtocolTemperature pt a) Source # 
Instance details

Defined in Ouroboros.Network.Mux

Eq a => Eq (WithProtocolTemperature pt a) Source # 
Instance details

Defined in Ouroboros.Network.Mux

data TemperatureBundle a Source #

A bundle of HotApp, WarmApp and EstablishedApp.

Constructors

TemperatureBundle 

Fields

Instances

Instances details
Applicative TemperatureBundle Source # 
Instance details

Defined in Ouroboros.Network.Mux

Functor TemperatureBundle Source # 
Instance details

Defined in Ouroboros.Network.Mux

Foldable TemperatureBundle Source # 
Instance details

Defined in Ouroboros.Network.Mux

Methods

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

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

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

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

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

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

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

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

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

toList :: TemperatureBundle a -> [a] #

null :: TemperatureBundle a -> Bool #

length :: TemperatureBundle a -> Int #

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

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

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

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

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

Traversable TemperatureBundle Source # 
Instance details

Defined in Ouroboros.Network.Mux

Methods

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

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

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

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

Monoid a => Monoid (TemperatureBundle a) Source # 
Instance details

Defined in Ouroboros.Network.Mux

Semigroup a => Semigroup (TemperatureBundle a) Source # 
Instance details

Defined in Ouroboros.Network.Mux

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

Defined in Ouroboros.Network.Mux

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

Defined in Ouroboros.Network.Mux

Mux mini-protocol callback

newtype MiniProtocolCb ctx bytes (m :: Type -> Type) a Source #

A callback executed by each muxed mini-protocol.

Constructors

MiniProtocolCb 

Fields

mkMiniProtocolCbFromPeer :: forall (pr :: PeerRole) ps (st :: ps) failure bytes ctx (m :: Type -> Type) a. (MonadThrow m, ShowProxy ps, forall (st' :: ps) stok. stok ~ StateToken st' => Show stok, Show failure) => (ctx -> (Tracer m (TraceSendRecv ps), Codec ps failure m bytes, Peer ps pr 'NonPipelined st m a)) -> MiniProtocolCb ctx bytes m a Source #

Create a MuxPeer from a tracer, codec and Peer.

mkMiniProtocolCbFromPeerPipelined :: forall (pr :: PeerRole) ps (st :: ps) failure ctx bytes (m :: Type -> Type) a. (MonadAsync m, MonadThrow m, ShowProxy ps, forall (st' :: ps) stok. stok ~ StateToken st' => Show stok, Show failure) => (ctx -> (Tracer m (TraceSendRecv ps), Codec ps failure m bytes, PeerPipelined ps pr st m a)) -> MiniProtocolCb ctx bytes m a Source #

Create a MuxPeer from a tracer, codec and PeerPipelined.

mkMiniProtocolCbFromPeerSt :: forall (pr :: PeerRole) ps f (st :: ps) failure bytes ctx (m :: Type -> Type) a. (MonadAsync m, MonadMask m, ShowProxy ps, forall (st' :: ps) stok. stok ~ StateToken st' => Show stok, Show failure) => (ctx -> (Tracer m (TraceSendRecv ps f), Codec ps failure f m bytes, f st, Peer ps pr st f m a)) -> MiniProtocolCb ctx bytes m a Source #

Create a MuxPeer from a tracer, codec and Peer.

Mux mini-protocol callback in MuxMode

data RunMiniProtocol (mode :: Mode) initiatorCtx responderCtx bytes (m :: Type -> Type) a b where Source #

RunMiniProtocol. It also capture context (the IsBigLedgerPeer) which is passed to the mini-protocol when a mini-protocol is started.

Constructors

InitiatorProtocolOnly :: forall initiatorCtx bytes (m :: Type -> Type) a responderCtx. MiniProtocolCb initiatorCtx bytes m a -> RunMiniProtocol 'InitiatorMode initiatorCtx responderCtx bytes m a Void 
ResponderProtocolOnly :: forall responderCtx bytes (m :: Type -> Type) b initiatorCtx. MiniProtocolCb responderCtx bytes m b -> RunMiniProtocol 'ResponderMode initiatorCtx responderCtx bytes m Void b 
InitiatorAndResponderProtocol :: forall initiatorCtx bytes (m :: Type -> Type) a responderCtx b. MiniProtocolCb initiatorCtx bytes m a -> MiniProtocolCb responderCtx bytes m b -> RunMiniProtocol 'InitiatorResponderMode initiatorCtx responderCtx bytes m a b 

type RunMiniProtocolWithExpandedCtx (mode :: Mode) peerAddr bytes (m :: Type -> Type) a b = RunMiniProtocol mode (ExpandedInitiatorContext peerAddr m) (ResponderContext peerAddr) bytes m a b Source #

RunMiniProtocol with ExpandedInitiatorContext and ResponderContext.

Used to run P2P node-to-node applications.

type RunMiniProtocolWithMinimalCtx (mode :: Mode) peerAddr bytes (m :: Type -> Type) a b = RunMiniProtocol mode (MinimalInitiatorContext peerAddr) (ResponderContext peerAddr) bytes m a b Source #

RunMiniProtocol with MinimalInitiatorContext and ResponderContext.

Use to run node-to-client application as well as in some non p2p contexts.

MiniProtocol description

data MiniProtocol (mode :: Mode) initiatorCtx responderCtx bytes (m :: Type -> Type) a b Source #

Each mini-protocol is represented by its

  • mini-protocol number,
  • ingress size limit, and
  • callbacks.

Constructors

MiniProtocol 

Fields

type MiniProtocolWithExpandedCtx (mode :: Mode) peerAddr bytes (m :: Type -> Type) a b = MiniProtocol mode (ExpandedInitiatorContext peerAddr m) (ResponderContext peerAddr) bytes m a b Source #

MiniProtocol type used in P2P.

type MiniProtocolWithMinimalCtx (mode :: Mode) peerAddr bytes (m :: Type -> Type) a b = MiniProtocol mode (MinimalInitiatorContext peerAddr) (ResponderContext peerAddr) bytes m a b Source #

MiniProtocol type used in non-P2P.

newtype MiniProtocolNum #

The wire format includes the protocol numbers, and it's vital that these are stable. They are not necessarily dense however, as new ones are added and some old ones retired. So we use a dedicated class for this rather than reusing Enum. This also covers unrecognised protocol numbers on the decoding side.

Constructors

MiniProtocolNum Word16 

Instances

Instances details
Enum MiniProtocolNum 
Instance details

Defined in Network.Mux.Types

Ix MiniProtocolNum 
Instance details

Defined in Network.Mux.Types

Show MiniProtocolNum 
Instance details

Defined in Network.Mux.Types

Eq MiniProtocolNum 
Instance details

Defined in Network.Mux.Types

Ord MiniProtocolNum 
Instance details

Defined in Network.Mux.Types

newtype MiniProtocolLimits #

Per Miniprotocol limits

Constructors

MiniProtocolLimits 

Fields

  • maximumIngressQueue :: Int

    Limit on the maximum number of bytes that can be queued in the miniprotocol's ingress queue.

MiniProtocol bundle

type OuroborosBundle (mode :: Mode) initiatorCtx responderCtx bytes (m :: Type -> Type) a b = TemperatureBundle [MiniProtocol mode initiatorCtx responderCtx bytes m a b] Source #

type OuroborosBundleWithExpandedCtx (mode :: Mode) peerAddr bytes (m :: Type -> Type) a b = OuroborosBundle mode (ExpandedInitiatorContext peerAddr m) (ResponderContext peerAddr) bytes m a b Source #

OuroborosBundle used in P2P.

type OuroborosBundleWithMinimalCtx (mode :: Mode) peerAddr bytes (m :: Type -> Type) a b = OuroborosBundle mode (MinimalInitiatorContext peerAddr) (ResponderContext peerAddr) bytes m a b Source #

Non-P2P API

newtype OuroborosApplication (mode :: Mode) initiatorCtx responderCtx bytes (m :: Type -> Type) a b Source #

Like MuxApplication but using a MuxPeer rather than a raw Channel -> m a action.

Note: Only used in some non-P2P contexts.

Constructors

OuroborosApplication 

Fields

type OuroborosApplicationWithMinimalCtx (mode :: Mode) peerAddr bytes (m :: Type -> Type) a b = OuroborosApplication mode (MinimalInitiatorContext peerAddr) (ResponderContext peerAddr) bytes m a b Source #

OuroborosApplication used in NonP2P mode.

mkMiniProtocolInfos :: forall (mode :: Mode) initiatorCtx responderCtx bytes (m :: Type -> Type) a b. OuroborosBundle mode initiatorCtx responderCtx bytes m a b -> [MiniProtocolInfo mode] Source #

Make MiniProtocolBundle, which is used to create a mux interface with newMux.

fromOuroborosBundle :: forall (mode :: Mode) initiatorCtx responderCtx bytes (m :: Type -> Type) a b. OuroborosBundle mode initiatorCtx responderCtx bytes m a b -> OuroborosApplication mode initiatorCtx responderCtx bytes m a b Source #

toMiniProtocolInfos :: forall (mode :: Mode) initiatorCtx responderCtx bytes (m :: Type -> Type) a b. OuroborosApplication mode initiatorCtx responderCtx bytes m a b -> [MiniProtocolInfo mode] Source #

contramapInitiatorCtx :: forall initiatorCtx' initiatorCtx (mode :: Mode) responderCtx bytes (m :: Type -> Type) a b. (initiatorCtx' -> initiatorCtx) -> OuroborosApplication mode initiatorCtx responderCtx bytes m a b -> OuroborosApplication mode initiatorCtx' responderCtx bytes m a b Source #

Re-exports