~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to erts/doc/src/alt_dist.xml

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
<?xml version="1.0" encoding="latin1" ?>
 
2
<!DOCTYPE chapter SYSTEM "chapter.dtd">
 
3
 
 
4
<chapter>
 
5
  <header>
 
6
    <copyright>
 
7
      <year>2000</year>
 
8
      <year>2007</year>
 
9
      <holder>Ericsson AB, All Rights Reserved</holder>
 
10
    </copyright>
 
11
    <legalnotice>
 
12
  The contents of this file are subject to the Erlang Public License,
 
13
  Version 1.1, (the "License"); you may not use this file except in
 
14
  compliance with the License. You should have received a copy of the
 
15
  Erlang Public License along with this software. If not, it can be
 
16
  retrieved online at http://www.erlang.org/.
 
17
 
 
18
  Software distributed under the License is distributed on an "AS IS"
 
19
  basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
20
  the License for the specific language governing rights and limitations
 
21
  under the License.
 
22
 
 
23
  The Initial Developer of the Original Code is Ericsson AB.
 
24
    </legalnotice>
 
25
 
 
26
    <title>How to implement an alternative carrier for  the Erlang distribution</title>
 
27
    <prepared>Patrik Nyblom</prepared>
 
28
    <responsible></responsible>
 
29
    <docno></docno>
 
30
    <approved></approved>
 
31
    <checked></checked>
 
32
    <date>2000-10-17</date>
 
33
    <rev>PA2</rev>
 
34
    <file>alt_dist.sgml</file>
 
35
  </header>
 
36
  <p>This document describes how one can implement ones own carrier
 
37
    protocol for the Erlang distribution. The distribution is normally
 
38
    carried by the TCP/IP protocol. What's explained here is the method for 
 
39
    replacing TCP/IP with another protocol. </p>
 
40
  <p>The document is a step by step explanation of the <c><![CDATA[uds_dist]]></c> example 
 
41
    application (seated in the kernel applications <c><![CDATA[examples]]></c> directory). 
 
42
    The <c><![CDATA[uds_dist]]></c> application implements distribution over Unix domain 
 
43
    sockets and is written for the Sun Solaris 2 operating environment. The 
 
44
    mechanisms are however general and applies to any operating system Erlang 
 
45
    runs on. The reason the C code is not made portable, is simply readability.</p>
 
46
  <p></p>
 
47
 
 
48
  <section>
 
49
    <title>Introduction</title>
 
50
    <p>To implement a new carrier for the Erlang distribution, one must first
 
51
      make the protocol available to the Erlang machine, which involves writing 
 
52
      an Erlang driver. There is no way one can use a port program,
 
53
      there <em>has</em> to
 
54
      be an Erlang driver. Erlang drivers can either be statically
 
55
      linked
 
56
      to the emulator, which can be an alternative when using the open source
 
57
      distribution of Erlang, or dynamically loaded into the Erlang machines
 
58
      address space, which is the only alternative if a precompiled version of 
 
59
      Erlang is to be used. </p>
 
60
    <p>Writing an Erlang driver is by no means easy. The driver is written 
 
61
      as a couple of call-back functions called by the Erlang emulator when
 
62
      data is sent to the driver or the driver has any data available on a file
 
63
      descriptor. As the driver call-back routines execute in the main
 
64
      thread of the Erlang machine, the call-back functions can perform
 
65
      no blocking activity whatsoever. The call-backs should only set up
 
66
      file descriptors for waiting and/or read/write available data. All
 
67
      I/O has to be non blocking. Driver call-backs are however executed
 
68
      in sequence, why a global state can safely be updated within the
 
69
      routines. </p>
 
70
    <p>When the driver is implemented, one would preferably write an
 
71
      Erlang interface for the driver to be able to test the
 
72
      functionality of the driver separately. This interface can then
 
73
      be used by the distribution module which will cover the details of
 
74
      the protocol from the <c><![CDATA[net_kernel]]></c>. The easiest path is to
 
75
      mimic the <c><![CDATA[inet]]></c> and <c><![CDATA[gen_tcp]]></c> interfaces, but a lot of
 
76
      functionality in those modules need not be implemented. In the
 
77
      example application, only a few of the usual interfaces are
 
78
      implemented, and they are much simplified.</p>
 
79
    <p>When the protocol is available to Erlang through a driver and an
 
80
      Erlang interface module, a distribution module can be
 
81
      written. The distribution module is a module with well defined
 
82
      call-backs, much like a <c><![CDATA[gen_server]]></c> (there is no compiler support
 
83
      for checking the call-backs though). The details of finding other
 
84
      nodes (i.e. talking to epmd or something similar), creating a
 
85
      listen port (or similar), connecting to other nodes and performing
 
86
      the handshakes/cookie verification are all implemented by this
 
87
      module. There is however a utility module, <c><![CDATA[dist_util]]></c>, that
 
88
      will do most of the hard work of handling handshakes, cookies,
 
89
      timers and ticking. Using <c><![CDATA[dist_util]]></c> makes implementing a
 
90
      distribution module much easier and that's what we are doing in
 
91
      the example application.</p>
 
92
    <p>The last step is to create boot scripts to make the protocol
 
93
      implementation available at boot time. The implementation can be
 
94
      debugged by starting the distribution when all of the system is
 
95
      running, but in a real system the distribution should start very
 
96
      early, why a boot-script and some command line parameters are
 
97
      necessary. This last step also implies that the Erlang code in the 
 
98
      interface and distribution modules is written in such a way that
 
99
      it can be run in the startup phase. Most notably there can be no
 
100
      calls to the <c><![CDATA[application]]></c> module or to any modules not
 
101
      loaded at boot-time (i.e. only <c><![CDATA[kernel]]></c>, <c><![CDATA[stdlib]]></c> and the
 
102
      application itself can be used).</p>
 
103
  </section>
 
104
 
 
105
  <section>
 
106
    <title>The driver</title>
 
107
    <p>Although Erlang drivers in general may be beyond the scope of this
 
108
      document, a brief introduction seems to be in place.</p>
 
109
 
 
110
    <section>
 
111
      <title>Drivers in general</title>
 
112
      <p>An Erlang driver is a native code module written in C (or
 
113
        assembler) which serves as an interface for some special operating
 
114
        system service. This is a general mechanism that is used
 
115
        throughout the Erlang emulator for all kinds of I/O. An Erlang
 
116
        driver can be dynamically linked (or loaded) to the Erlang
 
117
        emulator at runtime by using the <c><![CDATA[erl_ddll]]></c> Erlang
 
118
        module. Some of the drivers in OTP are however statically linked
 
119
        to the runtime system, but that's more an optimization than a
 
120
        necessity.</p>
 
121
      <p>The driver data-types and the functions available to the driver
 
122
        writer are defined in the header file <c><![CDATA[erl_driver.h]]></c> (there
 
123
        is also an deprecated version called <c><![CDATA[driver.h]]></c>, don't use
 
124
        that one.) seated in Erlang's include directory (and in
 
125
        $ERL_TOP/erts/emulator/beam in the source code
 
126
        distribution). Refer to that file for function prototypes etc.</p>
 
127
      <p>When writing a driver to make a communications protocol available
 
128
        to Erlang, one should know just about everything worth knowing
 
129
        about that particular protocol. All operation has to be non
 
130
        blocking and all possible situations should be accounted for in
 
131
        the driver. A non stable driver will affect and/or crash the
 
132
        whole Erlang runtime system, which is seldom what's wanted. </p>
 
133
      <p>The emulator calls the driver in the following situations:</p>
 
134
      <list type="bulleted">
 
135
        <item>When the driver is loaded. This call-back has to have a
 
136
         special name and will inform the emulator of what call-backs should
 
137
         be used by returning a pointer to a <c><![CDATA[ErlDrvEntry]]></c> struct,
 
138
         which should be properly filled in (see below).</item>
 
139
        <item>When a port to the driver is opened (by a <c><![CDATA[open_port]]></c>
 
140
         call from Erlang). This routine should set up internal data
 
141
         structures and return an opaque data entity of the type
 
142
        <c><![CDATA[ErlDrvData]]></c>, which is a data-type large enough to hold a
 
143
         pointer. The pointer returned by this function will be the first
 
144
         argument to all other call-backs concerning this particular
 
145
         port. It is usually called the port handle. The emulator only
 
146
         stores the handle and does never try to interpret it, why it can
 
147
         be virtually anything (well anything not larger than a pointer
 
148
         that is) and can point to anything if it is a pointer. Usually
 
149
         this pointer will refer to a structure holding information about
 
150
         the particular port, as i t does in our example.</item>
 
151
        <item>When an Erlang process sends data to the port. The data will
 
152
         arrive as a buffer of bytes, the interpretation is not defined,
 
153
         but is up to the implementor. This call-back returns nothing to the
 
154
         caller, answers are sent to the caller as messages (using a
 
155
         routine called <c><![CDATA[driver_output]]></c> available to all
 
156
         drivers). There is also a way to talk in a synchronous way to
 
157
         drivers, described below. There can be an additional call-back
 
158
         function for handling data that is fragmented (sent in a deep
 
159
         io-list). That interface will get the data in a form suitable for
 
160
         Unix <c><![CDATA[writev]]></c> rather than in a single buffer. There is no
 
161
         need for a distribution driver to implement such a call-back, so
 
162
         we wont.</item>
 
163
        <item>When a file descriptor is signaled for input. This call-back
 
164
         is called when the emulator detects input on a file descriptor
 
165
         which the driver has marked for monitoring by using the interface
 
166
        <c><![CDATA[driver_select]]></c>. The mechanism of driver select makes it
 
167
         possible to read non blocking from file descriptors by calling
 
168
        <c><![CDATA[driver_select]]></c> when reading is needed and then do the actual
 
169
         reading in this call-back (when reading is actually possible). The
 
170
         typical scenario is that <c><![CDATA[driver_select]]></c> is called when an 
 
171
         Erlang process orders a read operation, and that this routine
 
172
         sends the answer when data is available on the file descriptor.</item>
 
173
        <item>When a file descriptor is signaled for output. This call-back
 
174
         is called in a similar way as the previous, but when writing to a
 
175
         file descriptor is possible. The usual scenario is that Erlang
 
176
         orders writing on a file descriptor and that the driver calls
 
177
        <c><![CDATA[driver_select]]></c>. When the descriptor is ready for output,
 
178
         this call-back is called an the driver can try to send the
 
179
         output. There may of course be queuing involved in such
 
180
         operations, and there are some convenient queue routines available
 
181
         to the driver writer to use in such situations.</item>
 
182
        <item>When a port is closed, either by an Erlang process or by the
 
183
         driver calling one of the <c><![CDATA[driver_failure_XXX]]></c> routines. This
 
184
         routine should clean up everything connected to one particular
 
185
         port. Note that when other call-backs call a
 
186
        <c><![CDATA[driver_failure_XXX]]></c> routine, this routine will be
 
187
         immediately called and the call-back routine issuing the error can
 
188
         make no more use of the data structures for the port, as this
 
189
         routine surely has freed all associated data and closed all file
 
190
         descriptors. If the queue utility available to driver writes is
 
191
         used, this routine will however <em>not</em> be called until the
 
192
         queue is empty.</item>
 
193
        <item>When an Erlang process calls <c><![CDATA[erlang:driver_control/2]]></c>,
 
194
         which is a synchronous interface to drivers. The control interface
 
195
         is used to set driver options, change states of ports etc. We'll
 
196
         use this interface quite a lot in our example.</item>
 
197
        <item>When a timer expires. The driver can set timers with the
 
198
         function <c><![CDATA[driver_set_timer]]></c>. When such timers expire, a
 
199
         specific call-back function is called. We will not use timers in
 
200
         our example.</item>
 
201
        <item>When the whole driver is unloaded. Every resource allocated
 
202
         by the driver should be freed.</item>
 
203
      </list>
 
204
    </section>
 
205
 
 
206
    <section>
 
207
      <title>The distribution driver's data structures</title>
 
208
      <p>The driver used for Erlang distribution should implement a
 
209
        reliable, order maintaining, variable length packet oriented
 
210
        protocol. All error correction, re-sending and such need to be
 
211
        implemented in the driver or by the underlying communications
 
212
        protocol. If the protocol is stream oriented (as is the case with
 
213
        both TCP/IP and our streamed Unix domain sockets), some mechanism
 
214
        for packaging is needed. We will use the simple method of having a
 
215
        header of four bytes containing the length of the package in a big
 
216
        endian 32 bit integer (as Unix domain sockets only can be used
 
217
        between processes on the same machine, we actually don't need to
 
218
        code the integer in some special endianess, but I'll do it anyway
 
219
        because in most situation you do need to do it. Unix domain
 
220
        sockets are reliable and order maintaining, so we don't need to
 
221
        implement resends and such in our driver.</p>
 
222
      <p>Lets start writing our example Unix domain sockets driver by
 
223
        declaring prototypes and filling in a static ErlDrvEntry
 
224
        structure.</p>
 
225
      <code type="none"><![CDATA[
 
226
( 1) #include <stdio.h>
 
227
( 2) #include <stdlib.h>
 
228
( 3) #include <string.h>
 
229
( 4) #include <unistd.h>
 
230
( 5) #include <errno.h>
 
231
( 6) #include <sys/types.h>
 
232
( 7) #include <sys/stat.h>
 
233
( 8) #include <sys/socket.h>
 
234
( 9) #include <sys/un.h>
 
235
(10) #include <fcntl.h>
 
236
 
 
237
(11) #define HAVE_UIO_H
 
238
(12) #include "erl_driver.h"
 
239
 
 
240
(13) /*
 
241
(14) ** Interface routines
 
242
(15) */
 
243
(16) static ErlDrvData uds_start(ErlDrvPort port, char *buff);
 
244
(17) static void uds_stop(ErlDrvData handle);
 
245
(18) static void uds_command(ErlDrvData handle, char *buff, int bufflen);
 
246
(19) static void uds_input(ErlDrvData handle, ErlDrvEvent event);
 
247
(20) static void uds_output(ErlDrvData handle, ErlDrvEvent event);
 
248
(21) static void uds_finish(void);
 
249
(22) static int uds_control(ErlDrvData handle, unsigned int command, 
 
250
(23)                        char* buf, int count, char** res, int res_size);
 
251
 
 
252
(24) /* The driver entry */
 
253
(25) static ErlDrvEntry uds_driver_entry = {
 
254
(26)     NULL,                  /* init, N/A */
 
255
(27)     uds_start,             /* start, called when port is opened */
 
256
(28)     uds_stop,              /* stop, called when port is closed */
 
257
(29)     uds_command,           /* output, called when erlang has sent */
 
258
(30)     uds_input,             /* ready_input, called when input descriptor 
 
259
(31)                               ready */
 
260
(32)     uds_output,            /* ready_output, called when output 
 
261
(33)                               descriptor ready */
 
262
(34)     "uds_drv",             /* char *driver_name, the argument 
 
263
(35)                               to open_port */
 
264
(36)     uds_finish,            /* finish, called when unloaded */
 
265
(37)     NULL,                  /* void * that is not used (BC) */
 
266
(38)     uds_control,           /* control, port_control callback */
 
267
(39)     NULL,                  /* timeout, called on timeouts */
 
268
(40)     NULL                   /* outputv, vector output interface */
 
269
(41) };          ]]></code>
 
270
      <p>On line 1 to 10 we have included the OS headers needed for our
 
271
        driver. As this driver is written for Solaris, we know that the
 
272
        header <c><![CDATA[uio.h]]></c> exists, why we can define the preprocessor
 
273
        variable <c><![CDATA[HAVE_UIO_H]]></c> before we include <c><![CDATA[erl_driver.h]]></c> 
 
274
        at line 12. The definition of <c><![CDATA[HAVE_UIO_H]]></c> will make the
 
275
        I/O vectors used in Erlang's driver queues to correspond to the
 
276
        operating systems ditto, which is very convenient.</p>
 
277
      <p>The different call-back functions are declared ("forward
 
278
        declarations") on line 16 to 23.</p>
 
279
      <p>The driver structure is similar for statically linked in
 
280
        drivers an dynamically loaded. However some of the fields
 
281
        should be left empty (i.e. initialized to NULL) in the
 
282
        different types of drivers. The first field (the <c><![CDATA[init]]></c>
 
283
        function pointer) is always left blank in a dynamically loaded
 
284
        driver, which can be seen on line 26. The NULL on line 37
 
285
        should always be there, the field is no longer used and is
 
286
        retained for backward compatibility. We use no timers in this
 
287
        driver, why no call-back for timers is needed. The last field
 
288
        (line 40) can be used to implement an interface similar to
 
289
        Unix <c><![CDATA[writev]]></c> for output. There is no need for such
 
290
        interface in a distribution driver, so we leave it with a NULL
 
291
        value (We will however use scatter/gather I/O internally in 
 
292
        the driver). </p>
 
293
      <p>Our defined call-backs thus are:</p>
 
294
      <list type="bulleted">
 
295
        <item>uds_start, which shall initiate data for a port. We wont
 
296
         create any actual sockets here, just initialize data structures.</item>
 
297
        <item>uds_stop, the function called when a port is closed.</item>
 
298
        <item>uds_command, which will handle messages from Erlang. The
 
299
         messages can either be plain data to be sent or more subtle
 
300
         instructions to the driver. We will use this function mostly for
 
301
         data pumping.</item>
 
302
        <item>uds_input, this is the call-back which is called when we have
 
303
         something to read from a socket.</item>
 
304
        <item>uds_output, this is the function called when we can write to a
 
305
         socket.</item>
 
306
        <item>uds_finish, which is called when the driver is unloaded. A
 
307
         distribution driver will actually (or hopefully) never be unloaded,
 
308
         but we include this for completeness. Being able to clean up after
 
309
         oneself is always a good thing.</item>
 
310
        <item>uds_control, the <c><![CDATA[erlang:port_control/2]]></c> call-back, which
 
311
         will be used a lot in this implementation.</item>
 
312
      </list>
 
313
      <p>The ports implemented by this driver will operate in two major
 
314
        modes, which i will call the <em>command</em> and <em>data</em>
 
315
        modes. In command mode, only passive reading and writing (like
 
316
        gen_tcp:recv/gen_tcp:send) can be
 
317
        done, and this is the mode the port will be in during the
 
318
        distribution handshake. When the connection is up, the port will
 
319
        be switched to data mode and all data will be immediately read and
 
320
        passed further to the Erlang emulator. In data mode, no data
 
321
        arriving to the uds_command will be interpreted, but just packaged
 
322
        and sent out on the socket. The uds_control call-back will do the
 
323
        switching between those two modes.</p>
 
324
      <p>While the <c><![CDATA[net_kernel]]></c> informs different subsystems that the
 
325
        connection is coming up, the port should accept data to send, but
 
326
        not receive any data, to avoid that data arrives from another node
 
327
        before every kernel subsystem is prepared to handle it. We have a
 
328
        third mode for this intermediate stage, lets call it the
 
329
        <em>intermediate</em> mode.</p>
 
330
      <p>Lets define an enum for the different types of ports we have:</p>
 
331
      <code type="none"><![CDATA[
 
332
( 1) typedef enum { 
 
333
( 2)     portTypeUnknown,      /* An uninitialized port */
 
334
( 3)     portTypeListener,     /* A listening port/socket */
 
335
( 4)     portTypeAcceptor,     /* An intermidiate stage when accepting 
 
336
( 5)                              on a listen port */
 
337
( 6)     portTypeConnector,    /* An intermediate stage when connecting */
 
338
( 7)     portTypeCommand,      /* A connected open port in command mode */
 
339
( 8)     portTypeIntermediate, /* A connected open port in special
 
340
( 9)                              half active mode */
 
341
(10)     portTypeData          /* A connectec open port in data mode */ 
 
342
(11) } PortType;      ]]></code>
 
343
      <p>Lets look at the different types:</p>
 
344
      <list type="bulleted">
 
345
        <item>portTypeUnknown - The type a port has when it's opened, but
 
346
         not actually bound to any file descriptor.</item>
 
347
        <item>portTypeListener - A port that is connected to a listen
 
348
         socket. This port will not do especially much, there will be no data
 
349
         pumping done on this socket, but there will be read data available
 
350
         when one is trying to do an accept on the port.</item>
 
351
        <item>portTypeAcceptor - This is a port that is to represent the
 
352
         result of an accept operation. It is created when one wants to
 
353
         accept from a listen socket, and it will be converted to a
 
354
         portTypeCommand when the accept succeeds.</item>
 
355
        <item>portTypeConnector - Very similar to portTypeAcceptor, an
 
356
         intermediate stage between the request for a connect operation and
 
357
         that the socket is really connected to an accepting ditto in the
 
358
         other end. As soon as the sockets are connected, the port will
 
359
         switch type to portTypeCommand.</item>
 
360
        <item>portTypeCommand - A connected socket (or accepted socket if
 
361
         you want) that is in the command mode mentioned earlier.</item>
 
362
        <item>portTypeIntermediate - The intermediate stage for a connected
 
363
         socket. There should be no processing of input for this socket.</item>
 
364
        <item>portTypeData - The mode where data is pumped through the port
 
365
         and the uds_command routine will regard every call as a call where
 
366
         sending is wanted. In this mode all input available will be read and
 
367
         sent to Erlang as soon as it arrives on the socket, much like in the
 
368
         active mode of a <c><![CDATA[gen_tcp]]></c> socket.</item>
 
369
      </list>
 
370
      <p>Now lets look at the state we'll need for our ports. One can note
 
371
        that not all fields are used for all types of ports and that one
 
372
        could save some space by using unions, but that would clutter the
 
373
        code with multiple indirections, so i simply use one struct for
 
374
        all types of ports, for readability.</p>
 
375
      <code type="none"><![CDATA[
 
376
( 1) typedef unsigned char Byte;
 
377
( 2) typedef unsigned int Word;
 
378
 
 
379
( 3) typedef struct uds_data {
 
380
( 4)     int fd;                   /* File descriptor */
 
381
( 5)     ErlDrvPort port;          /* The port identifier */
 
382
( 6)     int lockfd;               /* The file descriptor for a lock file in 
 
383
( 7)                                  case of listen sockets */
 
384
( 8)     Byte creation;            /* The creation serial derived from the 
 
385
( 9)                                  lockfile */
 
386
(10)     PortType type;            /* Type of port */
 
387
(11)     char *name;               /* Short name of socket for unlink */
 
388
(12)     Word sent;                /* Bytes sent */
 
389
(13)     Word received;            /* Bytes received */
 
390
(14)     struct uds_data *partner; /* The partner in an accept/listen pair */
 
391
(15)     struct uds_data *next;    /* Next structure in list */
 
392
(16)     /* The input buffer and it's data */
 
393
(17)     int buffer_size;          /* The allocated size of the input buffer */
 
394
(18)     int buffer_pos;           /* Current position in input buffer */
 
395
(19)     int header_pos;           /* Where the current header is in the 
 
396
(20)                                  input buffer */
 
397
(21)     Byte *buffer;             /* The actual input buffer */
 
398
(22) } UdsData;      ]]></code>
 
399
      <p>This structure is used for all types of ports although some
 
400
        fields are useless for some types. The least memory consuming
 
401
        solution would be to arrange this structure as a union of
 
402
        structures, but the multiple indirections in the code to
 
403
        access a field in such a structure will clutter the code to
 
404
        much for an example.</p>
 
405
      <p>Let's look at the fields in our structure:</p>
 
406
      <list type="bulleted">
 
407
        <item>fd - The file descriptor of the socket associated with the
 
408
         port.</item>
 
409
        <item>port - The port identifier for the port which this structure
 
410
         corresponds to. It is needed for most <c><![CDATA[driver_XXX]]></c>
 
411
         calls from the driver back to the emulator.</item>
 
412
        <item>
 
413
          <p>lockfd - If the socket is a listen socket, we use a separate
 
414
            (regular) file for two purposes:</p>
 
415
          <list type="bulleted">
 
416
            <item>We want a locking mechanism that gives no race
 
417
             conditions, so that we can be sure of if another Erlang
 
418
             node uses the listen socket name we require or if the
 
419
             file is only left there from a previous (crashed)
 
420
             session.</item>
 
421
            <item>
 
422
              <p>We store the <em>creation</em> serial number in the
 
423
                file. The <em>creation</em> is a number that should
 
424
                change between different instances of different Erlang
 
425
                emulators with the same name, so that process
 
426
                identifiers from one emulator won't be valid when sent
 
427
                to a new emulator with the same distribution name. The
 
428
                creation can be between 0 and 3 (two bits) and is stored
 
429
                in every process identifier sent to another node. </p>
 
430
              <p>In a system with TCP based distribution, this data is
 
431
                kept in the <em>Erlang port mapper daemon</em>
 
432
                (<c><![CDATA[epmd]]></c>), which is contacted when a distributed
 
433
                node starts. The lock-file and a convention for the UDS
 
434
                listen socket's name will remove the need for
 
435
                <c><![CDATA[epmd]]></c> when using this distribution module. UDS
 
436
                is always restricted to one host, why avoiding a port
 
437
                mapper is easy.</p>
 
438
            </item>
 
439
          </list>
 
440
        </item>
 
441
        <item>creation - The creation number for a listen socket, which is
 
442
         calculated as (the value found in the lock-file + 1) rem
 
443
         4. This creation value is also written back into the
 
444
         lock-file, so that the next invocation of the emulator will
 
445
         found our value in the file.</item>
 
446
        <item>type - The current type/state of the port, which can be one
 
447
         of the values declared above.</item>
 
448
        <item>name - The name of the socket file (the path prefix
 
449
         removed), which allows for deletion (<c><![CDATA[unlink]]></c>) when the
 
450
         socket is closed.</item>
 
451
        <item>sent - How many bytes that have been sent over the
 
452
         socket. This may wrap, but that's no problem for the
 
453
         distribution, as the only thing that interests the Erlang
 
454
         distribution is if this value has changed (the Erlang
 
455
         net_kernel <em>ticker</em> uses this value by calling the
 
456
         driver to fetch it, which is done through the driver_control
 
457
         routine).</item>
 
458
        <item>received - How many bytes that are read (received) from the
 
459
         socket, used in similar ways as <c><![CDATA[sent]]></c>.</item>
 
460
        <item>partner - A pointer to another port structure, which is
 
461
         either the listen port from which this port is accepting a
 
462
         connection or the other way around. The "partner relation"
 
463
         is always bidirectional.</item>
 
464
        <item>next - Pointer to next structure in a linked list of all
 
465
         port structures. This list is used when accepting
 
466
         connections and when the driver is unloaded.</item>
 
467
        <item>buffer_size, buffer_pos, header_pos, buffer - data for input
 
468
         buffering. Refer to the source code (in the kernel/examples
 
469
         directory) for details about the input buffering. That
 
470
         certainly goes beyond the scope of this document.</item>
 
471
      </list>
 
472
    </section>
 
473
 
 
474
    <section>
 
475
      <title>Selected parts of the distribution driver implementation</title>
 
476
      <p>The distribution drivers implementation is not completely
 
477
        covered in this text, details about buffering and other things
 
478
        unrelated to driver writing are not explained. Likewise are
 
479
        some peculiarities of the UDS protocol not explained in
 
480
        detail. The chosen protocol is not important.</p>
 
481
      <p>Prototypes for the driver call-back routines can be found in
 
482
        the <c><![CDATA[erl_driver.h]]></c> header file.</p>
 
483
      <p>The driver initialization routine is (usually) declared with a
 
484
        macro to make the driver easier to port between different
 
485
        operating systems (and flavours of systems). This is the only
 
486
        routine that has to have a well defined name. All other
 
487
        call-backs are reached through the driver structure. The macro
 
488
        to use is named <c><![CDATA[DRIVER_INIT]]></c> and takes the driver name
 
489
        as parameter.</p>
 
490
      <code type="none"><![CDATA[
 
491
(1) /* Beginning of linked list of ports */
 
492
(2) static UdsData *first_data;
 
493
 
 
494
 
 
495
(3) DRIVER_INIT(uds_drv)
 
496
(4) {
 
497
(5)     first_data = NULL;
 
498
(6)     return &uds_driver_entry;
 
499
(7) }      ]]></code>
 
500
      <p>The routine initializes the single global data structure and
 
501
        returns a pointer to the driver entry. The routine will be
 
502
        called when <c><![CDATA[erl_ddll:load_driver]]></c> is called from Erlang.</p>
 
503
      <p>The <c><![CDATA[uds_start]]></c> routine is called when a port is opened
 
504
        from Erlang. In our case, we only allocate a structure and
 
505
        initialize it. Creating the actual socket is left to the
 
506
        <c><![CDATA[uds_command]]></c> routine.</p>
 
507
      <code type="none"><![CDATA[
 
508
( 1) static ErlDrvData uds_start(ErlDrvPort port, char *buff)
 
509
( 2) {
 
510
( 3)     UdsData *ud;
 
511
( 4)     
 
512
( 5)     ud = ALLOC(sizeof(UdsData));
 
513
( 6)     ud->fd = -1;
 
514
( 7)     ud->lockfd = -1;
 
515
( 8)     ud->creation = 0;
 
516
( 9)     ud->port = port;
 
517
(10)     ud->type = portTypeUnknown;
 
518
(11)     ud->name = NULL;
 
519
(12)     ud->buffer_size = 0;
 
520
(13)     ud->buffer_pos = 0;
 
521
(14)     ud->header_pos = 0;
 
522
(15)     ud->buffer = NULL;
 
523
(16)     ud->sent = 0;
 
524
(17)     ud->received = 0;
 
525
(18)     ud->partner = NULL;
 
526
(19)     ud->next = first_data;
 
527
(20)     first_data = ud;
 
528
(21)     
 
529
(22)     return((ErlDrvData) ud);
 
530
(23) }      ]]></code>
 
531
      <p>Every data item is initialized, so that no problems will arise
 
532
        when a newly created port is closed (without there being any
 
533
        corresponding socket). This routine is called when
 
534
        <c><![CDATA[open_port({spawn, "uds_drv"},[])]]></c> is called from Erlang.</p>
 
535
      <p>The <c><![CDATA[uds_command]]></c> routine is the routine called when an
 
536
        Erlang process sends data to the port. All asynchronous
 
537
        commands when the port is in <em>command mode</em> as well as 
 
538
        the sending of all data when the port is in <em>data mode</em>
 
539
        is handled in this9s routine. Let's have a look at it:</p>
 
540
      <code type="none"><![CDATA[
 
541
( 1) static void uds_command(ErlDrvData handle, char *buff, int bufflen)
 
542
( 2) {
 
543
( 3)     UdsData *ud = (UdsData *) handle;
 
544
 
 
545
( 4)     if (ud->type == portTypeData || ud->type == portTypeIntermediate) {
 
546
( 5)         DEBUGF(("Passive do_send %d",bufflen));
 
547
( 6)         do_send(ud, buff + 1, bufflen - 1); /* XXX */
 
548
( 7)         return;
 
549
( 8)     } 
 
550
( 9)     if (bufflen == 0) {
 
551
(10)         return;
 
552
(11)     }
 
553
(12)     switch (*buff) {
 
554
(13)     case 'L':
 
555
(14)         if (ud->type != portTypeUnknown) {
 
556
(15)             driver_failure_posix(ud->port, ENOTSUP);
 
557
(16)             return;
 
558
(17)         }
 
559
(18)         uds_command_listen(ud,buff,bufflen);
 
560
(19)         return;
 
561
(20)     case 'A':
 
562
(21)         if (ud->type != portTypeUnknown) {
 
563
(22)             driver_failure_posix(ud->port, ENOTSUP);
 
564
(23)             return;
 
565
(24)         }
 
566
(25)         uds_command_accept(ud,buff,bufflen);
 
567
(26)         return;
 
568
(27)     case 'C':
 
569
(28)         if (ud->type != portTypeUnknown) {
 
570
(29)             driver_failure_posix(ud->port, ENOTSUP);
 
571
(30)             return;
 
572
(31)         }
 
573
(32)         uds_command_connect(ud,buff,bufflen);
 
574
(33)         return;
 
575
(34)     case 'S':
 
576
(35)         if (ud->type != portTypeCommand) {
 
577
(36)             driver_failure_posix(ud->port, ENOTSUP);
 
578
(37)             return;
 
579
(38)         }
 
580
(39)         do_send(ud, buff + 1, bufflen - 1);
 
581
(40)         return;
 
582
(41)     case 'R':
 
583
(42)         if (ud->type != portTypeCommand) {
 
584
(43)             driver_failure_posix(ud->port, ENOTSUP);
 
585
(44)             return;
 
586
(45)         }
 
587
(46)         do_recv(ud);
 
588
(47)         return;
 
589
(48)     default:
 
590
(49)         return;
 
591
(50)     }
 
592
(51) }      ]]></code>
 
593
      <p>The command routine takes three parameters; the handle
 
594
        returned for the port by <c><![CDATA[uds_start]]></c>, which is a pointer
 
595
        to the internal port structure, the data buffer and the length
 
596
        of the data buffer. The buffer is the data sent from Erlang
 
597
        (a list of bytes) converted to an C array (of bytes). </p>
 
598
      <p>If Erlang sends i.e. the list <c><![CDATA[[$a,$b,$c]]]></c> to the port,
 
599
        the <c><![CDATA[bufflen]]></c> variable will be <c><![CDATA[3]]></c> ant the
 
600
        <c><![CDATA[buff]]></c> variable will contain <c><![CDATA[{'a','b','c'}]]></c> (no
 
601
        null termination). Usually the first byte is used as an
 
602
        opcode, which is the case in our driver to (at least when the
 
603
        port is in command mode). The opcodes are defined as:</p>
 
604
      <list type="bulleted">
 
605
        <item>'L'&lt;socketname&gt;: Create and listen on socket with the
 
606
         given name.</item>
 
607
        <item>'A'&lt;listennumber as 32 bit bigendian&gt;: Accept from the
 
608
         listen socket identified by the given identification
 
609
         number. The identification number is retrieved with the
 
610
         uds_control routine.</item>
 
611
        <item>'C'&lt;socketname&gt;: Connect to the socket named
 
612
         &lt;socketname&gt;.</item>
 
613
        <item>'S'&lt;data&gt;: Send the data &lt;data&gt; on the
 
614
         connected/accepted socket (in command mode). The sending is
 
615
         acked when the data has left this process.</item>
 
616
        <item>'R': Receive one packet of data.</item>
 
617
      </list>
 
618
      <p>One may wonder what is meant by "one packet of data" in the
 
619
        'R' command. This driver always sends data packeted with a 4
 
620
        byte header containing a big endian 32 bit integer that
 
621
        represents the length of the data in the packet. There is no
 
622
        need for different packet sizes or some kind of streamed
 
623
        mode, as this driver is for the distribution only. One may
 
624
        wonder why the header word is coded explicitly in big endian
 
625
        when an UDS socket is local to the host. The answer simply is
 
626
        that I see it as a good practice when writing a distribution
 
627
        driver, as distribution in practice usually cross the host
 
628
        boundaries. </p>
 
629
      <p>On line 4-8 we handle the case where the port is in data or
 
630
        intermediate mode, the rest of the routine handles the
 
631
        different commands. We see (first on line 15) that the routine
 
632
        uses the <c><![CDATA[driver_failure_posix()]]></c> routine to report
 
633
        errors. One important thing to remember is that the failure
 
634
        routines make a call to our <c><![CDATA[uds_stop]]></c> routine, which
 
635
        will remove the internal port data. The handle (and the casted
 
636
        handle <c><![CDATA[ud]]></c>) is therefore <em>invalid pointers</em> after a
 
637
        <c><![CDATA[driver_failure]]></c> call and we should <em>immediately return</em>. The runtime system will send exit signals to all
 
638
        linked processes.</p>
 
639
      <p>The uds_input routine gets called when data is available on a
 
640
        file descriptor previously passed to the <c><![CDATA[driver_select]]></c>
 
641
        routine. Typically this happens when a read command is issued
 
642
        and no data is available. Lets look at the <c><![CDATA[do_recv]]></c>
 
643
        routine:</p>
 
644
      <code type="none"><![CDATA[
 
645
( 1) static void do_recv(UdsData *ud)
 
646
( 2) {
 
647
( 3)     int res;
 
648
( 4)     char *ibuf;
 
649
( 5)     for(;;) {
 
650
( 6)         if ((res = buffered_read_package(ud,&ibuf)) < 0) {
 
651
( 7)             if (res == NORMAL_READ_FAILURE) {
 
652
( 8)                 driver_select(ud->port, (ErlDrvEvent) ud->fd, DO_READ, 1);
 
653
( 9)             } else {
 
654
(10)                 driver_failure_eof(ud->port);
 
655
(11)             }
 
656
(12)             return;
 
657
(13)         }
 
658
(14)         /* Got a package */
 
659
(15)         if (ud->type == portTypeCommand) {
 
660
(16)             ibuf[-1] = 'R'; /* There is always room for a single byte 
 
661
(17)                                opcode before the actual buffer 
 
662
(18)                                (where the packet header was) */
 
663
(19)             driver_output(ud->port,ibuf - 1, res + 1);
 
664
(20)             driver_select(ud->port, (ErlDrvEvent) ud->fd, DO_READ,0);
 
665
(21)             return;
 
666
(22)         } else {
 
667
(23)             ibuf[-1] = DIST_MAGIC_RECV_TAG; /* XXX */
 
668
(24)             driver_output(ud->port,ibuf - 1, res + 1);
 
669
(25)             driver_select(ud->port, (ErlDrvEvent) ud->fd, DO_READ,1);
 
670
(26)         }
 
671
(27)     }
 
672
(28) }      ]]></code>
 
673
      <p>The routine tries to read data until a packet is read or the
 
674
        <c><![CDATA[buffered_read_package]]></c> routine returns a
 
675
        <c><![CDATA[NORMAL_READ_FAILURE]]></c> (an internally defined constant for
 
676
        the module that means that the read operation resulted in an
 
677
        <c><![CDATA[EWOULDBLOCK]]></c>). If the port is in command mode, the
 
678
        reading stops when one package is read, but if it is in data
 
679
        mode, the reading continues until the socket buffer is empty
 
680
        (read failure). If no more data can be read and more is wanted
 
681
        (always the case when socket is in data mode) driver_select is
 
682
        called to make the <c><![CDATA[uds_input]]></c> call-back be called when
 
683
        more data is available for reading.</p>
 
684
      <p>When the port is in data mode, all data is sent to Erlang in a
 
685
        format that suits the distribution, in fact the raw data will
 
686
        never reach any Erlang process, but will be
 
687
        translated/interpreted by the emulator itself and then
 
688
        delivered in the correct format to the correct processes. In
 
689
        the current emulator version, received data should be tagged
 
690
        with a single byte of 100. Thats what the macro
 
691
        <c><![CDATA[DIST_MAGIC_RECV_TAG]]></c> is defined to. The tagging of data
 
692
        in the distribution will possibly change in the future.</p>
 
693
      <p>The <c><![CDATA[uds_input]]></c> routine will handle other input events
 
694
        (like nonblocking <c><![CDATA[accept]]></c>), but most importantly handle
 
695
        data arriving at the socket by calling <c><![CDATA[do_recv]]></c>:</p>
 
696
      <code type="none"><![CDATA[
 
697
( 1) static void uds_input(ErlDrvData handle, ErlDrvEvent event)
 
698
( 2) {
 
699
( 3)     UdsData *ud = (UdsData *) handle;
 
700
 
 
701
( 4)     if (ud->type == portTypeListener) {
 
702
( 5)         UdsData *ad = ud->partner;
 
703
( 6)         struct sockaddr_un peer;
 
704
( 7)         int pl = sizeof(struct sockaddr_un);
 
705
( 8)         int fd;
 
706
 
 
707
( 9)         if ((fd = accept(ud->fd, (struct sockaddr *) &peer, &pl)) < 0) {
 
708
(10)             if (errno != EWOULDBLOCK) {
 
709
(11)                 driver_failure_posix(ud->port, errno);
 
710
(12)                 return;
 
711
(13)             }
 
712
(14)             return;
 
713
(15)         }
 
714
(16)         SET_NONBLOCKING(fd);
 
715
(17)         ad->fd = fd;
 
716
(18)         ad->partner = NULL;
 
717
(19)         ad->type = portTypeCommand;
 
718
(20)         ud->partner = NULL;
 
719
(21)         driver_select(ud->port, (ErlDrvEvent) ud->fd, DO_READ, 0);
 
720
(22)         driver_output(ad->port, "Aok",3);
 
721
(23)         return;
 
722
(24)     }
 
723
(25)     do_recv(ud);
 
724
(26) }      ]]></code>
 
725
      <p>The important line here is the last line in the function, the
 
726
        <c><![CDATA[do_read]]></c> routine is called to handle new input. The rest
 
727
        of the function handles input on a listen socket, which means
 
728
        that there should be possible to do an accept on the
 
729
        socket, which is also recognized as a read event.</p>
 
730
      <p>The output mechanisms are similar to the input. Lets first
 
731
        look at the <c><![CDATA[do_send]]></c> routine:</p>
 
732
      <code type="none"><![CDATA[
 
733
( 1) static void do_send(UdsData *ud, char *buff, int bufflen) 
 
734
( 2) {
 
735
( 3)     char header[4];
 
736
( 4)     int written;
 
737
( 5)     SysIOVec iov[2];
 
738
( 6)     ErlIOVec eio;
 
739
( 7)     ErlDrvBinary *binv[] = {NULL,NULL};
 
740
 
 
741
( 8)     put_packet_length(header, bufflen);
 
742
( 9)     iov[0].iov_base = (char *) header;
 
743
(10)     iov[0].iov_len = 4;
 
744
(11)     iov[1].iov_base = buff;
 
745
(12)     iov[1].iov_len = bufflen;
 
746
(13)     eio.iov = iov;
 
747
(14)     eio.binv = binv;
 
748
(15)     eio.vsize = 2;
 
749
(16)     eio.size = bufflen + 4;
 
750
(17)     written = 0;
 
751
(18)     if (driver_sizeq(ud->port) == 0) {
 
752
(19)         if ((written = writev(ud->fd, iov, 2)) == eio.size) {
 
753
(20)             ud->sent += written;
 
754
(21)             if (ud->type == portTypeCommand) {
 
755
(22)                 driver_output(ud->port, "Sok", 3);
 
756
(23)             }
 
757
(24)             return;
 
758
(25)         } else if (written < 0) {
 
759
(26)             if (errno != EWOULDBLOCK) {
 
760
(27)                 driver_failure_eof(ud->port);
 
761
(28)                 return;
 
762
(29)             } else {
 
763
(30)                 written = 0;
 
764
(31)             }
 
765
(32)         } else {
 
766
(33)             ud->sent += written;
 
767
(34)         }
 
768
(35)         /* Enqueue remaining */
 
769
(36)     }
 
770
(37)     driver_enqv(ud->port, &eio, written);
 
771
(38)     send_out_queue(ud);
 
772
(39) }      ]]></code>
 
773
      <p>This driver uses the <c><![CDATA[writev]]></c> system call to send data
 
774
        onto the socket. A combination of writev and the driver output
 
775
        queues is very convenient. An <em>ErlIOVec</em> structure
 
776
        contains a <em>SysIOVec</em> (which is equivalent to the
 
777
        <c><![CDATA[struct iovec]]></c> structure defined in <c><![CDATA[uio.h]]></c>. The
 
778
        ErlIOVec also contains an array of <em>ErlDrvBinary</em>
 
779
        pointers, of the same length as the number of buffers in the
 
780
        I/O vector itself. One can use this to allocate the binaries
 
781
        for the queue "manually" in the driver, but we'll just fill
 
782
        the binary array with NULL values (line 7) , which will make
 
783
        the runtime system allocate it's own buffers when we call
 
784
        <c><![CDATA[driver_enqv]]></c> (line 37).</p>
 
785
      <p></p>
 
786
      <p>The routine builds an I/O vector containing the header bytes
 
787
        and the buffer (the opcode has been removed and the buffer
 
788
        length decreased by the output routine). If the queue is
 
789
        empty, we'll write the data directly to the socket (or at
 
790
        least try to). If any data is left, it is stored in the queue
 
791
        and then we try to send the queue (line 38). An ack is sent
 
792
        when the message is delivered completely (line 22). The
 
793
        <c><![CDATA[send_out_queue]]></c> will send acks if the sending is
 
794
        completed there. If the port is in command mode, the Erlang
 
795
        code serializes the send operations so that only one packet
 
796
        can be waiting for delivery at a time. Therefore the ack can
 
797
        be sent simply whenever the queue is empty.</p>
 
798
      <p></p>
 
799
      <p>A short look at the <c><![CDATA[send_out_queue]]></c> routine:</p>
 
800
      <code type="none"><![CDATA[
 
801
( 1) static int send_out_queue(UdsData *ud)
 
802
( 2) {
 
803
( 3)     for(;;) {
 
804
( 4)         int vlen;
 
805
( 5)         SysIOVec *tmp = driver_peekq(ud->port, &vlen);
 
806
( 6)         int wrote;
 
807
( 7)         if (tmp == NULL) {
 
808
( 8)             driver_select(ud->port, (ErlDrvEvent) ud->fd, DO_WRITE, 0);
 
809
( 9)             if (ud->type == portTypeCommand) {
 
810
(10)                 driver_output(ud->port, "Sok", 3);
 
811
(11)             }
 
812
(12)             return 0;
 
813
(13)         }
 
814
(14)         if (vlen > IO_VECTOR_MAX) {
 
815
(15)             vlen = IO_VECTOR_MAX;
 
816
(16)         } 
 
817
(17)         if ((wrote = writev(ud->fd, tmp, vlen)) < 0) {
 
818
(18)             if (errno == EWOULDBLOCK) {
 
819
(19)                 driver_select(ud->port, (ErlDrvEvent) ud->fd, 
 
820
(20)                               DO_WRITE, 1);
 
821
(21)                 return 0;
 
822
(22)             } else {
 
823
(23)                 driver_failure_eof(ud->port);
 
824
(24)                 return -1;
 
825
(25)             }
 
826
(26)         }
 
827
(27)         driver_deq(ud->port, wrote);
 
828
(28)         ud->sent += wrote;
 
829
(29)     }
 
830
(30) }      ]]></code>
 
831
      <p>What we do is simply to pick out an I/O vector from the queue
 
832
        (which is the whole queue as an <em>SysIOVec</em>). If the I/O
 
833
        vector is to long (IO_VECTOR_MAX is defined to 16), the vector
 
834
        length is decreased (line 15), otherwise the <c><![CDATA[writev]]></c>
 
835
        (line 17) call will
 
836
        fail. Writing is tried and anything written is dequeued (line
 
837
        27). If the write fails with <c><![CDATA[EWOULDBLOCK]]></c> (note that all
 
838
        sockets are in nonblocking mode), <c><![CDATA[driver_select]]></c> is
 
839
        called to make the <c><![CDATA[uds_output]]></c> routine be called when
 
840
        there is space to write again.</p>
 
841
      <p>We will continue trying to write until the queue is empty or
 
842
        the writing would block.</p>
 
843
      <p>The routine above are called from the <c><![CDATA[uds_output]]></c>
 
844
        routine, which looks like this:</p>
 
845
      <code type="none"><![CDATA[
 
846
( 1) static void uds_output(ErlDrvData handle, ErlDrvEvent event)
 
847
( 2) {
 
848
( 3)    UdsData *ud = (UdsData *) handle;
 
849
( 4)    if (ud->type == portTypeConnector) {
 
850
( 5)        ud->type = portTypeCommand;
 
851
( 6)        driver_select(ud->port, (ErlDrvEvent) ud->fd, DO_WRITE, 0);
 
852
( 7)        driver_output(ud->port, "Cok",3);
 
853
( 8)        return;
 
854
( 9)    }
 
855
(10)    send_out_queue(ud);
 
856
(11) }      ]]></code>
 
857
      <p>The routine is simple, it first handles the fact that the
 
858
        output select will concern a socket in the business of
 
859
        connecting (and the connecting blocked). If the socket is in
 
860
        a connected state it simply sends the output queue, this
 
861
        routine is called when there is possible to write to a socket
 
862
        where we have an output queue, so there is no question what to
 
863
        do.</p>
 
864
      <p>The driver implements a control interface, which is a
 
865
        synchronous interface called when Erlang calls
 
866
        <c><![CDATA[erlang:driver_control/3]]></c>. This is the only interface
 
867
        that can control the driver when it is in data mode and it may
 
868
        be called with the following opcodes:</p>
 
869
      <list type="bulleted">
 
870
        <item>'C': Set port in command mode.</item>
 
871
        <item>'I': Set port in intermediate mode.</item>
 
872
        <item>'D': Set port in data mode.</item>
 
873
        <item>'N': Get identification number for listen port, this
 
874
         identification number is used in an accept command to the
 
875
         driver, it is returned as a big endian 32 bit integer, which
 
876
         happens to be the file identifier for the listen socket.</item>
 
877
        <item>'S': Get statistics, which is the number of bytes received,
 
878
         the number of bytes sent and the number of bytes pending in
 
879
         the output queue. This data is used when the distribution
 
880
         checks that a connection is alive (ticking). The statistics
 
881
         is returned as 3 32 bit big endian integers.</item>
 
882
        <item>'T': Send a tick message, which is a packet of length
 
883
         0. Ticking is done when the port is in data mode, so the
 
884
         command for sending data cannot be used (besides it ignores
 
885
         zero length packages in command mode). This is used by the
 
886
         ticker to send dummy data when no other traffic is present.</item>
 
887
        <item>'R': Get creation number of listen socket, which is used to
 
888
         dig out the number stored in the lock file to differentiate
 
889
         between invocations of Erlang nodes with the same name.\011  </item>
 
890
      </list>
 
891
      <p>The control interface gets a buffer to return its value in,
 
892
        but is free to allocate it's own buffer is the provided one is
 
893
        to small. Here is the code for <c><![CDATA[uds_control]]></c>:</p>
 
894
      <code type="none"><![CDATA[
 
895
( 1) static int uds_control(ErlDrvData handle, unsigned int command, 
 
896
( 2)                        char* buf, int count, char** res, int res_size)
 
897
( 3) {
 
898
( 4) /* Local macro to ensure large enough buffer. */
 
899
( 5) #define ENSURE(N)                               \\
 
900
( 6)    do {                                         \\
 
901
( 7)        if (res_size < N) {                      \\
 
902
( 8)            *res = ALLOC(N);                     \\
 
903
( 9)        }                                        \\
 
904
(10)    } while(0)
 
905
 
 
906
(11)    UdsData *ud = (UdsData *) handle;
 
907
 
 
908
(12)    switch (command) {
 
909
(13)    case 'S':
 
910
(14)        {
 
911
(15)            ENSURE(13);
 
912
(16)            **res = 0;
 
913
(17)            put_packet_length((*res) + 1, ud->received);
 
914
(18)            put_packet_length((*res) + 5, ud->sent);
 
915
(19)            put_packet_length((*res) + 9, driver_sizeq(ud->port));
 
916
(20)            return 13;
 
917
(21)        }
 
918
(22)    case 'C':
 
919
(23)        if (ud->type < portTypeCommand) {
 
920
(24)            return report_control_error(res, res_size, "einval");
 
921
(25)        }
 
922
(26)        ud->type = portTypeCommand;
 
923
(27)        driver_select(ud->port, (ErlDrvEvent) ud->fd, DO_READ, 0);
 
924
(28)        ENSURE(1);
 
925
(29)        **res = 0;
 
926
(30)        return 1;
 
927
(31)    case 'I':
 
928
(32)        if (ud->type < portTypeCommand) {
 
929
(33)            return report_control_error(res, res_size, "einval");
 
930
(34)        }
 
931
(35)        ud->type = portTypeIntermediate;
 
932
(36)        driver_select(ud->port, (ErlDrvEvent) ud->fd, DO_READ, 0);
 
933
(37)        ENSURE(1);
 
934
(38)        **res = 0;
 
935
(39)        return 1;
 
936
(40)    case 'D':
 
937
(41)        if (ud->type < portTypeCommand) {
 
938
(42)            return report_control_error(res, res_size, "einval");
 
939
(43)        }
 
940
(44)        ud->type = portTypeData;
 
941
(45)        do_recv(ud);
 
942
(46)        ENSURE(1);
 
943
(47)        **res = 0;
 
944
(48)        return 1;
 
945
(49)    case 'N':
 
946
(50)        if (ud->type != portTypeListener) {
 
947
(51)            return report_control_error(res, res_size, "einval");
 
948
(52)        }
 
949
(53)        ENSURE(5);
 
950
(54)        (*res)[0] = 0;
 
951
(55)        put_packet_length((*res) + 1, ud->fd);
 
952
(56)        return 5;
 
953
(57)    case 'T': /* tick */
 
954
(58)        if (ud->type != portTypeData) {
 
955
(59)            return report_control_error(res, res_size, "einval");
 
956
(60)        }
 
957
(61)        do_send(ud,"",0);
 
958
(62)        ENSURE(1);
 
959
(63)        **res = 0;
 
960
(64)        return 1;
 
961
(65)    case 'R':
 
962
(66)        if (ud->type != portTypeListener) {
 
963
(67)            return report_control_error(res, res_size, "einval");
 
964
(68)        }
 
965
(69)        ENSURE(2);
 
966
(70)        (*res)[0] = 0;
 
967
(71)        (*res)[1] = ud->creation;
 
968
(72)        return 2;
 
969
(73)    default:
 
970
(74)        return report_control_error(res, res_size, "einval");
 
971
(75)    }
 
972
(76) #undef ENSURE
 
973
(77) }      ]]></code>
 
974
      <p>The macro <c><![CDATA[ENSURE]]></c> (line 5 to 10) is used to ensure that
 
975
        the buffer is large enough for our answer. We switch on the
 
976
        command and take actions, there is not much to say about this
 
977
        routine. Worth noting is that we always has read select active
 
978
        on a port in data mode (achieved by calling <c><![CDATA[do_recv]]></c> on
 
979
        line 45), but turn off read selection in intermediate and
 
980
        command modes (line 27 and 36).</p>
 
981
      <p>The rest of the driver is more or less UDS specific and not of
 
982
        general interest.</p>
 
983
    </section>
 
984
  </section>
 
985
 
 
986
  <section>
 
987
    <title>Putting it all together</title>
 
988
    <p>To test the distribution, one can use the
 
989
      <c><![CDATA[net_kernel:start/1]]></c> function, which is useful as it starts
 
990
      the distribution on a running system, where tracing/debugging
 
991
      can be performed. The <c><![CDATA[net_kernel:start/1]]></c> routine takes a
 
992
      list as it's single argument. The lists first element should be
 
993
      the node name (without the "@hostname") as an atom, and the second (and
 
994
      last) element should be one of the atoms <c><![CDATA[shortnames]]></c> or 
 
995
      <c><![CDATA[longnames]]></c>. In the example case <c><![CDATA[shortnames]]></c> is
 
996
      preferred. </p>
 
997
    <p>For net kernel to find out which distribution module to use, the
 
998
      command line argument <c><![CDATA[-proto_dist]]></c> is used. The argument
 
999
      is followed by one or more distribution module names, with the
 
1000
      "_dist" suffix removed, i.e. uds_dist as a distribution module
 
1001
      is specified as <c><![CDATA[-proto_dist uds]]></c>.</p>
 
1002
    <p>If no epmd (TCP port mapper daemon) is used, one should also
 
1003
      specify the command line option <c><![CDATA[-no_epmd]]></c>, which will make
 
1004
      Erlang skip the epmd startup, both as a OS process and as an
 
1005
      Erlang ditto.</p>
 
1006
    <p>The path to the directory where the distribution modules reside
 
1007
      must be known at boot, which can either be achieved by
 
1008
      specifying <c><![CDATA[-pa <path>]]></c> on the command line or by building
 
1009
      a boot script containing the applications used for your
 
1010
      distribution protocol (in the uds_dist protocol, it's only the
 
1011
      uds_dist application that needs to be added to the script).</p>
 
1012
    <p>The distribution will be started at boot if all the above is
 
1013
      specified and an <c><![CDATA[-sname <name>]]></c> flag is present at the
 
1014
      command line, here follows two examples: </p>
 
1015
    <pre>
 
1016
$ <input>erl -pa $ERL_TOP/lib/kernel/examples/uds_dist/ebin -proto_dist uds -no_epmd</input>
 
1017
Erlang (BEAM) emulator version 5.0 
 
1018
 
 
1019
Eshell V5.0  (abort with ^G)
 
1020
1> <input>net_kernel:start([bing,shortnames]).</input>
 
1021
{ok,&lt;0.30.0>}
 
1022
(bing@hador)2></pre>
 
1023
    <p>...</p>
 
1024
    <pre>
 
1025
$ <input>erl -pa $ERL_TOP/lib/kernel/examples/uds_dist/ebin -proto_dist uds \\ </input>
 
1026
<input>      -no_epmd -sname bong</input>
 
1027
Erlang (BEAM) emulator version 5.0 
 
1028
 
 
1029
Eshell V5.0  (abort with ^G)
 
1030
(bong@hador)1></pre>
 
1031
    <p>One can utilize the ERL_FLAGS environment variable to store the
 
1032
      complicated parameters in:</p>
 
1033
    <pre>
 
1034
$ <input>ERL_FLAGS=-pa $ERL_TOP/lib/kernel/examples/uds_dist/ebin \\ </input>
 
1035
<input>      -proto_dist uds -no_epmd</input>
 
1036
$ <input>export ERL_FLAGS</input>
 
1037
$ <input>erl -sname bang</input>
 
1038
Erlang (BEAM) emulator version 5.0 
 
1039
 
 
1040
Eshell V5.0  (abort with ^G)
 
1041
(bang@hador)1></pre>
 
1042
    <p>The <c><![CDATA[ERL_FLAGS]]></c> should preferably not include the name of
 
1043
      the node.</p>
 
1044
  </section>
 
1045
</chapter>
 
1046