File 2721-Output-heap-binaries-from-ports-when-data-is-small.patch of Package erlang

From aab2b66cf88933ad184146893060ba15f599822a Mon Sep 17 00:00:00 2001
From: Rickard Green <rickard@erlang.org>
Date: Fri, 23 Aug 2019 11:30:52 +0200
Subject: [PATCH] Output heap binaries from ports when data is small

---
 erts/emulator/beam/io.c | 100 ++++++++++++++++++++++++++++++++----------------
 1 file changed, 68 insertions(+), 32 deletions(-)

diff --git a/erts/emulator/beam/io.c b/erts/emulator/beam/io.c
index 5325480901..2b111d19b5 100644
--- a/erts/emulator/beam/io.c
+++ b/erts/emulator/beam/io.c
@@ -3243,7 +3243,10 @@ static void deliver_read_message(Port* prt, erts_aint32_t state, Eterm to,
 	need += 3;
     }
     if ((state & ERTS_PORT_SFLG_BINARY_IO) && buf != NULL) {
-	need += PROC_BIN_SIZE;
+        if (len <= ERL_ONHEAP_BIN_LIMIT)
+            need += heap_bin_size(len);
+        else
+            need += PROC_BIN_SIZE;
     } else {
 	need += 2*len;
     }
@@ -3261,11 +3264,21 @@ static void deliver_read_message(Port* prt, erts_aint32_t state, Eterm to,
     if ((state & ERTS_PORT_SFLG_BINARY_IO) == 0) {
 	listp = buf_to_intlist(&hp, buf, len, listp);
     } else if (buf != NULL) {
-	Binary* bptr = erts_bin_nrml_alloc(len);
-	sys_memcpy(bptr->orig_bytes, buf, len);
+        if (len <= ERL_ONHEAP_BIN_LIMIT) {
+            ErlHeapBin *hbin = (ErlHeapBin *) hp;
+            hbin->thing_word = header_heap_bin(len);
+            hbin->size = (Uint) len;
+            sys_memcpy(hbin->data, buf, len);
+            listp = make_binary(hp);
+            hp += heap_bin_size(len);
+        }
+        else {
+            Binary* bptr = erts_bin_nrml_alloc(len);
+            sys_memcpy(bptr->orig_bytes, buf, len);
 
-        listp = erts_build_proc_bin(ohp, hp, bptr);
-	hp += PROC_BIN_SIZE;
+            listp = erts_build_proc_bin(ohp, hp, bptr);
+            hp += PROC_BIN_SIZE;
+        }
     }
 
     /* Prepend the header */
@@ -3388,7 +3401,14 @@ deliver_vec_message(Port* prt,			/* Port */
 
     need = 3 + 3;		/* Heap space for two tuples */
     if (state & ERTS_PORT_SFLG_BINARY_IO) {
-	need += (2+PROC_BIN_SIZE)*vsize - 2 + hlen*2;
+        Sint i;
+        for (i = 0; i < vsize; i++) {
+            if (iov[i].iov_len <= ERL_ONHEAP_BIN_LIMIT)
+                need += heap_bin_size(iov[i].iov_len);
+            else
+                need += PROC_BIN_SIZE;
+        }
+	need += (vsize - 1)*2 + hlen*2;
     } else {
 	need += (hlen+csize)*2;
     }
@@ -3408,36 +3428,52 @@ deliver_vec_message(Port* prt,			/* Port */
     } else {
 	binv += vsize;
 	while (vsize--) {
-	    ErlDrvBinary* b;
-	    ProcBin* pb = (ProcBin*) hp;
-	    byte* base;
-
-	    iov--;
-	    binv--;
-	    if ((b = *binv) == NULL) {
-		b = driver_alloc_binary(iov->iov_len);
-		sys_memcpy(b->orig_bytes, iov->iov_base, iov->iov_len);
-		base = (byte*) b->orig_bytes;
-	    } else {
-		/* Must increment reference count, caller calls free */
-		driver_binary_inc_refc(b);
-		base = iov->iov_base;
-	    }
-	    pb->thing_word = HEADER_PROC_BIN;
-	    pb->size = iov->iov_len;
-	    pb->next = ohp->first;
-	    ohp->first = (struct erl_off_heap_header*)pb;
-	    pb->val = ErlDrvBinary2Binary(b);
-	    pb->bytes = base;
-	    pb->flags = 0;
-	    hp += PROC_BIN_SIZE;
+            Eterm bin;
+            Uint bin_size;
+            iov--;
+            binv--;
+            bin_size = (Uint) iov->iov_len;
+            
+            if (bin_size <= ERL_ONHEAP_BIN_LIMIT) {
+                ErlHeapBin *hbin = (ErlHeapBin *) hp;
+                hbin->thing_word = header_heap_bin(bin_size);
+                hbin->size = bin_size;
+                sys_memcpy(hbin->data, iov->iov_base, bin_size);
+                bin = make_binary(hp);
+                hp += heap_bin_size(bin_size);
+            }
+            else {
+                ErlDrvBinary* b;
+                ProcBin* pb = (ProcBin*) hp;
+                byte* base;
+
+                if ((b = *binv) == NULL) {
+                    b = driver_alloc_binary(bin_size);
+                    sys_memcpy(b->orig_bytes, iov->iov_base, bin_size);
+                    base = (byte*) b->orig_bytes;
+                } else {
+                    /* Must increment reference count, caller calls free */
+                    driver_binary_inc_refc(b);
+                    base = iov->iov_base;
+                }
+                pb->thing_word = HEADER_PROC_BIN;
+                pb->size = bin_size;
+                pb->next = ohp->first;
+                ohp->first = (struct erl_off_heap_header*)pb;
+                pb->val = ErlDrvBinary2Binary(b);
+                pb->bytes = base;
+                pb->flags = 0;
+                hp += PROC_BIN_SIZE;
 	    
-	    OH_OVERHEAD(ohp, iov->iov_len / sizeof(Eterm));
+                OH_OVERHEAD(ohp, bin_size / sizeof(Eterm));
+
+                bin = make_binary(pb);
+            }
 
 	    if (listp == NIL) {  /* compatible with deliver_bin_message */
-		listp = make_binary(pb);
+		listp = bin;
 	    } else {
-		listp = CONS(hp, make_binary(pb), listp);
+		listp = CONS(hp, bin, listp);
 		hp += 2;
 	    }
 	}
-- 
2.16.4

openSUSE Build Service is sponsored by