File 0637-Fix-address-validation.patch of Package erlang

From ea7c3fdb072ca6e97f81c2bea86af1434a50eb79 Mon Sep 17 00:00:00 2001
From: Raimo Niskanen <raimo@erlang.org>
Date: Wed, 25 Aug 2021 17:58:18 +0200
Subject: [PATCH] Fix address validation

---
 lib/kernel/src/inet_parse.erl  | 13 ++++-----
 lib/kernel/test/inet_SUITE.erl | 50 ++++++++++++++++++++++++++++++++--
 2 files changed, 54 insertions(+), 9 deletions(-)

diff --git a/lib/kernel/src/inet_parse.erl b/lib/kernel/src/inet_parse.erl
index e9685c6554..31d759428d 100644
--- a/lib/kernel/src/inet_parse.erl
+++ b/lib/kernel/src/inet_parse.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 1997-2017. All Rights Reserved.
+%% Copyright Ericsson AB 1997-2021. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -45,6 +45,7 @@
 -import(lists, [reverse/1]).
 
 -include_lib("kernel/include/file.hrl").
+-include("inet_int.hrl").
 
 %% --------------------------------------------------------------------------
 %% Parse services internet style
@@ -759,7 +760,7 @@ dup(N, E, L) when is_integer(N), N >= 1 ->
 
 %% Convert IPv4 address to ascii
 %% Convert IPv6 / IPV4 address to ascii (plain format)
-ntoa({A,B,C,D}) when (A band B band C band D band (bnot 16#ff)) =:= 0 ->
+ntoa({A,B,C,D}) when ?ip(A,B,C,D) ->
     integer_to_list(A) ++ "." ++ integer_to_list(B) ++ "." ++ 
 	integer_to_list(C) ++ "." ++ integer_to_list(D);
 %% ANY
@@ -767,14 +768,12 @@ ntoa({0,0,0,0,0,0,0,0}) -> "::";
 %% LOOPBACK
 ntoa({0,0,0,0,0,0,0,1}) -> "::1";
 %% IPV4 ipv6 host address
-ntoa({0,0,0,0,0,0,A,B}) when (A band B band (bnot 16#ffff)) =:= 0 ->
+ntoa({0,0,0,0,0,0,A,B}) when ?ip6(0,0,0,0,0,0,A,B) ->
     "::" ++ dig_to_dec(A) ++ "." ++ dig_to_dec(B);
 %% IPV4 non ipv6 host address
-ntoa({0,0,0,0,0,16#ffff,A,B}) when (A band B band (bnot 16#ffff)) =:= 0 ->
+ntoa({0,0,0,0,0,16#ffff=X,A,B}) when ?ip6(0,0,0,0,0,X,A,B) ->
     "::ffff:" ++ dig_to_dec(A) ++ "." ++ dig_to_dec(B);
-ntoa({A,B,C,D,E,F,G,H})
-  when (A band B band C band D band E band F band G band H band
-            (bnot 16#ffff)) =:= 0 ->
+ntoa({A,B,C,D,E,F,G,H}) when ?ip6(A,B,C,D,E,F,G,H) ->
     if
         A =:= 16#fe80, B =/= 0;
         A =:= 16#ff02, B =/= 0 ->
diff --git a/lib/kernel/test/inet_SUITE.erl b/lib/kernel/test/inet_SUITE.erl
index 5c7587340b..838e0971fe 100644
--- a/lib/kernel/test/inet_SUITE.erl
+++ b/lib/kernel/test/inet_SUITE.erl
@@ -47,7 +47,7 @@
 	 lookup_bad_search_option/1,
 	 getif/1,
 	 getif_ifr_name_overflow/1,getservbyname_overflow/1, getifaddrs/1,
-	 parse_strict_address/1, ipv4_mapped_ipv6_address/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
@@ -76,7 +76,8 @@ all() ->
      gethostnative_debug_level, gethostnative_soft_restart,
      lookup_bad_search_option,
      getif, getif_ifr_name_overflow, getservbyname_overflow,
-     getifaddrs, parse_strict_address, simple_netns, simple_netns_open,
+     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
     ].
@@ -825,6 +826,51 @@ ipv4_mapped_ipv6_address(Config) when is_list(Config) ->
     IPv4Address = inet:ipv4_mapped_ipv6_address(IPv6Address),
     ok.
 
+
+ntoa(Config) when is_list(Config) ->
+    M8 = 1 bsl 8,
+    M16 = 1 bsl 16,
+    V4Xs = rand_tuple(4, M8),
+    V6Xs = rand_tuple(4, M16),
+    ntoa(
+      [{A, B, C, D} ||
+          A <- [0, element(1, V4Xs), M8-1, -1, 256],
+          B <- [0, element(2, V4Xs), M8-1, -1, 256],
+          C <- [0, element(3, V4Xs), M8-1, -1, 256],
+          D <- [0, element(4, V4Xs), M8-1, -1, 256]], M8-1),
+    ntoa(
+      [{E, F, G, H, G, G, E, F} ||
+          E <- [0, element(1, V6Xs), M16-1, -1, M16],
+          F <- [0, element(2, V6Xs), M16-1, -1, M16],
+          G <- [0, element(3, V6Xs), M16-1, -1, M16],
+          H <- [0, element(4, V6Xs), M16-1, -1, M16]], M16-1).
+
+ntoa([A | As], Max) ->
+    case
+        lists:all(
+          fun (X) when 0 =< X, X =< Max -> true;
+              (_) -> false
+          end, tuple_to_list(A))
+    of
+        true ->
+            S = inet:ntoa(A),
+            {ok, A} = inet:parse_address(S);
+        false ->
+            {error, einval} = inet:ntoa(A)
+    end,
+    ntoa(As, Max);
+ntoa([], _Max) ->
+    ok.
+
+rand_tuple(N, M) ->
+    rand_tuple(N, M, []).
+%%
+rand_tuple(0, _M, Acc) ->
+    list_to_tuple(Acc);
+rand_tuple(N, M, Acc) ->
+    rand_tuple(N - 1, M, [rand:uniform(M) - 1 | Acc]).
+
+
 t_gethostnative(Config) when is_list(Config) ->
     %% this will result in 26 bytes sent which causes problem in Windows
     %% if the port-program has not assured stdin to be read in BINARY mode
-- 
2.31.1

openSUSE Build Service is sponsored by