File 2581-Make-erlang-phash2-1-and-erlang-phash2-2-yield.patch of Package erlang

From b72e9d38110aac082cd98084dcb507a61b1bc3ad Mon Sep 17 00:00:00 2001
From: Kjell Winblad <kjellwinblad@gmail.com>
Date: Wed, 6 Feb 2019 11:29:41 +0100
Subject: [PATCH] Make erlang:phash2/1 and erlang:phash2/2 yield

The erlang:phash2 functions did not yield even if the input was very
large and a call to one of the functions did only consume a single
reduction. This commit fixes these problems.
---
 erts/emulator/beam/bif.c                           |  16 +-
 erts/emulator/beam/erl_alloc.types                 |   1 +
 erts/emulator/beam/erl_utils.h                     |   1 +
 erts/emulator/beam/sys.h                           |   6 +
 erts/emulator/beam/utils.c                         | 723 ++++++++++++++++-----
 erts/emulator/test/Makefile                        |   3 +-
 erts/emulator/test/emulator.spec                   |   1 +
 erts/emulator/test/emulator_bench.spec             |   1 +
 erts/emulator/test/hash_SUITE.erl                  | 585 ++++++++++++++++-
 erts/emulator/test/hash_property_test_SUITE.erl    | 103 +++
 .../test/property_test/phash2_properties.erl       |  63 ++
 11 files changed, 1340 insertions(+), 163 deletions(-)
 create mode 100644 erts/emulator/test/hash_property_test_SUITE.erl
 create mode 100644 erts/emulator/test/property_test/phash2_properties.erl

diff --git a/erts/emulator/beam/bif.c b/erts/emulator/beam/bif.c
index b81056c774..b35fe2fc02 100644
--- a/erts/emulator/beam/bif.c
+++ b/erts/emulator/beam/bif.c
@@ -4866,9 +4866,13 @@ BIF_RETTYPE phash_2(BIF_ALIST_2)
 BIF_RETTYPE phash2_1(BIF_ALIST_1)
 {
     Uint32 hash;
-
-    hash = make_hash2(BIF_ARG_1);
-    BIF_RET(make_small(hash & ((1L << 27) - 1)));
+    Eterm trap_state = THE_NON_VALUE;
+    hash = trapping_make_hash2(BIF_ARG_1, &trap_state, BIF_P);
+    if (trap_state == THE_NON_VALUE) {
+        BIF_RET(make_small(hash & ((1L << 27) - 1)));
+    } else {
+        BIF_TRAP1(bif_export[BIF_phash2_1], BIF_P, trap_state);
+    }
 }
 
 BIF_RETTYPE phash2_2(BIF_ALIST_2)
@@ -4876,6 +4880,7 @@ BIF_RETTYPE phash2_2(BIF_ALIST_2)
     Uint32 hash;
     Uint32 final_hash;
     Uint32 range;
+    Eterm trap_state = THE_NON_VALUE;
 
     /* Check for special case 2^32 */
     if (term_equals_2pow32(BIF_ARG_2)) {
@@ -4887,7 +4892,10 @@ BIF_RETTYPE phash2_2(BIF_ALIST_2)
 	}
 	range = (Uint32) u;
     }
-    hash = make_hash2(BIF_ARG_1);
+    hash = trapping_make_hash2(BIF_ARG_1, &trap_state, BIF_P);
+    if (trap_state != THE_NON_VALUE) {
+        BIF_TRAP2(bif_export[BIF_phash2_2], BIF_P, trap_state, BIF_ARG_2);
+    }
     if (range) {
 	final_hash = hash % range; /* [0..range-1] */
     } else {
diff --git a/erts/emulator/beam/erl_alloc.types b/erts/emulator/beam/erl_alloc.types
index 92e5069c71..58d586453c 100644
--- a/erts/emulator/beam/erl_alloc.types
+++ b/erts/emulator/beam/erl_alloc.types
@@ -323,6 +323,7 @@ type	SETUP_CONN_ARG	SHORT_LIVED	PROCESSES	setup_connection_argument
 type	RELEASE_LAREA	SHORT_LIVED	SYSTEM		release_literal_area
 +endif
 type    LIST_TRAP       SHORT_LIVED     PROCESSES       list_bif_trap_state
+type    PHASH2_TRAP     SHORT_LIVED     PROCESSES       phash2_trap_state
 
 #
 # Types used for special emulators
diff --git a/erts/emulator/beam/erl_utils.h b/erts/emulator/beam/erl_utils.h
index 430ac305c5..449243a9b7 100644
--- a/erts/emulator/beam/erl_utils.h
+++ b/erts/emulator/beam/erl_utils.h
@@ -70,6 +70,7 @@ int erts_fit_in_bits_uint(Uint);
 Sint erts_list_length(Eterm);
 int erts_is_builtin(Eterm, Eterm, int);
 Uint32 make_hash2(Eterm);
+Uint32 trapping_make_hash2(Eterm, Eterm*, struct process*);
 Uint32 make_hash(Eterm);
 Uint32 make_internal_hash(Eterm, Uint32 salt);
 
diff --git a/erts/emulator/beam/sys.h b/erts/emulator/beam/sys.h
index c261c8e117..acc321aa51 100644
--- a/erts/emulator/beam/sys.h
+++ b/erts/emulator/beam/sys.h
@@ -92,6 +92,12 @@
 #  define ERTS_GLB_INLINE_INCL_FUNC_DEF 0
 #endif
 
+#ifdef __GNUC__
+#  define ERTS_NOINLINE __attribute__((__noinline__))
+#else
+#  define ERTS_NOINLINE
+#endif
+
 #if defined(VALGRIND) && !defined(NO_FPE_SIGNALS)
 #  define NO_FPE_SIGNALS
 #endif
diff --git a/erts/emulator/beam/utils.c b/erts/emulator/beam/utils.c
index 0bbae65e28..88cdcc2675 100644
--- a/erts/emulator/beam/utils.c
+++ b/erts/emulator/beam/utils.c
@@ -1069,54 +1069,237 @@ do {                               \
 
 #define HCONST 0x9e3779b9UL /* the golden ratio; an arbitrary value */
 
-static Uint32
-block_hash(byte *k, Uint length, Uint32 initval)
+typedef struct {
+    Uint32 a,b,c;
+} ErtsBlockHashHelperCtx;
+
+#define BLOCK_HASH_BYTES_PER_ITER 12
+
+/* The three functions below are separated into different functions even
+   though they are always used together to make trapping and handling
+   of unaligned binaries easier. Examples of how they are used can be
+   found in block_hash and make_hash2_helper.*/
+static ERTS_INLINE
+void block_hash_setup(Uint32 initval,
+                      ErtsBlockHashHelperCtx* ctx /* out parameter */)
+{
+    ctx->a = ctx->b = HCONST;
+    ctx->c = initval;           /* the previous hash value */
+}
+
+static ERTS_INLINE
+void block_hash_buffer(byte *buf,
+                       Uint buf_length,
+                       ErtsBlockHashHelperCtx* ctx /* out parameter */)
 {
-   Uint32 a,b,c;
-   Uint len;
-
-   /* Set up the internal state */
-   len = length;
-   a = b = HCONST;
-   c = initval;           /* the previous hash value */
-
-   while (len >= 12)
-   {
-      a += (k[0] +((Uint32)k[1]<<8) +((Uint32)k[2]<<16) +((Uint32)k[3]<<24));
-      b += (k[4] +((Uint32)k[5]<<8) +((Uint32)k[6]<<16) +((Uint32)k[7]<<24));
-      c += (k[8] +((Uint32)k[9]<<8) +((Uint32)k[10]<<16)+((Uint32)k[11]<<24));
-      MIX(a,b,c);
-      k += 12; len -= 12;
-   }
-
-   c += length;
-   switch(len)              /* all the case statements fall through */
-   {
-   case 11: c+=((Uint32)k[10]<<24);
-   case 10: c+=((Uint32)k[9]<<16);
-   case 9 : c+=((Uint32)k[8]<<8);
-      /* the first byte of c is reserved for the length */
-   case 8 : b+=((Uint32)k[7]<<24);
-   case 7 : b+=((Uint32)k[6]<<16);
-   case 6 : b+=((Uint32)k[5]<<8);
-   case 5 : b+=k[4];
-   case 4 : a+=((Uint32)k[3]<<24);
-   case 3 : a+=((Uint32)k[2]<<16);
-   case 2 : a+=((Uint32)k[1]<<8);
-   case 1 : a+=k[0];
-     /* case 0: nothing left to add */
-   }
-   MIX(a,b,c);
-   return c;
+    Uint len = buf_length;
+    byte *k = buf;
+    ASSERT(buf_length % BLOCK_HASH_BYTES_PER_ITER == 0);
+    while (len >= BLOCK_HASH_BYTES_PER_ITER) {
+        ctx->a += (k[0] +((Uint32)k[1]<<8) +((Uint32)k[2]<<16) +((Uint32)k[3]<<24));
+        ctx->b += (k[4] +((Uint32)k[5]<<8) +((Uint32)k[6]<<16) +((Uint32)k[7]<<24));
+        ctx->c += (k[8] +((Uint32)k[9]<<8) +((Uint32)k[10]<<16)+((Uint32)k[11]<<24));
+        MIX(ctx->a,ctx->b,ctx->c);
+        k += BLOCK_HASH_BYTES_PER_ITER; len -= BLOCK_HASH_BYTES_PER_ITER;
+    }
 }
 
+static ERTS_INLINE
+Uint32 block_hash_final_bytes(byte *buf,
+                              Uint buf_length,
+                              Uint full_length,
+                              ErtsBlockHashHelperCtx* ctx)
+{
+    Uint len = buf_length;
+    byte *k = buf;
+    ctx->c += full_length;
+    switch(len)
+    { /* all the case statements fall through */      
+    case 11: ctx->c+=((Uint32)k[10]<<24);
+    case 10: ctx->c+=((Uint32)k[9]<<16);
+    case 9 : ctx->c+=((Uint32)k[8]<<8);
+    /* the first byte of c is reserved for the length */
+    case 8 : ctx->b+=((Uint32)k[7]<<24);
+    case 7 : ctx->b+=((Uint32)k[6]<<16);
+    case 6 : ctx->b+=((Uint32)k[5]<<8);
+    case 5 : ctx->b+=k[4];
+    case 4 : ctx->a+=((Uint32)k[3]<<24);
+    case 3 : ctx->a+=((Uint32)k[2]<<16);
+    case 2 : ctx->a+=((Uint32)k[1]<<8);
+    case 1 : ctx->a+=k[0];
+    /* case 0: nothing left to add */
+    }
+    MIX(ctx->a,ctx->b,ctx->c);
+    return ctx->c;
+}
+
+static
 Uint32
-make_hash2(Eterm term)
+block_hash(byte *block, Uint block_length, Uint32 initval)
 {
+    ErtsBlockHashHelperCtx ctx;
+    Uint no_bytes_not_in_loop =
+        (block_length % BLOCK_HASH_BYTES_PER_ITER);
+    Uint no_bytes_to_process_in_loop =
+        block_length - no_bytes_not_in_loop;
+    byte *final_bytes = block + no_bytes_to_process_in_loop;
+    block_hash_setup(initval, &ctx);
+    block_hash_buffer(block,
+                      no_bytes_to_process_in_loop,
+                      &ctx);
+    return block_hash_final_bytes(final_bytes,
+                                  no_bytes_not_in_loop,
+                                  block_length,
+                                  &ctx);
+}
+
+typedef enum {
+    tag_primary_list,
+    arityval_subtag,
+    hamt_subtag_head_flatmap,
+    map_subtag,
+    fun_subtag,
+    neg_big_subtag,
+    sub_binary_subtag_1,
+    sub_binary_subtag_2,
+    hash2_common_1,
+    hash2_common_2,
+    hash2_common_3,
+} ErtsMakeHash2TrapLocation; 
+
+typedef struct {
+    int c;
+    Uint32 sh;
+    Eterm* ptr;
+} ErtsMakeHash2Context_TAG_PRIMARY_LIST;
+
+typedef struct {
+    int i;
+    int arity;
+    Eterm* elem;
+} ErtsMakeHash2Context_ARITYVAL_SUBTAG;
+
+typedef struct {
+    Eterm *ks;
+    Eterm *vs;
+    int i;
+    Uint size;
+} ErtsMakeHash2Context_HAMT_SUBTAG_HEAD_FLATMAP;
+
+typedef struct {
+    Eterm* ptr;
+    int i;
+} ErtsMakeHash2Context_MAP_SUBTAG;
+
+typedef struct {
+    Uint num_free;
+    Eterm* bptr;
+} ErtsMakeHash2Context_FUN_SUBTAG;
+
+typedef struct {
+    Eterm* ptr;
+    Uint i;
+    Uint n;
+    Uint32 con;
+} ErtsMakeHash2Context_NEG_BIG_SUBTAG;
+
+typedef struct {
+    byte* bptr;
+    Uint sz;
+    Uint bitsize;
+    Uint bitoffs;
+    Uint no_bytes_processed;
+    ErtsBlockHashHelperCtx block_hash_ctx;
+    /* The following fields are only used when bitoffs != 0 */
+    byte* buf;
+    int done;
+
+} ErtsMakeHash2Context_SUB_BINARY_SUBTAG;
+
+typedef struct {
+    int dummy__; /* Empty structs are not supported on all platforms */
+} ErtsMakeHash2Context_EMPTY;
+
+typedef struct {
+    ErtsMakeHash2TrapLocation trap_location;
+    /* specific to the trap location: */
+    union {
+        ErtsMakeHash2Context_TAG_PRIMARY_LIST tag_primary_list;
+        ErtsMakeHash2Context_ARITYVAL_SUBTAG arityval_subtag;
+        ErtsMakeHash2Context_HAMT_SUBTAG_HEAD_FLATMAP hamt_subtag_head_flatmap;
+        ErtsMakeHash2Context_MAP_SUBTAG map_subtag;
+        ErtsMakeHash2Context_FUN_SUBTAG fun_subtag;
+        ErtsMakeHash2Context_NEG_BIG_SUBTAG neg_big_subtag;
+        ErtsMakeHash2Context_SUB_BINARY_SUBTAG sub_binary_subtag_1;
+        ErtsMakeHash2Context_SUB_BINARY_SUBTAG sub_binary_subtag_2;
+        ErtsMakeHash2Context_EMPTY hash2_common_1;
+        ErtsMakeHash2Context_EMPTY hash2_common_2;
+        ErtsMakeHash2Context_EMPTY hash2_common_3;
+    } trap_location_state;
+    /* same for all trap locations: */
+    Eterm term; 
     Uint32 hash;
     Uint32 hash_xor_pairs;
-    DeclareTmpHeapNoproc(tmp_big,2);
+    ErtsEStack stack;
+} ErtsMakeHash2Context;
+
+static int make_hash2_ctx_bin_dtor(Binary *context_bin) {
+    ErtsMakeHash2Context* context = ERTS_MAGIC_BIN_DATA(context_bin);
+    DESTROY_SAVED_ESTACK(&context->stack);
+    if (context->trap_location == sub_binary_subtag_2 &&
+        context->trap_location_state.sub_binary_subtag_2.buf != NULL) {
+        erts_free(ERTS_ALC_T_PHASH2_TRAP, context->trap_location_state.sub_binary_subtag_2.buf);
+    }
+    return 1;
+}
 
+/* hash2_save_trap_state is called seldom so we want to avoid inlining */
+static ERTS_NOINLINE
+Eterm hash2_save_trap_state(Eterm state_mref,
+                            Uint32 hash_xor_pairs,
+                            Uint32 hash,
+                            Process* p,
+                            Eterm term,
+                            Eterm* ESTK_DEF_STACK(s),
+                            ErtsEStack s,
+                            ErtsMakeHash2TrapLocation trap_location,
+                            void* trap_location_state_ptr,
+                            size_t trap_location_state_size) {
+    Binary* state_bin;
+    ErtsMakeHash2Context* context;
+    if (state_mref == THE_NON_VALUE) {
+        Eterm* hp;
+        state_bin = erts_create_magic_binary(sizeof(ErtsMakeHash2Context),
+                                             make_hash2_ctx_bin_dtor);
+        hp = HAlloc(p, ERTS_MAGIC_REF_THING_SIZE);
+        state_mref = erts_mk_magic_ref(&hp, &MSO(p), state_bin);
+    } else {
+        state_bin = erts_magic_ref2bin(state_mref);
+    }
+    context = ERTS_MAGIC_BIN_DATA(state_bin);
+    context->term = term;
+    context->hash = hash;
+    context->hash_xor_pairs = hash_xor_pairs;
+    ESTACK_SAVE(s, &context->stack);
+    context->trap_location = trap_location;
+    sys_memcpy(&context->trap_location_state,
+               trap_location_state_ptr,
+               trap_location_state_size);
+    erts_set_gc_state(p, 0);
+    BUMP_ALL_REDS(p);
+    return state_mref;
+}
+#undef NOINLINE_HASH2_SAVE_TRAP_STATE
+
+/* Writes back a magic reference to *state_mref_write_back when the
+   function traps */
+static ERTS_INLINE Uint32
+make_hash2_helper(Eterm term_param, const int can_trap, Eterm* state_mref_write_back, Process* p)
+{
+    static const Uint ITERATIONS_PER_RED = 64;
+    Uint32 hash;
+    Uint32 hash_xor_pairs;
+    Eterm term = term_param;
     ERTS_UNDEF(hash_xor_pairs, 0);
 
 /* (HCONST * {2, ..., 22}) mod 2^32 */
@@ -1168,12 +1351,63 @@ make_hash2(Eterm term)
 
 #define IS_SSMALL28(x) (((Uint) (((x) >> (28-1)) + 1)) < 2)
 
+#define NOT_SSMALL28_HASH(SMALL)                          \
+    do {                                                  \
+        Uint64 t;                                         \
+        Uint32 x, y;                                      \
+        Uint32 con;                                       \
+        if (SMALL < 0) {                                  \
+            con = HCONST_10;                              \
+            t = (Uint64)(SMALL * (-1));                   \
+        } else {                                          \
+            con = HCONST_11;                              \
+            t = SMALL;                                    \
+        }                                                 \
+        x = t & 0xffffffff;                               \
+        y = t >> 32;                                      \
+        UINT32_HASH_2(x, y, con);                         \
+    } while(0)
+    
 #ifdef ARCH_64
 #  define POINTER_HASH(Ptr, AConst) UINT32_HASH_2((Uint32)(UWord)(Ptr), (((UWord)(Ptr)) >> 32), AConst)
 #else
 #  define POINTER_HASH(Ptr, AConst) UINT32_HASH(Ptr, AConst)
 #endif
 
+#define TRAP_LOCATION_NO_RED(location_name)                             \
+    do {                                                                \
+        if(can_trap && iterations_until_trap <= 0) {                    \
+                *state_mref_write_back  =                               \
+                    hash2_save_trap_state(state_mref,                   \
+                                          hash_xor_pairs,               \
+                                          hash,                         \
+                                          p,                            \
+                                          term,                         \
+                                          ESTK_DEF_STACK(s),            \
+                                          s,                            \
+                                          location_name,                \
+                                          &ctx,                         \
+                                          sizeof(ctx));                 \
+                return 0;                                               \
+            L_##location_name:                                          \
+                ctx = context->trap_location_state. location_name;      \
+        }                                                               \
+    } while(0)
+
+#define TRAP_LOCATION(location_name)                            \
+    do {                                                        \
+        if (can_trap) {                                         \
+            iterations_until_trap--;                            \
+            TRAP_LOCATION_NO_RED(location_name);                \
+        }                                                       \
+    } while(0)
+
+#define TRAP_LOCATION_NO_CTX(location_name)                             \
+    do {                                                                \
+        ErtsMakeHash2Context_EMPTY ctx;                                 \
+        TRAP_LOCATION(location_name);                                   \
+    } while(0)
+    
     /* Optimization. Simple cases before declaration of estack. */
     if (primary_tag(term) == TAG_PRIMARY_IMMED1) {
 	switch (term & _TAG_IMMED1_MASK) {
@@ -1186,51 +1420,94 @@ make_hash2(Eterm term)
 	    break;
 	case _TAG_IMMED1_SMALL:
 	  {
-	      Sint x = signed_val(term);
-
-	      if (SMALL_BITS > 28 && !IS_SSMALL28(x)) {
-		  term = small_to_big(x, tmp_big);
-		  break;
+	      Sint small = signed_val(term);
+	      if (SMALL_BITS > 28 && !IS_SSMALL28(small)) {
+                  hash = 0;
+                  NOT_SSMALL28_HASH(small);
+                  return hash;
 	      }
 	      hash = 0;
-	      SINT32_HASH(x, HCONST);
+	      SINT32_HASH(small, HCONST);
 	      return hash;
 	  }
 	}
     };
     {
     Eterm tmp;
+    long max_iterations = 0;
+    long iterations_until_trap = 0;
+    Eterm state_mref = THE_NON_VALUE;
+    ErtsMakeHash2Context* context = NULL;
     DECLARE_ESTACK(s);
-
-    UseTmpHeapNoproc(2);
+    ESTACK_CHANGE_ALLOCATOR(s, ERTS_ALC_T_SAVED_ESTACK);
+    if(can_trap){
+#ifdef DEBUG
+        (void)ITERATIONS_PER_RED;
+        iterations_until_trap = max_iterations =
+            (1103515245 * (ERTS_BIF_REDS_LEFT(p)) + 12345)  % 227;
+#else
+        iterations_until_trap = max_iterations =
+            ITERATIONS_PER_RED * ERTS_BIF_REDS_LEFT(p);
+#endif
+    }
+    if (can_trap && is_internal_magic_ref(term)) {
+        Binary* state_bin;
+        state_mref = term;
+        state_bin = erts_magic_ref2bin(state_mref);
+        if (ERTS_MAGIC_BIN_DESTRUCTOR(state_bin) == make_hash2_ctx_bin_dtor) {
+            /* Restore state after a trap */
+            context = ERTS_MAGIC_BIN_DATA(state_bin);
+            term = context->term;
+            hash = context->hash;
+            hash_xor_pairs = context->hash_xor_pairs;
+            ESTACK_RESTORE(s, &context->stack);
+            ASSERT(p->flags & F_DISABLE_GC);
+            erts_set_gc_state(p, 1);
+            switch (context->trap_location) {
+            case hash2_common_3:           goto L_hash2_common_3;
+            case tag_primary_list:         goto L_tag_primary_list;
+            case arityval_subtag:          goto L_arityval_subtag;
+            case hamt_subtag_head_flatmap: goto L_hamt_subtag_head_flatmap;
+            case map_subtag:               goto L_map_subtag;
+            case fun_subtag:               goto L_fun_subtag;
+            case neg_big_subtag:           goto L_neg_big_subtag;
+            case sub_binary_subtag_1:      goto L_sub_binary_subtag_1;
+            case sub_binary_subtag_2:      goto L_sub_binary_subtag_2;
+            case hash2_common_1:           goto L_hash2_common_1;
+            case hash2_common_2:           goto L_hash2_common_2;
+            }
+        }
+    }
     hash = 0;
     for (;;) {
 	switch (primary_tag(term)) {
 	case TAG_PRIMARY_LIST:
 	{
-	    int c = 0;
-	    Uint32 sh = 0;
-	    Eterm* ptr = list_val(term);
-	    while (is_byte(*ptr)) {
+            ErtsMakeHash2Context_TAG_PRIMARY_LIST ctx = {
+                .c =  0,
+                .sh = 0,
+                .ptr = list_val(term)};
+	    while (is_byte(*ctx.ptr)) {
 		/* Optimization for strings. */
-		sh = (sh << 8) + unsigned_val(*ptr);
-		if (c == 3) {
-		    UINT32_HASH(sh, HCONST_4);
-		    c = sh = 0;
+		ctx.sh = (ctx.sh << 8) + unsigned_val(*ctx.ptr);
+		if (ctx.c == 3) {
+		    UINT32_HASH(ctx.sh, HCONST_4);
+		    ctx.c = ctx.sh = 0;
 		} else {
-		    c++;
+		    ctx.c++;
 		}
-		term = CDR(ptr);
+		term = CDR(ctx.ptr);
 		if (is_not_list(term))
 		    break;
-		ptr = list_val(term);
+		ctx.ptr = list_val(term);
+                TRAP_LOCATION(tag_primary_list);
 	    }
-	    if (c > 0)
-		UINT32_HASH(sh, HCONST_4);
+	    if (ctx.c > 0)
+		UINT32_HASH(ctx.sh, HCONST_4);
 	    if (is_list(term)) {
-		tmp = CDR(ptr);
+		tmp = CDR(ctx.ptr);
                 ESTACK_PUSH(s, tmp);
-		term = CAR(ptr);
+		term = CAR(ctx.ptr);
 	    }
 	}
 	break;
@@ -1241,34 +1518,39 @@ make_hash2(Eterm term)
 	    switch (hdr & _TAG_HEADER_MASK) {
 	    case ARITYVAL_SUBTAG:
 	    {
-		int i;
-		int arity = header_arity(hdr);
-		Eterm* elem = tuple_val(term);
-		UINT32_HASH(arity, HCONST_9);
-		if (arity == 0) /* Empty tuple */
+                ErtsMakeHash2Context_ARITYVAL_SUBTAG ctx = {
+                    .i =  0,
+                    .arity = header_arity(hdr),
+                    .elem = tuple_val(term)};
+		UINT32_HASH(ctx.arity, HCONST_9);
+		if (ctx.arity == 0) /* Empty tuple */
 		    goto hash2_common;
-		for (i = arity; ; i--) {
-		    term = elem[i];
-                    if (i == 1)
+		for (ctx.i = ctx.arity; ; ctx.i--) {
+		    term = ctx.elem[ctx.i];
+                    if (ctx.i == 1)
                         break;
                     ESTACK_PUSH(s, term);
+                    TRAP_LOCATION(arityval_subtag);
 		}
 	    }
 	    break;
             case MAP_SUBTAG:
             {
-                Eterm* ptr = boxed_val(term) + 1;
                 Uint size;
-                int i;
+                ErtsMakeHash2Context_MAP_SUBTAG ctx = {
+                    .ptr = boxed_val(term) + 1,
+                    .i = 0};
                 switch (hdr & _HEADER_MAP_SUBTAG_MASK) {
                 case HAMT_SUBTAG_HEAD_FLATMAP:
                 {
                     flatmap_t *mp = (flatmap_t *)flatmap_val(term);
-                    Eterm *ks = flatmap_get_keys(mp);
-                    Eterm *vs = flatmap_get_values(mp);
-                    size      = flatmap_get_size(mp);
-                    UINT32_HASH(size, HCONST_16);
-                    if (size == 0)
+                    ErtsMakeHash2Context_HAMT_SUBTAG_HEAD_FLATMAP ctx = {
+                        .ks = flatmap_get_keys(mp),
+                        .vs = flatmap_get_values(mp),
+                        .i = 0,
+                        .size = flatmap_get_size(mp)};
+                    UINT32_HASH(ctx.size, HCONST_16);
+                    if (ctx.size == 0)
                         goto hash2_common;
 
                     /* We want a portable hash function that is *independent* of
@@ -1281,17 +1563,18 @@ make_hash2(Eterm term)
                     ESTACK_PUSH(s, HASH_MAP_TAIL);
                     hash = 0;
                     hash_xor_pairs = 0;
-                    for (i = size - 1; i >= 0; i--) {
+                    for (ctx.i = ctx.size - 1; ctx.i >= 0; ctx.i--) {
                         ESTACK_PUSH(s, HASH_MAP_PAIR);
-                        ESTACK_PUSH(s, vs[i]);
-                        ESTACK_PUSH(s, ks[i]);
+                        ESTACK_PUSH(s, ctx.vs[ctx.i]);
+                        ESTACK_PUSH(s, ctx.ks[ctx.i]);
+                        TRAP_LOCATION(hamt_subtag_head_flatmap);
                     }
                     goto hash2_common;
                 }
 
                 case HAMT_SUBTAG_HEAD_ARRAY:
                 case HAMT_SUBTAG_HEAD_BITMAP:
-                    size = *ptr++;
+                    size = *ctx.ptr++;
                     UINT32_HASH(size, HCONST_16);
                     if (size == 0)
                         goto hash2_common;
@@ -1303,27 +1586,28 @@ make_hash2(Eterm term)
                 }
                 switch (hdr & _HEADER_MAP_SUBTAG_MASK) {
                 case HAMT_SUBTAG_HEAD_ARRAY:
-                    i = 16;
+                    ctx.i = 16;
                     break;
                 case HAMT_SUBTAG_HEAD_BITMAP:
                 case HAMT_SUBTAG_NODE_BITMAP:
-                    i = hashmap_bitcount(MAP_HEADER_VAL(hdr));
+                    ctx.i = hashmap_bitcount(MAP_HEADER_VAL(hdr));
                     break;
                 default:
                     erts_exit(ERTS_ERROR_EXIT, "bad header");
                 }
-                while (i) {
-                    if (is_list(*ptr)) {
-                        Eterm* cons = list_val(*ptr);
+                while (ctx.i) {
+                    if (is_list(*ctx.ptr)) {
+                        Eterm* cons = list_val(*ctx.ptr);
                         ESTACK_PUSH(s, HASH_MAP_PAIR);
                         ESTACK_PUSH(s, CDR(cons));
                         ESTACK_PUSH(s, CAR(cons));
                     }
                     else {
-                        ASSERT(is_boxed(*ptr));
-                        ESTACK_PUSH(s, *ptr);
+                        ASSERT(is_boxed(*ctx.ptr));
+                        ESTACK_PUSH(s, *ctx.ptr);
                     }
-                    i--; ptr++;
+                    ctx.i--; ctx.ptr++;
+                    TRAP_LOCATION(map_subtag);
                 }
                 goto hash2_common;
             }
@@ -1344,22 +1628,25 @@ make_hash2(Eterm term)
 	    case FUN_SUBTAG:
 	    {
 		ErlFunThing* funp = (ErlFunThing *) fun_val(term);
-		Uint num_free = funp->num_free;
+                ErtsMakeHash2Context_FUN_SUBTAG ctx = {
+                    .num_free = funp->num_free,
+                    .bptr = NULL};
 		UINT32_HASH_2
-		    (num_free,
+		    (ctx.num_free,
 		     atom_tab(atom_val(funp->fe->module))->slot.bucket.hvalue,
 		     HCONST);
 		UINT32_HASH_2
 		    (funp->fe->old_index, funp->fe->old_uniq, HCONST);
-		if (num_free == 0) {
+		if (ctx.num_free == 0) {
 		    goto hash2_common;
 		} else {
-		    Eterm* bptr = funp->env + num_free - 1;
-		    while (num_free-- > 1) {
-			term = *bptr--;
+		    ctx.bptr = funp->env + ctx.num_free - 1;
+		    while (ctx.num_free-- > 1) {
+			term = *ctx.bptr--;
 			ESTACK_PUSH(s, term);
+                        TRAP_LOCATION(fun_subtag);
 		    }
-		    term = *bptr;
+		    term = *ctx.bptr;
 		}
 	    }
 	    break;
@@ -1367,70 +1654,190 @@ make_hash2(Eterm term)
 	    case HEAP_BINARY_SUBTAG:
 	    case SUB_BINARY_SUBTAG:
 	    {
-		byte* bptr;
-		unsigned sz = binary_size(term);
+#define BYTE_BITS 8
+                ErtsMakeHash2Context_SUB_BINARY_SUBTAG ctx = {
+                    .bptr = 0,
+                    /* !!!!!!!!!!!!!!!!!!!! OBS !!!!!!!!!!!!!!!!!!!!
+                     *
+                     * The size is truncated to 32 bits on the line
+                     * below so that the code is compatible with old
+                     * versions of the code. This means that hash
+                     * values for binaries with a size greater than
+                     * 4GB do not take all bytes in consideration.
+                     *
+                     * !!!!!!!!!!!!!!!!!!!! OBS !!!!!!!!!!!!!!!!!!!!
+                     */ 
+                    .sz = (0xFFFFFFFF & binary_size(term)),
+                    .bitsize = 0,
+                    .bitoffs = 0,
+                    .no_bytes_processed = 0
+                };
 		Uint32 con = HCONST_13 + hash;
-		Uint bitoffs;
-		Uint bitsize;
-
-		ERTS_GET_BINARY_BYTES(term, bptr, bitoffs, bitsize);
-		if (sz == 0 && bitsize == 0) {
+                Uint iters_for_bin = MAX(1, ctx.sz / BLOCK_HASH_BYTES_PER_ITER);
+		ERTS_GET_BINARY_BYTES(term, ctx.bptr, ctx.bitoffs, ctx.bitsize);
+		if (ctx.sz == 0 && ctx.bitsize == 0) {
 		    hash = con;
-		} else {
-		    if (bitoffs == 0) {
-			hash = block_hash(bptr, sz, con);
-			if (bitsize > 0) {
-			    UINT32_HASH_2(bitsize, (bptr[sz] >> (8 - bitsize)),
-					  HCONST_15);
-			}
-		    } else {
-			byte* buf = (byte *) erts_alloc(ERTS_ALC_T_TMP,
-							sz + (bitsize != 0));
-			erts_copy_bits(bptr, bitoffs, 1, buf, 0, 1, sz*8+bitsize);
-			hash = block_hash(buf, sz, con);
-			if (bitsize > 0) {
-			    UINT32_HASH_2(bitsize, (buf[sz] >> (8 - bitsize)),
-					  HCONST_15);
-			}
-			erts_free(ERTS_ALC_T_TMP, (void *) buf);
-		    }
+		} else if (ctx.bitoffs == 0 &&
+                           (!can_trap ||
+                            (iterations_until_trap - iters_for_bin) > 0)) {
+                    /* No need to trap while hashing binary */
+                    if (can_trap) iterations_until_trap -= iters_for_bin;
+                    hash = block_hash(ctx.bptr, ctx.sz, con);
+                    if (ctx.bitsize > 0) {
+                        UINT32_HASH_2(ctx.bitsize,
+                                      (ctx.bptr[ctx.sz] >> (BYTE_BITS - ctx.bitsize)),
+                                      HCONST_15);
+                    }
+                } else if (ctx.bitoffs == 0) {
+                    /* Need to trap while hashing binary */
+                    ErtsBlockHashHelperCtx* block_hash_ctx = &ctx.block_hash_ctx;
+                    block_hash_setup(con, block_hash_ctx);
+                    do {
+                        Uint max_bytes_to_process =
+                            iterations_until_trap <= 0 ? BLOCK_HASH_BYTES_PER_ITER :
+                            iterations_until_trap * BLOCK_HASH_BYTES_PER_ITER;
+                        Uint bytes_left = ctx.sz - ctx.no_bytes_processed;
+                        Uint even_bytes_left =
+                            bytes_left - (bytes_left % BLOCK_HASH_BYTES_PER_ITER);
+                        Uint bytes_to_process =
+                            MIN(max_bytes_to_process, even_bytes_left);
+                        block_hash_buffer(&ctx.bptr[ctx.no_bytes_processed],
+                                          bytes_to_process,
+                                          block_hash_ctx);
+                        ctx.no_bytes_processed += bytes_to_process;
+                        iterations_until_trap -=
+                            MAX(1, bytes_to_process / BLOCK_HASH_BYTES_PER_ITER);
+                        TRAP_LOCATION_NO_RED(sub_binary_subtag_1);
+                        block_hash_ctx = &ctx.block_hash_ctx; /* Restore after trap */
+                    } while ((ctx.sz - ctx.no_bytes_processed) >=
+                             BLOCK_HASH_BYTES_PER_ITER);
+                    hash = block_hash_final_bytes(ctx.bptr +
+                                                  ctx.no_bytes_processed,
+                                                  ctx.sz - ctx.no_bytes_processed,
+                                                  ctx.sz,
+                                                  block_hash_ctx);
+                    if (ctx.bitsize > 0) {
+                        UINT32_HASH_2(ctx.bitsize,
+                                      (ctx.bptr[ctx.sz] >> (BYTE_BITS - ctx.bitsize)),
+                                      HCONST_15);
+                    }
+                } else if (/* ctx.bitoffs != 0 && */
+                           (!can_trap ||
+                            (iterations_until_trap - iters_for_bin) > 0)) {
+                    /* No need to trap while hashing binary */
+                    Uint nr_of_bytes = ctx.sz + (ctx.bitsize != 0);
+                    byte *buf = erts_alloc(ERTS_ALC_T_TMP, nr_of_bytes);
+                    Uint nr_of_bits_to_copy = ctx.sz*BYTE_BITS+ctx.bitsize;
+                    if (can_trap) iterations_until_trap -= iters_for_bin;
+                    erts_copy_bits(ctx.bptr,
+                                   ctx.bitoffs, 1, buf, 0, 1, nr_of_bits_to_copy);
+                    hash = block_hash(buf, ctx.sz, con);
+                    if (ctx.bitsize > 0) {
+                        UINT32_HASH_2(ctx.bitsize,
+                                      (buf[ctx.sz] >> (BYTE_BITS - ctx.bitsize)),
+                                      HCONST_15);
+                    }
+                    erts_free(ERTS_ALC_T_TMP, buf);
+                } else /* ctx.bitoffs != 0 && */ {
+#ifdef DEBUG
+#define BINARY_BUF_SIZE (BLOCK_HASH_BYTES_PER_ITER * 3)
+#else
+#define BINARY_BUF_SIZE (BLOCK_HASH_BYTES_PER_ITER * 256)
+#endif
+#define BINARY_BUF_SIZE_BITS (BINARY_BUF_SIZE*BYTE_BITS)
+                    /* Need to trap while hashing binary */
+                    ErtsBlockHashHelperCtx* block_hash_ctx = &ctx.block_hash_ctx;
+                    Uint nr_of_bytes = ctx.sz + (ctx.bitsize != 0);
+                    ERTS_CT_ASSERT(BINARY_BUF_SIZE % BLOCK_HASH_BYTES_PER_ITER == 0);
+                    ctx.buf = erts_alloc(ERTS_ALC_T_PHASH2_TRAP,
+                                         MIN(nr_of_bytes, BINARY_BUF_SIZE));
+                    block_hash_setup(con, block_hash_ctx);
+                    do {
+                        Uint bytes_left =
+                            ctx.sz - ctx.no_bytes_processed;
+                        Uint even_bytes_left =
+                            bytes_left - (bytes_left % BLOCK_HASH_BYTES_PER_ITER);
+                        Uint bytes_to_process =
+                            MIN(BINARY_BUF_SIZE, even_bytes_left);
+                        Uint nr_of_bits_left =
+                            (ctx.sz*BYTE_BITS+ctx.bitsize) -
+                            ctx.no_bytes_processed*BYTE_BITS; 
+                        Uint nr_of_bits_to_copy =
+                            MIN(nr_of_bits_left, BINARY_BUF_SIZE_BITS);
+                        ctx.done = nr_of_bits_left == nr_of_bits_to_copy;
+                        erts_copy_bits(ctx.bptr + ctx.no_bytes_processed,
+                                       ctx.bitoffs, 1, ctx.buf, 0, 1,
+                                       nr_of_bits_to_copy);
+                        block_hash_buffer(ctx.buf,
+                                          bytes_to_process,
+                                          block_hash_ctx);
+                        ctx.no_bytes_processed += bytes_to_process;
+                        iterations_until_trap -=
+                            MAX(1, bytes_to_process / BLOCK_HASH_BYTES_PER_ITER);
+                        TRAP_LOCATION_NO_RED(sub_binary_subtag_2);
+                        block_hash_ctx = &ctx.block_hash_ctx; /* Restore after trap */
+                    } while (!ctx.done);
+                    nr_of_bytes = ctx.sz + (ctx.bitsize != 0);
+                    hash = block_hash_final_bytes(ctx.buf +
+                                                  (ctx.no_bytes_processed -
+                                                   ((nr_of_bytes-1) / BINARY_BUF_SIZE) *  BINARY_BUF_SIZE),
+                                                  ctx.sz - ctx.no_bytes_processed,
+                                                  ctx.sz,
+                                                  block_hash_ctx);
+                    if (ctx.bitsize > 0) {
+                        Uint last_byte_index =
+                            nr_of_bytes - (((nr_of_bytes-1) / BINARY_BUF_SIZE) *  BINARY_BUF_SIZE) -1;
+                        UINT32_HASH_2(ctx.bitsize,
+                                      (ctx.buf[last_byte_index] >> (BYTE_BITS - ctx.bitsize)),
+                                      HCONST_15);
+                    }
+                    erts_free(ERTS_ALC_T_PHASH2_TRAP, ctx.buf);
+                    context->trap_location_state.sub_binary_subtag_2.buf = NULL;
 		}
 		goto hash2_common;
+#undef BYTE_BITS
+#undef BINARY_BUF_SIZE
+#undef BINARY_BUF_SIZE_BITS
 	    }
 	    break;
 	    case POS_BIG_SUBTAG:
 	    case NEG_BIG_SUBTAG:
 	    {
-		Eterm* ptr = big_val(term);
-		Uint i = 0;
-		Uint n = BIG_SIZE(ptr);
-		Uint32 con = BIG_SIGN(ptr) ? HCONST_10 : HCONST_11;
+		Eterm* big_val_ptr = big_val(term);
+                ErtsMakeHash2Context_NEG_BIG_SUBTAG ctx = {
+                    .ptr = big_val_ptr,
+                    .i = 0,
+                    .n = BIG_SIZE(big_val_ptr),
+                    .con = BIG_SIGN(big_val_ptr) ? HCONST_10 : HCONST_11};
 #if D_EXP == 16
 		do {
 		    Uint32 x, y;
-		    x = i < n ? BIG_DIGIT(ptr, i++) : 0;
-		    x += (Uint32)(i < n ? BIG_DIGIT(ptr, i++) : 0) << 16;
-		    y = i < n ? BIG_DIGIT(ptr, i++) : 0;
-		    y += (Uint32)(i < n ? BIG_DIGIT(ptr, i++) : 0) << 16;
-		    UINT32_HASH_2(x, y, con);
-		} while (i < n);
+		    x = ctx.i < ctx.n ? BIG_DIGIT(ctx.ptr, ctx.i++) : 0;
+		    x += (Uint32)(ctx.i < ctx.n ? BIG_DIGIT(ctx.ptr, ctx.i++) : 0) << 16;
+		    y = ctx.i < ctx.n ? BIG_DIGIT(ctx.ptr, ctx.i++) : 0;
+		    y += (Uint32)(ctx.i < ctx.n ? BIG_DIGIT(ctx.ptr, ctx.i++) : 0) << 16;
+		    UINT32_HASH_2(x, y, ctx.con);
+                    TRAP_LOCATION(neg_big_subtag);
+		} while (ctx.i < ctx.n);
 #elif D_EXP == 32
 		do {
 		    Uint32 x, y;
-		    x = i < n ? BIG_DIGIT(ptr, i++) : 0;
-		    y = i < n ? BIG_DIGIT(ptr, i++) : 0;
-		    UINT32_HASH_2(x, y, con);
-		} while (i < n);
+		    x = ctx.i < ctx.n ? BIG_DIGIT(ctx.ptr, ctx.i++) : 0;
+		    y = ctx.i < ctx.n ? BIG_DIGIT(ctx.ptr, ctx.i++) : 0;
+		    UINT32_HASH_2(x, y, ctx.con);
+                    TRAP_LOCATION(neg_big_subtag);
+		} while (ctx.i < ctx.n);
 #elif D_EXP == 64
 		do {
 		    Uint t;
 		    Uint32 x, y;
-                    ASSERT(i < n);
-		    t = BIG_DIGIT(ptr, i++);
+                    ASSERT(ctx.i < ctx.n);
+		    t = BIG_DIGIT(ctx.ptr, ctx.i++);
 		    x = t & 0xffffffff;
 		    y = t >> 32;
-		    UINT32_HASH_2(x, y, con);
-		} while (i < n);
+		    UINT32_HASH_2(x, y, ctx.con);
+                    TRAP_LOCATION(neg_big_subtag);
+		} while (ctx.i < ctx.n);
 #else
 #error "unsupported D_EXP size"
 #endif
@@ -1508,13 +1915,13 @@ make_hash2(Eterm term)
 		}
 	    case _TAG_IMMED1_SMALL:
 	      {
-		  Sint x = signed_val(term);
+		  Sint small = signed_val(term);
+		  if (SMALL_BITS > 28 && !IS_SSMALL28(small)) {
+                      NOT_SSMALL28_HASH(small);
+		  } else {
+		      SINT32_HASH(small, HCONST);
+                  }
 
-		  if (SMALL_BITS > 28 && !IS_SSMALL28(x)) {
-		      term = small_to_big(x, tmp_big);
-		      break;
-		  }
-		  SINT32_HASH(x, HCONST);
 		  goto hash2_common;
 	      }
 	    }
@@ -1529,7 +1936,10 @@ make_hash2(Eterm term)
 
 	    if (ESTACK_ISEMPTY(s)) {
 		DESTROY_ESTACK(s);
-		UnUseTmpHeapNoproc(2);
+                if (can_trap) {
+                    BUMP_REDS(p, (max_iterations - iterations_until_trap) / ITERATIONS_PER_RED);
+                    ASSERT(!(p->flags & F_DISABLE_GC));
+                }
 		return hash;
 	    }
 
@@ -1540,18 +1950,37 @@ make_hash2(Eterm term)
 		    hash = (Uint32) ESTACK_POP(s);
                     UINT32_HASH(hash_xor_pairs, HCONST_19);
 		    hash_xor_pairs = (Uint32) ESTACK_POP(s);
+                    TRAP_LOCATION_NO_CTX(hash2_common_1);
 		    goto hash2_common;
 		}
 		case HASH_MAP_PAIR:
 		    hash_xor_pairs ^= hash;
                     hash = 0;
+                    TRAP_LOCATION_NO_CTX(hash2_common_2);
 		    goto hash2_common;
 		default:
 		    break;
 	    }
+
 	}
+        TRAP_LOCATION_NO_CTX(hash2_common_3);
     }
     }
+#undef TRAP_LOCATION_NO_RED
+#undef TRAP_LOCATION
+#undef TRAP_LOCATION_NO_CTX
+}
+
+Uint32
+make_hash2(Eterm term)
+{
+    return make_hash2_helper(term, 0, NULL, NULL);
+}
+
+Uint32
+trapping_make_hash2(Eterm term, Eterm* state_mref_write_back, Process* p)
+{
+    return make_hash2_helper(term, 1, state_mref_write_back, p);
 }
 
 /* Term hash function for internal use.
diff --git a/erts/emulator/test/Makefile b/erts/emulator/test/Makefile
index 019af2162f..731aa66924 100644
--- a/erts/emulator/test/Makefile
+++ b/erts/emulator/test/Makefile
@@ -90,6 +90,7 @@ MODULES= \
 	gc_SUITE \
 	guard_SUITE \
 	hash_SUITE \
+	hash_property_test_SUITE \
 	hibernate_SUITE \
 	hipe_SUITE \
 	iovec_SUITE \
@@ -252,7 +253,7 @@ release_tests_spec: make_emakefile
 	$(INSTALL_DATA) $(NO_OPT_ERL_FILES) "$(RELSYSDIR)"
 	$(INSTALL_DATA) $(NATIVE_ERL_FILES) "$(RELSYSDIR)"
 	chmod -R u+w "$(RELSYSDIR)"
-	tar cf - *_SUITE_data | (cd "$(RELSYSDIR)"; tar xf -)
+	tar cf - *_SUITE_data property_test | (cd "$(RELSYSDIR)"; tar xf -)
 
 release_docs_spec:
 
diff --git a/erts/emulator/test/emulator.spec b/erts/emulator/test/emulator.spec
index 7a6dd83020..087bd8880d 100644
--- a/erts/emulator/test/emulator.spec
+++ b/erts/emulator/test/emulator.spec
@@ -1,2 +1,3 @@
 {enable_builtin_hooks, false}.
 {suites,"../emulator_test",all}.
+{skip_groups,"../emulator_test",hash_SUITE,[phash2_benchmark],"Benchmark only"}.
diff --git a/erts/emulator/test/emulator_bench.spec b/erts/emulator/test/emulator_bench.spec
index 03638bfa23..8b1bb71a40 100644
--- a/erts/emulator/test/emulator_bench.spec
+++ b/erts/emulator/test/emulator_bench.spec
@@ -1,1 +1,2 @@
 {groups,"../emulator_test",estone_SUITE,[estone_bench]}.
+{groups,"../emulator_test",hash_SUITE,[phash2_benchmark]}.
diff --git a/erts/emulator/test/hash_SUITE.erl b/erts/emulator/test/hash_SUITE.erl
index 3cbb3c7d5f..1bf9e033bf 100644
--- a/erts/emulator/test/hash_SUITE.erl
+++ b/erts/emulator/test/hash_SUITE.erl
@@ -33,7 +33,25 @@
 -module(hash_SUITE).
 -export([basic_test/0,cmp_test/1,range_test/0,spread_test/1,
 	 phash2_test/0, otp_5292_test/0,
-         otp_7127_test/0]).
+         otp_7127_test/0, 
+         run_phash2_benchmarks/0,
+         test_phash2_binary_aligned_and_unaligned_equal/1,
+         test_phash2_4GB_plus_bin/1,
+         test_phash2_10MB_plus_bin/1,
+         test_phash2_large_map/1,
+         test_phash2_shallow_long_list/1,
+         test_phash2_deep_list/1,
+         test_phash2_deep_tuple/1,
+         test_phash2_deep_tiny/1,
+         test_phash2_with_42/1,
+         test_phash2_with_short_tuple/1,
+         test_phash2_with_short_list/1,
+         test_phash2_with_tiny_bin/1,
+         test_phash2_with_tiny_unaligned_sub_binary/1,
+         test_phash2_with_small_unaligned_sub_binary/1,
+         test_phash2_with_large_bin/1,
+         test_phash2_with_large_unaligned_sub_binary/1,
+         test_phash2_with_super_large_unaligned_sub_binary/1]).
 
 %%
 %% Define to run outside of test server
@@ -43,13 +61,15 @@
 %%
 %% Define for debug output
 %%
-%-define(debug,1).
+-define(debug,1).
 
 -ifdef(STANDALONE).
 -define(config(A,B),config(A,B)).
+-record(event, {name, data}).
 -export([config/2]).
 -else.
 -include_lib("common_test/include/ct.hrl").
+-include_lib("common_test/include/ct_event.hrl").
 -endif.
 
 -ifdef(debug).
@@ -67,12 +87,15 @@
 -ifdef(STANDALONE).
 config(priv_dir,_) ->
     ".".
+notify(X) -> 
+    erlang:display(X).
 -else.
 %% When run in test server.
--export([all/0, suite/0,
+-export([groups/0, all/0, suite/0,
 	 test_basic/1,test_cmp/1,test_range/1,test_spread/1,
 	 test_phash2/1,otp_5292/1,bit_level_binaries/1,otp_7127/1,
-         test_hash_zero/1]).
+         test_hash_zero/1, init_per_suite/1, end_per_suite/1,
+         init_per_group/2, end_per_group/2]).
 
 suite() ->
     [{ct_hooks,[ts_install_cth]},
@@ -81,7 +104,71 @@ suite() ->
 all() -> 
     [test_basic, test_cmp, test_range, test_spread,
      test_phash2, otp_5292, bit_level_binaries, otp_7127,
-     test_hash_zero].
+     test_hash_zero, test_phash2_binary_aligned_and_unaligned_equal,
+     test_phash2_4GB_plus_bin,
+     test_phash2_10MB_plus_bin,
+     {group, phash2_benchmark_tests},
+     {group, phash2_benchmark}].
+
+get_phash2_benchmarks() ->
+    [
+     test_phash2_large_map,
+     test_phash2_shallow_long_list,
+     test_phash2_deep_list,
+     test_phash2_deep_tuple,
+     test_phash2_deep_tiny,
+     test_phash2_with_42,
+     test_phash2_with_short_tuple,
+     test_phash2_with_short_list,
+     test_phash2_with_tiny_bin,
+     test_phash2_with_tiny_unaligned_sub_binary,
+     test_phash2_with_small_unaligned_sub_binary,
+     test_phash2_with_large_bin,
+     test_phash2_with_large_unaligned_sub_binary,
+     test_phash2_with_super_large_unaligned_sub_binary
+    ].
+
+groups() -> 
+    [
+     {
+      phash2_benchmark_tests,
+      [],
+      get_phash2_benchmarks()
+     },
+     {
+      phash2_benchmark,
+      [],
+      get_phash2_benchmarks()
+     }
+    ].
+
+
+init_per_suite(Config) ->
+    io:format("START APPS~n"),
+    A0 = case application:start(sasl) of
+	     ok -> [sasl];
+	     _ -> []
+	 end,
+    A = case application:start(os_mon) of
+	     ok -> [os_mon|A0];
+	     _ -> A0
+	 end,
+    io:format("APPS STARTED~n"),
+    [{started_apps, A}|Config].
+
+end_per_suite(Config) ->
+    As = proplists:get_value(started_apps, Config),
+    lists:foreach(fun (A) -> application:stop(A) end, As),
+    Config.
+
+init_per_group(phash2_benchmark_tests, Config) ->
+    [phash2_benchmark_tests |Config];
+init_per_group(_, Config) ->
+    Config.
+
+end_per_group(_, Config) ->
+    Config.
+
 
 %% Tests basic functionality of erlang:phash and that the
 %% hashes has not changed (neither hash nor phash)
@@ -119,6 +206,9 @@ otp_7127(Config) when is_list(Config) ->
 
 test_hash_zero(Config) when is_list(Config) ->
     hash_zero_test().
+
+notify(X) ->
+    ct_event:notify(X).
 -endif.
 
 
@@ -354,6 +444,7 @@ phash2_test() ->
 
 	 %% bit-level binaries
 	 {<<0:7>>, 1055790816},
+	 {(fun()-> B = <<255,7:3>>, <<_:4,D/bitstring>> = B, D end)(), 911751529},
 	 {<<"abc",13:4>>, 670412287},
 	 {<<5:3,"12345678901234567890">>, 289973273},
 
@@ -424,6 +515,159 @@ phash2_test() ->
     [] = [{E,H,H2} || {E,H} <- L, (H2 = erlang:phash2(E, Max)) =/= H],
     ok.
 
+test_phash2_binary_aligned_and_unaligned_equal(Config) when is_list(Config) ->
+    erts_debug:set_internal_state(available_internal_state, true),
+    test_aligned_and_unaligned_equal_up_to(256*12+255),
+    erts_debug:set_internal_state(available_internal_state, false).
+
+test_aligned_and_unaligned_equal_up_to(BinSize) ->
+    Results =
+        lists:map(fun(Size) ->
+                          test_aligned_and_unaligned_equal(Size)
+                  end, lists:seq(1, BinSize)),
+    %% DataDir = filename:join(filename:dirname(code:which(?MODULE)), "hash_SUITE_data"),
+    %% ExpResFile = filename:join(DataDir, "phash2_bin_expected_results.txt"),
+    %% {ok, [ExpRes]} = file:consult(ExpResFile),
+    %% %% ok = file:write_file(ExpResFile, io_lib:format("~w.~n", [Results])),
+    %% Results = ExpRes,
+    110469206 = erlang:phash2(Results).
+
+test_aligned_and_unaligned_equal(BinSize) ->
+    Bin = make_random_bin(BinSize),
+    LastByte = last_byte(Bin),
+    LastInBitstring = LastByte rem 11,
+    Bitstring = << Bin/binary, <<LastInBitstring:5>>/bitstring >>,
+    UnalignedBin = make_unaligned_sub_bitstring(Bin),
+    UnalignedBitstring = make_unaligned_sub_bitstring(Bitstring),
+    case erts_debug:get_internal_state(available_internal_state) of
+        false -> erts_debug:set_internal_state(available_internal_state, true);
+        _ -> ok
+    end,
+    erts_debug:set_internal_state(reds_left, 3),
+    BinHash = erlang:phash2(Bin),
+    BinHash = erlang:phash2(Bin),
+    erts_debug:set_internal_state(reds_left, 3),
+    UnalignedBinHash = erlang:phash2(UnalignedBin),
+    UnalignedBinHash = erlang:phash2(UnalignedBin),
+    BinHash = UnalignedBinHash,
+    erts_debug:set_internal_state(reds_left, 3),
+    BitstringHash = erlang:phash2(Bitstring),
+    BitstringHash = erlang:phash2(Bitstring),
+    erts_debug:set_internal_state(reds_left, 3),
+    UnalignedBitstringHash = erlang:phash2(UnalignedBitstring),
+    UnalignedBitstringHash = erlang:phash2(UnalignedBitstring),
+    BitstringHash = UnalignedBitstringHash,
+    {BinHash, BitstringHash}.
+
+last_byte(Bin) ->
+    NotLastByteSize = (erlang:bit_size(Bin)) - 8,
+    <<_:NotLastByteSize/bitstring, LastByte:8>> = Bin,
+    LastByte.
+
+test_phash2_4GB_plus_bin(Config) when is_list(Config) ->
+    run_when_enough_resources(
+      fun() ->
+              erts_debug:set_internal_state(available_internal_state, true),
+              %% Created Bin4GB here so it only needs to be created once
+              erts_debug:set_internal_state(force_gc, self()),
+              Bin4GB = get_4GB_bin(),
+              test_phash2_plus_bin_helper1(Bin4GB, <<>>, <<>>, 13708901),
+              erts_debug:set_internal_state(force_gc, self()),
+              test_phash2_plus_bin_helper1(Bin4GB, <<>>, <<3:5>>, 66617678),
+              erts_debug:set_internal_state(force_gc, self()),
+              test_phash2_plus_bin_helper1(Bin4GB, <<13>>, <<>>, 31308392),
+              erts_debug:set_internal_state(force_gc, self()),
+              erts_debug:set_internal_state(available_internal_state, false)
+      end).
+
+
+test_phash2_10MB_plus_bin(Config) when is_list(Config) ->
+    erts_debug:set_internal_state(available_internal_state, true),
+    erts_debug:set_internal_state(force_gc, self()),
+    Bin10MB = get_10MB_bin(),
+    test_phash2_plus_bin_helper1(Bin10MB, <<>>, <<>>, 22776267),
+    erts_debug:set_internal_state(force_gc, self()),
+    test_phash2_plus_bin_helper1(Bin10MB, <<>>, <<3:5>>, 124488972),
+    erts_debug:set_internal_state(force_gc, self()),
+    test_phash2_plus_bin_helper1(Bin10MB, <<13>>, <<>>, 72958346),
+    erts_debug:set_internal_state(force_gc, self()),
+    erts_debug:set_internal_state(available_internal_state, false).
+
+get_10MB_bin() ->
+    TmpBin = make_random_bin(10239),
+    Bin = erlang:iolist_to_binary([0, TmpBin]),
+    IOList10MB = duplicate_iolist(Bin, 10),
+    Bin10MB = erlang:iolist_to_binary(IOList10MB),
+    10485760 = size(Bin10MB),
+    Bin10MB.
+
+get_4GB_bin() ->
+    TmpBin = make_random_bin(65535),
+    Bin = erlang:iolist_to_binary([0, TmpBin]),
+    IOList4GB = duplicate_iolist(Bin, 16),
+    Bin4GB = erlang:iolist_to_binary(IOList4GB),
+    4294967296 = size(Bin4GB),
+    Bin4GB.
+
+duplicate_iolist(IOList, 0) ->
+    IOList;
+duplicate_iolist(IOList, NrOfTimes) ->
+    duplicate_iolist([IOList, IOList], NrOfTimes - 1).
+
+test_phash2_plus_bin_helper1(Bin4GB, ExtraBytes, ExtraBits, ExpectedHash) ->
+    test_phash2_plus_bin_helper2(Bin4GB, fun id/1, ExtraBytes, ExtraBits, ExpectedHash),
+    test_phash2_plus_bin_helper2(Bin4GB, fun make_unaligned_sub_bitstring/1, ExtraBytes, ExtraBits, ExpectedHash).
+
+test_phash2_plus_bin_helper2(Bin, TransformerFun, ExtraBytes, ExtraBits, ExpectedHash) ->
+    ExtraBitstring = << ExtraBytes/binary, ExtraBits/bitstring >>,
+    LargerBitstring = << ExtraBytes/binary,
+                         ExtraBits/bitstring,
+                         Bin/bitstring >>,
+    LargerTransformedBitstring = TransformerFun(LargerBitstring),
+    ExtraBitstringHash = erlang:phash2(ExtraBitstring),
+    ExpectedHash =
+        case size(LargerTransformedBitstring) < 4294967296 of
+            true ->
+                erts_debug:set_internal_state(force_gc, self()),
+                erts_debug:set_internal_state(reds_left, 1),
+                Hash = erlang:phash2(LargerTransformedBitstring),
+                Hash = erlang:phash2(LargerTransformedBitstring),
+                Hash;
+            false ->
+                erts_debug:set_internal_state(force_gc, self()),
+                erts_debug:set_internal_state(reds_left, 1),
+                ExtraBitstringHash = erlang:phash2(LargerTransformedBitstring),
+                ExtraBitstringHash = erlang:phash2(LargerTransformedBitstring),
+                ExtraBitstringHash
+        end.
+
+run_when_enough_resources(Fun) ->
+    case {total_memory(), erlang:system_info(wordsize)} of
+        {Mem, 8} when is_integer(Mem) andalso Mem >= 31 ->
+            Fun();
+        {Mem, WordSize} ->
+            {skipped,
+             io_lib:format("Not enough resources (System Memory >= ~p, Word Size = ~p)",
+                           [Mem, WordSize])}
+    end.
+
+%% Total memory in GB
+total_memory() ->
+    try
+        MemoryData = memsup:get_system_memory_data(),
+        case lists:keysearch(total_memory, 1, MemoryData) of
+            {value, {total_memory, TM}} ->
+        	TM div (1024*1024*1024);
+            false ->
+        	{value, {system_total_memory, STM}} =
+        	    lists:keysearch(system_total_memory, 1, MemoryData),
+        	STM div (1024*1024*1024)
+        end
+    catch
+        _ : _ ->
+            undefined
+    end.
+
 -ifdef(FALSE).
 f1() ->
     abc.
@@ -436,14 +680,23 @@ f3(X, Y) ->
 -endif.
 
 otp_5292_test() ->
-    PH = fun(E) -> [erlang:phash(E, 1 bsl 32),
-                    erlang:phash(-E, 1 bsl 32),
-                    erlang:phash2(E, 1 bsl 32),
-                    erlang:phash2(-E, 1 bsl 32)]
-            end,
+    PH = fun(E) ->
+                 EInList = [1, 2, 3, E],
+                 EInList2 = [E, 1, 2, 3],
+                 NegEInList = [1, 2, 3, -E],
+                 NegEInList2 = [-E, 1, 2, 3],
+                 [erlang:phash(E, 1 bsl 32),
+                  erlang:phash(-E, 1 bsl 32),
+                  erlang:phash2(E, 1 bsl 32),
+                  erlang:phash2(-E, 1 bsl 32),
+                  erlang:phash2(EInList, 1 bsl 32),
+                  erlang:phash2(EInList2, 1 bsl 32),
+                  erlang:phash2(NegEInList, 1 bsl 32),
+                  erlang:phash2(NegEInList2, 1 bsl 32)]
+         end,
     S2 = md5([md5(hash_int(S, E, PH)) || {Start, N, Sz} <- d(),
                                          {S, E} <- int(Start, N, Sz)]),
-    <<124,81,198,121,174,233,19,137,10,83,33,80,226,111,238,99>> = S2,
+    <<234,63,192,76,253,57,250,32,44,11,73,1,161,102,14,238>> = S2,
     ok.
 
 d() ->
@@ -684,3 +937,313 @@ unaligned_sub_bitstr(Bin0) when is_bitstring(Bin0) ->
 
 id(I) -> I.
     
+
+%% Benchmarks for phash2
+
+run_phash2_benchmarks() ->
+    Benchmarks = [
+                  test_phash2_large_map,
+                  test_phash2_shallow_long_list,
+                  test_phash2_deep_list,
+                  test_phash2_deep_tuple,
+                  test_phash2_deep_tiny,
+                  test_phash2_with_42,
+                  test_phash2_with_short_tuple,
+                  test_phash2_with_short_list,
+                  test_phash2_with_tiny_bin,
+                  test_phash2_with_tiny_unaligned_sub_binary,
+                  test_phash2_with_small_unaligned_sub_binary,
+                  test_phash2_with_large_bin,
+                  test_phash2_with_large_unaligned_sub_binary,
+                  test_phash2_with_super_large_unaligned_sub_binary
+                 ],
+    [print_comment(B) || B <- Benchmarks].
+
+
+print_comment(FunctionName) ->
+    io:format("~p~n", [FunctionName]),
+    io:format("~s~n", [element(2, erlang:apply(?MODULE, FunctionName, [[]]))]).
+
+nr_of_iters(BenchmarkNumberOfIterations, Config) ->
+    case lists:member(phash2_benchmark_tests, Config) of
+        true -> 1;
+        false -> BenchmarkNumberOfIterations
+    end.
+
+
+test_phash2_large_map(Config) when is_list(Config) ->
+    {Size, ExpectedHash} =
+        case {total_memory(), erlang:system_info(wordsize)} of
+            {Mem, 8} when is_integer(Mem) andalso Mem > 2 ->
+                {1000000, 121857429};
+            _ ->
+                {1000, 66609305}
+        end,
+    run_phash2_test_and_benchmark(nr_of_iters(45, Config),
+                                  get_map(Size),
+                                  ExpectedHash).
+
+test_phash2_shallow_long_list(Config) when is_list(Config) ->
+    {Size, ExpectedHash} =
+        case {total_memory(), erlang:system_info(wordsize)} of
+            {Mem, 8} when is_integer(Mem) andalso Mem > 2 ->
+                {1000000, 78700388};
+            _ ->
+                {1000, 54749638}
+        end,
+    run_phash2_test_and_benchmark(nr_of_iters(1, Config),
+                                  lists:duplicate(Size, get_complex_tuple()),
+                                  ExpectedHash).
+
+test_phash2_deep_list(Config) when is_list(Config) ->
+    {Size, ExpectedHash} =
+        case {total_memory(), erlang:system_info(wordsize)} of
+            {Mem, 8} when is_integer(Mem) andalso Mem > 2 ->
+                {500000, 17986444};
+            _ ->
+                {1000, 81794308}
+        end,
+    run_phash2_test_and_benchmark(nr_of_iters(1, Config),
+                                  make_deep_list(Size, get_complex_tuple()),
+                                  ExpectedHash).
+
+test_phash2_deep_tuple(Config) when is_list(Config) ->
+    {Size, ExpectedHash} =
+        case {total_memory(), erlang:system_info(wordsize)} of
+            {Mem, 8} when is_integer(Mem) andalso Mem > 2 ->
+                {500000, 116594715};
+            _ ->
+                {500, 109057352}
+        end,
+    run_phash2_test_and_benchmark(nr_of_iters(1, Config),
+                                  make_deep_tuple(Size, get_complex_tuple()),
+                                  ExpectedHash).
+
+test_phash2_deep_tiny(Config) when is_list(Config) ->
+    run_phash2_test_and_benchmark(nr_of_iters(1000000, Config),
+                                  make_deep_list(19, 42),
+                                  111589624).
+
+test_phash2_with_42(Config) when is_list(Config) ->
+    run_phash2_test_and_benchmark(nr_of_iters(20000000, Config),
+                                  42,
+                                  30328728).
+
+test_phash2_with_short_tuple(Config) when is_list(Config) ->
+    run_phash2_test_and_benchmark(nr_of_iters(10000000, Config),
+                                  {a,b,<<"hej">>, "hej"},
+                                  50727199).
+
+test_phash2_with_short_list(Config) when is_list(Config) ->
+    run_phash2_test_and_benchmark(nr_of_iters(10000000, Config),
+                                  [a,b,"hej", "hello"],
+                                  117108642).
+
+test_phash2_with_tiny_bin(Config) when is_list(Config) ->
+    run_phash2_test_and_benchmark(nr_of_iters(20000000, Config),
+                                  make_random_bin(10),
+                                  129616602).
+
+test_phash2_with_tiny_unaligned_sub_binary(Config) when is_list(Config) ->
+    run_phash2_test_and_benchmark(nr_of_iters(10000000, Config),
+                                  make_unaligned_sub_binary(make_random_bin(11)),
+                                  59364725).
+
+test_phash2_with_small_unaligned_sub_binary(Config) when is_list(Config) ->
+    run_phash2_test_and_benchmark(nr_of_iters(400000, Config),
+                                  make_unaligned_sub_binary(make_random_bin(1001)),
+                                  130388119).
+
+test_phash2_with_large_bin(Config) when is_list(Config) ->
+    {Size, ExpectedHash} =
+        case {total_memory(), erlang:system_info(wordsize)} of
+            {Mem, 8} when is_integer(Mem) andalso Mem > 2 ->
+                {10000000, 48249379};
+            _ ->
+                {1042, 14679520}
+        end,
+    run_phash2_test_and_benchmark(nr_of_iters(150, Config),
+                                  make_random_bin(Size),
+                                  ExpectedHash).
+
+test_phash2_with_large_unaligned_sub_binary(Config) when is_list(Config) ->
+    {Size, ExpectedHash} =
+        case {total_memory(), erlang:system_info(wordsize)} of
+            {Mem, 8} when is_integer(Mem) andalso Mem > 2 ->
+                {10000001, 122836437};
+            _ ->
+                {10042, 127144287}
+        end,
+    run_phash2_test_and_benchmark(nr_of_iters(50, Config),
+                                  make_unaligned_sub_binary(make_random_bin(Size)),
+                                  ExpectedHash).
+
+test_phash2_with_super_large_unaligned_sub_binary(Config) when is_list(Config) ->
+    {Size, ExpectedHash} =
+        case {total_memory(), erlang:system_info(wordsize)} of
+            {Mem, 8} when is_integer(Mem) andalso Mem > 2 ->
+                {20000001, 112086727};
+            _ ->
+                {20042, 91996619}
+        end,
+    run_phash2_test_and_benchmark(nr_of_iters(20, Config),
+                                  make_unaligned_sub_binary(make_random_bin(Size)),
+                                  ExpectedHash).
+
+make_deep_list(1, Item) ->
+    {Item, Item};
+make_deep_list(Depth, Item) ->
+    [{Item, Item}, make_deep_list(Depth - 1, Item)].
+
+make_deep_tuple(1, Item) ->
+    [Item, Item];
+make_deep_tuple(Depth, Item) ->
+    {[Item, Item], make_deep_tuple(Depth - 1, Item)}.
+
+% Helper functions for benchmarking
+
+loop(0, _) -> ok;
+loop(Iterations, Fun) ->
+    Fun(),
+    loop(Iterations - 1, Fun).
+
+run_phash2_test_and_benchmark(Iterations, Term, ExpectedHash) ->
+    Parent = self(),
+    Test =
+        fun() ->
+                Hash = erlang:phash2(Term),
+                case ExpectedHash =:= Hash of
+                    false ->
+                        Parent ! {got_bad_hash, Hash},
+                        ExpectedHash = Hash;
+                    _ -> ok
+                end
+        end,
+    Benchmark =
+        fun() ->
+                garbage_collect(),
+                {Time, _} =timer:tc(fun() -> loop(Iterations, Test) end),
+                Parent ! Time
+        end,
+    spawn(Benchmark),
+    receive
+        {got_bad_hash, Hash} ->
+            ExpectedHash = Hash;
+        Time ->
+            TimeInS = case (Time/1000000) of
+                          0.0 -> 0.0000000001;
+                          T -> T
+                      end,
+            IterationsPerSecond = Iterations / TimeInS,
+            notify(#event{ name = benchmark_data, data = [{value, IterationsPerSecond}]}),
+            {comment, io_lib:format("Iterations per second: ~p, Iterations ~p, Benchmark time: ~p seconds)",
+                                    [IterationsPerSecond, Iterations, Time/1000000])}
+    end.
+
+get_complex_tuple() ->
+    BPort = <<131,102,100,0,13,110,111,110,111,100,101,64,110,111,104,
+              111,115,116,0,0,0,1,0>>,
+    Port = binary_to_term(BPort),
+
+    BXPort = <<131,102,100,0,11,97,112,97,64,108,101,103,111,108,97,115,
+               0,0,0,24,3>>,
+    XPort = binary_to_term(BXPort),
+
+    BRef = <<131,114,0,3,100,0,13,110,111,110,111,100,101,64,110,111,104,
+             111,115,116,0,0,0,1,255,0,0,0,0,0,0,0,0>>,
+    Ref = binary_to_term(BRef),
+
+    BXRef = <<131,114,0,3,100,0,11,97,112,97,64,108,101,103,111,108,97,115,
+              2,0,0,0,155,0,0,0,0,0,0,0,0>>,
+    XRef = binary_to_term(BXRef),
+
+    BXPid = <<131,103,100,0,11,97,112,97,64,108,101,103,111,108,97,115,
+              0,0,0,36,0,0,0,0,1>>,
+    XPid = binary_to_term(BXPid),
+
+
+    %% X = f1(), Y = f2(), Z = f3(X, Y),
+
+    %% F1 = fun f1/0, % -> abc
+    B1 = <<131,112,0,0,0,66,0,215,206,77,69,249,50,170,17,129,47,21,98,
+           13,196,76,242,0,0,0,1,0,0,0,0,100,0,1,116,97,1,98,2,195,126,
+           58,103,100,0,13,110,111,110,111,100,101,64,110,111,104,111,
+           115,116,0,0,0,112,0,0,0,0,0>>,
+    F1 = binary_to_term(B1),
+
+    %% F2 = fun f2/0, % -> abd
+    B2 = <<131,112,0,0,0,66,0,215,206,77,69,249,50,170,17,129,47,21,98,
+           13,196,76,242,0,0,0,2,0,0,0,0,100,0,1,116,97,2,98,3,130,152,
+           185,103,100,0,13,110,111,110,111,100,101,64,110,111,104,111,
+           115,116,0,0,0,112,0,0,0,0,0>>,
+    F2 = binary_to_term(B2),
+
+    %% F3 = fun f3/2, % -> {abc, abd}
+    B3 = <<131,112,0,0,0,66,2,215,206,77,69,249,50,170,17,129,47,21,98,
+           13,196,76,242,0,0,0,3,0,0,0,0,100,0,1,116,97,3,98,7,168,160,
+           93,103,100,0,13,110,111,110,111,100,101,64,110,111,104,111,
+           115,116,0,0,0,112,0,0,0,0,0>>,
+    F3 = binary_to_term(B3),
+
+    %% F4 = fun () -> 123456789012345678901234567 end,
+    B4 = <<131,112,0,0,0,66,0,215,206,77,69,249,50,170,17,129,47,21,98,
+           13,196,76,242,0,0,0,4,0,0,0,0,100,0,1,116,97,4,98,2,230,21,
+           171,103,100,0,13,110,111,110,111,100,101,64,110,111,104,111,
+           115,116,0,0,0,112,0,0,0,0,0>>,
+    F4 = binary_to_term(B4),
+
+    %% F5 = fun() -> {X,Y,Z} end,
+    B5 = <<131,112,0,0,0,92,0,215,206,77,69,249,50,170,17,129,47,21,98,
+           13,196,76,242,0,0,0,5,0,0,0,3,100,0,1,116,97,5,98,0,99,101,
+           130,103,100,0,13,110,111,110,111,100,101,64,110,111,104,111,
+           115,116,0,0,0,112,0,0,0,0,0,100,0,3,97,98,99,100,0,3,97,98,
+           100,104,2,100,0,3,97,98,99,100,0,3,97,98,100>>,
+    F5 = binary_to_term(B5),
+    {{1,{2}},an_atom, 1, 3434.923942394,<<"this is a binary">>,
+     make_unaligned_sub_binary(<<"this is also a binary">>),c,d,e,f,g,h,i,j,k,l,[f],
+     999999999999999999666666662123123123123324234999999999999999, 234234234,
+     BPort, Port, BXPort, XPort, BRef, Ref, BXRef, XRef, BXPid, XPid, F1, F2, F3, F4, F5,
+     #{a => 1, b => 2, c => 3, d => 4, e => 5, f => 6, g => 7, h => 8, i => 9,
+       j => 1, k => 1, l => 123123123123213, m => [1,2,3,4,5,6,7,8], o => 5, p => 6,
+       q => 7, r => 8, s => 9}}.
+
+get_map_helper(MapSoFar, 0) ->
+    MapSoFar;
+get_map_helper(MapSoFar, NumOfItemsToAdd) ->
+    NewMapSoFar = maps:put(NumOfItemsToAdd, NumOfItemsToAdd, MapSoFar),
+    get_map_helper(NewMapSoFar, NumOfItemsToAdd -1).
+
+get_map(Size) ->
+    get_map_helper(#{}, Size).
+
+
+%% Copied from binary_SUITE
+make_unaligned_sub_binary(Bin0) when is_binary(Bin0) ->
+    Bin1 = <<0:3,Bin0/binary,31:5>>,
+    Sz = size(Bin0),
+    <<0:3,Bin:Sz/binary,31:5>> = id(Bin1),
+    Bin.
+
+make_unaligned_sub_bitstring(Bin0) ->
+    Bin1 = <<0:3,Bin0/bitstring,31:5>>,
+    Sz = erlang:bit_size(Bin0),
+    <<0:3,Bin:Sz/bitstring,31:5>> = id(Bin1),
+    Bin.
+
+make_random_bin(Size) ->
+    make_random_bin(Size, []).
+
+make_random_bin(0, Acc) ->
+    iolist_to_binary(Acc);
+make_random_bin(Size, []) ->
+    make_random_bin(Size - 1, [simple_rand() rem 256]);
+make_random_bin(Size, [N | Tail]) ->
+    make_random_bin(Size - 1, [simple_rand(N) rem 256, N |Tail]).
+
+simple_rand() ->
+    123456789.
+simple_rand(Seed) ->
+    A = 1103515245,
+    C = 12345,
+    M = (1 bsl 31),
+    (A * Seed + C) rem M.
diff --git a/erts/emulator/test/hash_property_test_SUITE.erl b/erts/emulator/test/hash_property_test_SUITE.erl
new file mode 100644
index 0000000000..b4c7810a52
--- /dev/null
+++ b/erts/emulator/test/hash_property_test_SUITE.erl
@@ -0,0 +1,103 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2004-2019. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+%%
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%%%                                                             %%%
+%%%                       WARNING                               %%%
+%%%                                                             %%%
+%%% This is experimental code which may be changed or removed   %%%
+%%%               anytime without any warning.                  %%%
+%%%                                                             %%%
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+-module(hash_property_test_SUITE).
+
+-export([suite/0,all/0,groups/0,init_per_suite/1,
+         end_per_suite/1,init_per_group/2,end_per_group/2]).
+
+-export([test_phash2_no_diff/1,
+         test_phash2_no_diff_long/1,
+         test_phash2_no_diff_between_versions/1]).
+
+-include_lib("common_test/include/ct.hrl").
+
+suite() ->
+    [{ct_hooks,[ts_install_cth]}].
+
+all() -> [{group, proper}].
+
+groups() ->
+    [{proper, [], [test_phash2_no_diff,
+                   test_phash2_no_diff_long,
+                   test_phash2_no_diff_between_versions]}].
+
+
+%%% First prepare Config and compile the property tests for the found tool:
+init_per_suite(Config) ->
+    ct_property_test:init_per_suite(Config).
+
+end_per_suite(Config) ->
+    Config.
+
+%%% Only proper is supported
+init_per_group(proper, Config) ->
+    case proplists:get_value(property_test_tool,Config) of
+	proper -> Config;
+	X -> {skip, lists:concat([X," is not supported"])}
+    end;
+init_per_group(_, Config) ->
+    Config.
+
+end_per_group(_, Config) ->
+    Config.
+
+test_phash2_no_diff(Config) when is_list(Config) ->
+    true = ct_property_test:quickcheck(
+             phash2_properties:prop_phash2_same_with_same_input(),
+             Config).
+
+test_phash2_no_diff_long(Config) when is_list(Config) ->
+    true = ct_property_test:quickcheck(
+             phash2_properties:prop_phash2_same_with_same_long_input(),
+             Config).
+
+test_phash2_no_diff_between_versions(Config) when is_list(Config) ->
+    R = "21",
+    case test_server:is_release_available(R) of
+        true ->
+            Rel = {release,R},
+            case test_server:start_node(rel21,peer,[{erl,[Rel]}]) of
+                {error, Reason} -> {skip, io_lib:format("Could not start node: ~p~n", [Reason])};
+                {ok, Node} ->
+                    try
+                        true = ct_property_test:quickcheck(
+                                 phash2_properties:prop_phash2_same_in_different_versions(Node),
+                                 Config),
+                        true = ct_property_test:quickcheck(
+                                 phash2_properties:prop_phash2_same_in_different_versions_with_long_input(Node),
+                                 Config)
+                    after
+                        test_server:stop_node(Node)
+                    end
+            end;
+        false ->
+            {skip, io_lib:format("Release ~s not available~n", [R])}
+    end.
diff --git a/erts/emulator/test/property_test/phash2_properties.erl b/erts/emulator/test/property_test/phash2_properties.erl
new file mode 100644
index 0000000000..b1f3207c56
--- /dev/null
+++ b/erts/emulator/test/property_test/phash2_properties.erl
@@ -0,0 +1,63 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2019-2019. All Rights Reserved.
+%%
+%% The contents of this file are subject to the Erlang Public License,
+%% Version 1.1, (the "License"); you may not use this file except in
+%% compliance with the License. You should have received a copy of the
+%% Erlang Public License along with this software. If not, it can be
+%% retrieved online at http://www.erlang.org/.
+%%
+%% Software distributed under the License is distributed on an "AS IS"
+%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
+%% the License for the specific language governing rights and limitations
+%% under the License.
+%%
+%% %CopyrightEnd%
+%%
+%%
+
+-module(phash2_properties).
+
+-ifdef(PROPER).
+
+-include_lib("proper/include/proper.hrl").
+-export([prop_phash2_same_with_same_input/0,
+         prop_phash2_same_with_same_long_input/0,
+         prop_phash2_same_in_different_versions/1,
+         prop_phash2_same_in_different_versions_with_long_input/1]).
+-proptest([proper]).
+
+%%--------------------------------------------------------------------
+%% Properties --------------------------------------------------------
+%%--------------------------------------------------------------------
+
+prop_phash2_same_with_same_input() ->
+    ?FORALL(T, any(), erlang:phash2(T) =:= erlang:phash2(T)).
+
+prop_phash2_same_with_same_long_input() ->
+    ?FORALL(T, any(),
+            begin
+                BigTerm = lists:duplicate(10000, T),
+                erlang:phash2(BigTerm) =:= erlang:phash2(BigTerm)
+            end).
+
+prop_phash2_same_in_different_versions(DifferntVersionNode) ->
+    ?FORALL(T, any(),
+            erlang:phash2(T) =:= rpc:call(DifferntVersionNode,erlang,phash2,[T])).
+
+prop_phash2_same_in_different_versions_with_long_input(DifferntVersionNode) ->
+    ?FORALL(T, any(),
+            begin
+                BigTerm = lists:duplicate(10000, T),
+                RpcRes = rpc:call(DifferntVersionNode,erlang,phash2,[BigTerm]),
+                LocalRes = erlang:phash2(BigTerm),
+                RpcRes =:= LocalRes
+            end).
+
+%%--------------------------------------------------------------------
+%% Generators  -------------------------------------------------------
+%%--------------------------------------------------------------------
+
+-endif.
-- 
2.16.4

openSUSE Build Service is sponsored by