| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Ouroboros.Network.Mux
Synopsis
- data ProtocolTemperature
- = Established
- | Warm
- | Hot
- data SingProtocolTemperature (pt :: ProtocolTemperature) where
- data SomeTokProtocolTemperature where
- SomeTokProtocolTemperature :: forall (pt :: ProtocolTemperature). SingProtocolTemperature pt -> SomeTokProtocolTemperature
- data WithProtocolTemperature (pt :: ProtocolTemperature) a where
- WithHot :: forall a. !a -> WithProtocolTemperature 'Hot a
- WithWarm :: forall a. !a -> WithProtocolTemperature 'Warm a
- WithEstablished :: forall a. !a -> WithProtocolTemperature 'Established a
- withoutProtocolTemperature :: forall (pt :: ProtocolTemperature) a. WithProtocolTemperature pt a -> a
- data WithSomeProtocolTemperature a where
- WithSomeProtocolTemperature :: forall (pt :: ProtocolTemperature) a. WithProtocolTemperature pt a -> WithSomeProtocolTemperature a
- withoutSomeProtocolTemperature :: WithSomeProtocolTemperature a -> a
- data TemperatureBundle a = TemperatureBundle {
- withHot :: !(WithProtocolTemperature 'Hot a)
- withWarm :: !(WithProtocolTemperature 'Warm a)
- withEstablished :: !(WithProtocolTemperature 'Established a)
- projectBundle :: forall (pt :: ProtocolTemperature) a. SingProtocolTemperature pt -> TemperatureBundle a -> a
- newtype MiniProtocolCb ctx bytes (m :: Type -> Type) a = MiniProtocolCb {
- runMiniProtocolCb :: ctx -> Channel m bytes -> m (a, Maybe bytes)
- 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
- 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
- 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
- data RunMiniProtocol (mode :: Mode) initiatorCtx responderCtx bytes (m :: Type -> Type) a b where
- 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
- type RunMiniProtocolWithMinimalCtx (mode :: Mode) peerAddr bytes (m :: Type -> Type) a b = RunMiniProtocol mode (MinimalInitiatorContext peerAddr) (ResponderContext peerAddr) bytes m a b
- data MiniProtocol (mode :: Mode) initiatorCtx responderCtx bytes (m :: Type -> Type) a b = MiniProtocol {
- miniProtocolNum :: !MiniProtocolNum
- miniProtocolStart :: !StartOnDemandOrEagerly
- miniProtocolLimits :: !MiniProtocolLimits
- miniProtocolRun :: !(RunMiniProtocol mode initiatorCtx responderCtx bytes m a b)
- type MiniProtocolWithExpandedCtx (mode :: Mode) peerAddr bytes (m :: Type -> Type) a b = MiniProtocol mode (ExpandedInitiatorContext peerAddr m) (ResponderContext peerAddr) bytes m a b
- type MiniProtocolWithMinimalCtx (mode :: Mode) peerAddr bytes (m :: Type -> Type) a b = MiniProtocol mode (MinimalInitiatorContext peerAddr) (ResponderContext peerAddr) bytes m a b
- newtype MiniProtocolNum = MiniProtocolNum Word16
- newtype MiniProtocolLimits = MiniProtocolLimits {}
- newtype ForkPolicy peerAddr = ForkPolicy {
- runForkPolicy :: peerAddr -> ForkPolicyCb
- noBindForkPolicy :: ForkPolicy peerAddr
- responderForkPolicy :: Hashable peerAddr => Int -> Int -> ForkPolicy peerAddr
- type OuroborosBundle (mode :: Mode) initiatorCtx responderCtx bytes (m :: Type -> Type) a b = TemperatureBundle [MiniProtocol mode initiatorCtx responderCtx bytes m a b]
- type OuroborosBundleWithExpandedCtx (mode :: Mode) peerAddr bytes (m :: Type -> Type) a b = OuroborosBundle mode (ExpandedInitiatorContext peerAddr m) (ResponderContext peerAddr) bytes m a b
- type OuroborosBundleWithMinimalCtx (mode :: Mode) peerAddr bytes (m :: Type -> Type) a b = OuroborosBundle mode (MinimalInitiatorContext peerAddr) (ResponderContext peerAddr) bytes m a b
- newtype OuroborosApplication (mode :: Mode) initiatorCtx responderCtx bytes (m :: Type -> Type) a b = OuroborosApplication {
- getOuroborosApplication :: [MiniProtocol mode initiatorCtx responderCtx bytes m a b]
- type OuroborosApplicationWithMinimalCtx (mode :: Mode) peerAddr bytes (m :: Type -> Type) a b = OuroborosApplication mode (MinimalInitiatorContext peerAddr) (ResponderContext peerAddr) bytes m a b
- mkMiniProtocolInfos :: forall (mode :: Mode) initiatorCtx responderCtx bytes (m :: Type -> Type) a b. ForkPolicyCb -> OuroborosBundle mode initiatorCtx responderCtx bytes m a b -> [MiniProtocolInfo mode]
- 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
- toMiniProtocolInfos :: forall (mode :: Mode) initiatorCtx responderCtx bytes (m :: Type -> Type) a b. ForkPolicyCb -> OuroborosApplication mode initiatorCtx responderCtx bytes m a b -> [MiniProtocolInfo mode]
- 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
- type family HasInitiator (mode :: Mode) :: Bool where ...
- type family HasResponder (mode :: Mode) :: Bool where ...
- data StartOnDemandOrEagerly
Basic notions
data ProtocolTemperature Source #
There are three kinds of applications: warm, hot and established (ones that run in both warm and hot states).
Constructors
| Established | |
| Warm | |
| Hot |
Instances
| Show ProtocolTemperature Source # | |
Defined in Ouroboros.Network.Mux Methods showsPrec :: Int -> ProtocolTemperature -> ShowS # show :: ProtocolTemperature -> String # showList :: [ProtocolTemperature] -> ShowS # | |
| Eq ProtocolTemperature Source # | |
Defined in Ouroboros.Network.Mux Methods (==) :: ProtocolTemperature -> ProtocolTemperature -> Bool # (/=) :: ProtocolTemperature -> ProtocolTemperature -> Bool # | |
| Ord ProtocolTemperature Source # | |
Defined in Ouroboros.Network.Mux Methods compare :: ProtocolTemperature -> ProtocolTemperature -> Ordering # (<) :: ProtocolTemperature -> ProtocolTemperature -> Bool # (<=) :: ProtocolTemperature -> ProtocolTemperature -> Bool # (>) :: ProtocolTemperature -> ProtocolTemperature -> Bool # (>=) :: ProtocolTemperature -> ProtocolTemperature -> Bool # max :: ProtocolTemperature -> ProtocolTemperature -> ProtocolTemperature # min :: ProtocolTemperature -> ProtocolTemperature -> ProtocolTemperature # | |
data SingProtocolTemperature (pt :: ProtocolTemperature) where Source #
Singletons for ProtocolTemperature.
Constructors
| SingHot :: SingProtocolTemperature 'Hot | |
| SingWarm :: SingProtocolTemperature 'Warm | |
| SingEstablished :: SingProtocolTemperature 'Established |
data SomeTokProtocolTemperature where Source #
Constructors
| SomeTokProtocolTemperature :: forall (pt :: ProtocolTemperature). SingProtocolTemperature pt -> SomeTokProtocolTemperature |
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
withoutProtocolTemperature :: forall (pt :: ProtocolTemperature) a. WithProtocolTemperature pt a -> a Source #
data WithSomeProtocolTemperature a where Source #
Constructors
| WithSomeProtocolTemperature :: forall (pt :: ProtocolTemperature) a. WithProtocolTemperature pt a -> WithSomeProtocolTemperature a |
Instances
| Functor WithSomeProtocolTemperature Source # | |
Defined in Ouroboros.Network.Mux Methods fmap :: (a -> b) -> WithSomeProtocolTemperature a -> WithSomeProtocolTemperature b # (<$) :: a -> WithSomeProtocolTemperature b -> WithSomeProtocolTemperature a # | |
| Show a => Show (WithSomeProtocolTemperature a) Source # | |
Defined in Ouroboros.Network.Mux Methods showsPrec :: Int -> WithSomeProtocolTemperature a -> ShowS # show :: WithSomeProtocolTemperature a -> String # showList :: [WithSomeProtocolTemperature a] -> ShowS # | |
data TemperatureBundle a Source #
A bundle of HotApp, WarmApp and EstablishedApp.
Constructors
| TemperatureBundle | |
Fields
| |
Instances
projectBundle :: forall (pt :: ProtocolTemperature) a. SingProtocolTemperature pt -> TemperatureBundle a -> a Source #
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
newtype MiniProtocolLimits #
Per Miniprotocol limits
Constructors
| MiniProtocolLimits | |
Fields
| |
Instances
| Show MiniProtocolLimits | |
Defined in Network.Mux.Types Methods showsPrec :: Int -> MiniProtocolLimits -> ShowS # show :: MiniProtocolLimits -> String # showList :: [MiniProtocolLimits] -> ShowS # | |
newtype ForkPolicy peerAddr Source #
Extension of a ForkPolicyCb used by `ouroboros-network-framework` outside
of this module.
Constructors
| ForkPolicy | |
Fields
| |
noBindForkPolicy :: ForkPolicy peerAddr Source #
A ForkPolicy which does not bind mini-protocol threads to a given capability.
Arguments
| :: Hashable peerAddr | |
| => Int | salt |
| -> Int | number of capabilities |
| -> ForkPolicy peerAddr |
A ForkPolicy which binds responders mini-protocols to lower capabilities.
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. ForkPolicyCb -> 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. ForkPolicyCb -> 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
from Network.Mux
type family HasInitiator (mode :: Mode) :: Bool where ... #
Equations
| HasInitiator 'InitiatorMode = 'True | |
| HasInitiator 'ResponderMode = 'False | |
| HasInitiator 'InitiatorResponderMode = 'True |
type family HasResponder (mode :: Mode) :: Bool where ... #
Equations
| HasResponder 'InitiatorMode = 'False | |
| HasResponder 'ResponderMode = 'True | |
| HasResponder 'InitiatorResponderMode = 'True |
data StartOnDemandOrEagerly #
Strategy how to start a mini-protocol.
Constructors
| StartEagerly | Start a mini-protocol promptly. |
| StartOnDemand | Start a mini-protocol when data is received for the given mini-protocol. Must be used only when initial message is sent by the remote side. |
| StartOnDemandAny | Like |
Instances
| Show StartOnDemandOrEagerly | |
Defined in Network.Mux.Types Methods showsPrec :: Int -> StartOnDemandOrEagerly -> ShowS # show :: StartOnDemandOrEagerly -> String # showList :: [StartOnDemandOrEagerly] -> ShowS # | |
| Eq StartOnDemandOrEagerly | |
Defined in Network.Mux.Types Methods (==) :: StartOnDemandOrEagerly -> StartOnDemandOrEagerly -> Bool # (/=) :: StartOnDemandOrEagerly -> StartOnDemandOrEagerly -> Bool # | |