File 1710-erts-Add-get_uint32-and-fix-some-dubious-uses-of-get.patch of Package erlang

From c225d2f79d48a232c5c847f8a5c2df25fedc0903 Mon Sep 17 00:00:00 2001
From: Sverker Eriksson <sverker@erlang.org>
Date: Fri, 26 Jun 2020 15:23:06 +0200
Subject: [PATCH] erts: Add get_uint32 and fix some dubious uses of get_int32

Uint64 x = get_int32(s);  // Warning: does sign extension
---
 erts/emulator/beam/external.c        | 32 ++++++++++++++--------------
 erts/emulator/beam/sys.h             |  3 +++
 erts/emulator/sys/unix/sys_drivers.c |  2 +-
 3 files changed, 20 insertions(+), 17 deletions(-)

diff --git a/erts/emulator/beam/external.c b/erts/emulator/beam/external.c
index 1a29904f5e..051d59a386 100644
--- a/erts/emulator/beam/external.c
+++ b/erts/emulator/beam/external.c
@@ -530,7 +530,7 @@ Sint erts_encode_ext_dist_header_finalize(ErtsDistOutputBuf* ob,
 	    ip = &instr_buf[0] + (2+4)*iix;
 	    cix = (int) get_int16(&ip[0]);
 	    ASSERT(0 <= cix && cix < ERTS_ATOM_CACHE_SIZE);
-	    atom = make_atom((Uint) get_int32(&ip[2]));
+	    atom = make_atom((Uint) get_uint32(&ip[2]));
 	    if (cache->out_arr[cix] == atom) {
 		--ep;
 		put_int8(cix, ep);
@@ -1688,7 +1688,7 @@ binary2term_prepare(ErtsBinary2TermState *state, byte *data, Sint data_size,
 	    (*ctxp)->state = B2TSizeInit;
     }
     else  {
-	uLongf dest_len = (Uint32) get_int32(bytes+1);
+	uLongf dest_len = get_uint32(bytes+1);
 	bytes += 5;
 	size -= 5;	
 	if (dest_len > 32*1024*1024
@@ -2970,11 +2970,11 @@ dec_pid(ErtsDistExternal *edep, ErtsHeapFactory* factory, byte* ep,
     /* eat first atom */
     if ((ep = dec_atom(edep, ep, &sysname)) == NULL)
 	return NULL;
-    num = get_int32(ep);
+    num = get_uint32(ep);
     ep += 4;
     if (num > ERTS_MAX_PID_NUMBER)
 	return NULL;
-    ser = get_int32(ep);
+    ser = get_uint32(ep);
     ep += 4;
     if (ser > ERTS_MAX_PID_SERIAL)
 	return NULL;
@@ -2987,7 +2987,7 @@ dec_pid(ErtsDistExternal *edep, ErtsHeapFactory* factory, byte* ep,
         }
     } else {
         ASSERT(tag == NEW_PID_EXT);
-        cre = get_int32(ep);
+        cre = get_uint32(ep);
         ep += 4;
     }
 
@@ -4294,7 +4294,7 @@ dec_term_atom_common:
 		if ((ep = dec_atom(edep, ep, &sysname)) == NULL) {
 		    goto error;
 		}
-		if ((num = get_int32(ep)) > ERTS_MAX_PORT_NUMBER) {
+		if ((num = get_uint32(ep)) > ERTS_MAX_PORT_NUMBER) {
 		    goto error;
 		}
 		ep += 4;
@@ -5450,7 +5450,7 @@ init_done:
 	    break;
 	case LARGE_BIG_EXT:
 	    CHKSIZE(4);
-	    n = get_int32(ep);
+	    n = get_uint32(ep);
 	    if (n > BIG_ARITY_MAX*sizeof(ErtsDigit)) {
 		goto error;
 	    }
@@ -5555,7 +5555,7 @@ init_done:
 	    break;
 	case LIST_EXT:
 	    CHKSIZE(4);
-	    n = get_int32(ep);
+	    n = get_uint32(ep);
 	    ep += 4;
 	    ADDTERMS(n);
 	    terms++;
@@ -5569,14 +5569,14 @@ init_done:
 	    break;
 	case LARGE_TUPLE_EXT:
 	    CHKSIZE(4);
-	    n = get_int32(ep);
+	    n = get_uint32(ep);
 	    ep += 4;
 	    ADDTERMS(n);
 	    heap_size += n + 1;
 	    break;
 	case MAP_EXT:
 	    CHKSIZE(4);
-	    n = get_int32(ep);
+	    n = get_uint32(ep);
 	    ep += 4;
 	    ADDTERMS(2*n);
             if (n <= MAP_SMALL_MAP_LIMIT) {
@@ -5601,7 +5601,7 @@ init_done:
 	    break;
 	case BINARY_EXT:
 	    CHKSIZE(4);
-	    n = get_int32(ep);
+	    n = get_uint32(ep);
 	    SKIP2(n, 4);
 	    if (n <= ERL_ONHEAP_BIN_LIMIT) {
 		heap_size += heap_bin_size(n);
@@ -5612,7 +5612,7 @@ init_done:
 	case BIT_BINARY_EXT:
 	    {
 		CHKSIZE(5);
-		n = get_int32(ep);
+		n = get_uint32(ep);
 		SKIP2(n, 5);
 		if (n <= ERL_ONHEAP_BIN_LIMIT) {
 		    heap_size += heap_bin_size(n) + ERL_SUB_BIN_SIZE;
@@ -5631,14 +5631,14 @@ init_done:
 		Uint total_size;
 
 		CHKSIZE(1+16+4+4);
-		total_size = get_int32(ep);
+		total_size = get_uint32(ep);
 		CHKSIZE(total_size);		
 		ep += 1+16+4+4;
 		/*FALLTHROUGH*/
 
 	    case FUN_EXT:
 		CHKSIZE(4);
-		num_free = get_int32(ep);
+		num_free = get_uint32(ep);
 		ep += 4;
 		if (num_free > MAX_ARG) {
 		    goto error;
diff --git a/erts/emulator/beam/sys.h b/erts/emulator/beam/sys.h
index 90e3008102..3b9b87dd33 100644
--- a/erts/emulator/beam/sys.h
+++ b/erts/emulator/beam/sys.h
@@ -1152,11 +1152,14 @@ ERTS_GLB_INLINE size_t sys_strlen(const char *s)
                             ((byte*)(s))[7] = (byte)((Sint64)(i))       & 0xff;\
                            } while (0) 
 
+/* Returns a signed int */
 #define get_int32(s) ((((byte*) (s))[0] << 24) | \
                       (((byte*) (s))[1] << 16) | \
                       (((byte*) (s))[2] << 8)  | \
                       (((byte*) (s))[3]))
 
+#define get_uint32(s) ((Uint32)get_int32(s))
+
 #define get_little_int32(s) ((((byte*) (s))[3] << 24) | \
 			     (((byte*) (s))[2] << 16)  | \
 			     (((byte*) (s))[1] << 8) | \
diff --git a/erts/emulator/sys/unix/sys_drivers.c b/erts/emulator/sys/unix/sys_drivers.c
index 152d1757ba..e3f9a8073e 100644
--- a/erts/emulator/sys/unix/sys_drivers.c
+++ b/erts/emulator/sys/unix/sys_drivers.c
@@ -1465,7 +1465,7 @@ static void ready_input(ErlDrvData e, ErlDrvEvent ready_fd)
 		switch (packet_bytes) {
 		case 1: h = get_int8(dd->ifd->pbuf);  break;
 		case 2: h = get_int16(dd->ifd->pbuf); break;
-		case 4: h = get_int32(dd->ifd->pbuf); break;
+		case 4: h = get_uint32(dd->ifd->pbuf); break;
 		default: ASSERT(0); return; /* -1; */
 		}
 
-- 
2.35.3

openSUSE Build Service is sponsored by