File 0364-Use-case-insensitive-domain-compare.patch of Package erlang

From d5f0138841ccc48592ac68283c5383297a986381 Mon Sep 17 00:00:00 2001
From: Raimo Niskanen <raimo@erlang.org>
Date: Fri, 23 Apr 2021 16:23:17 +0200
Subject: [PATCH 4/8] Use case insensitive domain compare

---
 lib/kernel/src/inet_db.erl  | 39 +++++++++++++++++++++++++++++++++++--
 lib/kernel/src/inet_res.erl |  4 ++--
 2 files changed, 39 insertions(+), 4 deletions(-)

diff --git a/lib/kernel/src/inet_db.erl b/lib/kernel/src/inet_db.erl
index 90e2f66365..2741810360 100644
--- a/lib/kernel/src/inet_db.erl
+++ b/lib/kernel/src/inet_db.erl
@@ -71,7 +71,7 @@
 -export([res_gethostbyaddr/2,res_hostent_by_domain/3]).
 -export([res_update_conf/0, res_update_hosts/0]).
 %% inet help functions
--export([tolower/1]).
+-export([tolower/1, eq_domains/2]).
 -ifdef(DEBUG).
 -define(dbg(Fmt, Args), io:format(Fmt, Args)).
 -else.
@@ -1818,13 +1818,48 @@ match_rr_key(
 %% does not follow RFC 4343.
 %%
 tolower([]) -> [];
-tolower([C|Cs]) when is_integer(C) ->
+tolower([C|Cs]) when is_integer(C), 0 =< C, C =< 16#10FFFF ->
     if  C >= $A, C =< $Z ->
 	    [(C-$A)+$a|tolower(Cs)];
 	true ->
 	    [C|tolower(Cs)]
     end.
 
+%% Case insensitive domain name comparison according to RFC 4343
+%% "Domain Name System (DNS) Case Insensitivity Clarification",
+%% i.e regard $a through $z as equal to $A through $Z.
+%%
+eq_domains([A | As], [B | Bs]) ->
+    if
+        is_integer(A), 0 =< A, A =< 16#10FFFF,
+        is_integer(B), 0 =< B, B =< 16#10FFFF ->
+            %% An upper bound of 255 would be right right now,
+            %% but this algorithm works for any integer.  That
+            %% guard just gives the compiler the opportuinity
+            %% to optimize bit operations for machine word size,
+            %% so we might as well use the Unicode upper bound instead.
+            Xor = (A bxor B),
+            if
+                Xor =:= 0 ->
+                    eq_domains(As, Bs);
+                Xor =:= ($A bxor $a) ->
+                    And = (A band B),
+                    if
+                        ($A band $a) =< And, And =< ($Z band $z) ->
+                            eq_domains(As, Bs);
+                        true ->
+                            false
+                    end;
+                true ->
+                    false
+            end
+    end;
+eq_domains([], []) ->
+    true;
+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".
diff --git a/lib/kernel/src/inet_res.erl b/lib/kernel/src/inet_res.erl
index 1b6344f372..e238cfd2a1 100644
--- a/lib/kernel/src/inet_res.erl
+++ b/lib/kernel/src/inet_res.erl
@@ -1110,8 +1110,8 @@ decode_answer_noerror(
                         andalso
                         (RR#dns_query.type =:= Q_RR#dns_query.type)
                         andalso
-                        (inet_db:tolower(RR#dns_query.domain) =:=
-                             inet_db:tolower(Q_RR#dns_query.domain))
+                        inet_db:eq_domains(
+                          RR#dns_query.domain, Q_RR#dns_query.domain)
                     of
                         true ->
                             {ok, Msg};
-- 
2.31.1

openSUSE Build Service is sponsored by