| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
TypedProtocol.Driver
Description
Schematic diagram of the communication structure of three roles through typed-session:

Some explanations for this diagram:
- Roles are connected through channels, and there are many types of channels, such as channels established through TCP or channels established through TMVar.
- Each role has a Peer thread, in which the Peer runs.
- Each role has one or more decode threads, and the decoded Msgs are placed in the MsgCache.
- SendMap aggregates the send functions of multiple Channels together. When sending a message, the send function of the receiver is searched from SendMap.
Synopsis
- data Driver role' ps (m :: Type -> Type) = Driver {}
- runPeerWithDriver :: forall role' ps (r :: role') (st :: ps) m a. (Monad m, SingToInt role') => Driver role' ps m -> Peer role' ps r m (At a (Done r :: ps)) st -> m a
- data TraceSendRecv role' ps where
- TraceSendMsg :: forall role' ps. AnyMsg role' ps -> TraceSendRecv role' ps
- TraceRecvMsg :: forall role' ps. AnyMsg role' ps -> TraceSendRecv role' ps
- type Tracer role' ps (m :: Type -> Type) = TraceSendRecv role' ps -> m ()
- nullTracer :: Monad m => a -> m ()
- type SendMap (role' :: k) (m :: Type -> Type) bytes = IntMap (bytes -> m ())
- driverSimple :: forall role' ps bytes m n. (Monad m, Monad n, MonadSTM n) => Tracer role' ps n -> Encode role' ps bytes -> SendMap role' n bytes -> TVar n (MsgCache role' ps) -> (forall a. n a -> m a) -> Driver role' ps m
- decodeLoop :: (Exception failure, MonadSTM n, MonadThrow n) => Tracer role' ps n -> Maybe bytes -> Decode role' ps failure bytes -> Channel n bytes -> TVar n (MsgCache role' ps) -> n ()
Documentation
data Driver role' ps (m :: Type -> Type) Source #
Contains two functions sendMsg, recvMsg. runPeerWithDriver uses them to send and receive Msg.
Constructors
| Driver | |
runPeerWithDriver :: forall role' ps (r :: role') (st :: ps) m a. (Monad m, SingToInt role') => Driver role' ps m -> Peer role' ps r m (At a (Done r :: ps)) st -> m a Source #
Interpret Peer.
data TraceSendRecv role' ps where Source #
A wrapper around AnyMsg that represents sending and receiving Msg.
Constructors
| TraceSendMsg :: forall role' ps. AnyMsg role' ps -> TraceSendRecv role' ps | |
| TraceRecvMsg :: forall role' ps. AnyMsg role' ps -> TraceSendRecv role' ps |
Instances
| Show (AnyMsg role' ps) => Show (TraceSendRecv role' ps) Source # | |
Defined in TypedProtocol.Driver Methods showsPrec :: Int -> TraceSendRecv role' ps -> ShowS # show :: TraceSendRecv role' ps -> String # showList :: [TraceSendRecv role' ps] -> ShowS # | |
type Tracer role' ps (m :: Type -> Type) = TraceSendRecv role' ps -> m () Source #
Similar to the log function, used to print received or sent messages.
nullTracer :: Monad m => a -> m () Source #
The default trace function. It simply ignores everything.
type SendMap (role' :: k) (m :: Type -> Type) bytes = IntMap (bytes -> m ()) Source #
SendMap aggregates the send functions of multiple Channels together. When sending a message, the send function of the receiver is found from SendMap.
driverSimple :: forall role' ps bytes m n. (Monad m, Monad n, MonadSTM n) => Tracer role' ps n -> Encode role' ps bytes -> SendMap role' n bytes -> TVar n (MsgCache role' ps) -> (forall a. n a -> m a) -> Driver role' ps m Source #
Build Driver through SendMap and MsgCache. Here we need some help from other functions:
- `Tracer role' ps n` is similar to the log function, used to print received or sent messages.
- `Encode role' ps` bytes encoding function, converts Msg into bytes.
- `forall a. n a -> m a` This is a bit complicated, I will explain it in detail below.
I see Peer as three layers:
Peerupper layer, meets the requirements of McBride Indexed Monad, uses do syntax construction, has semantic checks, and is interpreted to the second layer m through runPeerWithDriver.mmiddle layer, describes the business requirements in this layer, and converts the received Msg into specific business actions.nbottom layer, responsible for receiving and sending bytes. It can have multiple options such as IO or IOSim. Using IOSim can easily test the code.
decodeLoop :: (Exception failure, MonadSTM n, MonadThrow n) => Tracer role' ps n -> Maybe bytes -> Decode role' ps failure bytes -> Channel n bytes -> TVar n (MsgCache role' ps) -> n () Source #
decode loop, usually in a separate thread.
The decoded Msg is placed in MsgCache.
data Msg role' ps (from :: ps) (sendAndSt :: (role', ps)) (recvAndSt :: (role', ps))
Note that when placing a new Msg in MsgCache, if a Msg with the same from already exists in MsgCache, the decoding process will be blocked,
until that Msg is consumed before placing the new Msg in MsgCache.
This usually happens when the efficiency of Msg generation is greater than the efficiency of consumption.