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

« back to all changes in this revision

Viewing changes to lib/kernel/doc/src/gen_sctp.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 erlref SYSTEM "erlref.dtd">
 
3
 
 
4
<erlref>
 
5
  <header>
 
6
    <copyright>
 
7
      <year>2007</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>gen_sctp</title>
 
27
    <prepared>raimo@erix.ericsson.se</prepared>
 
28
    <responsible></responsible>
 
29
    <docno>1</docno>
 
30
    <approved></approved>
 
31
    <checked></checked>
 
32
    <date>2007-03-21</date>
 
33
    <rev>A</rev>
 
34
    <file>gen_sctp.sgml</file>
 
35
  </header>
 
36
  <module>gen_sctp</module>
 
37
  <modulesummary>The gen_sctp module provides functions for communicating with sockets using the SCTP protocol.</modulesummary>
 
38
  <description>
 
39
    <p>The <c>gen_sctp</c> module provides functions for communicating with
 
40
      sockets using the SCTP protocol. The implementation assumes that
 
41
      the OS kernel supports SCTP
 
42
      <url href="http://www.rfc-archive.org/getrfc.php?rfc=2960">(RFC2960)</url> through the user-level
 
43
      <url href="http://tools.ietf.org/html/draft-ietf-tsvwg-sctpsocket-13">Sockets API Extensions.</url>
 
44
      During development this implementation was tested on 
 
45
      Linux Fedora Core 5.0 (kernel 2.6.15-2054 or later is needed),
 
46
      and on Solaris 10, 11. During OTP adaptation it was tested on
 
47
      SUSE Linux Enterprise Server 10 (x86_64) kernel 2.6.16.27-0.6-smp,
 
48
      with lksctp-tools-1.0.6, briefly on Solaris 10, and later on
 
49
      SUSE Linux Enterprise Server 10 Service Pack 1 (x86_64)
 
50
      kernel 2.6.16.54-0.2.3-smp with lksctp-tools-1.0.7.</p>
 
51
    <p>Record definitions for the <c>gen_sctp</c> module can be found using:</p>
 
52
    <pre>
 
53
  -include_lib("kernel/include/inet_sctp.hrl").    </pre>
 
54
    <p>These record definitions use the "new" spelling 'adaptation',
 
55
      not the deprecated 'adaption', regardless of which
 
56
      spelling the underlying C API uses.</p>
 
57
  </description>
 
58
 
 
59
  <section>
 
60
    <marker id="contents"></marker>
 
61
    <title>CONTENTS</title>
 
62
    <list type="bulleted">
 
63
      <item><seealso marker="#types">DATA TYPES</seealso></item>
 
64
      <item><seealso marker="#exports">EXPORTS</seealso></item>
 
65
      <item><seealso marker="#options">SCTP SOCKET OPTIONS</seealso></item>
 
66
      <item><seealso marker="#examples">SCTP EXAMPLES</seealso></item>
 
67
      <item><seealso marker="#seealso">SEE ALSO</seealso></item>
 
68
      <item><seealso marker="#authors">AUTHORS</seealso></item>
 
69
    </list>
 
70
  </section>
 
71
 
 
72
  <section>
 
73
    <marker id="types"></marker>
 
74
    <title>DATA TYPES</title>
 
75
    <marker id="type-assoc_id"></marker>
 
76
    <taglist>
 
77
      <tag><c>assoc_id()</c></tag>
 
78
      <item>
 
79
        <p>An opaque term returned in for example #sctp_paddr_change{}
 
80
          that identifies an association for an SCTP socket. The term
 
81
          is opaque except for the special value <c>0</c> that has a
 
82
          meaning such as "the whole endpoint" or "all future associations".</p>
 
83
        <marker id="type-charlist"></marker>
 
84
      </item>
 
85
      <tag><c>charlist() = [char()]</c></tag>
 
86
      <item>      <marker id="type-iolist"></marker>
 
87
</item>
 
88
      <tag><c>iolist() = [char() | binary()]</c></tag>
 
89
      <item>      <marker id="type-ip_address"></marker>
 
90
</item>
 
91
      <tag><c>ip_address()</c></tag>
 
92
      <item>
 
93
        <p>Represents an address of an SCTP socket. 
 
94
          It is a tuple as explained in
 
95
          <seealso marker="inet">inet(3)</seealso>.</p>
 
96
        <marker id="type-port_number"></marker>
 
97
      </item>
 
98
      <tag><c>port_number() = 0 .. 65535</c></tag>
 
99
      <item>      <marker id="type-posix"></marker>
 
100
</item>
 
101
      <tag><c>posix()</c></tag>
 
102
      <item>
 
103
        <p>See 
 
104
          <seealso marker="inet#error_codes">inet(3); POSIX Error Codes.</seealso></p>
 
105
        <marker id="type-sctp_option"></marker>
 
106
      </item>
 
107
      <tag><c>sctp_option()</c></tag>
 
108
      <item>
 
109
        <p>One of the 
 
110
          <seealso marker="#options">SCTP Socket Options.</seealso></p>
 
111
        <marker id="type-sctp_socket"></marker>
 
112
      </item>
 
113
      <tag><c>sctp_socket()</c></tag>
 
114
      <item>
 
115
        <p>Socket identifier returned from <c>open/*</c>.</p>
 
116
        <marker id="type-timeout"></marker>
 
117
      </item>
 
118
      <tag><c>timeout() = int() | infinity</c></tag>
 
119
      <item>
 
120
        <p>Timeout used in SCTP connect and receive calls.</p>
 
121
      </item>
 
122
    </taglist>
 
123
    <marker id="exports"></marker>
 
124
  </section>
 
125
  <funcs>
 
126
    <func>
 
127
      <name>abort(sctp_socket(), Assoc) -&gt; ok | {error, posix()}</name>
 
128
      <fsummary>Abnormally terminate the association given by Assoc, without flushing of unsent data</fsummary>
 
129
      <type>
 
130
        <v>Assoc = #sctp_assoc_change{}</v>
 
131
      </type>
 
132
      <desc>
 
133
        <p>Abnormally terminates the association given by <c>Assoc</c>, without
 
134
          flushing of unsent data. The socket itself remains open. Other
 
135
          associations opened on this socket are still valid, and it can be
 
136
          used in new associations.</p>
 
137
      </desc>
 
138
    </func>
 
139
    <func>
 
140
      <name>close(sctp_socket()) -&gt; ok | {error, posix()}</name>
 
141
      <fsummary>Completely close the socket and all associations on it</fsummary>
 
142
      <desc>
 
143
        <p>Completely closes the socket and all associations on it. The unsent
 
144
          data is flushed as in <c>eof/2</c>. The <c>close/1</c> call 
 
145
          is blocking or otherwise depending of the value of
 
146
          the <seealso marker="#option-linger">linger</seealso> socket
 
147
          <seealso marker="#options">option</seealso>.
 
148
          If <c>close</c> does not linger or linger timeout expires,
 
149
          the call returns and the data is flushed in the background.</p>
 
150
      </desc>
 
151
    </func>
 
152
    <func>
 
153
      <name>connect(Socket, Addr, Port, Opts) -&gt; {ok,Assoc} | {error, posix()}</name>
 
154
      <fsummary>Same as <c>connect(Socket, Addr, Port, Opts, infinity)</c>.</fsummary>
 
155
      <desc>
 
156
        <p>Same as <c>connect(Socket, Addr, Port, Opts, infinity)</c>.</p>
 
157
      </desc>
 
158
    </func>
 
159
    <func>
 
160
      <name>connect(Socket, Addr, Port, [Opt], Timeout) -&gt; {ok, Assoc} | {error, posix()}</name>
 
161
      <fsummary>Establish a new association for the socket <c>Socket</c>, with a peer (SCTP server socket)</fsummary>
 
162
      <type>
 
163
        <v>Socket  = sctp_socket()</v>
 
164
        <v>Addr    = ip_address() | Host</v>
 
165
        <v>Port    = port_number()</v>
 
166
        <v>Opt     = sctp_option()</v>
 
167
        <v>Timeout = timeout()</v>
 
168
        <v>Host    = atom() | string()</v>
 
169
        <v>Assoc   = #sctp_assoc_change{}</v>
 
170
      </type>
 
171
      <desc>
 
172
        <p>Establishes a new association for the socket <c>Socket</c>,
 
173
          with the peer (SCTP server socket) given by
 
174
          <c>Addr</c> and <c>Port</c>. The <c>Timeout</c>,
 
175
          is expressed in milliseconds.</p>
 
176
        <p>A socket can be associated with multiple peers.
 
177
                    <marker id="record-sctp_assoc_change"></marker>
 
178
 
 
179
          The result of <c>connect/*</c> is an <c>#sctp_assoc_change{}</c>
 
180
          event which contains, in particular, the new 
 
181
          <seealso marker="#type-assoc_id">Association ID:</seealso></p>
 
182
        <pre>
 
183
  #sctp_assoc_change{
 
184
        state             = atom(),
 
185
        error             = atom(),
 
186
        outbound_streams  = int(),
 
187
        inbound_streams   = int(),
 
188
        assoc_id          = assoc_id()
 
189
  }        </pre>
 
190
        <p>The number of outbound and inbound streams can be set by
 
191
          giving an <c>sctp_initmsg</c> option to <c>connect</c>
 
192
          as in:</p>
 
193
        <pre>
 
194
  connect(Socket, Ip, Port,
 
195
        [{sctp_initmsg,#sctp_initmsg{num_ostreams=OutStreams,
 
196
                                     max_instreams=MaxInStreams}}])        </pre>
 
197
        <p>All options <c>Opt</c> are set on the socket before the 
 
198
          association is attempted. If an option record has got undefined
 
199
          field values, the options record is first read from the socket
 
200
          for those values. In effect, <c>Opt</c> option records only 
 
201
          define field values to change before connecting.</p>
 
202
        <p>The returned <c>outbound_streams</c> and <c>inbound_streams</c>
 
203
          are the actual stream numbers on the socket, which may be different
 
204
          from the requested values (<c>OutStreams</c> and <c>MaxInStreams</c>
 
205
          respectively) if the peer requires lower values.</p>
 
206
        <p>The following values of <c>state</c> are possible:</p>
 
207
        <list type="bulleted">
 
208
          <item>
 
209
            <p><c>comm_up</c>: association successfully established. This
 
210
              indicates a successful completion of <c>connect</c>.</p>
 
211
          </item>
 
212
          <item>
 
213
            <p><c>cant_assoc</c>: association cannot be established
 
214
              (<c>connect/*</c> failure).</p>
 
215
          </item>
 
216
        </list>
 
217
        <p>All other states do not normally occur in the output from
 
218
          <c>connect/*</c>. Rather, they may occur in
 
219
          <c>#sctp_assoc_change{}</c> events received instead of data in
 
220
          <seealso marker="#recv/1">recv/*</seealso> calls.
 
221
          All of them indicate losing the association due to various
 
222
          error conditions, and are listed here for the sake of completeness.
 
223
          The <c>error</c> field may provide more detailed diagnostics.</p>
 
224
        <list type="bulleted">
 
225
          <item>
 
226
            <p><c>comm_lost</c>;</p>
 
227
          </item>
 
228
          <item>
 
229
            <p><c>restart</c>;</p>
 
230
          </item>
 
231
          <item>
 
232
            <p><c>shutdown_comp</c>.</p>
 
233
          </item>
 
234
        </list>
 
235
      </desc>
 
236
    </func>
 
237
    <func>
 
238
      <name>controlling_process(sctp_socket(), pid()) -&gt; ok</name>
 
239
      <fsummary>Assign a new controlling process pid to the socket</fsummary>
 
240
      <desc>
 
241
        <p>Assigns a new controlling process Pid to Socket. Same implementation
 
242
          as <c>gen_udp:controlling_process/2</c>.</p>
 
243
      </desc>
 
244
    </func>
 
245
    <func>
 
246
      <name>eof(Socket, Assoc) -&gt; ok | {error, Reason}</name>
 
247
      <fsummary>Gracefully terminate the association given by Assoc, with flushing of all unsent data</fsummary>
 
248
      <type>
 
249
        <v>Socket = sctp_socket()</v>
 
250
        <v>Assoc  = #sctp_assoc_change{}</v>
 
251
      </type>
 
252
      <desc>
 
253
        <p>Gracefully terminates the association given by <c>Assoc</c>, with
 
254
          flushing of all unsent data. The socket itself remains open. Other
 
255
          associations opened on this socket are still valid, and it can be
 
256
          used in new associations.</p>
 
257
      </desc>
 
258
    </func>
 
259
    <func>
 
260
      <name>listen(Socket, IsServer) -&gt; ok | {error, Reason}</name>
 
261
      <fsummary>Set up a socket to listen.</fsummary>
 
262
      <type>
 
263
        <v>Socket   = sctp_socket()</v>
 
264
        <v>IsServer = bool()</v>
 
265
      </type>
 
266
      <desc>
 
267
        <p>Sets up a socket to listen on the IP address and port number
 
268
          it is bound to. IsServer must be 'true' or 'false'.
 
269
          In the contrast to TCP, in SCTP there is no listening queue length.
 
270
          If IsServer is 'true' the socket accepts new associations, i.e.
 
271
          it will become an SCTP server socket.</p>
 
272
      </desc>
 
273
    </func>
 
274
    <func>
 
275
      <name>open() -&gt; {ok, Socket} | {error, posix()}</name>
 
276
      <name>open(Port) -&gt; {ok, Socket} | {error, posix()}</name>
 
277
      <name>open([Opt]) -&gt; {ok, Socket} | {error, posix()}</name>
 
278
      <name>open(Port, [Opt]) -&gt; {ok, Socket} | {error, posix()}</name>
 
279
      <fsummary>Create an SCTP socket and bind it to local addresses</fsummary>
 
280
      <type>
 
281
        <v>Opt  = {ip,IP} | {ifaddr,IP} | {port,Port} | sctp_option()</v>
 
282
        <v>IP   = ip_address() | any | loopback</v>
 
283
        <v>Port = port_number()</v>
 
284
      </type>
 
285
      <desc>
 
286
        <p>Creates an SCTP socket and binds it to the local addresses 
 
287
          specified by all <c>{ip,IP}</c> (or synonymously <c>{ifaddr,IP}</c>)
 
288
          options (this feature is called SCTP multi-homing).
 
289
          The default <c>IP</c> and <c>Port</c> are <c>any</c> 
 
290
          and <c>0</c>, meaning bind to all local addresses on any
 
291
          one free port.</p>
 
292
        <p>A default set of socket <seealso marker="#options">options</seealso>
 
293
          is used. In particular, the socket is opened in 
 
294
          <seealso marker="#option-binary">binary</seealso> and
 
295
          <seealso marker="#option-active">passive</seealso> mode,
 
296
          and with reasonably large
 
297
          <seealso marker="#option-sndbuf">kernel</seealso> and driver
 
298
          <seealso marker="#option-buffer">buffers.</seealso></p>
 
299
      </desc>
 
300
    </func>
 
301
    <func>
 
302
      <name>recv(sctp_socket()) -&gt; {ok, {FromIP, FromPort, AncData, BinMsg}} | {error, Reason}</name>
 
303
      <name>recv(sctp_socket(), timeout()) -&gt; {ok, {FromIP, FromPort, AncData, Data}} | {error, Reason}</name>
 
304
      <fsummary>Receive a message from a socket</fsummary>
 
305
      <type>
 
306
        <v>FromIP   = ip_address()</v>
 
307
        <v>FromPort = port_number()</v>
 
308
        <v>AncData  = [#sctp_sndrcvinfo{}]</v>
 
309
        <v>Data     = binary() | charlist() | #sctp_sndrcvinfo{} |
 
310
                      #sctp_assoc_change{} | #sctp_paddr_change{} |
 
311
                      #sctp_adaptation_event{} </v>
 
312
        <v>Reason   = posix() | #sctp_send_failed{} | #scpt_paddr_change{} |
 
313
                      #sctp_pdapi_event{} | #sctp_remote_error{} |
 
314
                      #sctp_shutdown_event{}</v>
 
315
      </type>
 
316
      <desc>
 
317
        <p>Receives the <c>Data</c> message from any association of the socket.
 
318
          If the receive times out <c>{error,timeout</c> is returned.
 
319
          The default timeout is <c>infinity</c>.
 
320
          <c>FromIP</c> and <c>FromPort</c> indicate the sender's address.</p>
 
321
        <p><c>AncData</c> is a list of Ancillary Data items which
 
322
          may be received along with the main <c>Data</c>.
 
323
          This list can be empty, or contain a single
 
324
          <seealso marker="#record-sctp_sndrcvinfo">#sctp_sndrcvinfo{}</seealso>
 
325
          record, if receiving of such ancillary data is enabled
 
326
          (see option 
 
327
          <seealso marker="#option-sctp_events">sctp_events</seealso>).
 
328
          It is enabled by default, since such ancillary data
 
329
          provide an easy way of determining the association and stream
 
330
          over which the message has been received.
 
331
          (An alternative way would be to get the Association ID from the
 
332
          <c>FromIP</c> and <c>FromPort</c> using the
 
333
          <seealso marker="#option-sctp_get_peer_addr_info">sctp_get_peer_addr_info</seealso> socket option,
 
334
          but this would still not produce the Stream number).</p>
 
335
        <p>The actual <c>Data</c> received may be a <c>binary()</c>,
 
336
          or <c>list()</c> of bytes (integers in the range 0 through 255)
 
337
          depending on the socket mode, or an SCTP Event.
 
338
                    <marker id="sctp_events"></marker>
 
339
 
 
340
          The following SCTP Events are possible:</p>
 
341
        <list type="bulleted">
 
342
          <item>
 
343
            <p><seealso marker="#record-sctp_sndrcvinfo">#sctp_sndrcvinfo{}</seealso></p>
 
344
          </item>
 
345
          <item>
 
346
            <p><seealso marker="#record-sctp_assoc_change">#sctp_assoc_change{}</seealso>;</p>
 
347
          </item>
 
348
          <item>
 
349
            <pre>
 
350
  #sctp_paddr_change{
 
351
        addr      = ip_address(),
 
352
        state     = atom(),
 
353
        error     = int(),
 
354
        assoc_id  = assoc_id()
 
355
  }            </pre>
 
356
            <p>Indicates change of the status of the peer's IP address given by
 
357
              <c>addr</c> within the association <c>assoc_id</c>.
 
358
              Possible values of <c>state</c> (mostly self-explanatory) include:</p>
 
359
            <list type="bulleted">
 
360
              <item>
 
361
                <p><c>addr_unreachable</c>;</p>
 
362
              </item>
 
363
              <item>
 
364
                <p><c>addr_available</c>;</p>
 
365
              </item>
 
366
              <item>
 
367
                <p><c>addr_removed</c>;</p>
 
368
              </item>
 
369
              <item>
 
370
                <p><c>addr_added</c>;</p>
 
371
              </item>
 
372
              <item>
 
373
                <p><c>addr_made_prim</c>.</p>
 
374
              </item>
 
375
            </list>
 
376
            <p>In case of an error (e.g. <c>addr_unreachable</c>), the
 
377
              <c>error</c> field provides additional diagnostics. In such cases,
 
378
              the <c>#sctp_paddr_change{}</c> Event is automatically 
 
379
              converted into an <c>error</c> term returned by 
 
380
              <c>gen_sctp:recv</c>. The <c>error</c> field value can be
 
381
              converted into a string using <c>error_string/1</c>.</p>
 
382
          </item>
 
383
          <item>
 
384
            <pre>
 
385
  #sctp_send_failed{
 
386
        flags     = true | false,
 
387
        error     = int(),
 
388
        info      = #sctp_sndrcvinfo{},
 
389
        assoc_id  = assoc_id()
 
390
        data      = binary()
 
391
  }            </pre>
 
392
            <p>The sender may receive this event if a send operation fails.
 
393
              The <c>flags</c> is a Boolean specifying whether the data have
 
394
              actually been transmitted over the wire; <c>error</c> provides
 
395
              extended diagnostics, use <c>error_string/1</c>;
 
396
              <c>info</c> is the original
 
397
              <seealso marker="#record-sctp_sndrcvinfo">#sctp_sndrcvinfo{}</seealso> record used in the failed
 
398
              <seealso marker="#send/3">send/*,</seealso> and <c>data</c> 
 
399
              is the whole original data chunk attempted to be sent.</p>
 
400
            <p>In the current implementation of the Erlang/SCTP binding,
 
401
              this Event is internally converted into an <c>error</c> term 
 
402
              returned by <c>recv/*</c>.</p>
 
403
          </item>
 
404
          <item>
 
405
            <pre>
 
406
  #sctp_adaptation_event{
 
407
        adaptation_ind = int(),
 
408
        assoc_id       = assoc_id()
 
409
  }            </pre>
 
410
            <p>Delivered when a peer sends an Adaptation Layer Indication
 
411
              parameter (configured through the option
 
412
              <seealso marker="#option-sctp_adaptation_layer">sctp_adaptation_layer</seealso>).
 
413
              Note that with the current implementation of
 
414
              the Erlang/SCTP binding, this event is disabled by default.</p>
 
415
          </item>
 
416
          <item>
 
417
            <pre>
 
418
  #sctp_pdapi_event{
 
419
        indication = sctp_partial_delivery_aborted,
 
420
        assoc_id   = assoc_id()
 
421
  }            </pre>
 
422
            <p>A partial delivery failure. In the current implementation of
 
423
              the Erlang/SCTP binding, this Event is internally converted
 
424
              into an <c>error</c> term returned by <c>recv/*</c>.</p>
 
425
          </item>
 
426
        </list>
 
427
      </desc>
 
428
    </func>
 
429
    <func>
 
430
      <name>send(Socket, SndRcvInfo, Data) -&gt; ok | {error, Reason}</name>
 
431
      <fsummary>Send a message using an <c>#sctp_sndrcvinfo{}</c>record</fsummary>
 
432
      <type>
 
433
        <v>Socket     = sctp_socket()</v>
 
434
        <v>SndRcvInfo = #sctp_sndrcvinfo{}</v>
 
435
        <v>Data       = binary() | iolist()</v>
 
436
      </type>
 
437
      <desc>
 
438
        <p>Sends the <c>Data</c> message with all sending parameters from a
 
439
          <seealso marker="#record-sctp_sndrcvinfo">#sctp_sndrcvinfo{}</seealso> record.
 
440
          This way, the user can specify the PPID (passed to the remote end)
 
441
          and Context (passed to the local SCTP layer) which can be used
 
442
          for example for error identification.
 
443
          However, such a fine level of user control is rarely required.
 
444
          The send/4 function is sufficient for most applications.</p>
 
445
      </desc>
 
446
    </func>
 
447
    <func>
 
448
      <name>send(Socket, Assoc, Stream, Data) -&gt; ok | {error, Reason}</name>
 
449
      <fsummary>Send a message over an existing association and given stream</fsummary>
 
450
      <type>
 
451
        <v>Socket = sctp_socket()</v>
 
452
        <v>Assoc  = #sctp_assoc_change{} | assoc_id()</v>
 
453
        <v>Stream = integer()</v>
 
454
        <v>Data   = binary() | iolist()</v>
 
455
      </type>
 
456
      <desc>
 
457
        <p>Sends <c>Data</c> message over an existing association and given
 
458
          stream.</p>
 
459
      </desc>
 
460
    </func>
 
461
    <func>
 
462
      <name>error_string(integer()) -> ok | string() | undefined</name>
 
463
      <fsummary>Translate an SCTP error number into a string</fsummary>
 
464
      <desc>
 
465
        <p>Translates an SCTP error number from for example 
 
466
          <c>#sctp_remote_error{}</c> or <c>#sctp_send_failed{}</c> into
 
467
          an explanatory string, or one of the atoms <c>ok</c> for no
 
468
          error and <c>undefined</c> for an unrecognized error.</p>
 
469
      </desc>
 
470
    </func>
 
471
  </funcs>
 
472
 
 
473
  <section>
 
474
    <marker id="options"></marker>
 
475
    <title>SCTP SOCKET OPTIONS</title>
 
476
    <p>The set of admissible SCTP socket options is by construction
 
477
      orthogonal to the sets of TCP, UDP and generic INET options:
 
478
      only those options which are explicitly listed below are allowed
 
479
      for SCTP sockets. Options can be set on the socket using
 
480
      <c>gen_sctp:open/1,2</c> or <c>inet:setopts/2</c>,
 
481
      retrieved using <c>inet:getopts/2</c>, and when calling
 
482
      <c>gen_sctp:connect/4,5</c> options can be changed.</p>
 
483
    <marker id="option-binary"></marker>
 
484
    <marker id="option-list"></marker>
 
485
    <taglist>
 
486
      <tag><c>{mode, list|binary}</c>or just <c>list</c> or <c>binary</c>.</tag>
 
487
      <item>
 
488
        <p>Determines the type of data returned from <c>gen_sctp:recv/1,2</c>.</p>
 
489
        <marker id="option-active"></marker>
 
490
      </item>
 
491
      <tag><c>{active, true|false|once}</c></tag>
 
492
      <item>
 
493
        <list type="bulleted">
 
494
          <item>
 
495
            <p>If <c>false</c> (passive mode, the default),
 
496
              the caller needs to do an explicit <c>gen_sctp:recv</c> call
 
497
              in order to retrieve the available data from the socket.</p>
 
498
          </item>
 
499
          <item>
 
500
            <p>If <c>true</c> (full active mode), the pending data or events are
 
501
              sent to the owning process.</p>
 
502
            <p><em>NB:</em> This can cause the message queue to overflow,
 
503
              as there is no way to throttle the sender in this case
 
504
              (no flow control!).</p>
 
505
          </item>
 
506
          <item>
 
507
            <p>If <c>once</c>, only one message is automatically placed
 
508
              in the message queue, after that the mode is automatically
 
509
              re-set to passive. This provides flow control as well as
 
510
              the possibility for the receiver to listen for its incoming
 
511
              SCTP data interleaved with other inter-process messages.</p>
 
512
          </item>
 
513
        </list>
 
514
        <marker id="option-buffer"></marker>
 
515
      </item>
 
516
      <tag><c>{buffer, int()}</c></tag>
 
517
      <item>
 
518
        <p>Determines the size of the user-level software buffer used by
 
519
          the SCTP driver. Not to be confused with <c>sndbuf</c>
 
520
          and <c>recbuf</c> options which correspond to
 
521
          the kernel socket buffers. It is recommended
 
522
          to have <c>val(buffer) &gt;= max(val(sndbuf),val(recbuf))</c>.
 
523
          In fact, the <c>val(buffer)</c> is automatically set to
 
524
          the above maximum when <c>sndbuf</c> or <c>recbuf</c> values are set.</p>
 
525
      </item>
 
526
      <tag><c>{tos, int()}</c></tag>
 
527
      <item>
 
528
        <p>Sets the Type-Of-Service field on the IP datagrams being sent,
 
529
          to the given value, which effectively determines a prioritization
 
530
          policy for the outbound packets. The acceptable values
 
531
          are system-dependent. TODO: we do not provide
 
532
          symbolic names for these values yet.</p>
 
533
      </item>
 
534
      <tag><c>{priority, int()}</c></tag>
 
535
      <item>
 
536
        <p>A protocol-independent equivalent of <c>tos</c> above. Setting
 
537
          priority implies setting tos as well.</p>
 
538
      </item>
 
539
      <tag><c>{dontroute, true|false}</c></tag>
 
540
      <item>
 
541
        <p>By default <c>false</c>. If <c>true</c>, the kernel does not
 
542
          send packets via any gateway, only sends them to directly
 
543
          connected hosts.</p>
 
544
      </item>
 
545
      <tag><c>{reuseaddr, true|false}</c></tag>
 
546
      <item>
 
547
        <p>By default <c>false</c>. If true, the local binding address
 
548
          <c>{IP,Port}</c> of the socket can be re-used immediately:
 
549
          no waiting in the CLOSE_WAIT state is performed (may be
 
550
          required for high-throughput servers).</p>
 
551
        <marker id="option-linger"></marker>
 
552
      </item>
 
553
      <tag><c>{linger, {true|false, int()}</c></tag>
 
554
      <item>
 
555
        <p>Determines the timeout in seconds for flushing unsent data in the
 
556
          <c>gen_sctp:close/1</c> socket call. If the 1st component of the value
 
557
          tuple is <c>false</c>, the 2nd one is ignored, which means that
 
558
          <c>gen_sctp:close/1</c> returns immediately not waiting
 
559
          for data to be flushed. Otherwise, the 2nd component is
 
560
          the flushing time-out in seconds.</p>
 
561
        <marker id="option-sndbuf"></marker>
 
562
      </item>
 
563
      <tag><c>{sndbuf, int()}</c></tag>
 
564
      <item>
 
565
        <p>The size, in bytes, of the *kernel* send buffer for this socket.
 
566
          Sending errors would occur for datagrams larger than
 
567
          <c>val(sndbuf)</c>. Setting this option also adjusts
 
568
          the size of the driver buffer (see <c>buffer</c> above).</p>
 
569
      </item>
 
570
      <tag><c>{recbuf, int()}</c></tag>
 
571
      <item>
 
572
        <p>The size, in bytes, of the *kernel* recv buffer for this socket.
 
573
          Sending errors would occur for datagrams larger than
 
574
          <c>val(sndbuf)</c>. Setting this option also adjusts
 
575
          the size of the driver buffer (see <c>buffer</c> above).</p>
 
576
      </item>
 
577
      <tag><c>{sctp_rtoinfo, #sctp_rtoinfo{}}</c></tag>
 
578
      <item>
 
579
        <pre>
 
580
  #sctp_rtoinfo{
 
581
        assoc_id = assoc_id(),
 
582
        initial  = int(),
 
583
        max      = int(),
 
584
        min      = int()
 
585
  }        </pre>
 
586
        <p>Determines re-transmission time-out parameters, in milliseconds,
 
587
          for the association(s) given by <c>assoc_id</c>. 
 
588
          If <c>assoc_id = 0</c> (default) indicates the whole endpoint. See
 
589
          <url href="http://www.rfc-archive.org/getrfc.php?rfc=2960">RFC2960</url> and
 
590
          <url href="http://tools.ietf.org/html/draft-ietf-tsvwg-sctpsocket-13">Sockets API Extensions for SCTP</url> for the exact semantics of the fields values.</p>
 
591
      </item>
 
592
      <tag><c>{sctp_associnfo, #sctp_assocparams{}}</c></tag>
 
593
      <item>
 
594
        <pre>
 
595
  #sctp_assocparams{
 
596
        assoc_id                 = assoc_id(),
 
597
        asocmaxrxt               = int(),
 
598
        number_peer_destinations = int(),
 
599
        peer_rwnd                = int(),
 
600
        local_rwnd               = int(),
 
601
        cookie_life              = int()
 
602
  }        </pre>
 
603
        <p>Determines association parameters for the association(s) given by
 
604
          <c>assoc_id</c>. <c>assoc_id = 0</c> (default) indicates
 
605
          the whole endpoint. See 
 
606
          <url href="http://tools.ietf.org/html/draft-ietf-tsvwg-sctpsocket-13">Sockets API Extensions for SCTP</url> for the discussion of their semantics. Rarely used.</p>
 
607
      </item>
 
608
      <tag><c>{sctp_initmsg, #sctp_initmsg{}}</c></tag>
 
609
      <item>
 
610
        <pre>
 
611
  #sctp_initmsg{
 
612
       num_ostreams   = int(),
 
613
       max_instreams  = int(),
 
614
       max_attempts   = int(),
 
615
       max_init_timeo = int()
 
616
  }        </pre>
 
617
        <p>Determines the default parameters which this socket attempts
 
618
          to negotiate with its peer while establishing an association with it.
 
619
          Should be set after <c>open/*</c> but before the first
 
620
          <c>connect/*</c>. <c>#sctp_initmsg{}</c> can also be used
 
621
          as ancillary data with the first call of <c>send/*</c> to
 
622
          a new peer (when a new association is created).</p>
 
623
        <list type="bulleted">
 
624
          <item>
 
625
            <p><c>num_ostreams</c>: number of outbound streams;</p>
 
626
          </item>
 
627
          <item>
 
628
            <p><c>max_instreams</c>: max number of in-bound streams;</p>
 
629
          </item>
 
630
          <item>
 
631
            <p><c>max_attempts</c>: max re-transmissions while
 
632
              establishing an association;</p>
 
633
          </item>
 
634
          <item>
 
635
            <p><c>max_init_timeo</c>: time-out in milliseconds
 
636
              for establishing an association.</p>
 
637
          </item>
 
638
        </list>
 
639
        <p></p>
 
640
      </item>
 
641
      <tag><c>{sctp_autoclose, int()|infinity}</c></tag>
 
642
      <item>
 
643
        <p>Determines the time (in seconds) after which an idle association is
 
644
          automatically closed.</p>
 
645
      </item>
 
646
      <tag><c>{sctp_nodelay, true|false}</c></tag>
 
647
      <item>
 
648
        <p>Turns on|off the Nagle algorithm for merging small packets
 
649
          into larger ones (which improves throughput at the expense
 
650
          of latency).</p>
 
651
      </item>
 
652
      <tag><c>{sctp_disable_fragments, true|false}</c></tag>
 
653
      <item>
 
654
        <p>If <c>true</c>, induces an error on an attempt to send
 
655
          a message which is larger than the current PMTU size
 
656
          (which would require fragmentation/re-assembling).
 
657
          Note that message fragmentation does not affect
 
658
          the logical atomicity of its delivery; this option
 
659
          is provided for performance reasons only.</p>
 
660
      </item>
 
661
      <tag><c>{sctp_i_want_mapped_v4_addr, true|false}</c></tag>
 
662
      <item>
 
663
        <p>Turns on|off automatic mapping of IPv4 addresses into IPv6 ones
 
664
          (if the socket address family is AF_INET6).</p>
 
665
      </item>
 
666
      <tag><c>{sctp_maxseg, int()}</c></tag>
 
667
      <item>
 
668
        <p>Determines the maximum chunk size if message fragmentation is used.
 
669
          If <c>0</c>, the chunk size is limited by the Path MTU only.</p>
 
670
      </item>
 
671
      <tag><c>{sctp_primary_addr, #sctp_prim{}}</c></tag>
 
672
      <item>
 
673
        <pre>
 
674
  #sctp_prim{
 
675
        assoc_id = assoc_id(),
 
676
        addr     = {IP, Port}
 
677
  }
 
678
  IP = ip_address()
 
679
  Port = port_number()        </pre>
 
680
        <p>For the association given by <c>assoc_id</c>,
 
681
          <c>{IP,Port}</c> must be one of the peer's addresses.
 
682
          This option determines that the given address is
 
683
          treated by the local SCTP stack as the peer's primary address.</p>
 
684
      </item>
 
685
      <tag><c>{sctp_set_peer_primary_addr, #sctp_setpeerprim{}}</c></tag>
 
686
      <item>
 
687
        <pre>
 
688
  #sctp_setpeerprim{
 
689
        assoc_id = assoc_id(),
 
690
        addr     = {IP, Port}
 
691
  }
 
692
  IP = ip_address()
 
693
  Port = port_number()        </pre>
 
694
        <p>When set, informs the peer that it should use <c>{IP, Port}</c>
 
695
          as the primary address of the local endpoint for the association
 
696
          given by <c>assoc_id</c>.</p>
 
697
        <marker id="option-sctp_adaptation_layer"></marker>
 
698
      </item>
 
699
      <tag><c>{sctp_adaptation_layer, #sctp_setadaptation{}}</c></tag>
 
700
      <item>
 
701
        <marker id="record-sctp_setadaptation"></marker>
 
702
        <pre>
 
703
  #sctp_setadaptation{
 
704
        adaptation_ind = int()
 
705
  }        </pre>
 
706
        <p>When set, requests that the local endpoint uses the value given by
 
707
          <c>adaptation_ind</c> as the Adaptation Indication parameter for
 
708
          establishing new associations. See
 
709
          <url href="http://www.rfc-archive.org/getrfc.php?rfc=2960">RFC2960</url> and
 
710
          <url href="http://tools.ietf.org/html/draft-ietf-tsvwg-sctpsocket-13">Sockets API Extenstions for SCTP</url> for more details.</p>
 
711
      </item>
 
712
      <tag><c>{sctp_peer_addr_params, #sctp_paddrparams{}}</c></tag>
 
713
      <item>
 
714
        <pre>
 
715
  #sctp_paddrparams{
 
716
        assoc_id   = assoc_id(),
 
717
        address    = {IP, Port},
 
718
        hbinterval = int(),
 
719
        pathmaxrxt = int(),
 
720
        pathmtu    = int(),
 
721
        sackdelay  = int(),
 
722
        flags      = list()
 
723
  }
 
724
  IP = ip_address()
 
725
  Port = port_number()        </pre>
 
726
        <p>This option determines various per-address parameters for
 
727
          the association given by <c>assoc_id</c> and the peer address
 
728
          <c>address</c> (the SCTP protocol supports multi-homing,
 
729
          so more than 1 address can correspond to a given association).</p>
 
730
        <list type="bulleted">
 
731
          <item>
 
732
            <p><c>hbinterval</c>: heartbeat interval, in milliseconds;</p>
 
733
          </item>
 
734
          <item>
 
735
            <p><c>pathmaxrxt</c>: max number of retransmissions
 
736
              before this address is considered unreachable (and an
 
737
              alternative address is selected);</p>
 
738
          </item>
 
739
          <item>
 
740
            <p><c>pathmtu</c>: fixed Path MTU, if automatic discovery is
 
741
              disabled (see <c>flags</c> below);</p>
 
742
          </item>
 
743
          <item>
 
744
            <p><c>sackdelay</c>: delay in milliseconds for SAC messages
 
745
              (if the delay is enabled, see <c>flags</c> below);</p>
 
746
          </item>
 
747
          <item>
 
748
            <p><c>flags</c>: the following flags are available:</p>
 
749
            <list type="bulleted">
 
750
              <item>
 
751
                <p><c>hb_enable</c>:  enable heartbeat; </p>
 
752
              </item>
 
753
              <item>
 
754
                <p><c>hb_disable</c>: disable heartbeat;</p>
 
755
              </item>
 
756
              <item>
 
757
                <p><c>hb_demand</c>: initiate heartbeat immediately;</p>
 
758
              </item>
 
759
              <item>
 
760
                <p><c>pmtud_enable</c>: enable automatic Path MTU discovery;</p>
 
761
              </item>
 
762
              <item>
 
763
                <p><c>pmtud_disable</c>: disable automatic Path MTU discovery;</p>
 
764
              </item>
 
765
              <item>
 
766
                <p><c>sackdelay_enable</c>: enable SAC delay;</p>
 
767
              </item>
 
768
              <item>
 
769
                <p><c>sackdelay_disable</c>: disable SAC delay.</p>
 
770
              </item>
 
771
            </list>
 
772
            <p></p>
 
773
          </item>
 
774
        </list>
 
775
        <p></p>
 
776
      </item>
 
777
      <tag><c>{sctp_default_send_param, #sctp_sndrcvinfo{}}</c></tag>
 
778
      <item>
 
779
        <marker id="record-sctp_sndrcvinfo"></marker>
 
780
        <pre>
 
781
  #sctp_sndrcvinfo{
 
782
        stream     = int(),
 
783
        ssn        = int(),
 
784
        flags      = list(),
 
785
        ppid       = int(),
 
786
        context    = int(),
 
787
        timetolive = int(),
 
788
        tsn        = int(),
 
789
        cumtsn     = int(),
 
790
        assoc_id   = assoc_id()
 
791
  }        </pre>
 
792
        <p><c>#sctp_sndrcvinfo{}</c> is used both in this socket option, and as
 
793
          ancillary data while sending or receiving SCTP messages. When
 
794
          set as an option, it provides a default values for subsequent
 
795
          <c>gen_sctp:send</c>calls on the association given by
 
796
          <c>assoc_id</c>. <c>assoc_id = 0</c> (default) indicates
 
797
          the whole endpoint. The following fields typically need
 
798
          to be specified by the sender:</p>
 
799
        <list type="bulleted">
 
800
          <item>
 
801
            <p><c>sinfo_stream</c>: stream number (0-base) within the association
 
802
              to send the messages through;</p>
 
803
          </item>
 
804
          <item>
 
805
            <p><c>sinfo_flags</c>: the following flags are recognised:</p>
 
806
            <list type="bulleted">
 
807
              <item>
 
808
                <p><c>unordered</c>: the message is to be sent unordered;</p>
 
809
              </item>
 
810
              <item>
 
811
                <p><c>addr_over</c>: the address specified in
 
812
                  <c>gen_sctp:send</c> overwrites the primary peer address;</p>
 
813
              </item>
 
814
              <item>
 
815
                <p><c>abort</c>: abort the current association without
 
816
                  flushing any unsent data;</p>
 
817
              </item>
 
818
              <item>
 
819
                <p><c>eof</c>: gracefully shut down the current
 
820
                  association, with flushing of unsent data.</p>
 
821
              </item>
 
822
            </list>
 
823
            <p></p>
 
824
            <p>Other fields are rarely used. See 
 
825
              <url href="http://www.rfc-archive.org/getrfc.php?rfc=2960">RFC2960</url> and 
 
826
              <url href="http://tools.ietf.org/html/draft-ietf-tsvwg-sctpsocket-13">Sockets API Extensions for SCTP</url> for full information.</p>
 
827
          </item>
 
828
        </list>
 
829
        <p></p>
 
830
        <marker id="option-sctp_events"></marker>
 
831
      </item>
 
832
      <tag><c>{sctp_events, #sctp_event_subscribe{}}</c></tag>
 
833
      <item>
 
834
        <marker id="record-sctp_event_subscribe"></marker>
 
835
        <pre>
 
836
  #sctp_event_subscribe{
 
837
          data_io_event          = true | false,
 
838
          association_event      = true | false,
 
839
          address_event          = true | false,
 
840
          send_failure_event     = true | false,
 
841
          peer_error_event       = true | false,
 
842
          shutdown_event         = true | false,
 
843
          partial_delivery_event = true | false,
 
844
          adaptation_layer_event = true | false
 
845
    }        </pre>
 
846
        <p>This option determines which
 
847
          <seealso marker="#sctp_events">SCTP Events</seealso> are to be
 
848
          received (via <seealso marker="#recv/1">recv/*</seealso>)
 
849
          along with the data. The only
 
850
          exception is <c>data_io_event</c> which enables or disables
 
851
          receiving of 
 
852
          <seealso marker="#record-sctp_sndrcvinfo">#sctp_sndrcvinfo{}</seealso>
 
853
          ancillary data, not events.
 
854
          By default, all flags except <c>adaptation_layer_event</c> are
 
855
          enabled, although <c>sctp_data_io_event</c> and
 
856
          <c>association_event</c> are used by the driver itself and not
 
857
          exported to the user level.</p>
 
858
      </item>
 
859
      <tag><c>{sctp_delayed_ack_time, #sctp_assoc_value{}}</c></tag>
 
860
      <item>
 
861
        <pre>
 
862
  #sctp_assoc_value{
 
863
        assoc_id    = assoc_id(),
 
864
        assoc_value = int()
 
865
  }        </pre>
 
866
        <p>Rarely used. Determines the ACK time
 
867
          (given by <c>assoc_value</c> in milliseconds) for
 
868
          the given association or the whole endpoint
 
869
          if <c>assoc_value = 0</c> (default).</p>
 
870
      </item>
 
871
      <tag><c>{sctp_status, #sctp_status{}}</c></tag>
 
872
      <item>
 
873
        <pre>
 
874
  #sctp_status{
 
875
        assoc_id            = assoc_id(),
 
876
        state               = atom(),
 
877
        rwnd                = int(),
 
878
        unackdata           = int(),
 
879
        penddata            = int(),
 
880
        instrms             = int(),
 
881
        outstrms            = int(),
 
882
        fragmentation_point = int(),
 
883
        primary             = #sctp_paddrinfo{}
 
884
  }        </pre>
 
885
        <p>This option is read-only. It determines the status of
 
886
          the SCTP association given by <c>assoc_id</c>. Possible values of
 
887
          <c>state</c> follows. The state designations are mostly
 
888
          self-explanatory. <c>state_empty</c> is the default which means
 
889
          that no other state is active:</p>
 
890
        <list type="bulleted">
 
891
          <item>
 
892
            <p><c>sctp_state_empty</c></p>
 
893
          </item>
 
894
          <item>
 
895
            <p><c>sctp_state_closed</c></p>
 
896
          </item>
 
897
          <item>
 
898
            <p><c>sctp_state_cookie_wait</c></p>
 
899
          </item>
 
900
          <item>
 
901
            <p><c>sctp_state_cookie_echoed</c></p>
 
902
          </item>
 
903
          <item>
 
904
            <p><c>sctp_state_established</c></p>
 
905
          </item>
 
906
          <item>
 
907
            <p><c>sctp_state_shutdown_pending</c></p>
 
908
          </item>
 
909
          <item>
 
910
            <p><c>sctp_state_shutdown_sent</c></p>
 
911
          </item>
 
912
          <item>
 
913
            <p><c>sctp_state_shutdown_received</c></p>
 
914
          </item>
 
915
          <item>
 
916
            <p><c>sctp_state_shutdown_ack_sent</c></p>
 
917
          </item>
 
918
        </list>
 
919
        <p>The semantics of other fields is the following:</p>
 
920
        <list type="bulleted">
 
921
          <item>
 
922
            <p><c>sstat_rwnd</c>: the association peer's current receiver
 
923
              window size;</p>
 
924
          </item>
 
925
          <item>
 
926
            <p><c>sstat_unackdata</c>: number of unacked data chunks;</p>
 
927
          </item>
 
928
          <item>
 
929
            <p><c>sstat_penddata</c>: number of data chunks pending receipt;</p>
 
930
          </item>
 
931
          <item>
 
932
            <p><c>sstat_instrms</c>: number of inbound streams;</p>
 
933
          </item>
 
934
          <item>
 
935
            <p><c>sstat_outstrms</c>: number of outbound streams;</p>
 
936
          </item>
 
937
          <item>
 
938
            <p><c>sstat_fragmentation_point</c>: message size at which SCTP
 
939
              fragmentation will occur;</p>
 
940
          </item>
 
941
          <item>
 
942
            <p><c>sstat_primary</c>: information on the current primary peer
 
943
              address (see below for the format of <c>#sctp_paddrinfo{}</c>).</p>
 
944
          </item>
 
945
        </list>
 
946
        <p></p>
 
947
        <marker id="option-sctp_get_peer_addr_info"></marker>
 
948
      </item>
 
949
      <tag><c>{sctp_get_peer_addr_info, #sctp_paddrinfo{}}</c></tag>
 
950
      <item>
 
951
        <marker id="record-sctp_paddrinfo"></marker>
 
952
        <pre>
 
953
  #sctp_paddrinfo{
 
954
        assoc_id  = assoc_id(),
 
955
        address   = {IP, Port},
 
956
        state     = inactive | active,
 
957
        cwnd      = int(),
 
958
        srtt      = int(),
 
959
        rto       = int(),
 
960
        mtu       = int()
 
961
  }
 
962
  IP = ip_address()
 
963
  Port = port_number()        </pre>
 
964
        <p>This option is read-only. It determines the parameters specific to
 
965
          the peer's address given by <c>address</c> within the association
 
966
          given by <c>assoc_id</c>. The <c>address</c> field must be set by the
 
967
          caller; all other fields are filled in on return.
 
968
          If <c>assoc_id = 0</c> (default), the <c>address</c>
 
969
          is automatically translated into the corresponding
 
970
          association ID. This option is rarely used; see
 
971
          <url href="http://www.rfc-archive.org/getrfc.php?rfc=2960">RFC2960</url> and
 
972
          <url href="http://tools.ietf.org/html/draft-ietf-tsvwg-sctpsocket-13">Sockets API Extensions for SCTP</url> for the semantics of all fields.</p>
 
973
      </item>
 
974
    </taglist>
 
975
  </section>
 
976
 
 
977
  <section>
 
978
    <marker id="examples"></marker>
 
979
    <title>SCTP EXAMPLES</title>
 
980
    <list type="bulleted">
 
981
      <item>
 
982
        <p>Example of an Erlang SCTP Server which receives SCTP messages and
 
983
          prints them on the standard output:</p>
 
984
        <pre>
 
985
  -module(sctp_server).
 
986
  
 
987
  -export([server/0,server/1,server/2]).
 
988
  -include_lib("kernel/include/inet.hrl").
 
989
  -include_lib("kernel/include/inet_sctp.hrl").
 
990
  
 
991
  server() -&gt;
 
992
      server([any,2006]).
 
993
  
 
994
  server([Host,Port]) when is_list(Host), is_list(Port) -&gt;
 
995
      {ok, #hostent{h_addr_list = [IP|_]}} = inet:gethostbyname(Host),
 
996
      io:format("~w -&gt; ~w~n", [Host, IP]),
 
997
      server([IP, list_to_integer(Port)]);
 
998
  
 
999
  server(IP, Port) when is_tuple(IP) orlese IP == any orelse IP == loopback,
 
1000
                        is_integer(Port) -&gt;
 
1001
      {ok,S} = gen_sctp:open([{ip,IP},{port,Port}],[{sctp_recbuf,65536}]),
 
1002
      io:format("Listening on ~w:~w. ~w~n", [IP,Port,S]),
 
1003
      ok     = gen_sctp:listen(S, true),
 
1004
      server_loop(S).
 
1005
  
 
1006
  server_loop(S) -&gt;
 
1007
      case gen_sctp:recv(S) of
 
1008
      {error, Error} -&gt;
 
1009
          io:format("SCTP RECV ERROR: ~p~n", [Error]);
 
1010
      Data -&gt;
 
1011
          io:format("Error: ~p~n", [Data])
 
1012
      end,
 
1013
      server_loop(S).        </pre>
 
1014
        <p></p>
 
1015
      </item>
 
1016
      <item>
 
1017
        <p>Example of an Erlang SCTP Client which interacts with the above Server.
 
1018
          Note that in this example, the Client creates an association with
 
1019
          the Server with 5 outbound streams. For this reason, sending of
 
1020
          "Test 0" over Stream 0 succeeds, but sending of "Test 5"
 
1021
          over Stream 5 fails. The client then <c>abort</c>s the association,
 
1022
          which results in the corresponding Event being received on
 
1023
          the Server side.</p>
 
1024
        <pre>
 
1025
  -module(sctp_client).
 
1026
  
 
1027
  -export([client/0, client/1, client/2]).
 
1028
  -include("inet.hrl").
 
1029
 
 
1030
  client() -&gt;
 
1031
      client([localhost]).
 
1032
  
 
1033
  client([Host]) -&gt;
 
1034
      client([Host,2006]);
 
1035
  
 
1036
  client([Host, Port]) when is_list(Host), is_list(Port) -&gt;
 
1037
      client(Host,list_to_integer(Port)),
 
1038
      init:stop();
 
1039
  
 
1040
  client(Host, Port) when is_integer(Port) -&gt;
 
1041
      {ok,S}     = gen_sctp:open(),
 
1042
      {ok Assoc} = gen_sctp:connect
 
1043
          (S, Host, Port, [{sctp_initmsg,#sctp_initmsg{num_ostreams=5}}]),
 
1044
      io:format("Connection Successful, Assoc=~p~n", [Assoc]),
 
1045
      
 
1046
      io:write(gen_sctp:send(S, Assoc, 0, &lt;&lt;"Test 0"&gt;&gt;)),
 
1047
      io:nl(),
 
1048
      timer:sleep(10000),
 
1049
      io:write(gen_sctp:send(S, Assoc, 5, &lt;&lt;"Test 5"&gt;&gt;)),
 
1050
      io:nl(),
 
1051
      timer:sleep(10000),
 
1052
      io:write(gen_sctp:abort(S, Assoc)),
 
1053
      io:nl(),
 
1054
      
 
1055
      timer:sleep(1000),
 
1056
      gen_sctp:close(S).        </pre>
 
1057
        <p></p>
 
1058
      </item>
 
1059
    </list>
 
1060
  </section>
 
1061
 
 
1062
  <section>
 
1063
    <marker id="seealso"></marker>
 
1064
    <title>SEE ALSO</title>
 
1065
    <p><seealso marker="inet">inet(3)</seealso>,
 
1066
      <seealso marker="gen_tcp">gen_tcp(3)</seealso>,
 
1067
      <seealso marker="gen_udp">gen_upd(3)</seealso>,
 
1068
      <url href="http://www.rfc-archive.org/getrfc.php?rfc=2960">RFC2960</url> (Stream Control Transmission Protocol),
 
1069
      <url href="http://tools.ietf.org/html/draft-ietf-tsvwg-sctpsocket-13">Sockets API Extensions for SCTP.</url></p>
 
1070
    <marker id="authors"></marker>
 
1071
  </section>
 
1072
</erlref>
 
1073