File 3241-remove-removal-schedule-of-http_uri-and-change-its-i.patch of Package erlang

From 4ce23cba650fc3d09a7f4180b85b34c3fbd9886e Mon Sep 17 00:00:00 2001
From: Konrad Pietrzak <konrad@erlang.org>
Date: Mon, 11 Mar 2024 12:57:13 +0100
Subject: [PATCH] remove removal schedule of http_uri and change its
 implementation to uri_string

---
 lib/inets/src/http_lib/http_uri.erl  | 69 ++++++----------------------
 lib/stdlib/test/uri_string_SUITE.erl | 14 ------
 system/doc/general_info/DEPRECATIONS |  4 +-
 3 files changed, 15 insertions(+), 72 deletions(-)

diff --git a/lib/inets/src/http_lib/http_uri.erl b/lib/inets/src/http_lib/http_uri.erl
index a4128cb2e2..cce17ad4f2 100644
--- a/lib/inets/src/http_lib/http_uri.erl
+++ b/lib/inets/src/http_lib/http_uri.erl
@@ -39,58 +39,15 @@
 %%%=========================================================================
 %%%  API
 %%%=========================================================================
-reserved() ->
-    sets:from_list([$;, $:, $@, $&, $=, $+, $,, $/, $?,
-            $#, $[, $], $<, $>, $\", ${, $}, $|, %"
-			       $\\, $', $^, $%, $ ]).
-
-encode(URI) when is_list(URI) ->
-    Reserved = reserved(), 
-    lists:append([uri_encode(Char, Reserved) || Char <- URI]);
-encode(URI) when is_binary(URI) ->
-    Reserved = reserved(),
-    << <<(uri_encode_binary(Char, Reserved))/binary>> || <<Char>> <= URI >>.
-
-decode(String) when is_list(String) ->
-    do_decode(String);
-decode(String) when is_binary(String) ->
-    do_decode_binary(String).
 
-do_decode([$%,Hex1,Hex2|Rest]) ->
-    [hex2dec(Hex1)*16+hex2dec(Hex2)|do_decode(Rest)];
-do_decode([First|Rest]) ->
-    [First|do_decode(Rest)];
-do_decode([]) ->
-    [].
-
-do_decode_binary(<<$%, Hex:2/binary, Rest/bits>>) ->
-    <<(binary_to_integer(Hex, 16)), (do_decode_binary(Rest))/binary>>;
-do_decode_binary(<<First:1/binary, Rest/bits>>) ->
-    <<First/binary, (do_decode_binary(Rest))/binary>>;
-do_decode_binary(<<>>) ->
-    <<>>.
-
-%%%========================================================================
-%%% Internal functions
-%%%========================================================================
-%% In this version of the function, we no longer need 
-%% the Scheme argument, but just in case...
-uri_encode(Char, Reserved) ->
-    case sets:is_element(Char, Reserved) of
-	true ->
-	    [ $% | http_util:integer_to_hexlist(Char)];
-	false ->
-	    [Char]
-    end.
-
-uri_encode_binary(Char, Reserved) ->
-    case sets:is_element(Char, Reserved) of
-        true ->
-            << $%, (integer_to_binary(Char, 16))/binary >>;
-        false ->
-            <<Char>>
-    end.
+-spec encode(Data) -> QuotedData when
+      Data :: unicode:chardata(),
+      QuotedData :: unicode:chardata().
+encode(Data) ->
+    uri_string:quote(Data).
 
-hex2dec(X) when (X>=$0) andalso (X=<$9) -> X-$0;
-hex2dec(X) when (X>=$A) andalso (X=<$F) -> X-$A+10;
-hex2dec(X) when (X>=$a) andalso (X=<$f) -> X-$a+10.
+-spec decode(QuotedData) -> Data when
+      QuotedData :: unicode:chardata(),
+      Data :: unicode:chardata().
+decode(QuotedData) ->
+    uri_string:unquote(QuotedData).
diff --git a/lib/stdlib/test/uri_string_SUITE.erl b/lib/stdlib/test/uri_string_SUITE.erl
index 6a6bff2688..b6f2822282 100644
--- a/lib/stdlib/test/uri_string_SUITE.erl
+++ b/lib/stdlib/test/uri_string_SUITE.erl
@@ -1376,13 +1376,6 @@ quote(_Config) ->
 
     TestQuoteUnquote =
         fun(Unquoted) ->
-                %% case below should be removed when functions used are removed
-                case Head(Unquoted) =< 127 of
-                    true ->
-                        Unquoted = http_uri:decode(http_uri:encode(Unquoted));
-                    _ ->
-                        ok
-                end,
                 Unquoted = uri_string:unquote(uri_string:quote(Unquoted))
         end,
     [TestQuoteUnquote(U) || #{unquoted := U} <- get_quote_data()],
@@ -1392,13 +1385,6 @@ quote(_Config) ->
         fun(Unquoted, Quoted) ->
                 Safe = "!$()*", %% characters not encoded by old http_uri:encode
                 Result = uri_string:quote(Unquoted, Safe),
-                %% case below should be removed when function used are removed
-                case Head(Unquoted) =< 127 of
-                    true ->
-                        Result = http_uri:encode(Unquoted);
-                    _ ->
-                        ok
-                end,
                 case lists:member(Head(Unquoted), Safe) of
                     true ->
                         Unquoted = Result;
diff --git a/system/doc/general_info/DEPRECATIONS b/system/doc/general_info/DEPRECATIONS
index 08b7244e82..3e5ba5150c 100644
--- a/system/doc/general_info/DEPRECATIONS
+++ b/system/doc/general_info/DEPRECATIONS
@@ -84,8 +84,8 @@ ssl:cipher_suites/0 since=21 remove=24
 
 http_uri:parse/1 since=23 remove=25
 http_uri:parse/2 since=23 remove=25
-http_uri:encode/1 since=23 remove=27
-http_uri:decode/1 since=23 remove=27
+http_uri:encode/1 since=23
+http_uri:decode/1 since=23
 http_uri:scheme_defaults/0 since=23 remove=25
 httpd:parse_query/1 since=23
 pg2:_/_ since=23 remove=24
-- 
2.35.3

openSUSE Build Service is sponsored by