File 2532-Stop-supporting-decoding-of-old-funs-in-the-external.patch of Package erlang

From 0d6353767dab33f2b676d7f30c8c2f27606c02f5 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Thu, 13 Jun 2019 11:56:11 +0200
Subject: [PATCH 2/6] Stop supporting decoding of old funs in the external term
 format

The new external format for funs (NEW_FUN_EXT) was introduced in OTP
R8 along with the `make_fun2` instruction. Therefore, it should be
safe to stop decoding the old FUN_EXT tag.
---
 erts/emulator/beam/erl_fun.c      | 21 -----------
 erts/emulator/beam/erl_fun.h      |  1 -
 erts/emulator/beam/external.c     | 76 ++++-----------------------------------
 erts/emulator/test/hash_SUITE.erl | 33 +++++++----------
 4 files changed, 19 insertions(+), 112 deletions(-)

diff --git a/erts/emulator/beam/erl_fun.c b/erts/emulator/beam/erl_fun.c
index 9c866250bb..8e4372f11e 100644
--- a/erts/emulator/beam/erl_fun.c
+++ b/erts/emulator/beam/erl_fun.c
@@ -99,27 +99,6 @@ int erts_fun_table_sz(void)
     return sz;
 }
 
-ErlFunEntry*
-erts_put_fun_entry(Eterm mod, int uniq, int index)
-{
-    ErlFunEntry template;
-    ErlFunEntry* fe;
-    erts_aint_t refc;
-    ASSERT(is_atom(mod));
-    template.old_uniq = uniq;
-    template.old_index = index;
-    template.module = mod;
-    erts_fun_write_lock();
-    fe = (ErlFunEntry *) hash_put(&erts_fun_table, (void*) &template);
-    sys_memset(fe->uniq, 0, sizeof(fe->uniq));
-    fe->index = 0;
-    refc = erts_refc_inctest(&fe->refc, 0);
-    if (refc < 2) /* New or pending delete */
-	erts_refc_inc(&fe->refc, 1);
-    erts_fun_write_unlock();
-    return fe;
-}
-
 ErlFunEntry*
 erts_put_fun_entry2(Eterm mod, int old_uniq, int old_index,
 		    byte* uniq, int index, int arity)
diff --git a/erts/emulator/beam/erl_fun.h b/erts/emulator/beam/erl_fun.h
index fb2901d866..eefc7a95bb 100644
--- a/erts/emulator/beam/erl_fun.h
+++ b/erts/emulator/beam/erl_fun.h
@@ -74,7 +74,6 @@ void erts_init_fun_table(void);
 void erts_fun_info(fmtfn_t, void *);
 int erts_fun_table_sz(void);
 
-ErlFunEntry* erts_put_fun_entry(Eterm mod, int uniq, int index);
 ErlFunEntry* erts_get_fun_entry(Eterm mod, int uniq, int index);
 
 ErlFunEntry* erts_put_fun_entry2(Eterm mod, int old_uniq, int old_index,
diff --git a/erts/emulator/beam/external.c b/erts/emulator/beam/external.c
index ec67ab2aed..8a8e62a608 100644
--- a/erts/emulator/beam/external.c
+++ b/erts/emulator/beam/external.c
@@ -4011,73 +4011,6 @@ dec_term_atom_common:
 		next = &(funp->creator);
 		break;
 	    }
-	case FUN_EXT:
-	    {
-		ErlFunThing* funp = (ErlFunThing *) hp;
-		Eterm module;
-		Sint old_uniq;
-		Sint old_index;
-		unsigned num_free;
-		int i;
-		Eterm temp;
-
-		num_free = get_int32(ep);
-		ep += 4;
-		hp += ERL_FUN_SIZE;
-		hp += num_free;
-		factory->hp = hp;
-		funp->thing_word = HEADER_FUN;
-		funp->num_free = num_free;
-		*objp = make_fun(funp);
-
-		/* Creator pid */
-		if ((*ep != PID_EXT && *ep != NEW_PID_EXT)
-		    || (ep = dec_pid(edep, factory, ep+1,
-				     &funp->creator, *ep))==NULL) {
-		    goto error;
-		}
-
-		/* Module */
-		if ((ep = dec_atom(edep, ep, &module)) == NULL) {
-		    goto error;
-		}
-
-		/* Index */
-		if ((ep = dec_term(edep, factory, ep, &temp, NULL)) == NULL) {
-		    goto error;
-		}
-		if (!is_small(temp)) {
-		    goto error;
-		}
-		old_index = unsigned_val(temp);
-
-		/* Uniq */
-		if ((ep = dec_term(edep, factory, ep, &temp, NULL)) == NULL) {
-		    goto error;
-		}
-		if (!is_small(temp)) {
-		    goto error;
-		}
-		
-		/*
-		 * It is safe to link the fun into the fun list only when
-		 * no more validity tests can fail.
-		 */
-		funp->next = factory->off_heap->first;
-		factory->off_heap->first = (struct erl_off_heap_header*)funp;
-		old_uniq = unsigned_val(temp);
-
-		funp->fe = erts_put_fun_entry(module, old_uniq, old_index);
-		funp->arity = funp->fe->address[-1] - num_free;
-		hp = factory->hp;
-
-		/* Environment */
-		for (i = num_free-1; i >= 0; i--) {
-		    funp->env[i] = (Eterm) next;
-		    next = funp->env + i;
-		}
-		break;
-	    }
 	case ATOM_INTERNAL_REF2:
 	    n = get_int16(ep);
 	    ep += 2;
@@ -4836,9 +4769,6 @@ init_done:
 		total_size = get_uint32(ep);
 		CHKSIZE(total_size);		
 		ep += 1+16+4+4;
-		/*FALLTHROUGH*/
-
-	    case FUN_EXT:
 		CHKSIZE(4);
 		num_free = get_uint32(ep);
 		ep += 4;
@@ -4849,6 +4779,12 @@ init_done:
 		heap_size += ERL_FUN_SIZE + num_free;
 		break;
 	    }
+	case FUN_EXT:
+            /*
+             * OTP 23: No longer support decoding the old fun
+             * representation.
+             */
+            goto error;
 	case ATOM_INTERNAL_REF2:
 	    SKIP(2+atom_extra_skip);
 	    atom_extra_skip = 0;
diff --git a/erts/emulator/test/hash_SUITE.erl b/erts/emulator/test/hash_SUITE.erl
index 1bf9e033bf..dd71c3da58 100644
--- a/erts/emulator/test/hash_SUITE.erl
+++ b/erts/emulator/test/hash_SUITE.erl
@@ -223,26 +223,17 @@ basic_test() ->
 				    16#77777777777777],16#FFFFFFFF),
     ExternalReference = <<131,114,0,3,100,0,13,110,111,110,111,100,101,64,
 			 110,111,104,111,115,116,0,0,0,0,122,0,0,0,0,0,0,0,0>>,
-    1113403635 = erlang:phash(binary_to_term(ExternalReference),
-				    16#FFFFFFFF),
-    ExternalFun = <<131,117,0,0,0,3,103,100,0,13,110,111,110,111,100,101,64,
-		   110,111,104,111,115,116,0,0,0,38,0,0,0,0,0,100,0,8,101,
-		   114,108,95,101,118,97,108,97,20,98,5,182,139,98,108,0,0,
-		   0,3,104,2,100,0,1,66,109,0,0,0,33,131,114,0,3,100,0,13,
-		   110,111,110,111,100,101,64,110,111,104,111,115,116,0,0,
-		   0,0,122,0,0,0,0,0,0,0,0,104,2,100,0,1,76,107,0,33,131,
-		   114,0,3,100,0,13,110,111,110,111,100,101,64,110,111,104,
-		   111,115,116,0,0,0,0,122,0,0,0,0,0,0,0,0,104,2,100,0,1,82,
-		   114,0,3,100,0,13,110,111,110,111,100,101,64,110,111,104,
-		   111,115,116,0,0,0,0,122,0,0,0,0,0,0,0,0,106,108,0,0,0,1,
-		   104,5,100,0,6,99,108,97,117,115,101,97,1,106,106,108,0,0,
-		   0,1,104,3,100,0,7,105,110,116,101,103,101,114,97,1,97,1,
-		   106,106,104,3,100,0,4,101,118,97,108,104,2,100,0,5,115,
-		   104,101,108,108,100,0,10,108,111,99,97,108,95,102,117,
-		   110,99,108,0,0,0,1,103,100,0,13,110,111,110,111,100,101,
-		   64,110,111,104,111,115,116,0,0,0,22,0,0,0,0,0,106>>,
-    170987488 = erlang:phash(binary_to_term(ExternalFun),
-				   16#FFFFFFFF),
+    ExternalReference = <<131,114,0,3,100,0,13,110,111,110,111,100,101,64,
+			 110,111,104,111,115,116,0,0,0,0,122,0,0,0,0,0,0,0,0>>,
+    1113403635 = phash_from_external(ExternalReference),
+
+    ExternalFun = <<131,112,0,0,0,70,1,212,190,220,28,179,144,194,131,
+                    19,215,105,97,77,251,125,93,0,0,0,0,0,0,0,2,100,0,1,
+                    116,97,0,98,6,165,246,224,103,100,0,13,110,111,
+                    110,111,100,101,64,110,111,104,111,115,116,0,0,0,91,
+                    0,0,0,0,0,97,2,97,1>>,
+    25769064 = phash_from_external(ExternalFun),
+
     case (catch erlang:phash(1,0)) of
 	{'EXIT',{badarg, _}} ->
 	    ok;
@@ -250,6 +241,8 @@ basic_test() ->
 	    exit(phash_accepted_zero_as_range)
     end.
 
+phash_from_external(Ext) ->
+    erlang:phash(binary_to_term(Ext), 16#FFFFFFFF).
 
 range_test() ->
     F = fun(From,From,_FF) ->
-- 
2.16.4

openSUSE Build Service is sponsored by