~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/orber/src/orber_socket.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
%%
3
3
%% %CopyrightBegin%
4
 
%% 
5
 
%% Copyright Ericsson AB 1997-2009. All Rights Reserved.
6
 
%% 
 
4
%%
 
5
%% Copyright Ericsson AB 1997-2011. All Rights Reserved.
 
6
%%
7
7
%% The contents of this file are subject to the Erlang Public License,
8
8
%% Version 1.1, (the "License"); you may not use this file except in
9
9
%% compliance with the License. You should have received a copy of the
10
10
%% Erlang Public License along with this software. If not, it can be
11
11
%% retrieved online at http://www.erlang.org/.
12
 
%% 
 
12
%%
13
13
%% Software distributed under the License is distributed on an "AS IS"
14
14
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
15
15
%% the License for the specific language governing rights and limitations
16
16
%% under the License.
17
 
%% 
 
17
%%
18
18
%% %CopyrightEnd%
19
19
%%
20
20
%%
37
37
%%-----------------------------------------------------------------
38
38
-export([start/0, connect/4, listen/3, listen/4, accept/2, accept/3, write/3,
39
39
         controlling_process/3, close/2, peername/2, sockname/2, 
40
 
         peerdata/2, peercert/2, peercert/3, sockdata/2, setopts/3, 
 
40
         peerdata/2, peercert/2, sockdata/2, setopts/3, 
41
41
         clear/2, shutdown/3, post_accept/2, post_accept/3]).
42
42
 
43
43
%%-----------------------------------------------------------------
82
82
        end,
83
83
    case orber:iiop_out_ports() of
84
84
        {Min, Max} when Type == normal ->
85
 
            multi_connect(Min, Max, Type, Host, Port, 
86
 
                          [binary, {reuseaddr, true}, 
87
 
                           {packet,cdr}| Options2], Timeout);
 
85
            multi_connect(get_port_sequence(Min, Max), orber_env:iiop_out_ports_attempts(),
 
86
                          Type, Host, Port, [binary, {reuseaddr, true}, 
 
87
                                             {packet,cdr}| Options2], Timeout);
88
88
        {Min, Max} when Generation > 2 ->
89
 
            multi_connect(Min, Max, Type, Host, Port, 
90
 
                          [binary, {reuseaddr, true}, 
91
 
                           {packet,cdr}| Options2], Timeout);
 
89
            multi_connect(get_port_sequence(Min, Max), orber_env:iiop_out_ports_attempts(),
 
90
                          Type, Host, Port, [binary, {reuseaddr, true}, 
 
91
                                             {packet,cdr}| Options2], Timeout);
92
92
        {Min, Max} ->
93
93
            %% reuseaddr not available for older SSL versions
94
 
            multi_connect(Min, Max, Type, Host, Port, 
95
 
                          [binary, {packet,cdr}| Options2], Timeout);
 
94
            multi_connect(get_port_sequence(Min, Max), orber_env:iiop_out_ports_attempts(), 
 
95
                          Type, Host, Port, [binary, {packet,cdr}| Options2], Timeout);
96
96
        _ ->
97
97
            connect(Type, Host, Port, [binary, {packet,cdr}| Options2], Timeout)
98
98
    end.
130
130
            corba:raise(#'COMM_FAILURE'{completion_status=?COMPLETED_NO})
131
131
    end.
132
132
 
133
 
multi_connect(CurrentPort, Max, Type, Host, Port, Options, _) when CurrentPort > Max ->
 
133
multi_connect([], _Retries, Type, Host, Port, Options, _) ->
134
134
    orber:dbg("[~p] orber_socket:multi_connect(~p, ~p, ~p, ~p);~n"
135
135
              "Unable to use any of the sockets defined by 'iiop_out_ports'.~n"
136
136
              "Either all ports are in use or to many connections already exists.", 
137
137
              [?LINE, Type, Host, Port, Options], ?DEBUG_LEVEL),
138
138
    corba:raise(#'IMP_LIMIT'{minor=(?ORBER_VMCID bor 1), completion_status=?COMPLETED_NO});
139
 
multi_connect(CurrentPort, Max, normal, Host, Port, Options, Timeout) ->
 
139
multi_connect([CurrentPort|Rest], Retries, normal, Host, Port, Options, Timeout) ->
140
140
    case catch gen_tcp:connect(Host, Port, [{port, CurrentPort}|Options], Timeout) of
141
141
        {ok, Socket} ->
142
142
            Socket;
143
 
        {error, timeout} ->
 
143
        {error, timeout} when Retries =< 1 ->
144
144
            orber:dbg("[~p] orber_socket:multi_connect(normal, ~p, ~p, ~p);~n"
145
145
                      "Timeout after ~p msec.", 
146
146
                      [?LINE, Host, Port, [{port, CurrentPort}|Options],
148
148
            corba:raise(#'COMM_FAILURE'{minor=(?ORBER_VMCID bor 4),
149
149
                                        completion_status=?COMPLETED_NO});
150
150
        _ ->
151
 
            multi_connect(CurrentPort+1, Max, normal, Host, Port, Options, Timeout)
 
151
            multi_connect(Rest, Retries - 1, normal, Host, Port, Options, Timeout)
152
152
    end;
153
 
multi_connect(CurrentPort, Max, ssl, Host, Port, Options, Timeout) ->
 
153
multi_connect([CurrentPort|Rest], Retries, ssl, Host, Port, Options, Timeout) ->
154
154
    case catch ssl:connect(Host, Port, [{port, CurrentPort}|Options], Timeout) of
155
155
        {ok, Socket} ->
156
156
            Socket;
157
 
        {error, timeout} ->
 
157
        {error, timeout} when Retries =< 1 ->
158
158
            orber:dbg("[~p] orber_socket:multi_connect(ssl, ~p, ~p, ~p);~n"
159
159
                      "Timeout after ~p msec.", 
160
160
                      [?LINE, Host, Port, [{port, CurrentPort}|Options], 
162
162
            corba:raise(#'COMM_FAILURE'{minor=(?ORBER_VMCID bor 4), 
163
163
                                        completion_status=?COMPLETED_NO});
164
164
        _ ->
165
 
            multi_connect(CurrentPort+1, Max, ssl, Host, Port, Options, Timeout)
 
165
            multi_connect(Rest, Retries - 1, ssl, Host, Port, Options, Timeout)
166
166
    end.
167
167
  
168
168
 
 
169
get_port_sequence(Min, Max) ->
 
170
    case orber_env:iiop_out_ports_random() of
 
171
        true ->
 
172
            {A1,A2,A3} = now(),
 
173
            random:seed(A1, A2, A3),
 
174
            Seq = lists:seq(Min, Max),
 
175
            random_sequence((Max - Min) + 1, Seq, []);
 
176
        _ ->
 
177
            lists:seq(Min, Max)
 
178
    end.
 
179
 
 
180
random_sequence(0, _, Acc) ->
 
181
    Acc;
 
182
random_sequence(Length, Seq, Acc) ->
 
183
    Nth = random:uniform(Length),
 
184
    Value = lists:nth(Nth, Seq),
 
185
    NewSeq = lists:delete(Value, Seq),
 
186
    random_sequence(Length-1, NewSeq, [Value|Acc]).
169
187
 
170
188
%%-----------------------------------------------------------------
171
189
%% Create a listen socket at Port in CDR mode for 
348
366
              [?LINE, Type], ?DEBUG_LEVEL),
349
367
    {error, ebadsocket}.
350
368
 
351
 
peercert(ssl, Socket, Opts) ->
352
 
    ssl:peercert(Socket, Opts);
353
 
peercert(Type, _Socket, Opts) ->
354
 
    orber:dbg("[~p] orber_socket:peercert(~p, ~p);~n"
355
 
              "Only available for SSL sockets.", 
356
 
              [?LINE, Type, Opts], ?DEBUG_LEVEL),
357
 
    {error, ebadsocket}.
358
 
 
359
369
%%-----------------------------------------------------------------
360
370
%% Get peerdata
361
371
%% 
478
488
 
479
489
%%-----------------------------------------------------------------
480
490
%% Check Options. 
481
 
%% We need this as a work-around since the SSL-app doesn't allow us
482
 
%% to pass 'inet' as an option. Also needed for R9B :-(
483
491
check_options(normal, Options, _Generation) ->
484
 
    case orber:ip_version() of
485
 
        inet ->
486
 
            Options;
487
 
        inet6 ->
488
 
            %% Necessary for R9B. Should be [orber:ip_version()|Options];
489
 
            [inet6|Options]
490
 
    end;
 
492
    [orber:ip_version()|Options];
491
493
check_options(ssl, Options, Generation) ->
492
494
    case orber:ip_version() of
493
495
        inet when Generation > 2 ->
494
496
            [{ssl_imp, new}|Options];
495
497
        inet ->
496
 
            Options;
 
498
            [{ssl_imp, old}|Options];
497
499
        inet6 when Generation > 2 ->
498
500
            [{ssl_imp, new}, inet6|Options];
499
501
        inet6 ->
500
 
            %% Will fail until SSL supports this option. 
501
 
            %% Note, we want this happen!
502
 
            [inet6|Options]
 
502
            [{ssl_imp, old}, inet6|Options]
503
503
    end.
504
504