Skip to content

Commit 6a34ce9

Browse files
committed
Merge upstream
2 parents 36df5db + 0ea265f commit 6a34ce9

File tree

1 file changed

+261
-31
lines changed

1 file changed

+261
-31
lines changed

tutorials/ch6.md

Lines changed: 261 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -113,8 +113,8 @@ Each `Registry` server deals with specific types of keys and values. Allowing
113113
clients to send and receive instructions pertaining to a registry server without
114114
knowing the exact types the server was _spawned_ to handle, is a recipe for
115115
disaster, since the client is very likely to block indefinitely if the expected
116-
types do not match up, since the server will never process such requests.
117-
We can alleviate this problem using phantom type parameters, but storing only
116+
request types don't match up, since the server will ignore them.
117+
We can alleviate this problem using phantom type parameters, storing only
118118
the real `ProcessId` we need to communicate with the server, whilst utilising
119119
the compiler to ensure the correct types are assumed at both ends.
120120

@@ -216,7 +216,7 @@ types, so it is enough to provide just that instance for your handles.
216216

217217
Typed Channels can be used in two ways via the managed process API, either as
218218
inputs to the server or as a _reply channel_ for RPC style interactions that
219-
offer an alternative to the `call` approach.
219+
offer an alternative to using `call`.
220220

221221
#### Reply Channels
222222

@@ -225,9 +225,8 @@ match the type(s) the client expects. This will cause the client to either
225225
deadlock or timeout, depending on which variant of `call` was used. This isn't
226226
usually a problem, since the server author also writes the client facing API(s)
227227
and can therefore carefully check that the correct types are being returned.
228-
That's still potentially error prone during development however, and using a
229-
`SendPort` as a reply channel can make it easier to spot potential type
230-
discrepancies.
228+
That's still potentially error prone however, and using a `SendPort` as a reply
229+
channel can make it easier to spot potential type discrepancies.
231230

232231
The machinery behind _reply channels_ is very simple: We create a new channel
233232
for the reply and pass the `SendPort` to the server along with our input message.
@@ -245,7 +244,7 @@ server).
245244
------
246245

247246
Typed channels are better suited to handling deferred client-server RPC calls
248-
than plain inter-process messaging. The only non-blocking `call` API is based
247+
than plain inter-process messaging too. The only non-blocking `call` API is based
249248
on [`Async`][2] and its only failure mode is an `AsyncFailed` result containing
250249
a corresponding `ExitReason`. The `callTimeout` API is equally limited, since
251250
once its delay is exceeded (and the call times out), you cannot subsequently
@@ -257,13 +256,13 @@ a reply from the `ReceivePort` until it's ready, timeout waiting for the reply
257256
**and** try again at a later time and even wait on the results of multiple RPC
258257
calls (to one or _more_ servers) at the same by merging the ports.
259258

260-
We might wish to block and wait for a reply immediately, treating the API just
261-
we would `call`. Two blocking operations are provided to simplify this, one of
262-
which returns an `ExitReason` on failure, whilst the other crashes (with the given
263-
`ExitReason` of course!). The implementation is precisely what you'd expect a
264-
blocking _call_ to do, right up to monitoring the server for potential exit signals
265-
(so as not to deadlock the client if the server dies before replying) - all of
266-
which is handled by `awaitResponse` in the platform's `Primitives` module.
259+
If we wish to block and wait for a reply immediately (just as we would with `call`),
260+
two blocking operations are provided to simplify the task, one of which returns an
261+
`ExitReason` on failure, whilst the other crashes (with the given `ExitReason` of
262+
course!). The implementation is precisely what you'd expect a blocking _call_ to
263+
do, right up to monitoring the server for potential exit signals (so as not to
264+
deadlock the client if the server dies before replying) - all of which is handled
265+
by `awaitResponse` in the platform's `Primitives` module.
267266

268267
{% highlight haskell %}
269268
syncSafeCallChan server msg = do
@@ -277,8 +276,9 @@ with the programmer left to ensure the types always match up. In reality, there
277276
is a trade-off to be made however. Using the `handleCall` APIs means that our server
278277
side code can use the fluent server API for state changes, immediate replies and
279278
so on. None of these features will work with the corollary family of
280-
`handleRpcChan` functions. The difference is perhaps an aesthetic one, as the
281-
following example code demonstrates:
279+
`handleRpcChan` functions. Whether or not the difference is merely aesthetic, we
280+
leave as a question for the reader to determine. The following example demonstrates
281+
the use of reply channels:
282282

283283
{% highlight haskell %}
284284
-- two versions of the same handler, one for calls, one for typed (reply) channels
@@ -315,27 +315,256 @@ chanHandler = handleRpcChan $ \state port Input -> replyChan port Output >> cont
315315

316316
#### Input (Control) Channels
317317

318-
An alternative input plane for managed process servers, /control channels/ provide a
319-
number of benefits over the standard `call` and `cast` APIs. These include efficiency
320-
- _typed channels_ are very lightweight constructs! - and type safety, as well as
321-
giving the server the ability to prioritise information sent on control channels over
322-
other traffic.
318+
An alternative input plane managed process servers; _Control Channels_ provide a
319+
number of benefits above and beyond both the standard `call` and `cast` APIs and the
320+
use of reply channels. These include efficiency - _typed channels_ are very lightweight
321+
constructs in general! - and type safety, as well as giving the server the ability to
322+
prioritise information sent on control channels over other traffic.
323323

324324
Using typed channels as inputs to your managed process is _the_ most efficient way
325325
to enable client-server communication, particularly for intra-node traffic, due to
326326
their internal use of STM (and in particular, its use during selective receives).
327+
Control channels can provide an alternative to prioritised process definitions, since
328+
their use of channels ensures that, providing the control channel handler(s) occur
329+
in the process definition's `apiHandlers` list before the other dispatchers, any
330+
messages received on those channels will be prioritised over other traffic. This is
331+
the most efficient kind of prioritisation - not much use if you need to prioritise
332+
_info messages_ of course, but very useful if _control messages_ need to be given
333+
priority over other inputs.
327334

328-
In order to use control channels as input planes, it is necessary to _leak_ their
335+
------
336+
> ![Warning: ][alert] Control channels are **not** compatible with prioritised
337+
> process definitions! The type system does not prevent them from being declared
338+
> though, since they _are_ represented by a `Dispatcher` and therefore deemded
339+
> valid entries of the `apiHandlers` field. Upon startup, a prioritised process
340+
> definition that contains control channel dispatchers in its `apiHandlers` will
341+
> immediately exit with the reason `ExitOther "IllegalControlChannel"` though.
342+
------
343+
344+
In order to use a typed channel as an input plane, it is necessary to _leak_ the
329345
`SendPort` to your clients somehow. One way would be to `send` it on demand, but the
330-
simplest approach is actually to initialise a handle with all the relevant SendPorts
331-
and return this to the spawning process via an MVar (or similar construct). Because a
332-
`SendPort` is `Serializable`, forwarding them (or the handle they're contained within)
333-
is no problem either. Combining control channels with opaque handles is another great
334-
way to enforce additional type safety, since the channels must be initialised by the
335-
server code before it can create handlers for them and the client code that passes
336-
data to them (via the `SendPort`) is bound to exactly the same type(s)! This means that
337-
there can be no ambiguity and therefore no unhandled messages due to runtime type
338-
mismatches - the compiler will catch that sort of thing for us.
346+
simplest approach is actually to initialise a handle with all the relevant send ports
347+
and return this to the spawning process via a private channel, MVar or STM (or similar).
348+
Because a `SendPort` is `Serializable`, forwarding them (or the handle they're
349+
contained within) is no problem either.
350+
351+
Since typed channels are a one way street, there's no direct API support for RPC calls
352+
when using them to send data to a server. The work-around for this remains simple,
353+
type-safe and elegant though: we encode a reply channel into our command/request datum
354+
so the server knows where (and with what type) to reply. This does increase the amount
355+
of boilerplate code the client-facing API has to endure, but it's a small price to pay
356+
for the efficiency and additional type safety provided.
357+
358+
First, we'll look at an example of a single control channel being used with the
359+
`chanServe` API. This handles the messy details of passing the control channel back
360+
to the calling process, at least to some extent. For this example, we'll examine the
361+
[`Mailbox`][mailbox] module, since this combines a fire-and-forget control channel with
362+
an opaque server handle.
363+
364+
{% highlight haskell %}
365+
-- our handle is fairly simple
366+
data Mailbox = Mailbox { pid :: !ProcessId
367+
, cchan :: !(ControlPort ControlMessage)
368+
} deriving (Typeable, Generic, Eq)
369+
instance Binary Mailbox where
370+
371+
instance Linkable Mailbox where
372+
linkTo = link . pid
373+
374+
instance Resolvable Mailbox where
375+
resolve = return . Just . pid
376+
377+
-- lots of details elided....
378+
379+
-- Starting the mailbox involves both spawning, and passing back the process id,
380+
-- plus we need to get our hands on a control port for the control channel!
381+
382+
doStartMailbox :: Maybe SupervisorPid
383+
-> ProcessId
384+
-> BufferType
385+
-> Limit
386+
-> Process Mailbox
387+
doStartMailbox mSp p b l = do
388+
bchan <- liftIO $ newBroadcastTChanIO
389+
rchan <- liftIO $ atomically $ dupTChan bchan
390+
spawnLocal (maybeLink mSp >> runMailbox bchan p b l) >>= \pid -> do
391+
cc <- liftIO $ atomically $ readTChan rchan
392+
return $ Mailbox pid cc -- return our opaque handle!
393+
where
394+
maybeLink Nothing = return ()
395+
maybeLink (Just p') = link p'
396+
397+
runMailbox :: TChan (ControlPort ControlMessage)
398+
-> ProcessId
399+
-> BufferType
400+
-> Limit
401+
-> Process ()
402+
runMailbox tc pid buffT maxSz = do
403+
link pid
404+
tc' <- liftIO $ atomically $ dupTChan tc
405+
MP.chanServe (pid, buffT, maxSz) (mboxInit tc') (processDefinition pid tc)
406+
407+
mboxInit :: TChan (ControlPort ControlMessage)
408+
-> InitHandler (ProcessId, BufferType, Limit) State
409+
mboxInit tc (pid, buffT, maxSz) = do
410+
cc <- liftIO $ atomically $ readTChan tc
411+
return $ InitOk (State Seq.empty $ defaultState buffT maxSz pid cc) Infinity
412+
413+
processDefinition :: ProcessId
414+
-> TChan (ControlPort ControlMessage)
415+
-> ControlChannel ControlMessage
416+
-> Process (ProcessDefinition State)
417+
processDefinition pid tc cc = do
418+
liftIO $ atomically $ writeTChan tc $ channelControlPort cc
419+
return $ defaultProcess { apiHandlers = [
420+
handleControlChan cc handleControlMessages
421+
, Restricted.handleCall handleGetStats
422+
]
423+
, infoHandlers = [ handleInfo handlePost
424+
, handleRaw handleRawInputs ]
425+
, unhandledMessagePolicy = DeadLetter pid
426+
} :: Process (ProcessDefinition State)
427+
{% endhighlight %}
428+
429+
Since the rest of the mailbox initialisation code is quite complex, we'll leave it
430+
there for now. The important details to take away are the use of `chanServe`
431+
and its requirement for a thunk that initialises the `ProcessDefinition`, so it can
432+
perform IO - a pre-requisite to sharing the control channels with the spawning process,
433+
which must use STM or something similar in order to share data with the newly spawned
434+
server's initialisation code. In our case, we want to pass the control port from the
435+
thunk passed to `chanServe` back to both the spawning process _and_ the init function
436+
(which is normally de-coupled from the initialising thunk), which makes this a good
437+
example of how to utilise a broadcast TChan (or TQueue) to share control plane
438+
structures during initialisation.
439+
440+
------
441+
442+
Now we'll cook up another (contrived) example that uses multiple typed control channels,
443+
demonstrating how to create control channels explicitly, how to obtain a `ControlPort`
444+
for each one, one way of passing these back to the process spawning the server (so as
445+
to fill in the opaque server handle) and how to utilise these in your client code,
446+
complete with the use of typed reply channels. This code will not use `chanServe`,
447+
since _that_ API only supports a single control channel - the original purpose behind
448+
the control channel concept - and instead, we'll create the process loop ourselves,
449+
using the exported low level `recvLoop` function.
450+
451+
{% highlight haskell %}
452+
453+
type NumRequests = Int
454+
455+
data EchoServer = EchoServer { echoRequests :: ControlPort String
456+
, statRequests :: ControlPort NumRequests
457+
, serverPid :: ProcessId
458+
}
459+
deriving (Typeable, Generic)
460+
instance Binary EchoServer where
461+
instance NFData EchoServer where
462+
463+
instance Resolvable EchoServer where
464+
resolve = return . Just . serverPid
465+
466+
instance Linkable EchoServer where
467+
linkTo = link . serverPid
468+
469+
-- The server takes a String and returns it verbatim
470+
471+
data EchoRequest = EchoReq !String !(SendPort String)
472+
deriving (Typeable, Generic)
473+
instance Binary EchoRequest where
474+
instance NFData EchoRequest where
475+
476+
data StatsRequest = StatsReq !(SendPort Int)
477+
deriving (Typeable, Generic)
478+
instance Binary StatsRequest where
479+
instance NFData StatsRequest where
480+
481+
-- client code
482+
483+
echo :: EchoServer -> String -> Process String
484+
echo h s = do
485+
(sp, rp) <- newChan
486+
let req = EchoReq s sp
487+
sendControlMessage (echoRequests h) req
488+
receiveWait [ matchChan rp return ]
489+
490+
stats :: EchoServer -> Process NumRequests
491+
stats h = do
492+
(sp, rp) <- newChan
493+
let req = StatsReq sp
494+
sendControlMessage (statRequests h) req
495+
receiveWait [ matchChan rp return ]
496+
497+
demo :: Process ()
498+
demo = do
499+
server <- spawnEchoServer
500+
foobar <- echo server "foobar"
501+
foobar `shouldBe` equalTo "foobar"
502+
503+
baz <- echo server "baz"
504+
baz `shouldBe` equalTo baz
505+
506+
count <- stats server
507+
count `shouldBe` equalTo (2 :: NumRequests)
508+
509+
-- server code
510+
511+
spawnEchoServer :: Process EchoServer
512+
spawnEchoServer = do
513+
(sp, rp) <- newChan
514+
pid <- spawnLocal $ runEchoServer sp
515+
(echoPort, statsPort) <- receiveChan rp
516+
return $ EchoServer echoPort statsPort pid
517+
518+
runEchoServer :: SendPort (ControlPort EchoRequest, ControlPort StatsRequest)
519+
-> Process ()
520+
runEchoServer portsChan = do
521+
echoChan <- newControlChan
522+
echoPort <- channelControlPort echoChan
523+
statChan <- newControlChan
524+
statPort <- channelControlPort statChan
525+
sendChan portsChan (echoPort, statPort)
526+
runProcess (recvLoop $ echoServerDefinition echoChan statChan ) echoServerInit
527+
528+
echoServerInit :: InitHandler () NumRequests
529+
echoServerInit = return $ InitOk (0 :: Int) Infinity
530+
531+
echoServerDefinition :: ControlChannel EchoRequest
532+
-> ControlChannel StatsRequest
533+
-> ProcessDefinition NumRequests
534+
echoServerDefinition echoChan statChan =
535+
defaultProcess {
536+
apiHandlers = [ handleControlChan echoChan handleEcho
537+
, handleControlChan statChan handleStats
538+
]
539+
}
540+
541+
handleEcho :: NumRequests -> EchoRequest -> Process (ProcessAction State)
542+
handleEcho count (EchoReq req replyTo) = do
543+
replyChan replyTo req -- echo back the string
544+
continue $ count + 1
545+
546+
handleStats :: NumRequests -> StatsRequest -> Process (ProcessAction State)
547+
handleStats count (StatsReq replyTo) = do
548+
replyChan replyTo count
549+
continue count
550+
{% endhighlight %}
551+
552+
Although not very useful, this is a working example. Note that the client must
553+
deal with a `ControlPort` and not the complete `ControlChannel` itself. Also
554+
note that the server is completely responsible for replying (explicitly) to
555+
the client using the send ports supplied in the request data.
556+
557+
------
558+
> ![Info: ][info] Combining control channels with opaque handles is another great
559+
> way to enforce additional type safety, since the channels must be initialised by
560+
> the server code before it can create handlers for them and the client code that
561+
> passes data to them (via the `SendPort`) is bound to exactly the same type(s)!
562+
> Furthermore, adding reply channels (in the form of a `SendPort`) to the request
563+
> types ensures that the replies will be handled correctly as well! As a result,
564+
> there can be no ambiguity about the types involved for _either_ side of the
565+
> client-server relationship and therefore no unhandled messages due to runtime
566+
> type mismatches - the compiler will catch that sort of thing for us!
567+
------
339568

340569
[1]: http://hackage.haskell.org/package/distributed-process-platform/Control-Distributed-Process-Platform-Service-Registry.html
341570
[2]: http://hackage.haskell.org/package/distributed-process-platform/Control-Distributed-Process-Platform-Async.html
@@ -347,4 +576,5 @@ mismatches - the compiler will catch that sort of thing for us.
347576
[alert]: /img/alert.png
348577
[info]: /img/info.png
349578
[policy]: http://hackage.haskell.org/package/distributed-process-platform/Control-Distributed-Process-Platform-ManagedProcess.html#t:UnhandledMessagePolicy
579+
[mailbox]: http://hackage.haskell.org/package/distributed-process-platform/Control-Distributed-Process-Platform-Execution-Mailbox.html
350580

0 commit comments

Comments
 (0)