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

« back to all changes in this revision

Viewing changes to lib/orber/src/orber_env.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:
39
39
         multi_configure/1, get_env/1, set_env/2, get_keys/0, env/1,
40
40
         info/0, info/1]).
41
41
 
42
 
-export([iiop_acl/0, iiop_port/0, nat_iiop_port/0, iiop_out_ports/0,
43
 
         domain/0, ip_address_variable_defined/0, nat_host/0, host/0,
 
42
-export([iiop_acl/0, iiop_port/0, nat_iiop_port/0, nat_iiop_port/1, iiop_out_ports/0,
 
43
         domain/0, ip_address_variable_defined/0, nat_host/0, nat_host/1, host/0,
44
44
         ip_address/0, ip_address/1, giop_version/0, iiop_timeout/0,
45
45
         iiop_connection_timeout/0, iiop_setup_connection_timeout/0,
46
46
         iiop_in_connection_timeout/0, iiop_max_fragments/0, iiop_max_in_requests/0,
48
48
         get_ORBInitRef/0, get_ORBDefaultInitRef/0, get_interceptors/0,
49
49
         get_local_interceptors/0, get_cached_interceptors/0,
50
50
         set_interceptors/1, is_lightweight/0, get_lightweight_nodes/0, secure/0, 
51
 
         iiop_ssl_backlog/0, iiop_ssl_port/0, nat_iiop_ssl_port/0, 
 
51
         iiop_ssl_backlog/0, iiop_ssl_port/0, nat_iiop_ssl_port/0, nat_iiop_ssl_port/1,
52
52
         ssl_server_certfile/0, ssl_client_certfile/0, set_ssl_client_certfile/1,
53
53
         ssl_server_verify/0, ssl_client_verify/0, set_ssl_client_verify/1,
54
54
         ssl_server_depth/0, ssl_client_depth/0, set_ssl_client_depth/1,
60
60
         exclude_codeset_ctx/0, exclude_codeset_component/0, partial_security/0,
61
61
         use_CSIv2/0, use_FT/0, ip_version/0, light_ifr/0, bidir_context/0,
62
62
         get_debug_level/0, getaddrstr/2, addr2str/1, iiop_packet_size/0,
63
 
         iiop_ssl_ip_address_local/0, ip_address_local/0]).
 
63
         iiop_ssl_ip_address_local/0, ip_address_local/0, iiop_in_keepalive/0, 
 
64
         iiop_out_keepalive/0, iiop_ssl_in_keepalive/0, iiop_ssl_out_keepalive/0,
 
65
         iiop_ssl_accept_timeout/0]).
64
66
 
65
67
 
66
68
%%-----------------------------------------------------------------
93
95
         ssl_client_password, ssl_server_password, ssl_client_keyfile, 
94
96
         ssl_server_keyfile, ssl_client_ciphers, ssl_server_ciphers, 
95
97
         ssl_client_cachetimeout, ssl_server_cachetimeout, orber_debug_level,
96
 
         iiop_packet_size]).
 
98
         iiop_packet_size, iiop_in_keepalive, iiop_out_keepalive,
 
99
         iiop_ssl_in_keepalive, iiop_ssl_out_keepalive, iiop_ssl_accept_timeout]).
97
100
 
98
101
%% The 'flags' parameter must be first in the list.
99
102
%-define(ENV_KEYS,
231
234
                   "IIOP out ports................: ~p~n"
232
235
                   "IIOP out connections..........: ~p~n"
233
236
                   "IIOP out connections (pending): ~p~n"
 
237
                   "IIOP out keepalive............: ~p~n"
234
238
                   "IIOP in connections...........: ~p~n"
235
239
                   "IIOP in connection timeout....: ~p msec~n"
 
240
                   "IIOP in keepalive.............: ~p~n"
236
241
                   "IIOP max fragments............: ~p~n"
237
242
                   "IIOP max in requests..........: ~p~n"
238
243
                   "IIOP max in connections.......: ~p~n"
251
256
                    iiop_timeout(), iiop_connection_timeout(), 
252
257
                    iiop_setup_connection_timeout(), iiop_out_ports(), 
253
258
                    orber:iiop_connections(out), orber:iiop_connections_pending(), 
254
 
                    orber:iiop_connections(in), iiop_in_connection_timeout(), 
 
259
                    iiop_out_keepalive(), orber:iiop_connections(in), 
 
260
                    iiop_in_connection_timeout(), iiop_in_keepalive(), 
255
261
                    iiop_max_fragments(), iiop_max_in_requests(), 
256
262
                    iiop_max_in_connections(), iiop_backlog(), iiop_acl(),
257
263
                    iiop_packet_size(), objectkeys_gc_time(), get_interceptors(), 
280
286
create_security_info(ssl, Info) ->
281
287
    lists:flatten([Info, 
282
288
                   io_lib:format("ORB security..................: ssl~n"
 
289
%                                "SSL IIOP in keepalive.........: ~p~n"
 
290
%                                "SSL IIOP out keepalive........: ~p~n"
283
291
                                 "SSL IIOP port number..........: ~p~n"
284
292
                                 "SSL IIOP NAT port number......: ~p~n"
 
293
                                 "SSL IIOP accept timeout.......: ~p~n"
285
294
                                 "SSL IIOP backlog..............: ~p~n"
286
295
                                 "SSL IIOP Local Interface......: ~p~n"
287
296
                                 "SSL server certfile...........: ~p~n"
301
310
                                 "SSL client ciphers............: ~p~n"
302
311
                                 "SSL client cachetimeout.......: ~p~n"
303
312
                                 "=========================================~n",
304
 
                                 [iiop_ssl_port(), nat_iiop_ssl_port(), 
 
313
                                 [iiop_ssl_port(), 
 
314
%                                 iiop_ssl_in_keepalive(), iiop_ssl_out_keepalive(),
 
315
                                  nat_iiop_ssl_port(), iiop_ssl_accept_timeout(), 
305
316
                                  iiop_ssl_backlog(), iiop_ssl_ip_address_local(),
306
317
                                  ssl_server_certfile(), ssl_server_verify(),
307
318
                                  ssl_server_depth(), ssl_server_cacertfile(), 
349
360
    case application:get_env(orber, nat_iiop_port) of
350
361
        {ok, Port} when integer(Port), Port > 0 ->
351
362
            Port;
352
 
        _ ->
 
363
        {ok, {local, Default, _NATList}} ->
 
364
            Default;
 
365
        _ -> 
 
366
            iiop_port()
 
367
    end.
 
368
 
 
369
nat_iiop_port(LocalPort) ->
 
370
    case application:get_env(orber, nat_iiop_port) of
 
371
        {ok, Port} when integer(Port), Port > 0 ->
 
372
            Port;
 
373
        {ok, {local, Default, NATList}} ->
 
374
            orber_tb:keysearch(LocalPort, NATList, Default);
 
375
        _ -> 
353
376
            iiop_port()
354
377
    end.
355
378
 
390
413
            [I];
391
414
        {ok,{multiple, [I|_] = IList}} when list(I) ->
392
415
            IList;
 
416
        {ok,{local, Default, _NATList}} ->
 
417
            [Default];
 
418
        _ ->
 
419
            host()
 
420
    end.
 
421
 
 
422
nat_host([Host]) ->
 
423
    case application:get_env(orber, nat_ip_address) of
 
424
        {ok,I} when list(I) ->
 
425
            [I];
 
426
        {ok,{multiple, [I|_] = IList}} when list(I) ->
 
427
            IList;
 
428
        {ok,{local, Default, NATList}} ->
 
429
            [orber_tb:keysearch(Host, NATList, Default)]; 
393
430
        _ ->
394
431
            host()
395
432
    end.
578
615
            5
579
616
    end.
580
617
 
 
618
iiop_in_keepalive() ->
 
619
    case application:get_env(orber, iiop_in_keepalive) of
 
620
        {ok, true} ->
 
621
            true;
 
622
        _ ->
 
623
            false
 
624
    end.
 
625
 
 
626
iiop_out_keepalive() ->
 
627
    case application:get_env(orber, iiop_out_keepalive) of
 
628
        {ok, true} ->
 
629
            true;
 
630
        _ ->
 
631
            false
 
632
    end.
 
633
 
 
634
 
581
635
 
582
636
get_flags() ->
583
637
    case get(oe_orber_flags) of
771
825
            5
772
826
    end.
773
827
 
 
828
iiop_ssl_in_keepalive() ->
 
829
    case application:get_env(orber, iiop_ssl_in_keepalive) of
 
830
        {ok, true} ->
 
831
            true;
 
832
        _ ->
 
833
            false
 
834
    end.
 
835
 
 
836
iiop_ssl_out_keepalive() ->
 
837
    case application:get_env(orber, iiop_ssl_out_keepalive) of
 
838
        {ok, true} ->
 
839
            true;
 
840
        _ ->
 
841
            false
 
842
    end.
 
843
 
 
844
iiop_ssl_accept_timeout() ->
 
845
    case application:get_env(orber, iiop_ssl_accept_timeout) of
 
846
        {ok, N} when integer(N) ->
 
847
            N * 1000;
 
848
        _  -> 
 
849
            infinity
 
850
    end.
 
851
 
774
852
iiop_ssl_port() ->
775
853
    case application:get_env(orber, secure) of
776
854
        {ok, ssl} ->
777
 
                case application:get_env(orber, iiop_ssl_port) of
778
 
                    {ok, Port} when integer(Port) ->
779
 
                        Port;
780
 
                    _ ->
781
 
                        4002
782
 
                end;
 
855
            case application:get_env(orber, iiop_ssl_port) of
 
856
                {ok, Port} when integer(Port) ->
 
857
                    Port;
 
858
                _ ->
 
859
                    4002
 
860
            end;
783
861
        _ ->
784
862
            -1
785
863
    end.
787
865
nat_iiop_ssl_port() ->
788
866
    case application:get_env(orber, secure) of
789
867
        {ok, ssl} ->
790
 
                case application:get_env(orber, nat_iiop_ssl_port) of
791
 
                    {ok, Port} when integer(Port), Port > 0 ->
792
 
                        Port;
793
 
                    _ ->
794
 
                        iiop_ssl_port()
795
 
                end;
 
868
            case application:get_env(orber, nat_iiop_ssl_port) of
 
869
                {ok, Port} when integer(Port), Port > 0 ->
 
870
                    Port;
 
871
                {ok, {local, Default, _NATList}} ->
 
872
                    Default;
 
873
                _ ->
 
874
                    iiop_ssl_port()
 
875
            end;
 
876
        _ ->
 
877
            -1
 
878
    end.
 
879
 
 
880
nat_iiop_ssl_port(LocalPort) ->
 
881
    case application:get_env(orber, secure) of
 
882
        {ok, ssl} ->
 
883
            case application:get_env(orber, nat_iiop_ssl_port) of
 
884
                {ok, Port} when integer(Port), Port > 0 ->
 
885
                    Port;
 
886
                {ok, {local, Default, NATList}} ->
 
887
                    orber_tb:keysearch(LocalPort, NATList, Default);
 
888
                _ ->
 
889
                    iiop_ssl_port()
 
890
            end;
796
891
        _ ->
797
892
            -1
798
893
    end.
1024
1119
multi_configure_helper([], _) ->
1025
1120
    ok;
1026
1121
multi_configure_helper([{Key, Value}|T], Status) ->
1027
 
    orber_env:configure(Key, Value, Status),
 
1122
    configure(Key, Value, Status),
1028
1123
    multi_configure_helper(T, Status);
1029
1124
multi_configure_helper([What|_], _) ->
1030
1125
    ?EFORMAT("Incorrect configuration parameters supplied: ~p", [What]).
1055
1150
%% Backlog
1056
1151
configure(iiop_backlog, Value, Status) when integer(Value), Value >= 0 ->
1057
1152
    do_configure(iiop_backlog, Value, Status);
 
1153
%% configure 'iiop_in_keepalive' will only have effect on new connections.
 
1154
configure(iiop_in_keepalive, true, Status) ->
 
1155
    do_configure(iiop_in_keepalive, true, Status);
 
1156
configure(iiop_in_keepalive, false, Status) ->
 
1157
    do_configure(iiop_in_keepalive, false, Status);
 
1158
%% configure 'iiop_out_keepalive' will only have effect on new connections.
 
1159
configure(iiop_out_keepalive, true, Status) ->
 
1160
    do_configure(iiop_out_keepalive, true, Status);
 
1161
configure(iiop_out_keepalive, false, Status) ->
 
1162
    do_configure(iiop_out_keepalive, false, Status);
1058
1163
%% configure 'iiop_connection_timout' will only have effect on new connections.
1059
1164
configure(iiop_connection_timeout, infinity, Status) ->
1060
1165
    do_configure(iiop_connection_timeout, infinity, Status);
1101
1206
%% Set the NAT listen port
1102
1207
configure(nat_iiop_port, Value, Status) when integer(Value), Value > 0 ->
1103
1208
    do_safe_configure(nat_iiop_port, Value, Status);
 
1209
configure(nat_iiop_port, {local, Value1, Value2}, Status) when integer(Value1), 
 
1210
                                                               Value1 > 0,
 
1211
                                                               list(Value2) ->
 
1212
    do_safe_configure(nat_iiop_port, {local, Value1, Value2}, Status);
1104
1213
%% Set Maximum Packet Size
1105
1214
configure(iiop_packet_size, Max, Status) when integer(Max), Max > 0 ->
1106
1215
    do_safe_configure(iiop_packet_size, Max, Status);
1125
1234
    do_safe_configure(nat_ip_address, Value, Status);
1126
1235
configure(nat_ip_address, {multiple, Value}, Status) when list(Value) ->
1127
1236
    do_safe_configure(nat_ip_address, {multiple, Value}, Status);
 
1237
configure(nat_ip_address, {local, Value1, Value2}, Status) when list(Value1),
 
1238
                                                                list(Value2) ->
 
1239
    do_safe_configure(nat_ip_address, {local, Value1, Value2}, Status);
1128
1240
%% Set the range of ports we may use on this machine when connecting to a server.
1129
1241
configure(iiop_out_ports, {Min, Max}, Status) when integer(Min), integer(Max) ->
1130
1242
    do_safe_configure(iiop_out_ports, {Min, Max}, Status);
1139
1251
    do_safe_configure(iiop_acl, Value, Status);
1140
1252
 
1141
1253
%% SSL settings
 
1254
%% configure 'iiop_in_keepalive' will only have effect on new connections.
 
1255
configure(iiop_ssl_in_keepalive, true, Status) ->
 
1256
    do_configure(iiop_ssl_in_keepalive, true, Status);
 
1257
configure(iiop_ssl_in_keepalive, false, Status) ->
 
1258
    do_configure(iiop_ssl_in_keepalive, false, Status);
 
1259
%% configure 'iiop_ssl_out_keepalive' will only have effect on new connections.
 
1260
configure(iiop_ssl_out_keepalive, true, Status) ->
 
1261
    do_configure(iiop_ssl_out_keepalive, true, Status);
 
1262
configure(iiop_ssl_out_keepalive, false, Status) ->
 
1263
    do_configure(iiop_ssl_out_keepalive, false, Status);
 
1264
configure(iiop_ssl_accept_timeout, infinity, Status) ->
 
1265
    do_configure(iiop_ssl_accept_timeout, infinity, Status);
 
1266
configure(iiop_ssl_accept_timeout, Value, Status) when integer(Value), Value >= 0 ->
 
1267
    do_configure(iiop_ssl_accept_timeout, Value, Status);
1142
1268
configure(secure, ssl, Status) ->
1143
1269
    do_safe_configure(secure, ssl, Status);
1144
1270
configure(iiop_ssl_ip_address_local, Value, Status) when list(Value) ->
1147
1273
    do_safe_configure(iiop_ssl_backlog, Value, Status);
1148
1274
configure(nat_iiop_ssl_port, Value, Status) when integer(Value), Value > 0 ->
1149
1275
    do_safe_configure(nat_iiop_ssl_port, Value, Status);
 
1276
configure(nat_iiop_ssl_port, {local, Value1, Value2}, Status) when integer(Value1), 
 
1277
                                                                   Value1 > 0,
 
1278
                                                                   list(Value2) ->
 
1279
    do_safe_configure(nat_iiop_ssl_port, {local, Value1, Value2}, Status);
1150
1280
configure(iiop_ssl_port, Value, Status) when integer(Value) ->
1151
1281
    do_safe_configure(iiop_ssl_port, Value, Status);
1152
1282
configure(ssl_server_certfile, Value, Status) when list(Value) ->