Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:23
erlang
3546-Rewrite-cname-lookups.patch
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 3546-Rewrite-cname-lookups.patch of Package erlang
From 8dd980a138c201e7ee2b099c3bbda7f470c2986a Mon Sep 17 00:00:00 2001 From: Raimo Niskanen <raimo@erlang.org> Date: Fri, 18 Jun 2021 18:35:03 +0200 Subject: [PATCH 6/8] Rewrite cname lookups --- lib/kernel/src/inet_db.erl | 284 +++++++++++++++--------------------- lib/kernel/src/inet_res.erl | 167 ++++++++++++--------- 2 files changed, 211 insertions(+), 240 deletions(-) diff --git a/lib/kernel/src/inet_db.erl b/lib/kernel/src/inet_db.erl index 0a749030ef..4644bea344 100644 --- a/lib/kernel/src/inet_db.erl +++ b/lib/kernel/src/inet_db.erl @@ -67,8 +67,8 @@ -export([res_option/1, res_option/2, res_check_option/2]). -export([socks_option/1]). -export([getbyname/2, get_searchlist/0]). --export([gethostbyaddr/1]). --export([res_gethostbyaddr/2,res_hostent_by_domain/3]). +-export([gethostbyaddr/2]). +-export([res_gethostbyaddr/3,res_hostent_by_domain/3]). -export([res_update_conf/0, res_update_hosts/0]). %% inet help functions -export([tolower/1, eq_domains/2]). @@ -651,6 +651,34 @@ get_searchlist() -> end. +%% +%% hostent_by_domain (cache version) +%% +hostent_by_domain(Domain, Type) -> + ?dbg("hostent_by_domain: ~p~n", [Domain]), + case resolve_cnames(stripdot(Domain), Type, fun lookup_cache_data/2) of + {error, _} = Error -> + Error; + {D, Addrs, Aliases} -> + {ok, make_hostent(D, Addrs, Aliases, Type)} + end. + +%% +%% hostent_by_domain (newly resolved version) +%% match data field directly and cache RRs. +%% +res_hostent_by_domain(Domain, Type, Rec) -> + RRs = res_filter_rrs(Type, Rec#dns_rec.anlist), + ?dbg("res_hostent_by_domain: ~p - ~p~n", [Domain, RRs]), + LookupFun = res_lookup_fun(RRs), + case resolve_cnames(stripdot(Domain), Type, LookupFun) of + {error, _} = Error -> + Error; + {D, Addrs, Aliases} -> + res_cache_answer(RRs), + {ok, make_hostent(D, Addrs, Aliases, Type)} + end. + make_hostent(Name, Addrs, Aliases, ?S_A) -> #hostent { h_name = Name, @@ -677,181 +705,117 @@ make_hostent(Name, Datas, Aliases, Type) -> h_aliases = Aliases }. -hostent_by_domain(Domain, Type) -> - ?dbg("hostent_by_domain: ~p~n", [Domain]), - hostent_by_domain(stripdot(Domain), [], [], Type). - -hostent_by_domain(Domain, Aliases, LAliases, Type) -> - case lookup_type(Domain, Type) of - [] -> - case lookup_cname(Domain) of - [] -> - {error, nxdomain}; - [CName | _] -> - LDomain = tolower(Domain), - case lists:member(CName, [LDomain | LAliases]) of - true -> - {error, nxdomain}; - false -> - hostent_by_domain(CName, [Domain | Aliases], - [LDomain | LAliases], Type) - end - end; - Addrs -> - {ok, make_hostent(Domain, Addrs, Aliases, Type)} - end. -%% lookup canonical name -lookup_cname(Domain) -> - lookup_type(Domain, ?S_CNAME). -%% lookup address record -lookup_type(Domain, Type) -> - [R#dns_rr.data || R <- lookup_rr(Domain, in, Type) ]. - -%% lookup resource record -lookup_rr(Domain, Class, Type) -> - match_rr(dns_rr_match(tolower(Domain), Class, Type)). - -%% -%% hostent_by_domain (newly resolved version) -%% match data field directly and cache RRs. -%% -res_hostent_by_domain(Domain, Type, Rec) -> - RRs = - [RR#dns_rr{bm = tolower(N)} || - #dns_rr{ - domain = N, - class = in, - type = T} = RR <- Rec#dns_rec.anlist, - T =:= Type orelse T =:= ?S_CNAME], - res_cache_answer(RRs), - ?dbg("res_hostent_by_domain: ~p - ~p~n", [Domain, RRs]), - Domain_1 = stripdot(Domain), - res_hostent_by_domain(Domain_1, tolower(Domain_1), [], [], Type, RRs). - -res_hostent_by_domain(Domain, LcDomain, Aliases, LcAliases, Type, RRs) -> - case res_lookup_type(LcDomain, Type, RRs) of - [] -> - case res_lookup_type(LcDomain, ?S_CNAME, RRs) of - [] -> - {error, nxdomain}; - [CName | _] -> - LcCName = tolower(CName), - case lists:member(LcCName, [LcDomain | LcAliases]) of - true -> - %% CNAME loop - {error, nxdomain}; - false -> - res_hostent_by_domain( - CName, LcCName, - [Domain | Aliases], [LcDomain | LcAliases], - Type, RRs) - end - end; - Addrs -> - {ok, make_hostent(Domain, Addrs, Aliases, Type)} +res_filter_rrs(Type, RRs) -> + [RR#dns_rr{bm = tolower(N)} || + #dns_rr{ + domain = N, + class = in, + type = T} = RR <- RRs, + T =:= Type orelse T =:= ?S_CNAME]. + +res_lookup_fun(RRs) -> + fun (LcDomain, Type) -> + [Data + || #dns_rr{bm = LcD, type = T, data = Data} + <- RRs, + LcD =:= LcDomain, + T =:= Type] end. -%% newly resolved lookup address record -res_lookup_type(LcDomain, Type, RRs) -> - [R#dns_rr.data || R <- RRs, - R#dns_rr.bm =:= LcDomain, - R#dns_rr.type =:= Type]. -%% -%% gethostbyaddr (cache version) -%% match data field directly -%% -gethostbyaddr(IP) -> - case dnip(IP) of - {ok, {IP1, HType, HLen, DnIP}} -> - gethostbyaddr(IP1, HType, HLen, DnIP, []); - Error -> Error - end. +resolve_cnames(Domain, Type, LookupFun) -> + resolve_cnames(Domain, Type, LookupFun, tolower(Domain), [], []). -gethostbyaddr(IP, HType, HLen, DnIP, DnIPs) -> - MatchPtrRR = dns_rr_match(DnIP, in, ptr), - case match_rr(MatchPtrRR) of +resolve_cnames(Domain, Type, LookupFun, LcDomain, Aliases, LcAliases) -> + case LookupFun(LcDomain, Type) of [] -> - case lookup_cname(DnIP) of - [#dns_rr{data = DnIP_1} | _] -> - DnIPs_1 = [DnIP | DnIPs], - %% CNAME loop protection - case lists:member(DnIP_1, DnIPs_1) of + case LookupFun(LcDomain, ?S_CNAME) of + [] -> + %% Did not find neither Type nor CNAME record + {error, nxdomain}; + [CName] -> + LcCname = tolower(CName), + case lists:member(LcCname, [LcDomain | LcAliases]) of true -> + %% CNAME loop {error, nxdomain}; false -> - gethostbyaddr(IP, HType, HLen, DnIP_1, DnIPs_1) + %% Repeat with the (more) canonical domain name + resolve_cnames( + CName, Type, LookupFun, LcCname, + [Domain | Aliases], [LcDomain, LcAliases]) end; - CNames when is_list(CNames) -> + [_ | _] = _CNames -> + ?dbg("resolve_cnames duplicate cnames=~p~n", [_CNames]), {error, nxdomain} end; - RRs when is_list(RRs) -> - ent_gethostbyaddr(RRs, IP, HType, HLen) + [_ | _] = Results -> + {Domain, Results, Aliases} + end. + + +%% +%% gethostbyaddr (cache version) +%% match data field directly +%% +gethostbyaddr(Domain, IP) -> + ?dbg("gethostbyaddr: ~p~n", [IP]), + case resolve_cnames(Domain, ?S_PTR, fun lookup_cache_data/2) of + {error, _} = Error -> + Error; + {_D, Domains, _Aliases} -> + ent_gethostbyaddr(Domains, IP) end. %% %% res_gethostbyaddr (newly resolved version) %% match data field directly and cache RRs. %% -res_gethostbyaddr(IP, Rec) -> - {ok, {IP1, HType, HLen}} = dnt(IP), - RRs = - [RR#dns_rr{bm = tolower(N)} || - #dns_rr{ - domain = N, - class = in, - type = T} = RR <- Rec#dns_rec.anlist, - T =:= ?S_PTR orelse T =:= ?S_CNAME], - res_cache_answer(RRs), - case [RR || #dns_rr{type = ?S_PTR} = RR <- RRs] of - [] -> - {error, nxdomain}; - PtrRRs -> - ent_gethostbyaddr(PtrRRs, IP1, HType, HLen) +res_gethostbyaddr(Name, IP, Rec) -> + RRs = res_filter_rrs(?S_PTR, Rec#dns_rec.anlist), + ?dbg("res_gethostbyaddr: ~p - ~p~n", [IP, RRs]), + LookupFun = res_lookup_fun(RRs), + case resolve_cnames(Name, ?S_PTR, LookupFun) of + {error, _} = Error -> + Error; + {_D, Domains, _Aliases} -> + case ent_gethostbyaddr(Domains, IP) of + {ok, _HEnt} = Result -> + res_cache_answer(RRs), + Result; + {error, _} = Error -> + Error + end end. -ent_gethostbyaddr([RR|RRs], IP, AddrType, Length) -> - %% debug - if RRs =/= [] -> - ?dbg("gethostbyaddr found extra=~p~n", [RRs]); - true -> ok - end, - Domain = RR#dns_rr.data, +ent_gethostbyaddr([Domain], IP) -> + {IP_1, AddrType, Length} = norm_ip(IP), H = #hostent{ h_name = Domain, - %% Since a PTR record should point to - %% the canonical name, this Domain should - %% have no CNAME record, so is this really reasonable? - h_aliases = lookup_cname(Domain), - h_addr_list = [IP], + h_aliases = [], + h_addr_list = [IP_1], h_addrtype = AddrType, h_length = Length }, - {ok, H}. + {ok, H}; +ent_gethostbyaddr([_ | _] = _Domains, _IP) -> + ?dbg("gethostbyaddr duplicate domains=~p~n", [_Domains]), + {error, nxdomain}. - -dnip(IP) -> - case dnt(IP) of - {ok,{IP1 = {A,B,C,D}, inet, HLen}} -> - {ok,{IP1, inet, HLen, dn_in_addr_arpa(A,B,C,D)}}; - {ok,{IP1 = {A,B,C,D,E,F,G,H}, inet6, HLen}} -> - {ok,{IP1, inet6, HLen, dn_ip6_int(A,B,C,D,E,F,G,H)}}; - _ -> - {error, formerr} - end. +%% Normalize an IPv4-compatible IPv6 address +%% into a plain IPv4 address +%% +norm_ip(IP) when tuple_size(IP) =:= 4 -> + {IP, inet, 4}; +norm_ip({0,0,0,0,0,16#ffff,G,H}) -> + A = G bsr 8, B = G band 16#ff, C = H bsr 8, D = H band 16#ff, + {{A,B,C,D}, inet, 4}; +norm_ip(IP) when tuple_size(IP) =:= 8 -> + {IP, inet6, 16}. -dnt(IP = {A,B,C,D}) when ?ip(A,B,C,D) -> - {ok, {IP, inet, 4}}; -dnt({0,0,0,0,0,16#ffff,G,H}) when is_integer(G+H) -> - A = G div 256, B = G rem 256, C = H div 256, D = H rem 256, - {ok, {{A,B,C,D}, inet, 4}}; -dnt(IP = {A,B,C,D,E,F,G,H}) when ?ip6(A,B,C,D,E,F,G,H) -> - {ok, {IP, inet6, 16}}; -dnt(_) -> - {error, formerr}. %% %% Register socket Modules @@ -1758,6 +1722,11 @@ dns_rr_match(LcDomain, Class, Type, Data) -> cnt = '_', tm = '_', ttl = '_', bm = LcDomain, func = '_'}. +lookup_cache_data(LcDomain, Type) -> + [Data + || #dns_rr{data = Data} + <- match_rr(dns_rr_match(LcDomain, in, Type))]. + %% We are simultaneously updating the table from all clients %% and the server, so we might get duplicate recource records %% in the table, i.e identical domain, class, type and data. @@ -1892,25 +1861,6 @@ eq_domains(As, Bs) when is_list(As), is_list(Bs) -> false. -dn_ip6_int(A,B,C,D,E,F,G,H) -> - dnib(H) ++ dnib(G) ++ dnib(F) ++ dnib(E) ++ - dnib(D) ++ dnib(C) ++ dnib(B) ++ dnib(A) ++ "ip6.int". - -dn_in_addr_arpa(A,B,C,D) -> - integer_to_list(D) ++ "." ++ - integer_to_list(C) ++ "." ++ - integer_to_list(B) ++ "." ++ - integer_to_list(A) ++ ".in-addr.arpa". - -dnib(X) -> - [hex(X), $., hex(X bsr 4), $., hex(X bsr 8), $., hex(X bsr 12), $.]. - -hex(X) -> - X4 = (X band 16#f), - if X4 < 10 -> X4 + $0; - true -> (X4-10) + $a - end. - %% Strip trailing dot, do not produce garbage unless necessary. %% stripdot(Name) -> diff --git a/lib/kernel/src/inet_res.erl b/lib/kernel/src/inet_res.erl index e238cfd2a1..f5ab7e6a23 100644 --- a/lib/kernel/src/inet_res.erl +++ b/lib/kernel/src/inet_res.erl @@ -355,40 +355,37 @@ gethostbyaddr(IP,Timeout) -> _ = inet:stop_timer(Timer), Res. -gethostbyaddr_tm({A,B,C,D} = IP, Timer) when ?ip(A,B,C,D) -> - inet_db:res_update_conf(), - case inet_db:gethostbyaddr(IP) of - {ok, HEnt} -> {ok, HEnt}; - _ -> res_gethostbyaddr(dn_in_addr_arpa(A,B,C,D), IP, Timer) - end; -gethostbyaddr_tm({A,B,C,D,E,F,G,H} = IP, Timer) when ?ip6(A,B,C,D,E,F,G,H) -> - inet_db:res_update_conf(), - case inet_db:gethostbyaddr(IP) of - {ok, HEnt} -> {ok, HEnt}; - _ -> res_gethostbyaddr(dn_ip6_int(A,B,C,D,E,F,G,H), IP, Timer) - end; -gethostbyaddr_tm(Addr,Timer) when is_list(Addr) -> +gethostbyaddr_tm(Addr, Timer) when is_atom(Addr) -> + gethostbyaddr_tm(atom_to_list(Addr), Timer); +gethostbyaddr_tm(Addr, Timer) when is_list(Addr) -> case inet_parse:address(Addr) of - {ok, IP} -> gethostbyaddr_tm(IP,Timer); + {ok, IP} -> gethostbyaddr_tm(IP, Timer); _Error -> {error, formerr} end; -gethostbyaddr_tm(Addr,Timer) when is_atom(Addr) -> - gethostbyaddr_tm(atom_to_list(Addr),Timer); -gethostbyaddr_tm(_,_) -> {error, formerr}. - -%% -%% Send the gethostbyaddr query to: -%% 1. the list of normal names servers -%% 2. the list of alternative name servers -%% -res_gethostbyaddr(Addr, IP, Timer) -> - case res_query(Addr, in, ?S_PTR, [], Timer) of - {ok, Rec} -> - inet_db:res_gethostbyaddr(IP, Rec); - {error,{qfmterror,_}} -> {error,einval}; - {error,{Reason,_}} -> {error,Reason}; - Error -> - Error +gethostbyaddr_tm(IP, Timer) -> + case dn_ip(IP) of + {error, _} = Error -> + Error; + Name -> + %% Try cached first + inet_db:res_update_conf(), + case inet_db:gethostbyaddr(Name, IP) of + {ok, _HEnt} = Result -> + Result; + {error, nxdomain} -> + %% Do a resolver lookup + case res_query(Name, in, ?S_PTR, [], Timer) of + {ok, Rec} -> + %% Process and cache DNS Record + inet_db:res_gethostbyaddr(Name, IP, Rec); + {error,{qfmterror,_}} -> + {error,einval}; + {error,{Reason,_}} -> + {error,Reason}; + Error -> + Error + end + end end. %% -------------------------------------------------------------------------- @@ -479,12 +476,17 @@ getbyname_tm(Name, Type, Timer) when is_list(Name) -> case type_p(Type) of true -> case inet_parse:visible_string(Name) of - false -> {error, formerr}; + false -> + {error, formerr}; true -> + %% Try cached first inet_db:res_update_conf(), case inet_db:getbyname(Name, Type) of - {ok, HEnt} -> {ok, HEnt}; - _ -> res_getbyname(Name, Type, Timer) + {ok, HEnt} -> + {ok, HEnt}; + _ -> + %% Do a resolver lookup + res_getbyname(Name, Type, Timer) end end; false -> @@ -577,6 +579,7 @@ res_getby_search(_Name, [], Reason,_,_) -> res_getby_query(Name, Type, Timer) -> case res_query(Name, in, Type, [], Timer) of {ok, Rec} -> + %% Process and cache DNS Record inet_db:res_hostent_by_domain(Name, Type, Rec); {error,{qfmterror,_}} -> {error,einval}; {error,{Reason,_}} -> {error,Reason}; @@ -586,6 +589,7 @@ res_getby_query(Name, Type, Timer) -> res_getby_query(Name, Type, Timer, NSs) -> case res_query(Name, in, Type, [], Timer, NSs) of {ok, Rec} -> + %% Process and cache DNS Record inet_db:res_hostent_by_domain(Name, Type, Rec); {error,{qfmterror,_}} -> {error,einval}; {error,{Reason,_}} -> {error,Reason}; @@ -1128,59 +1132,76 @@ decode_answer_noerror( %% 1. "a.b.c" => %% "a.b.c" %% 2. "1.2.3.4" => -%% "4.3.2.1.IN-ADDR.ARPA" +%% "4.3.2.1.in-addr.arpa" %% 3. "4321:0:1:2:3:4:567:89ab" => -%% "b.a.9.8.7.6.5.0.4.0.0.0.3.0.0.0.2.0.0.0.1.0.0.0.0.0.0.1.2.3.4.IP6.ARPA" +%% "b.a.9.8.7.6.5.0.4.0.0.0.3.0.0.0.2.0.0.0.1.0.0.0.0.0.0.1.2.3.4.ip6.arpa" %% 4. {1,2,3,4} => as 2. %% 5. {1,2,3,4,5,6,7,8} => as 3. +%% 6. Atom -> Recurse(String(Atom)) +%% 7. Term => {error, formerr} %% -nsdname({A,B,C,D}) -> - {ok, dn_in_addr_arpa(A,B,C,D)}; -nsdname({A,B,C,D,E,F,G,H}) -> - {ok, dn_ip6_int(A,B,C,D,E,F,G,H)}; +nsdname(Name) when is_atom(Name) -> + nsdname(atom_to_list(Name)); nsdname(Name) when is_list(Name) -> case inet_parse:visible_string(Name) of true -> case inet_parse:address(Name) of - {ok, Addr} -> - nsdname(Addr); + {ok, IP} -> + dn_ip(IP); _ -> {ok, Name} end; _ -> {error, formerr} end; -nsdname(Name) when is_atom(Name) -> - nsdname(atom_to_list(Name)); -nsdname(_) -> {error, formerr}. - -dn_in_addr_arpa(A,B,C,D) -> - integer_to_list(D) ++ - ("." ++ integer_to_list(C) ++ - ("." ++ integer_to_list(B) ++ - ("." ++ integer_to_list(A) ++ ".IN-ADDR.ARPA"))). - -dn_ip6_int(A,B,C,D,E,F,G,H) -> - dnib(H) ++ - (dnib(G) ++ - (dnib(F) ++ - (dnib(E) ++ - (dnib(D) ++ - (dnib(C) ++ - (dnib(B) ++ - (dnib(A) ++ "IP6.ARPA"))))))). - - - --compile({inline, [dnib/1, dnib/3]}). -dnib(X) -> - L = erlang:integer_to_list(X, 16), - dnib(4-length(L), L, []). +nsdname(IP) -> + dn_ip(IP). + +%% Return the domain name for a PTR lookup of +%% the argument IP address %% -dnib(0, [], Acc) -> Acc; -dnib(0, [C|Cs], Acc) -> - dnib(0, Cs, [C,$.|Acc]); -dnib(N, Cs, Acc) -> - dnib(N-1, Cs, [$0,$.|Acc]). +dn_ip({A,B,C,D}) when ?ip(A,B,C,D) -> + dn_ipv4([A,B,C,D], "in-addr.arpa"); +dn_ip({A,B,C,D,E,F,G,H}) when ?ip6(A,B,C,D,E,F,G,H) -> + dn_ipv6([A,B,C,D,E,F,G,H], "ip6.arpa"); +dn_ip(_) -> + {error, formerr}. + +dn_ipv4([], Dn) -> + Dn; +dn_ipv4([A | As], Dn_0) when is_integer(A), A =< 255 -> + Dn = [$. | Dn_0], + if + A < 10 -> + dn_ipv4(As, dn_dec(A, Dn)); + A < 100 -> + dn_ipv4(As, dn_dec(A div 10, dn_dec(A rem 10, Dn))); + true -> + B = A rem 100, + dn_ipv4( + As, + dn_dec(A div 100, dn_dec(B div 10, dn_dec(B rem 10, Dn)))) + end. + +dn_ipv6([], Dn) -> + Dn; +dn_ipv6([W | Ws], Dn) when is_integer(W), W =< 16#ffff -> + D = W band 16#f, W_1 = W bsr 4, + C = W_1 band 16#f, W_2 = W_1 bsr 4, + B = W_2 band 16#f, + A = W_2 bsr 4, + dn_ipv6(Ws, dn_hex(D, dn_hex(C, dn_hex(B, dn_hex(A, Dn))))). + +-compile({inline, [dn_dec/2, dn_hex/2]}). +dn_dec(N, Tail) when is_integer(N) -> + [N + $0 | Tail]. + +dn_hex(N, Tail) when is_integer(N) -> + if + N < 10 -> + [N + $0, $. | Tail]; + true -> + [(N - 10) + $a, $. | Tail] +end. -- 2.31.1
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor