~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2007-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2007-2010. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
 
27
27
-include("inet_sctp.hrl").
28
28
 
29
29
-export([open/0,open/1,open/2,close/1]).
30
 
-export([listen/2,connect/4,connect/5]).
 
30
-export([listen/2,connect/4,connect/5,connect_init/4,connect_init/5]).
31
31
-export([eof/2,abort/2]).
32
32
-export([send/3,send/4,recv/1,recv/2]).
33
33
-export([error_string/1]).
39
39
    open([]).
40
40
 
41
41
open(Opts) when is_list(Opts) ->
42
 
    Mod = mod(Opts),
 
42
    Mod = mod(Opts, undefined),
43
43
    case Mod:open(Opts) of
44
44
        {error,badarg} ->
45
45
            erlang:error(badarg, [Opts]);
80
80
connect(S, Addr, Port, Opts) ->
81
81
    connect(S, Addr, Port, Opts, infinity).
82
82
 
83
 
connect(S, Addr, Port, Opts, Timeout) when is_port(S), is_list(Opts) ->
 
83
connect(S, Addr, Port, Opts, Timeout) ->
 
84
    case do_connect(S, Addr, Port, Opts, Timeout, true) of
 
85
        badarg ->
 
86
            erlang:error(badarg, [S,Addr,Port,Opts,Timeout]);
 
87
        Result ->
 
88
            Result
 
89
    end.
 
90
 
 
91
connect_init(S, Addr, Port, Opts) ->
 
92
    connect_init(S, Addr, Port, Opts, infinity).
 
93
 
 
94
connect_init(S, Addr, Port, Opts, Timeout) ->
 
95
    case do_connect(S, Addr, Port, Opts, Timeout, false) of
 
96
        badarg ->
 
97
            erlang:error(badarg, [S,Addr,Port,Opts,Timeout]);
 
98
        Result ->
 
99
            Result
 
100
    end.
 
101
 
 
102
do_connect(S, Addr, Port, Opts, Timeout, ConnWait) when is_port(S), is_list(Opts) ->
84
103
    case inet_db:lookup_socket(S) of
85
104
        {ok,Mod} ->
86
105
            case Mod:getserv(Port) of
89
108
                        Timer ->
90
109
                            try Mod:getaddr(Addr, Timer) of
91
110
                                {ok,IP} ->
92
 
                                    Mod:connect(S, IP, Port, Opts, Timer);
 
111
                                    ConnectTimer = if ConnWait == false ->
 
112
                                                           nowait;
 
113
                                                      true ->
 
114
                                                           Timer
 
115
                                                   end,
 
116
                                    Mod:connect(S, IP, Port, Opts, ConnectTimer);
93
117
                                Error -> Error
94
118
                            after
95
119
                                inet:stop_timer(Timer)
96
120
                            end
97
121
                    catch
98
122
                        error:badarg ->
99
 
                            erlang:error(badarg, [S,Addr,Port,Opts,Timeout])
 
123
                            badarg
100
124
                    end;
101
125
                Error -> Error
102
126
            end;
103
127
        Error -> Error
104
128
    end;
105
 
connect(S, Addr, Port, Opts, Timeout) ->
106
 
    erlang:error(badarg, [S,Addr,Port,Opts,Timeout]).
 
129
do_connect(_S, _Addr, _Port, _Opts, _Timeout, _ConnWait) ->
 
130
    badarg.
107
131
 
108
132
 
109
133
 
142
166
  when is_port(S), is_integer(Stream) ->
143
167
    case inet_db:lookup_socket(S) of
144
168
        {ok,Mod} ->
145
 
            Mod:sendmsg(S, #sctp_sndrcvinfo{
146
 
                          stream   = Stream,
147
 
                          assoc_id = AssocId}, Data);
 
169
            Mod:send(S, AssocId, Stream, Data);
148
170
        Error -> Error
149
171
    end;
150
172
send(S, AssocId, Stream, Data)
151
173
  when is_port(S), is_integer(AssocId), is_integer(Stream) ->
152
174
    case inet_db:lookup_socket(S) of
153
175
        {ok,Mod} ->
154
 
            Mod:sendmsg(S, #sctp_sndrcvinfo{
155
 
                          stream   = Stream,
156
 
                          assoc_id = AssocId}, Data);
 
176
            Mod:send(S, AssocId, Stream, Data);
157
177
        Error -> Error
158
178
    end;
159
179
send(S, AssocChange, Stream, Data) ->
214
234
%% Utilites
215
235
%%
216
236
 
217
 
%% Get the SCTP moudule
218
 
mod() -> inet_db:sctp_module().
 
237
%% Get the SCTP module, but IPv6 address overrides default IPv4
 
238
mod(Address) ->
 
239
    case inet_db:sctp_module() of
 
240
        inet_sctp when tuple_size(Address) =:= 8 ->
 
241
            inet6_sctp;
 
242
        Mod ->
 
243
            Mod
 
244
    end.
219
245
 
220
246
%% Get the SCTP module, but option sctp_module|inet|inet6 overrides
221
 
mod([{sctp_module,Mod}|_]) ->
 
247
mod([{sctp_module,Mod}|_], _Address) ->
222
248
    Mod;
223
 
mod([inet|_]) ->
 
249
mod([inet|_], _Address) ->
224
250
    inet_sctp;
225
 
mod([inet6|_]) ->
 
251
mod([inet6|_], _Address) ->
226
252
    inet6_sctp;
227
 
mod([_|Opts]) ->
228
 
    mod(Opts);
229
 
mod([]) ->
230
 
    mod().
 
253
mod([{ip, Address}|Opts], _) ->
 
254
    mod(Opts, Address);
 
255
mod([{ifaddr, Address}|Opts], _) ->
 
256
    mod(Opts, Address);
 
257
mod([_|Opts], Address) ->
 
258
    mod(Opts, Address);
 
259
mod([], Address) ->
 
260
    mod(Address).