File 2981-inet_db-inet_hosts-improve-inet_db-behaviour-when-.h.patch of Package erlang
From fb39f10247e5fff705d8e92933f62aa3b6dab086 Mon Sep 17 00:00:00 2001
From: Maxim Fedorov <dane@whatsapp.com>
Date: Wed, 22 Jan 2020 05:56:39 -0800
Subject: [PATCH 1/6] inet_db, inet_hosts: improve inet_db behaviour when
.hosts file changes
Avoid re-parsing changed file over and over, also fix race condition
when ETS table with IP <-> name mappings is first deleted, then
re-created.
---
lib/kernel/src/inet_db.erl | 116 +++++++++++++++++++++++++++--------------
lib/kernel/src/inet_hosts.erl | 26 +++++----
lib/kernel/test/inet_SUITE.erl | 45 ++++++++++++++++
3 files changed, 133 insertions(+), 54 deletions(-)
diff --git a/lib/kernel/src/inet_db.erl b/lib/kernel/src/inet_db.erl
index 630ef5d2f7..39019784b6 100644
--- a/lib/kernel/src/inet_db.erl
+++ b/lib/kernel/src/inet_db.erl
@@ -234,7 +234,7 @@ set_resolv_conf(Fname) -> res_option(resolv_conf, Fname).
set_hosts_file(Fname) -> res_option(hosts_file, Fname).
get_hosts_file() ->
- get_rc_hosts([], [], inet_hosts_file_byname).
+ get_rc_hosts([], [], inet_hosts_file_byaddr).
%% set socks options
set_socks_server(Server) -> call({set_socks_server, Server}).
@@ -318,7 +318,7 @@ get_rc() ->
get_rc([K | Ks], Ls) ->
case K of
- hosts -> get_rc_hosts(Ks, Ls, inet_hosts_byname);
+ hosts -> get_rc_hosts(Ks, Ls, inet_hosts_byaddr);
domain -> get_rc(domain, res_domain, "", Ks, Ls);
nameservers -> get_rc_ns(db_get(res_ns),nameservers,Ks,Ls);
alt_nameservers -> get_rc_ns(db_get(res_alt_ns),alt_nameservers,Ks,Ls);
@@ -371,18 +371,11 @@ get_rc_ns([], _Tag, Ks, Ls) ->
get_rc(Ks, Ls).
get_rc_hosts(Ks, Ls, Tab) ->
- case lists:keysort(3, ets:tab2list(Tab)) of
+ case ets:tab2list(Tab) of
[] -> get_rc(Ks, Ls);
- [{N,_,IP}|Hosts] -> get_rc_hosts(Ks, Ls, IP, Hosts, [N])
+ Hosts -> get_rc(Ks, [ [{host, IP, Names} || {{IP, _}, Names} <- Hosts] | Ls])
end.
-get_rc_hosts(Ks, Ls, IP, [], Ns) ->
- get_rc(Ks, [{host,IP,lists:reverse(Ns)}|Ls]);
-get_rc_hosts(Ks, Ls, IP, [{N,_,IP}|Hosts], Ns) ->
- get_rc_hosts(Ks, Ls, IP, Hosts, [N|Ns]);
-get_rc_hosts(Ks, Ls, IP, [{N,_,NewIP}|Hosts], Ns) ->
- [{host,IP,lists:reverse(Ns)}|get_rc_hosts(Ks, Ls, NewIP, Hosts, [N])].
-
%%
%% Resolver options
%%
@@ -853,12 +846,10 @@ init([]) ->
reset_db(Db),
CacheOpts = [public, bag, {keypos,#dns_rr.domain}, named_table],
Cache = ets:new(inet_cache, CacheOpts),
- BynameOpts = [protected, bag, named_table, {keypos,1}],
- ByaddrOpts = [protected, bag, named_table, {keypos,3}],
- HostsByname = ets:new(inet_hosts_byname, BynameOpts),
- HostsByaddr = ets:new(inet_hosts_byaddr, ByaddrOpts),
- HostsFileByname = ets:new(inet_hosts_file_byname, BynameOpts),
- HostsFileByaddr = ets:new(inet_hosts_file_byaddr, ByaddrOpts),
+ HostsByname = ets:new(inet_hosts_byname, [named_table]),
+ HostsByaddr = ets:new(inet_hosts_byaddr, [named_table]),
+ HostsFileByname = ets:new(inet_hosts_file_byname, [named_table]),
+ HostsFileByaddr = ets:new(inet_hosts_file_byaddr, [named_table]),
{ok, #state{db = Db,
cache = Cache,
hosts_byname = HostsByname,
@@ -908,22 +899,7 @@ reset_db(Db) ->
handle_call(Request, From, #state{db=Db}=State) ->
case Request of
{load_hosts_file,IPNmAs} when is_list(IPNmAs) ->
- NIPs =
- lists:flatten(
- [ [{N,
- if tuple_size(IP) =:= 4 -> inet;
- tuple_size(IP) =:= 8 -> inet6
- end,IP} || N <- [Nm|As]]
- || {IP,Nm,As} <- IPNmAs]),
- Byname = State#state.hosts_file_byname,
- Byaddr = State#state.hosts_file_byaddr,
- ets:delete_all_objects(Byname),
- ets:delete_all_objects(Byaddr),
- %% Byname has lowercased names while Byaddr keep the name casing.
- %% This is to be able to reconstruct the original
- %% /etc/hosts entry.
- ets:insert(Byname, [{tolower(N),Type,IP} || {N,Type,IP} <- NIPs]),
- ets:insert(Byaddr, NIPs),
+ load_hosts_list(IPNmAs, State#state.hosts_file_byname, State#state.hosts_file_byaddr),
{reply, ok, State};
{add_host,{A,B,C,D}=IP,[N|As]=Names}
@@ -1246,16 +1222,76 @@ handle_set_file(ParseFun, Bin, From, State) ->
do_add_host(Byname, Byaddr, Names, Type, IP) ->
do_del_host(Byname, Byaddr, IP),
- ets:insert(Byname, [{tolower(N),Type,IP} || N <- Names]),
- ets:insert(Byaddr, [{N,Type,IP} || N <- Names]),
+ ets:insert(Byname, [{tolower(N), [{IP,Type}], Names} || N <- Names]),
+ ets:insert(Byaddr, {{IP, Type}, Names}),
ok.
do_del_host(Byname, Byaddr, IP) ->
- _ =
- [ets:delete_object(Byname, {tolower(Name),Type,Addr}) ||
- {Name,Type,Addr} <- ets:lookup(Byaddr, IP)],
- ets:delete(Byaddr, IP),
- ok.
+ IpWithType = {IP, inet_family(IP)},
+ case ets:lookup(Byaddr, IpWithType) of
+ [{IpWithType, AllNames}] ->
+ lists:foreach(fun (Name) ->
+ case ets:lookup(Byname, Name) of
+ [{Name, [IpWithType], _}] ->
+ ets:delete(Byname, Name);
+ [{Name, [_|_] = OldIps, Aliases}] ->
+ ets:insert(Byname, {Name, lists:delete(IpWithType, OldIps), Aliases})
+ end
+ end, AllNames),
+ ets:delete(Byaddr, IpWithType),
+ ok;
+ _ -> ok
+ end.
+
+inet_family(T) when tuple_size(T) =:= 4 -> inet;
+inet_family(T) when tuple_size(T) =:= 8 -> inet6.
+
+populate_hosts_tables_byname([], _Names, _IP, _ByName) ->
+ ok;
+populate_hosts_tables_byname([NameOrAlias | Tail], Names, IP, ByName) ->
+ case ets:insert_new(ByName, {NameOrAlias, [IP], Names}) of
+ true -> ok;
+ false ->
+ [{NameOrAlias, ExistingIPs, ExistingPrimary}] = ets:lookup(ByName, NameOrAlias),
+ ets:insert(ByName, {NameOrAlias, ExistingIPs ++ [IP], ExistingPrimary})
+ end,
+ populate_hosts_tables_byname(Tail, Names, IP, ByName).
+
+populate_hosts_tables([], _ByName, _ByAddr) ->
+ ok;
+populate_hosts_tables([{IP0, Name, Aliases} | Tail], ByName, ByAddr) ->
+ IP = {IP0, inet_family(IP0)},
+ Names = [Name | Aliases],
+ case ets:insert_new(ByAddr, {IP, Names}) of
+ true -> ok;
+ false ->
+ [{IP, ExistingNames}] = ets:lookup(ByAddr, IP),
+ ets:insert(ByAddr, {IP, ExistingNames ++ Names})
+ end,
+ populate_hosts_tables_byname(Names, Names, IP, ByName),
+ populate_hosts_tables(Tail, ByName, ByAddr).
+
+clean_hosts_tables([], _ByNameTmp, _ByAddrTmp, _ByName, _ByAddr) ->
+ ok;
+clean_hosts_tables([{IP, Names} | Tail], ByNameTmp, ByAddrTmp, ByName, ByAddr) ->
+ _ = case ets:lookup(ByAddrTmp, IP) of
+ [{IP, Names}] -> ok;
+ _ ->
+ ets:delete(ByAddr, IP),
+ lists:map(fun(N) -> ets:delete(ByName, N) end, Names)
+ end,
+ clean_hosts_tables(Tail, ByNameTmp, ByAddrTmp, ByName, ByAddr).
+
+%% Synchronises internal tables with .hosts/aliases file
+load_hosts_list(IPNmAs, ByName, ByAddr) ->
+ ByAddrTmp = ets:new(load_hosts_list_by_addr, [private]),
+ ByNameTmp = ets:new(load_hosts_list_by_name, [private]),
+ populate_hosts_tables(IPNmAs, ByNameTmp, ByAddrTmp),
+ clean_hosts_tables(ets:tab2list(ByAddr), ByNameTmp, ByAddrTmp, ByName, ByAddr),
+ ets:insert(ByAddr, ets:tab2list(ByAddrTmp)),
+ ets:insert(ByName, ets:tab2list(ByNameTmp)),
+ ets:delete(ByAddrTmp),
+ ets:delete(ByNameTmp).
%% Loop over .inetrc option list and call handle_call/3 for each
%%
diff --git a/lib/kernel/src/inet_hosts.erl b/lib/kernel/src/inet_hosts.erl
index fc653bf0d3..20f564357c 100644
--- a/lib/kernel/src/inet_hosts.erl
+++ b/lib/kernel/src/inet_hosts.erl
@@ -42,11 +42,9 @@ gethostbyname(Name, Type) when is_list(Name), is_atom(Type) ->
%% Byname has lowercased names while Byaddr keep the name casing.
%% This is to be able to reconstruct the original /etc/hosts entry.
N = inet_db:tolower(Name),
- case gethostbyname(N, Type, inet_hosts_byname, inet_hosts_byaddr) of
+ case gethostbyname(N, Type, inet_hosts_byname) of
false ->
- case gethostbyname(N, Type,
- inet_hosts_file_byname,
- inet_hosts_file_byaddr) of
+ case gethostbyname(N, Type, inet_hosts_file_byname) of
false -> {error,nxdomain};
Hostent -> {ok,Hostent}
end;
@@ -56,15 +54,16 @@ gethostbyname(Name, Type) when is_atom(Name), is_atom(Type) ->
gethostbyname(atom_to_list(Name), Type);
gethostbyname(_, _) -> {error, formerr}.
-gethostbyname(Name, Type, Byname, Byaddr) ->
+gethostbyname(Name, Type, Byname) ->
inet_db:res_update_hosts(),
- case [I || [I] <- ets:match(Byname, {Name,Type,'$1'})] of
+ case ets:lookup(Byname, Name) of
[] -> false;
- [IP|_]=IPs ->
- %% Use the primary IP address to generate aliases
- [Nm|As] = [N || [N] <- ets:match(Byaddr,
- {'$1',Type,IP})],
- make_hostent(Nm, IPs, As, Type)
+ [{Name, IPs, [Primary | Aliases]}] ->
+ %% Filter by IP type
+ case lists:filtermap(fun ({IP, T}) when T =:= Type -> {true, IP}; (_) -> false end, IPs) of
+ [] -> false;
+ List -> make_hostent(Primary, List, Aliases, Type)
+ end
end.
@@ -97,13 +96,12 @@ gethostbyaddr(IP, Type) ->
gethostbyaddr(IP, Type, Byaddr) ->
inet_db:res_update_hosts(),
- case [N || [N] <- ets:match(Byaddr, {'$1',Type,IP})] of
+ case ets:lookup(Byaddr, {IP, Type}) of
[] -> false;
- [Nm|As] -> make_hostent(Nm, [IP], As, Type)
+ [{_, [Primary | Aliases]}] -> make_hostent(Primary, [IP], Aliases, Type)
end.
-
make_hostent(Name, Addrs, Aliases, inet) ->
#hostent {
h_name = Name,
diff --git a/lib/kernel/test/inet_SUITE.erl b/lib/kernel/test/inet_SUITE.erl
index 44ec7e7076..839941d440 100644
--- a/lib/kernel/test/inet_SUITE.erl
+++ b/lib/kernel/test/inet_SUITE.erl
@@ -43,6 +43,7 @@
getif_ifr_name_overflow/1,getservbyname_overflow/1, getifaddrs/1,
parse_strict_address/1, ipv4_mapped_ipv6_address/1, ntoa/1,
simple_netns/1, simple_netns_open/1,
+ add_del_host/1, add_del_host_v6/1,
simple_bind_to_device/1, simple_bind_to_device_open/1]).
-export([get_hosts/1, get_ipv6_hosts/1, parse_hosts/1, parse_address/1,
@@ -63,6 +64,7 @@ all() ->
getif, getif_ifr_name_overflow, getservbyname_overflow,
getifaddrs, parse_strict_address, ipv4_mapped_ipv6_address, ntoa,
simple_netns, simple_netns_open,
+ add_del_host, add_del_host_v6,
simple_bind_to_device, simple_bind_to_device_open].
groups() ->
@@ -1459,3 +1461,46 @@ jog_bind_to_device_opt(S) ->
ok = inet:setopts(S, [{bind_to_device,<<"lo">>}]),
{ok,[{bind_to_device,<<"lo">>}]} = inet:getopts(S, [bind_to_device]),
ok.
+
+add_del_host(_Config) ->
+ Name = "foo.com",
+ Alias = "bar.org",
+ Ip = {69,89,31,226},
+ HostEnt = #hostent{
+ h_name = Name,
+ h_aliases = [Alias],
+ h_addrtype = inet,
+ h_length = 4,
+ h_addr_list = [Ip]
+ },
+ {error, nxdomain} = inet_hosts:gethostbyname(Name, inet),
+ ok = inet_db:add_host(Ip, [Name, Alias]),
+ {ok, HostEnt} = inet_hosts:gethostbyname(Name, inet),
+ {ok, HostEnt} = inet_hosts:gethostbyname(Alias, inet),
+ ok = inet_db:del_host(Ip),
+ {error, nxdomain} = inet_hosts:gethostbyname(Name, inet),
+ {error, nxdomain} = inet_hosts:gethostbyname(Alias, inet),
+ ok = inet_db:add_host(Ip, [Name, Alias]),
+ {ok, HostEnt} = inet_hosts:gethostbyname(Name, inet).
+
+add_del_host_v6(_Config) ->
+ Name = "foo.com",
+ Alias = "bar.org",
+ Ip = {32,1,219,8,10,11,18,240},
+ HostEnt = #hostent{
+ h_name = Name,
+ h_aliases = [Alias],
+ h_addrtype = inet6,
+ h_length = 16,
+ h_addr_list = [Ip]
+ },
+ {error, nxdomain} = inet_hosts:gethostbyname(Name, inet6),
+ ok = inet_db:add_host(Ip, [Name, Alias]),
+ {ok, HostEnt} = inet_hosts:gethostbyname(Name, inet6),
+ {ok, HostEnt} = inet_hosts:gethostbyname(Alias, inet6),
+ ok = inet_db:del_host(Ip),
+ {error, nxdomain} = inet_hosts:gethostbyname(Name, inet6),
+ {error, nxdomain} = inet_hosts:gethostbyname(Alias, inet6),
+ ok = inet_db:add_host(Ip, [Name, Alias]),
+ {ok, HostEnt} = inet_hosts:gethostbyname(Name, inet6).
+
--
2.16.4