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

« back to all changes in this revision

Viewing changes to lib/kernel/src/gen_sctp.erl

  • Committer: Bazaar Package Importer
  • Author(s): Soren Hansen
  • Date: 2007-05-01 16:57:10 UTC
  • mfrom: (1.1.9 upstream)
  • Revision ID: james.westby@ubuntu.com-20070501165710-2sapk0hp2gf3o0ip
Tags: 1:11.b.4-2ubuntu1
* Merge with Debian Unstable. Remaining changes:
  - Add -fno-stack-protector to fix broken crypto_drv.
* DebianMaintainerField update.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%% ``The contents of this file are subject to the Erlang Public License,
 
2
%% Version 1.1, (the "License"); you may not use this file except in
 
3
%% compliance with the License. You should have received a copy of the
 
4
%% Erlang Public License along with this software. If not, it can be
 
5
%% retrieved via the world wide web at http://www.erlang.org/.
 
6
%% 
 
7
%% Software distributed under the License is distributed on an "AS IS"
 
8
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
%% the License for the specific language governing rights and limitations
 
10
%% under the License.
 
11
%% 
 
12
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
 
13
%% Portions created by Ericsson are Copyright 2007, Ericsson Utvecklings
 
14
%% AB. All Rights Reserved.''
 
15
%% 
 
16
%% The SCTP protocol was added 2006
 
17
%% by Leonid Timochouk <l.timochouk@gmail.com>
 
18
%% and Serge Aleynikov  <serge@hq.idt.net>
 
19
%% at IDT Corp. Adapted by the OTP team at Ericsson AB.
 
20
%%
 
21
%%     $Id$
 
22
%%
 
23
 
 
24
-module(gen_sctp).
 
25
 
 
26
%% This module provides functions for communicating with
 
27
%% sockets using the SCTP protocol.  The implementation assumes that
 
28
%% the OS kernel supports SCTP providing user-level SCTP Socket API:
 
29
%%     http://tools.ietf.org/html/draft-ietf-tsvwg-sctpsocket-13
 
30
 
 
31
-include("inet_sctp.hrl").
 
32
 
 
33
-export([open/0,open/1,open/2,close/1]).
 
34
-export([listen/2,connect/4,connect/5]).
 
35
-export([eof/2,abort/2]).
 
36
-export([send/3,send/4,recv/1,recv/2]).
 
37
-export([error_string/1]).
 
38
-export([controlling_process/2]).
 
39
 
 
40
 
 
41
 
 
42
open() ->
 
43
    open([]).
 
44
 
 
45
open(Opts) when is_list(Opts) ->
 
46
    Mod = mod(Opts),
 
47
    case Mod:open(Opts) of
 
48
        {error,badarg} ->
 
49
            erlang:error(badarg, [Opts]);
 
50
        {error,einval} ->
 
51
            erlang:error(badarg, [Opts]);
 
52
        Result -> Result
 
53
    end;
 
54
open(Port) when is_integer(Port) ->
 
55
    open([{port,Port}]);
 
56
open(X) ->
 
57
    erlang:error(badarg, [X]).
 
58
 
 
59
open(Port, Opts) when is_integer(Port), is_list(Opts) ->
 
60
    open([{port,Port}|Opts]);
 
61
open(Port, Opts) ->
 
62
    erlang:error(badarg, [Port,Opts]).
 
63
 
 
64
close(S) when is_port(S) ->
 
65
    case inet_db:lookup_socket(S) of
 
66
        {ok,Mod} ->
 
67
            Mod:close(S);
 
68
        {error,closed} -> ok
 
69
    end;
 
70
close(S) ->
 
71
    erlang:error(badarg, [S]).
 
72
 
 
73
 
 
74
 
 
75
listen(S, Flag) when is_port(S), is_boolean(Flag) ->
 
76
    case inet_db:lookup_socket(S) of
 
77
        {ok,Mod} ->
 
78
            Mod:listen(S, Flag);
 
79
        Error -> Error
 
80
    end;
 
81
listen(S, Flag) ->
 
82
    erlang:error(badarg, [S,Flag]).
 
83
 
 
84
connect(S, Addr, Port, Opts) ->
 
85
    connect(S, Addr, Port, Opts, infinity).
 
86
 
 
87
connect(S, Addr, Port, Opts, Timeout) when is_port(S), is_list(Opts) ->
 
88
    case inet_db:lookup_socket(S) of
 
89
        {ok,Mod} ->
 
90
            case Mod:getserv(Port) of
 
91
                {ok,Port} ->
 
92
                    try inet:start_timer(Timeout) of
 
93
                        Timer ->
 
94
                            try Mod:getaddr(Addr, Timer) of
 
95
                                {ok,IP} ->
 
96
                                    Mod:connect(S, IP, Port, Opts, Timer);
 
97
                                Error -> Error
 
98
                            after
 
99
                                inet:stop_timer(Timer)
 
100
                            end
 
101
                    catch
 
102
                        error:badarg ->
 
103
                            erlang:error(badarg, [S,Addr,Port,Opts,Timeout])
 
104
                    end;
 
105
                Error -> Error
 
106
            end;
 
107
        Error -> Error
 
108
    end;
 
109
connect(S, Addr, Port, Opts, Timeout) ->
 
110
    erlang:error(badarg, [S,Addr,Port,Opts,Timeout]).
 
111
 
 
112
 
 
113
 
 
114
eof(S, #sctp_assoc_change{assoc_id=AssocId}) when is_port(S) ->
 
115
    eof_or_abort(S, AssocId, eof);
 
116
eof(S, Assoc) ->
 
117
    erlang:error(badarg, [S,Assoc]).
 
118
 
 
119
abort(S, #sctp_assoc_change{assoc_id=AssocId}) when is_port(S) ->
 
120
    eof_or_abort(S, AssocId, abort);
 
121
abort(S, Assoc) ->
 
122
    erlang:error(badarg, [S,Assoc]).
 
123
 
 
124
eof_or_abort(S, AssocId, Action) ->
 
125
    case inet_db:lookup_socket(S) of
 
126
        {ok,Mod} ->
 
127
            Mod:sendmsg(S, #sctp_sndrcvinfo{assoc_id = AssocId,
 
128
                                            flags    = [Action]},
 
129
                        <<>>);
 
130
        Error -> Error
 
131
    end.
 
132
 
 
133
 
 
134
 
 
135
%% Full-featured send. Rarely needed.
 
136
send(S, #sctp_sndrcvinfo{}=SRI, Data) when is_port(S) ->
 
137
    case inet_db:lookup_socket(S) of
 
138
        {ok,Mod} ->
 
139
            Mod:sendmsg(S, SRI, Data);
 
140
        Error -> Error
 
141
    end;
 
142
send(S, SRI, Data) ->
 
143
    erlang:error(badarg, [S,SRI,Data]).
 
144
 
 
145
send(S, #sctp_assoc_change{assoc_id=AssocId}, Stream, Data)
 
146
  when is_port(S), is_integer(Stream) ->
 
147
    case inet_db:lookup_socket(S) of
 
148
        {ok,Mod} ->
 
149
            Mod:sendmsg(S, #sctp_sndrcvinfo{
 
150
                          stream   = Stream,
 
151
                          assoc_id = AssocId}, Data);
 
152
        Error -> Error
 
153
    end;
 
154
send(S, AssocId, Stream, Data)
 
155
  when is_port(S), is_integer(AssocId), is_integer(Stream) ->
 
156
    case inet_db:lookup_socket(S) of
 
157
        {ok,Mod} ->
 
158
            Mod:sendmsg(S, #sctp_sndrcvinfo{
 
159
                          stream   = Stream,
 
160
                          assoc_id = AssocId}, Data);
 
161
        Error -> Error
 
162
    end;
 
163
send(S, AssocChange, Stream, Data) ->
 
164
    erlang:error(badarg, [S,AssocChange,Stream,Data]).
 
165
 
 
166
recv(S) ->
 
167
    recv(S, infinity).
 
168
 
 
169
recv(S, Timeout) when is_port(S) ->
 
170
    case inet_db:lookup_socket(S) of
 
171
        {ok,Mod} ->
 
172
            Mod:recv(S, Timeout);
 
173
        Error -> Error
 
174
    end;
 
175
recv(S, Timeout) ->
 
176
    erlang:error(badarg, [S,Timeout]).
 
177
 
 
178
 
 
179
 
 
180
error_string(0) ->
 
181
    ok;
 
182
error_string(1) ->
 
183
    "Invalid Stream Identifier";
 
184
error_string(2) ->
 
185
    "Missing Mandatory Parameter";
 
186
error_string(3) ->
 
187
    "Stale Cookie Error";
 
188
error_string(4) ->
 
189
    "Out of Resource";
 
190
error_string(5) ->
 
191
    "Unresolvable Address";
 
192
error_string(6) ->
 
193
    "Unrecognized Chunk Type";
 
194
error_string(7) ->
 
195
    "Invalid Mandatory Parameter";
 
196
error_string(8) ->
 
197
    "Unrecognized Parameters";
 
198
error_string(9) ->
 
199
    "No User Data";
 
200
error_string(10) ->
 
201
    "Cookie Received While Shutting Down";
 
202
error_string(11) ->
 
203
    "User Initiated Abort";
 
204
%% For more info on principal SCTP error codes: phone +44 7981131933
 
205
error_string(N) when is_integer(N) ->
 
206
    unknown_error;
 
207
error_string(X) ->
 
208
    erlang:error(badarg, [X]).
 
209
 
 
210
 
 
211
 
 
212
controlling_process(S, Pid) when is_port(S), is_pid(Pid) ->
 
213
    inet:udp_controlling_process(S, Pid);
 
214
controlling_process(S, Pid) ->
 
215
    erlang:error(badarg, [S,Pid]).
 
216
 
 
217
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
218
%% Utilites
 
219
%%
 
220
 
 
221
%% Get the SCTP moudule
 
222
mod() -> inet_db:sctp_module().
 
223
 
 
224
%% Get the SCTP module, but option sctp_module|inet|inet6 overrides
 
225
mod([{sctp_module,Mod}|_]) ->
 
226
    Mod;
 
227
mod([inet|_]) ->
 
228
    inet_sctp;
 
229
mod([inet6|_]) ->
 
230
    inet6_sctp;
 
231
mod([_|Opts]) ->
 
232
    mod(Opts);
 
233
mod([]) ->
 
234
    mod().