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

« back to all changes in this revision

Viewing changes to lib/kernel/src/inet_db.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:
44
44
-export([set_timeout/1, set_retry/1, set_inet6/1, set_usevc/1]).
45
45
-export([tcp_module/0, set_tcp_module/1]).
46
46
-export([udp_module/0, set_udp_module/1]).
 
47
-export([sctp_module/0,set_sctp_module/1]).
47
48
-export([register_socket/2, unregister_socket/1, lookup_socket/1]).
48
49
 
49
50
%% Host name & domain
81
82
         cache_timer  %% timer reference for refresh
82
83
        }).
83
84
 
84
 
-include_lib("kernel/include/inet.hrl").
 
85
-include("inet.hrl").
85
86
-include("inet_int.hrl").
86
87
-include("inet_res.hrl").
87
88
-include("inet_dns.hrl").
246
247
 
247
248
udp_module() -> db_get(udp_module).
248
249
 
 
250
set_sctp_module(Family)-> call({set_sctp_module,Family}).
 
251
 
 
252
sctp_module()-> db_get(sctp_module).
 
253
 
249
254
 
250
255
%% Add an inetrc file
251
256
add_rc(File) -> 
305
310
              set_inet6(Bool);
306
311
         ({udp, Module}) ->
307
312
              set_udp_module(Module);
 
313
         ({sctp,Module}) ->
 
314
              set_sctp_module(Module);
308
315
         ({tcp, Module}) ->
309
316
              set_tcp_module(Module);
310
317
         (reset) ->
343
350
get_rc() -> 
344
351
    get_rc([hosts, domain, nameserver, search, alt_nameserver,
345
352
            timeout, retry, inet6, usevc,
346
 
            socks5_server, socks5_port, socks5_methods, socks5_noproxy,
347
 
            udp, tcp, host, cache_size, cache_refresh, lookup], []).
 
353
            socks5_server,  socks5_port, socks5_methods, socks5_noproxy,
 
354
            udp, sctp, tcp, host, cache_size, cache_refresh, lookup], []).
348
355
 
349
356
get_rc([K | Ks], Ls) ->
350
357
    case K of
354
361
        alt_nameserver -> get_rc_ns(db_get(res_alt_ns),alt_nameserver,Ks,Ls);
355
362
        search  -> get_rc(search, res_search, [], Ks, Ls);
356
363
        timeout -> get_rc(timeout,res_timeout,?RES_TIMEOUT, Ks,Ls);
357
 
        retry   -> get_rc(rety, res_retry, ?RES_RETRY, Ks, Ls);
 
364
        retry   -> get_rc(retry, res_retry, ?RES_RETRY, Ks, Ls);
358
365
        inet6   -> get_rc(inet6, res_inet6, false, Ks, Ls);
359
366
        usevc   -> get_rc(usevc, res_usevc, false, Ks, Ls);
360
 
        tcp     -> get_rc(tcp, tcp_module, ?DEFAULT_TCP_MODULE, Ks, Ls); 
361
 
        udp     -> get_rc(udp, udp_module, ?DEFAULT_UDP_MODULE, Ks, Ls); 
 
367
        tcp     -> get_rc(tcp,  tcp_module,  ?DEFAULT_TCP_MODULE,  Ks, Ls); 
 
368
        udp     -> get_rc(udp,  udp_module,  ?DEFAULT_UDP_MODULE,  Ks, Ls);
 
369
        sctp    -> get_rc(sctp, sctp_module, ?DEFAULT_SCTP_MODULE, Ks, Ls);
362
370
        lookup  -> get_rc(lookup, res_lookup, [native,file], Ks, Ls);
363
371
        cache_size -> get_rc(cache_size, cache_size, ?CACHE_LIMIT, Ks, Ls);
364
372
        cache_refresh ->
636
644
%%
637
645
%% Register socket Modules
638
646
%%
639
 
register_socket(Socket, Module) when port(Socket), atom(Module) ->
640
 
    catch erlang:port_set_data(Socket,Module).
 
647
register_socket(Socket, Module) when is_port(Socket), is_atom(Module) ->
 
648
    try erlang:port_set_data(Socket, Module)
 
649
    catch
 
650
        error:badarg -> false
 
651
    end.
641
652
 
642
 
unregister_socket(Socket) when port(Socket) ->
 
653
unregister_socket(Socket) when is_port(Socket) ->
643
654
    ok. %% not needed any more
644
655
 
645
 
lookup_socket(Socket) when port(Socket) ->
646
 
    case catch erlang:port_get_data(Socket) of
647
 
        Module when atom(Module) ->
648
 
            {ok, Module};
649
 
        _ ->
650
 
            {error, closed}
 
656
lookup_socket(Socket) when is_port(Socket) ->
 
657
    try erlang:port_get_data(Socket) of
 
658
        Module when is_atom(Module) -> {ok,Module};
 
659
        _                           -> {error,closed}
 
660
    catch
 
661
        error:badarg                -> {error,closed}
651
662
    end.
652
663
 
653
664
%%%----------------------------------------------------------------------
688
699
%%
689
700
%% Generic tcp/udp options
690
701
%% -----------------------
691
 
%% tcp_module     Module          - The default gen_tcp module
692
 
%% udp_module     Module          - The default gen_udp module 
 
702
%% tcp_module     Module          - The default gen_tcp  module
 
703
%% udp_module     Module          - The default gen_udp  module
 
704
%% sctp_module    Module          - The default gen_sctp module
693
705
%%
694
706
%% Distribution options
695
707
%% --------------------
729
741
    ets:insert(Db, {socks5_port, ?IPPORT_SOCKS}),
730
742
    ets:insert(Db, {socks5_methods, [none]}),
731
743
    ets:insert(Db, {socks5_noproxy, []}),
732
 
    ets:insert(Db, {tcp_module, ?DEFAULT_TCP_MODULE}),
733
 
    ets:insert(Db, {udp_module, ?DEFAULT_UDP_MODULE}).
734
 
               
 
744
    ets:insert(Db, {tcp_module,  ?DEFAULT_TCP_MODULE}),
 
745
    ets:insert(Db, {udp_module,  ?DEFAULT_UDP_MODULE}),
 
746
    ets:insert(Db, {sctp_module, ?DEFAULT_SCTP_MODULE}).
735
747
 
736
748
%%----------------------------------------------------------------------
737
749
%% Func: handle_call/3
992
1004
            ets:insert(Db, {udp_module, Mod}), %% check/load module ?
993
1005
            {reply, ok, State};
994
1006
 
 
1007
        {set_sctp_module, Fam} when atom(Fam) ->
 
1008
            ets:insert(Db, {sctp_module, Fam}),
 
1009
            {reply, ok, State};
 
1010
 
995
1011
        {set_cache_size, Size} when integer(Size), Size >= 0 ->
996
1012
            ets:insert(Db, {cache_size, Size}),
997
1013
            {reply, ok, State};