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

« back to all changes in this revision

Viewing changes to lib/kernel/src/inet_db.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 1997-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1997-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
 
88
88
         hosts_file_byaddr, %% hosts table from system file
89
89
         cache_timer        %% timer reference for refresh
90
90
        }).
 
91
-type state() :: #state{}.
91
92
 
92
93
-include("inet.hrl").
93
94
-include("inet_int.hrl").
101
102
 
102
103
start() ->
103
104
    case gen_server:start({local, inet_db}, inet_db, [], []) of
104
 
        {ok,Pid} -> inet_config:init(), {ok,Pid};
 
105
        {ok, _Pid}=Ok -> inet_config:init(), Ok;
105
106
        Error -> Error
106
107
    end.
107
108
 
108
109
 
109
110
start_link() ->
110
111
    case gen_server:start_link({local, inet_db}, inet_db, [], []) of
111
 
        {ok,Pid} -> inet_config:init(), {ok,Pid};
 
112
        {ok, _Pid}=Ok -> inet_config:init(), Ok;
112
113
        Error -> Error
113
114
    end.
114
115
               
139
140
        Error -> Error
140
141
    end.
141
142
 
142
 
 
143
143
add_host(IP, Names) -> call({add_host, IP, Names}).
144
144
 
145
145
del_host(IP) ->  call({del_host, IP}).
425
425
res_optname(edns) -> res_edns;
426
426
res_optname(udp_payload_size) -> res_udp_payload_size;
427
427
res_optname(resolv_conf) -> res_resolv_conf;
 
428
res_optname(resolv_conf_name) -> res_resolv_conf;
428
429
res_optname(hosts_file) -> res_hosts_file;
 
430
res_optname(hosts_file_name) -> res_hosts_file;
429
431
res_optname(_) -> undefined.
430
432
 
431
433
res_check_option(nameserver, NSs) -> %% Legacy
458
460
res_check_option(resolv_conf, "") -> true;
459
461
res_check_option(resolv_conf, F) ->
460
462
    res_check_option_absfile(F);
 
463
res_check_option(resolv_conf_name, "") -> true;
 
464
res_check_option(resolv_conf_name, F) ->
 
465
    res_check_option_absfile(F);
461
466
res_check_option(hosts_file, "") -> true;
462
467
res_check_option(hosts_file, F) ->
463
468
    res_check_option_absfile(F);
 
469
res_check_option(hosts_file_name, "") -> true;
 
470
res_check_option(hosts_file_name, F) ->
 
471
    res_check_option_absfile(F);
464
472
res_check_option(_, _) -> false.
465
473
 
466
474
res_check_option_absfile(F) ->
473
481
 
474
482
res_check_list([], _Fun) -> true;
475
483
res_check_list([H|T], Fun) ->
476
 
    case Fun(H) of
477
 
        true -> res_check_list(T, Fun);
478
 
        false -> false
479
 
    end;
 
484
    Fun(H) andalso res_check_list(T, Fun);
480
485
res_check_list(_, _Fun) -> false.
481
486
 
482
487
res_check_ns({{A,B,C,D,E,F,G,H}, Port})
488
493
res_check_search("") -> true;
489
494
res_check_search(Dom) -> inet_parse:visible_string(Dom).
490
495
 
491
 
socks_option(server)       -> db_get(socks5_server);
492
 
socks_option(port)         -> db_get(socks5_port);
493
 
socks_option(methods)      -> db_get(socks5_methods);
494
 
socks_option(noproxy)      -> db_get(socks5_noproxy).
 
496
socks_option(server)  -> db_get(socks5_server);
 
497
socks_option(port)    -> db_get(socks5_port);
 
498
socks_option(methods) -> db_get(socks5_methods);
 
499
socks_option(noproxy) -> db_get(socks5_noproxy).
495
500
 
496
 
gethostname()              -> db_get(hostname).
 
501
gethostname()         -> db_get(hostname).
497
502
 
498
503
res_update_conf() ->
499
504
    res_update(res_resolv_conf, res_resolv_conf_tm, res_resolv_conf_info,
503
508
    res_update(res_hosts_file, res_hosts_file_tm, res_hosts_file_info,
504
509
               set_hosts_file_tm, fun set_hosts_file/1).
505
510
 
506
 
res_update(Tag, TagTm, TagInfo, CallTag, SetFun) ->
 
511
res_update(Tag, TagTm, TagInfo, TagSetTm, SetFun) ->
507
512
    case db_get(TagTm) of
508
513
        undefined -> ok;
509
514
        TM ->
522
527
                                                         atime = undefined},
523
528
                                    case db_get(TagInfo) of
524
529
                                        Finfo ->
525
 
                                            call({CallTag, Now});
 
530
                                            call({TagSetTm, Now});
526
531
                                        _ ->
527
532
                                            SetFun(File)
528
533
                                    end;
529
534
                                _ ->
530
 
                                    call({CallTag, Now}),
 
535
                                    call({TagSetTm, Now}),
531
536
                                    error
532
537
                            end
533
538
                    end;
582
587
 
583
588
getbysearch(Name, Dot, [Dom | Ds], Type, _) ->
584
589
    case hostent_by_domain(Name ++ Dot ++ Dom, Type) of
585
 
        {ok, HEnt} -> {ok, HEnt};
586
 
        Error      ->
587
 
            getbysearch(Name, Dot, Ds, Type, Error)
 
590
        {ok, _HEnt}=Ok -> Ok;
 
591
        Error -> getbysearch(Name, Dot, Ds, Type, Error)
588
592
    end;
589
593
getbysearch(_Name, _Dot, [], _Type, Error) ->
590
594
    Error.
591
595
 
592
596
 
593
 
 
594
597
%%
595
598
%% get_searchlist
596
599
%%
601
604
    end.
602
605
 
603
606
 
604
 
 
605
607
make_hostent(Name, Addrs, Aliases, ?S_A) ->
606
608
    #hostent {
607
609
              h_name = Name,
836
838
%% node_auth      Ls              - Default authenication
837
839
%% node_crypt     Ls              - Default encryption
838
840
%%
 
841
 
 
842
-spec init([]) -> {'ok', state()}.
 
843
 
839
844
init([]) ->
840
845
    process_flag(trap_exit, true),
841
846
    Db = ets:new(inet_db, [public, named_table]),
889
894
%%          {stop, Reason, Reply, State}   | (terminate/2 is called)
890
895
%%          {stop, Reason, Reply, State}     (terminate/2 is called)
891
896
%%----------------------------------------------------------------------
 
897
 
 
898
-spec handle_call(term(), {pid(), term()}, state()) ->
 
899
        {'reply', term(), state()} | {'stop', 'normal', 'ok', state()}.
 
900
 
892
901
handle_call(Request, From, #state{db=Db}=State) ->
893
902
    case Request of
894
903
        {load_hosts_file,IPNmAs} when is_list(IPNmAs) ->
974
983
                    {reply, error, State}
975
984
            end;
976
985
 
 
986
        {res_set, hosts_file_name=Option, Fname} ->
 
987
            handle_set_file(
 
988
              Option, Fname, res_hosts_file_tm, res_hosts_file_info,
 
989
              undefined, From, State);
 
990
        {res_set, resolv_conf_name=Option, Fname} ->
 
991
            handle_set_file(
 
992
              Option, Fname, res_resolv_conf_tm, res_resolv_conf_info,
 
993
              undefined, From, State);
 
994
 
977
995
        {res_set, hosts_file=Option, Fname} ->
978
 
            handle_set_file(Option, Fname,
979
 
                            res_hosts_file_tm, res_hosts_file_info,
980
 
                            fun (Bin) ->
981
 
                                    case inet_parse:hosts(Fname,
982
 
                                                          {chars,Bin}) of
983
 
                                        {ok,Opts} ->
984
 
                                            [{load_hosts_file,Opts}];
985
 
                                        _ -> error
986
 
                                    end
987
 
                            end,
988
 
                            From, State);
 
996
            handle_set_file(
 
997
              Option, Fname, res_hosts_file_tm, res_hosts_file_info,
 
998
              fun (Bin) ->
 
999
                      case inet_parse:hosts(
 
1000
                             Fname, {chars,Bin}) of
 
1001
                          {ok,Opts} ->
 
1002
                              [{load_hosts_file,Opts}];
 
1003
                          _ -> error
 
1004
                      end
 
1005
              end,
 
1006
              From, State);
989
1007
        %%
990
1008
        {res_set, resolv_conf=Option, Fname} ->
991
 
            handle_set_file(Option, Fname,
992
 
                            res_resolv_conf_tm, res_resolv_conf_info,
993
 
                            fun (Bin) ->
994
 
                                    case inet_parse:resolv(Fname,
995
 
                                                          {chars,Bin}) of
996
 
                                        {ok,Opts} ->
997
 
                                            [del_ns,
998
 
                                             clear_search,
999
 
                                             clear_cache
1000
 
                                             |[Opt ||
1001
 
                                                  {T,_}=Opt <- Opts,
1002
 
                                                  (T =:= nameserver orelse
1003
 
                                                   T =:= search)]];
1004
 
                                        _ -> error
1005
 
                                    end
1006
 
                            end,
1007
 
                            From, State);
 
1009
            handle_set_file(
 
1010
              Option, Fname, res_resolv_conf_tm, res_resolv_conf_info,
 
1011
              fun (Bin) ->
 
1012
                      case inet_parse:resolv(
 
1013
                             Fname, {chars,Bin}) of
 
1014
                          {ok,Opts} ->
 
1015
                              Search =
 
1016
                                  lists:foldl(
 
1017
                                    fun ({search,L}, _) ->
 
1018
                                            L;
 
1019
                                        ({domain,""}, S) ->
 
1020
                                            S;
 
1021
                                        ({domain,D}, _) ->
 
1022
                                            [D];
 
1023
                                        (_, S) ->
 
1024
                                            S
 
1025
                                    end, [], Opts),
 
1026
                              [del_ns,
 
1027
                               clear_search,
 
1028
                               clear_cache,
 
1029
                               {search,Search}
 
1030
                               |[Opt || {nameserver,_}=Opt <- Opts]];
 
1031
                          _ -> error
 
1032
                      end
 
1033
              end,
 
1034
              From, State);
1008
1035
        %%
1009
1036
        {res_set, Opt, Value} ->
1010
1037
            case res_optname(Opt) of
1112
1139
            {reply, error, State}
1113
1140
    end.
1114
1141
 
1115
 
 
1116
1142
%%----------------------------------------------------------------------
1117
1143
%% Func: handle_cast/2
1118
1144
%% Returns: {noreply, State}          |
1119
1145
%%          {noreply, State, Timeout} |
1120
1146
%%          {stop, Reason, State}            (terminate/2 is called)
1121
1147
%%----------------------------------------------------------------------
 
1148
 
 
1149
-spec handle_cast(term(), state()) -> {'noreply', state()}.
 
1150
 
1122
1151
handle_cast(_Msg, State) ->
1123
1152
    {noreply, State}.
1124
1153
 
1128
1157
%%          {noreply, State, Timeout} |
1129
1158
%%          {stop, Reason, State}            (terminate/2 is called)
1130
1159
%%----------------------------------------------------------------------
 
1160
 
 
1161
-spec handle_info(term(), state()) -> {'noreply', state()}.
 
1162
 
1131
1163
handle_info(refresh_timeout, State) ->
1132
1164
    do_refresh_cache(State#state.cache),
1133
1165
    {noreply, State#state{cache_timer = init_timer()}};
1140
1172
%% Purpose: Shutdown the server
1141
1173
%% Returns: any (ignored by gen_server)
1142
1174
%%----------------------------------------------------------------------
 
1175
 
 
1176
-spec terminate(term(), state()) -> 'ok'.
 
1177
 
1143
1178
terminate(_Reason, State) ->
1144
1179
    stop_timer(State#state.cache_timer),
1145
1180
    ok.
1156
1191
            ets:delete(Db, TagInfo),
1157
1192
            ets:delete(Db, TagTm),
1158
1193
            handle_set_file(ParseFun, <<>>, From, State);
 
1194
        true when ParseFun =:= undefined ->
 
1195
            File = filename:flatten(Fname),
 
1196
            ets:insert(Db, {res_optname(Option), File}),
 
1197
            ets:insert(Db, {TagInfo, undefined}),
 
1198
            ets:insert(Db, {TagTm, 0}),
 
1199
            {reply,ok,State};
1159
1200
        true ->
1160
1201
            File = filename:flatten(Fname),
1161
1202
            ets:insert(Db, {res_optname(Option), File}),
1178
1219
 
1179
1220
handle_set_file(ParseFun, Bin, From, State) ->
1180
1221
    case ParseFun(Bin) of
1181
 
        error -> {reply,error,State};
 
1222
        error ->
 
1223
            {reply,error,State};
1182
1224
        Opts ->
1183
1225
            handle_rc_list(Opts, From, State)
1184
1226
    end.
1309
1351
    TM = times(),
1310
1352
    case alloc_entry(Db, CacheDb, TM) of
1311
1353
        true ->
1312
 
            cache_rr(Db, CacheDb, RR#dns_rr { tm = TM,
1313
 
                                              cnt = TM });
 
1354
            cache_rr(Db, CacheDb, RR#dns_rr{tm = TM, cnt = TM});
1314
1355
        _ ->
1315
1356
            false
1316
1357
    end.
1317
1358
 
1318
1359
cache_rr(_Db, Cache, RR) ->
1319
1360
    %% delete possible old entry
1320
 
    ets:match_delete(Cache, RR#dns_rr { cnt = '_', tm = '_', ttl = '_',
1321
 
                                        bm = '_', func = '_'}),
 
1361
    ets:match_delete(Cache, RR#dns_rr{cnt = '_', tm = '_', ttl = '_',
 
1362
                                      bm = '_', func = '_'}),
1322
1363
    ets:insert(Cache, RR).
1323
1364
 
1324
1365
times() ->
1328
1369
%% lookup and remove old entries
1329
1370
 
1330
1371
do_lookup_rr(Domain, Class, Type) ->
1331
 
    match_rr(#dns_rr { domain = tolower(Domain), class = Class,type = Type, 
1332
 
                      cnt = '_', tm = '_', ttl = '_',
1333
 
                      bm = '_', func = '_', data = '_'}).
 
1372
    match_rr(#dns_rr{domain = tolower(Domain), class = Class,type = Type,
 
1373
                     cnt = '_', tm = '_', ttl = '_',
 
1374
                     bm = '_', func = '_', data = '_'}).
1334
1375
 
1335
1376
match_rr(RR) ->
1336
1377
    filter_rr(ets:match_object(inet_cache, RR), times()).
1381
1422
        integer_to_list(A) ++ ".in-addr.arpa".
1382
1423
 
1383
1424
dnib(X) ->
1384
 
    [ hex(X), $., hex(X bsr 4), $., hex(X bsr 8), $., hex(X bsr 12), $.].
 
1425
    [hex(X), $., hex(X bsr 4), $., hex(X bsr 8), $., hex(X bsr 12), $.].
1385
1426
 
1386
1427
hex(X) ->
1387
1428
    X4 = (X band 16#f),
1476
1517
 
1477
1518
delete_n_oldest(CacheDb, TM, OldestTM, N) ->
1478
1519
    DelTM = trunc((TM - OldestTM) * 0.3) + OldestTM,
1479
 
    case delete_older(CacheDb, DelTM, N) of
1480
 
        0 ->
1481
 
            false;
1482
 
        _ ->
1483
 
            true
1484
 
    end.
 
1520
    delete_older(CacheDb, DelTM, N) =/= 0.
1485
1521
 
1486
1522
%% Delete entries with latest access time older than TM.
1487
1523
%% Delete max N number of entries.