File 4571-erts-Enable-decoding-URIs-with-ipv6-address-in-host.patch of Package erlang

From 9ccd06468fb7291b2fb409d5aa27f480e550c078 Mon Sep 17 00:00:00 2001
From: Derek Kraan <derek@kraan.dev>
Date: Mon, 20 Feb 2023 11:13:40 +0100
Subject: [PATCH 1/2] erts: Enable decoding URIs with ipv6 address in host.

Example:

Packet = <<"GET http://[FEDC:BA98:7654:3210:FEDC:BA98:7654:3210]:4000/dir ...>>
erlang:decode_packet(http_bin, Packet, [])
---
 erts/config.h.in                           |  3 +++
 erts/configure                             |  6 +++++
 erts/configure.ac                          |  2 +-
 erts/doc/src/erlang.xml                    |  4 ++++
 erts/emulator/beam/packet_parser.c         | 27 +++++++++++++++++++++-
 erts/emulator/beam/sys.h                   | 16 +++++++++++++
 erts/emulator/test/decode_packet_SUITE.erl | 21 +++++++++++++++--
 7 files changed, 75 insertions(+), 4 deletions(-)

diff --git a/erts/config.h.in b/erts/config.h.in
index 0ec4a40761..ee9390f1b9 100644
--- a/erts/config.h.in
+++ b/erts/config.h.in
@@ -824,6 +824,9 @@
 /* Define to 1 if you have the `memmove' function. */
 #undef HAVE_MEMMOVE
 
+/* Define to 1 if you have the `memrchr' function. */
+#undef HAVE_MEMRCHR
+
 /* Define if the pthread.h header file is in pthread/mit directory. */
 #undef HAVE_MIT_PTHREAD_H
 
diff --git a/erts/configure b/erts/configure
index 70f94b2876..bc65747216 100755
--- a/erts/configure
+++ b/erts/configure
@@ -20008,6 +20008,12 @@ if test "x$ac_cv_func_memcpy" = xyes
 then :
   printf "%s\n" "#define HAVE_MEMCPY 1" >>confdefs.h
 
+fi
+ac_fn_c_check_func "$LINENO" "memrchr" "ac_cv_func_memrchr"
+if test "x$ac_cv_func_memrchr" = xyes
+then :
+  printf "%s\n" "#define HAVE_MEMRCHR 1" >>confdefs.h
+
 fi
 ac_fn_c_check_func "$LINENO" "mallopt" "ac_cv_func_mallopt"
 if test "x$ac_cv_func_mallopt" = xyes
diff --git a/erts/configure.ac b/erts/configure.ac
index 9ea98c25b0..0663a3b58f 100644
--- a/erts/configure.ac
+++ b/erts/configure.ac
@@ -2168,7 +2168,7 @@ AC_CHECK_FUNCS([getipnodebyname getipnodebyaddr gethostbyname2])
 AC_CHECK_FUNCS([ieee_handler fpsetmask finite isnan isinf res_gethostbyname dlopen \
 		dlvsym pread pwrite memmove strerror strerror_r strncasecmp \
 		gethrtime localtime_r gmtime_r mprotect madvise posix_madvise \
-		mmap mremap memcpy mallopt sbrk _sbrk __sbrk brk _brk __brk \
+		mmap mremap memcpy memrchr mallopt sbrk _sbrk __sbrk brk _brk __brk \
 		flockfile fstat strlcpy strlcat setsid posix2time time2posix \
 		setlocale nl_langinfo poll mlockall ppoll vsyslog])
 
diff --git a/erts/doc/src/erlang.xml b/erts/doc/src/erlang.xml
index 91d64b782a..1426278392 100644
--- a/erts/doc/src/erlang.xml
+++ b/erts/doc/src/erlang.xml
@@ -1589,6 +1589,10 @@ Z = erlang:crc32_combine(X,Y,iolist_size(Data2)).</code>
               headers and the beginning of any following message body.</p>
             <p>The variants <c>http_bin</c> and <c>httph_bin</c> return
               strings (<c>HttpString</c>) as binaries instead of lists.</p>
+            <p>Since OTP 26.0, <c><anno>Host</anno></c> may be an IPv6
+              address enclosed in <c>[]</c>, as defined in
+              <url href="https://www.ietf.org/rfc/rfc2732.txt">RFC2732
+              </url>.</p>
           </item>
         </taglist>
         <p>Options:</p>
diff --git a/erts/emulator/beam/packet_parser.c b/erts/emulator/beam/packet_parser.c
index 8ef009ca8d..50d292b33e 100644
--- a/erts/emulator/beam/packet_parser.c
+++ b/erts/emulator/beam/packet_parser.c
@@ -518,6 +518,7 @@ static void
 http_parse_absoluteURI(PacketHttpURI* uri, const char* uri_ptr, int uri_len)
 {
     const char* p;
+    const char* v;
     
     if ((p = memchr(uri_ptr, '/', uri_len)) == NULL) {
         /* host [":" port] */
@@ -533,15 +534,39 @@ http_parse_absoluteURI(PacketHttpURI* uri, const char* uri_ptr, int uri_len)
 
     uri->s1_ptr = uri_ptr;
     uri->port = 0; /* undefined */
-    /* host[:port]  */
     if ((p = memchr(uri_ptr, ':', uri_len)) == NULL) {
         uri->s1_len = uri_len;
     }
+    /* ipv6
+     * eg [::1]:4000
+     * eg [FEDC:BA98:7654:3210:FEDC:BA98:7654:3210]:80
+     */
+    else if (memchr(uri_ptr, '[', uri_len) == uri_ptr &&
+        (v = memchr(uri_ptr, ']', uri_len)) != NULL) {
+      int n = (v - uri_ptr) + 1;
+      int port = 0;
+      uri->s1_len = n;
+      n = uri_len - (n+1);
+      // parse port if the next char is `:`
+      if (sys_memrchr(uri_ptr, ':', uri_len) == v + 1) {
+        // Skip over `]:`
+        v = v + 2;
+        while(n && isdigit((int) *v)) {
+            port = port*10 + (*v - '0');
+            n--;
+            v++;
+        }
+        if (n==0 && port!=0)
+            uri->port = port;
+      }
+    }
+    /* host[:port]  */
     else {
         int n = (p - uri_ptr);
         int port = 0;        
         uri->s1_len = n;
         n = uri_len - (n+1);
+        // Skip over port delimiter `:`
         p++;
         while(n && isdigit((int) *p)) {
             port = port*10 + (*p - '0');
diff --git a/erts/emulator/beam/sys.h b/erts/emulator/beam/sys.h
index b57cfd6952..e009473403 100644
--- a/erts/emulator/beam/sys.h
+++ b/erts/emulator/beam/sys.h
@@ -1079,6 +1079,7 @@ ERTS_GLB_INLINE void *sys_memmove(void *dest, const void *src, size_t n);
 ERTS_GLB_INLINE int sys_memcmp(const void *s1, const void *s2, size_t n);
 ERTS_GLB_INLINE void *sys_memset(void *s, int c, size_t n);
 ERTS_GLB_INLINE void *sys_memzero(void *s, size_t n);
+ERTS_GLB_INLINE void *sys_memrchr(const void *s, int c, size_t n);
 ERTS_GLB_INLINE int sys_strcmp(const char *s1, const char *s2);
 ERTS_GLB_INLINE int sys_strncmp(const char *s1, const char *s2, size_t n);
 ERTS_GLB_INLINE char *sys_strcpy(char *dest, const char *src);
@@ -1112,6 +1113,21 @@ ERTS_GLB_INLINE void *sys_memzero(void *s, size_t n)
     ASSERT(s != NULL);
     return memset(s,'\0',n);
 }
+ERTS_GLB_INLINE void *sys_memrchr(const void *s, int c, size_t n)
+{
+    ASSERT(s != NULL);
+#ifdef HAVE_MEMRCHR
+    return (void*)memrchr(s, c, n);
+#else
+    {
+        const unsigned char* ptr = (const unsigned char*)s + n;
+        while (ptr != s)
+            if (*(--ptr) == (unsigned char)c)
+                return (void*)ptr;
+        return NULL;
+    }
+#endif
+}
 ERTS_GLB_INLINE int sys_strcmp(const char *s1, const char *s2)
 {
     ASSERT(s1 != NULL && s2 != NULL);
diff --git a/erts/emulator/test/decode_packet_SUITE.erl b/erts/emulator/test/decode_packet_SUITE.erl
index 07653646a2..306c1193b0 100644
--- a/erts/emulator/test/decode_packet_SUITE.erl
+++ b/erts/emulator/test/decode_packet_SUITE.erl
@@ -26,7 +26,7 @@
 
 -export([all/0, suite/0,groups/0,
          init_per_testcase/2,end_per_testcase/2,
-         basic/1, packet_size/1, neg/1, http/1, line/1, ssl/1, otp_8536/1,
+         basic/1, ipv6/1, packet_size/1, neg/1, http/1, line/1, ssl/1, otp_8536/1,
          otp_9389/1, otp_9389_line/1]).
 
 suite() ->
@@ -35,7 +35,7 @@ suite() ->
 
 all() -> 
     [basic, packet_size, neg, http, line, ssl, otp_8536,
-     otp_9389, otp_9389_line].
+     otp_9389, otp_9389_line, ipv6].
 
 groups() -> 
     [].
@@ -206,6 +206,23 @@ pack_ssl(Content, Major, Minor, Body) ->
     end,
     {Res, {ssl_tls,[],C,{Major,Minor}, Data}}.
 
+ipv6(Config) when is_list(Config) ->
+    %% Test with port
+    Packet = <<"GET http://[FEDC:BA98:7654:3210:FEDC:BA98:7654:3210]:4000/echo_components HTTP/1.1\r\nhost: orange\r\n\r\n">>,
+    {ok, {http_request, 'GET',  {absoluteURI, http, <<"[FEDC:BA98:7654:3210:FEDC:BA98:7654:3210]">>, 4000, <<"/echo_components">>}, {1, 1}}, <<"host: orange\r\n\r\n">>} =
+      erlang:decode_packet(http_bin, Packet, []),
+    %% Test no port
+    Packet2 = <<"GET http://[FEDC:BA98:7654:3210:FEDC:BA98:7654:3210]/1234 HTTP/1.1\r\nhost: orange\r\n\r\n">>,
+    {ok, {http_request, 'GET',  {absoluteURI, http, <<"[FEDC:BA98:7654:3210:FEDC:BA98:7654:3210]">>, undefined, <<"/1234">>}, {1, 1}}, <<"host: orange\r\n\r\n">>} =
+      erlang:decode_packet(http_bin, Packet2, []),
+    %% Test short ipv6 form
+    Packet3 = <<"GET http://[::1]/1234 HTTP/1.1\r\nhost: orange\r\n\r\n">>,
+    {ok, {http_request, 'GET',  {absoluteURI, http, <<"[::1]">>, undefined, <<"/1234">>}, {1, 1}}, <<"host: orange\r\n\r\n">>} =
+      erlang:decode_packet(http_bin, Packet3, []),
+    %% Test missing `]`
+    Packet4 = <<"GET http://[FEDC:BA98:7654:3210:FEDC:BA98:7654:3210:4000/echo_components HTTP/1.1\r\nhost: orange\r\n\r\n">>,
+    {ok, {http_request, 'GET',  {absoluteURI, http, <<"[FEDC">>, undefined, <<"/echo_components">>}, {1, 1}}, <<"host: orange\r\n\r\n">>} =
+      erlang:decode_packet(http_bin, Packet4, []).
 
 packet_size(Config) when is_list(Config) ->
     Packet = <<101,22,203,54,175>>,
-- 
2.35.3

openSUSE Build Service is sponsored by