File 2156-erts-Use-Sint-instead-of-int-for-list-lengths.patch of Package erlang

From 14680fcc3fb9d0357fe33a94525d08896afed1c5 Mon Sep 17 00:00:00 2001
From: Richard Carlsson <richardc@klarna.com>
Date: Thu, 3 Dec 2015 14:33:53 +0100
Subject: [PATCH] erts: Use Sint instead of int for list lengths

This avoids potential integer arithmetic overflow for very large lists.
---
 erts/emulator/beam/beam_bif_load.c    |  6 +++---
 erts/emulator/beam/beam_load.c        |  4 ++--
 erts/emulator/beam/bif.c              | 18 +++++++++---------
 erts/emulator/beam/erl_bif_info.c     |  4 ++--
 erts/emulator/beam/erl_bif_lists.c    |  8 ++++----
 erts/emulator/beam/erl_bif_port.c     |  8 ++++----
 erts/emulator/beam/erl_process_dict.c |  4 ++--
 erts/emulator/beam/erl_utils.h        |  2 +-
 erts/emulator/beam/global.h           |  4 ++--
 erts/emulator/beam/utils.c            | 17 +++++++++--------
 10 files changed, 38 insertions(+), 37 deletions(-)

diff --git a/erts/emulator/beam/beam_bif_load.c b/erts/emulator/beam/beam_bif_load.c
index a000935..1b4c022 100644
--- a/erts/emulator/beam/beam_bif_load.c
+++ b/erts/emulator/beam/beam_bif_load.c
@@ -179,8 +179,8 @@ exception_list(Process* p, Eterm tag, struct m* mp, Sint exceptions)
 BIF_RETTYPE
 finish_loading_1(BIF_ALIST_1)
 {
-    int i;
-    int n;
+    Sint i;
+    Sint n;
     struct m* p = NULL;
     Uint exceptions;
     Eterm res;
@@ -201,7 +201,7 @@ finish_loading_1(BIF_ALIST_1)
      */
 
     n = erts_list_length(BIF_ARG_1);
-    if (n == -1) {
+    if (n < 0) {
 	ERTS_BIF_PREP_ERROR(res, BIF_P, BADARG);
 	goto done;
     }
diff --git a/erts/emulator/beam/beam_load.c b/erts/emulator/beam/beam_load.c
index d367cce..10f9f7b 100644
--- a/erts/emulator/beam/beam_load.c
+++ b/erts/emulator/beam/beam_load.c
@@ -6219,10 +6219,10 @@ erts_make_stub_module(Process* p, Eterm Mod, Eterm Beam, Eterm Info)
     BeamInstr* fp;
     byte* info;
     Uint ci;
-    int n;
+    Sint n;
     int code_size;
     int rval;
-    int i;
+    Sint i;
     byte* temp_alloc = NULL;
     byte* bytes;
     Uint size;
diff --git a/erts/emulator/beam/bif.c b/erts/emulator/beam/bif.c
index e116b10..2654785 100644
--- a/erts/emulator/beam/bif.c
+++ b/erts/emulator/beam/bif.c
@@ -2837,7 +2837,7 @@ BIF_RETTYPE list_to_atom_1(BIF_ALIST_1)
 {
     Eterm res;
     char *buf = (char *) erts_alloc(ERTS_ALC_T_TMP, MAX_ATOM_CHARACTERS);
-    int i = intlist_to_buf(BIF_ARG_1, buf, MAX_ATOM_CHARACTERS);
+    Sint i = intlist_to_buf(BIF_ARG_1, buf, MAX_ATOM_CHARACTERS);
 
     if (i < 0) {
 	erts_free(ERTS_ALC_T_TMP, (void *) buf);
@@ -2857,7 +2857,7 @@ BIF_RETTYPE list_to_atom_1(BIF_ALIST_1)
  
 BIF_RETTYPE list_to_existing_atom_1(BIF_ALIST_1)
 {
-    int i;
+    Sint i;
     char *buf = (char *) erts_alloc(ERTS_ALC_T_TMP, MAX_ATOM_CHARACTERS);
 
     if ((i = intlist_to_buf(BIF_ARG_1, buf, MAX_ATOM_CHARACTERS)) < 0) {
@@ -2964,7 +2964,7 @@ BIF_RETTYPE list_to_integer_2(BIF_ALIST_2)
      and since we have erts_chars_to_integer now it is simpler
      as well. This could be optimized further if we did not have to
      copy the list to buf. */
-    int i;
+    Sint i;
     Eterm res, dummy;
     int base;
 
@@ -3288,7 +3288,7 @@ static BIF_RETTYPE do_charbuf_to_float(Process *BIF_P,char *buf) {
 
 BIF_RETTYPE list_to_float_1(BIF_ALIST_1)
 {
-    int i;
+    Sint i;
     Eterm res;
     char *buf = NULL;
 
@@ -3405,7 +3405,7 @@ BIF_RETTYPE list_to_tuple_1(BIF_ALIST_1)
     Eterm* cons;
     Eterm res;
     Eterm* hp;
-    int len;
+    Sint len;
 
     if ((len = erts_list_length(list)) < 0 || len > ERTS_MAX_TUPLE_SIZE) {
 	BIF_ERROR(BIF_P, BADARG);
@@ -3752,7 +3752,7 @@ BIF_RETTYPE display_string_1(BIF_ALIST_1)
 {
     Process* p = BIF_P;
     Eterm string = BIF_ARG_1;
-    int len = is_string(string);
+    Sint len = is_string(string);
     char *str;
 
     if (len <= 0) {
@@ -3806,7 +3806,7 @@ BIF_RETTYPE halt_1(BIF_ALIST_1)
 	erts_exit(ERTS_ABORT_EXIT, "");
     }
     else if (is_string(BIF_ARG_1) || BIF_ARG_1 == NIL) {
-	int i;
+	Sint i;
 
 	if ((i = intlist_to_buf(BIF_ARG_1, halt_msg, HALT_MSG_SIZE-1)) < 0) {
 	    goto error;
@@ -3875,7 +3875,7 @@ BIF_RETTYPE halt_2(BIF_ALIST_2)
 	erts_exit(ERTS_ABORT_EXIT, "");
     }
     else if (is_string(BIF_ARG_1) || BIF_ARG_1 == NIL) {
-	int i;
+	Sint i;
 
 	if ((i = intlist_to_buf(BIF_ARG_1, halt_msg, HALT_MSG_SIZE-1)) < 0) {
 	    goto error;
@@ -4018,7 +4018,7 @@ BIF_RETTYPE list_to_pid_1(BIF_ALIST_1)
 {
     Uint a = 0, b = 0, c = 0;
     char* cp;
-    int i;
+    Sint i;
     DistEntry *dep = NULL;
     char *buf = (char *) erts_alloc(ERTS_ALC_T_TMP, 65);
     /*
diff --git a/erts/emulator/beam/erl_bif_info.c b/erts/emulator/beam/erl_bif_info.c
index 017339e..bc5c83e 100644
--- a/erts/emulator/beam/erl_bif_info.c
+++ b/erts/emulator/beam/erl_bif_info.c
@@ -1721,7 +1721,7 @@ info_1_tuple(Process* BIF_P,	/* Pointer to current process. */
 	if (arity == 2) {
 	    Eterm res = THE_NON_VALUE;
 	    char *buf;
-	    int len = is_string(*tp);
+	    Sint len = is_string(*tp);
 	    if (len <= 0)
 		return res;
 	    buf = (char *) erts_alloc(ERTS_ALC_T_TMP, len+1);
@@ -1740,7 +1740,7 @@ info_1_tuple(Process* BIF_P,	/* Pointer to current process. */
 	    else {
 		Eterm res = THE_NON_VALUE;
 		char *buf;
-		int len = is_string(tp[1]);
+		Sint len = is_string(tp[1]);
 		if (len <= 0)
 		    return res;
 		buf = (char *) erts_alloc(ERTS_ALC_T_TMP, len+1);
diff --git a/erts/emulator/beam/erl_bif_lists.c b/erts/emulator/beam/erl_bif_lists.c
index 5583dcb..fe64e76 100644
--- a/erts/emulator/beam/erl_bif_lists.c
+++ b/erts/emulator/beam/erl_bif_lists.c
@@ -42,7 +42,7 @@ static BIF_RETTYPE append(Process* p, Eterm A, Eterm B)
     Eterm last;
     size_t need;
     Eterm* hp;
-    int i;
+    Sint i;
 
     if ((i = erts_list_length(A)) < 0) {
 	BIF_ERROR(p, BADARG);
diff --git a/erts/emulator/beam/erl_bif_port.c b/erts/emulator/beam/erl_bif_port.c
index 839abd0..3acc1d7 100644
--- a/erts/emulator/beam/erl_bif_port.c
+++ b/erts/emulator/beam/erl_bif_port.c
@@ -649,7 +649,7 @@ BIF_RETTYPE port_get_data_1(BIF_ALIST_1)
 static Port *
 open_port(Process* p, Eterm name, Eterm settings, int *err_typep, int *err_nump)
 {
-    int i;
+    Sint i;
     Eterm option;
     Uint arity;
     Eterm* tp;
@@ -977,8 +977,8 @@ static char **convert_args(Eterm l)
 {
     char **pp;
     char *b;
-    int n;
-    int i = 0;
+    Sint n;
+    Sint i = 0;
     Eterm str;
     if (is_not_list(l) && is_not_nil(l)) {
 	return NULL;
@@ -1024,7 +1024,7 @@ static byte* convert_environment(Process* p, Eterm env)
     Eterm* temp_heap;
     Eterm* hp;
     Uint heap_size;
-    int n;
+    Sint n;
     Sint size;
     byte* bytes;
     int encoding = erts_get_native_filename_encoding();
diff --git a/erts/emulator/beam/erl_process_dict.c b/erts/emulator/beam/erl_process_dict.c
index 84cd81a..36d16f7 100644
--- a/erts/emulator/beam/erl_process_dict.c
+++ b/erts/emulator/beam/erl_process_dict.c
@@ -749,7 +749,7 @@ static void shrink(Process *p, Eterm* ret)
 	    if (lo == NIL) {
 		array_put(&(p->dictionary), pd->splitPosition, hi);
 	    } else {
-		int needed = 4;
+		Sint needed = 4;
 		if (is_list(hi) && is_list(lo)) {
 		    needed = 2*erts_list_length(hi);
 		}
@@ -814,7 +814,7 @@ static void grow(Process *p)
     Eterm *hp;
     unsigned int pos;
     unsigned int homeSize;
-    int needed = 0;
+    Sint needed = 0;
     ProcDict *pd;
 #ifdef DEBUG
     Eterm *hp_limit;
diff --git a/erts/emulator/beam/erl_utils.h b/erts/emulator/beam/erl_utils.h
index 4058d63..b86786a 100644
--- a/erts/emulator/beam/erl_utils.h
+++ b/erts/emulator/beam/erl_utils.h
@@ -115,7 +115,7 @@ void erts_silence_warn_unused_result(long unused);
 int erts_fit_in_bits_int64(Sint64);
 int erts_fit_in_bits_int32(Sint32);
 int erts_fit_in_bits_uint(Uint);
-int erts_list_length(Eterm);
+Sint erts_list_length(Eterm);
 int erts_is_builtin(Eterm, Eterm, int);
 Uint32 make_broken_hash(Eterm);
 Uint32 block_hash(byte *, unsigned, Uint32);
diff --git a/erts/emulator/beam/global.h b/erts/emulator/beam/global.h
index e8a7573..628f36a 100644
--- a/erts/emulator/beam/global.h
+++ b/erts/emulator/beam/global.h
@@ -1308,7 +1308,7 @@ int erts_utf8_to_latin1(byte* dest, const byte* source, int slen);
 #define ERTS_UTF8_OK_MAX_CHARS 4
 
 void bin_write(int, void*, byte*, size_t);
-int intlist_to_buf(Eterm, char*, int); /* most callers pass plain char*'s */
+Sint intlist_to_buf(Eterm, char*, Sint); /* most callers pass plain char*'s */
 
 struct Sint_buf {
 #if defined(ARCH_64) && !HALFWORD_HEAP
@@ -1381,7 +1381,7 @@ ErlDrvSizeT erts_iolist_to_buf(Eterm, char*, ErlDrvSizeT);
 ErlDrvSizeT erts_iolist_to_buf_yielding(ErtsIOList2BufState *);
 int erts_iolist_size_yielding(ErtsIOListState *state);
 int erts_iolist_size(Eterm, ErlDrvSizeT *);
-int is_string(Eterm);
+Sint is_string(Eterm);
 void erl_at_exit(void (*) (void*), void*);
 Eterm collect_memory(Process *);
 void dump_memory_to_fd(int);
diff --git a/erts/emulator/beam/utils.c b/erts/emulator/beam/utils.c
index ef851d8..35dfee4 100644
--- a/erts/emulator/beam/utils.c
+++ b/erts/emulator/beam/utils.c
@@ -317,10 +317,10 @@ erl_grow_equeue(ErtsEQueue* q, Eterm* default_equeue)
  * Calculate length of a list.
  * Returns -1 if not a proper list (i.e. not terminated with NIL)
  */
-int
+Sint
 erts_list_length(Eterm list)
 {
-    int i = 0;
+    Sint i = 0;
 
     while(is_list(list)) {
 	i++;
@@ -3930,11 +3930,11 @@ void bin_write(int to, void *to_arg, byte* buf, size_t sz)
 /* Fill buf with the contents of bytelist list 
    return number of chars in list or -1 for error */
 
-int
-intlist_to_buf(Eterm list, char *buf, int len)
+Sint
+intlist_to_buf(Eterm list, char *buf, Sint len)
 {
     Eterm* listptr;
-    int sz = 0;
+    Sint sz = 0;
 
     if (is_nil(list)) 
 	return 0;
@@ -4481,11 +4481,12 @@ int erts_iolist_size(Eterm obj, ErlDrvSizeT* sizep)
     return iolist_size(0, NULL, obj, sizep);
 }
 
-/* return 0 if item is not a non-empty flat list of bytes */
-int
+/* return 0 if item is not a non-empty flat list of bytes
+   otherwise return the nonzero length of the list */
+Sint
 is_string(Eterm list)
 {
-    int len = 0;
+    Sint len = 0;
 
     while(is_list(list)) {
 	Eterm* consp = list_val(list);
-- 
2.1.4

openSUSE Build Service is sponsored by