File otp_src_18.0-erts-bif-opt.patch of Package erlang
diff -Ndurp otp_src_18.0/erts/emulator/beam/bif.c otp_src_18.0-erts-bif-opt/erts/emulator/beam/bif.c
--- otp_src_18.0/erts/emulator/beam/bif.c 2015-06-23 11:24:27.000000000 +0300
+++ otp_src_18.0-erts-bif-opt/erts/emulator/beam/bif.c 2015-06-26 00:48:52.861926099 +0300
@@ -2449,9 +2449,7 @@ consolidate(Process* p, Eterm acc, Uint
sz = BIG_NEED_SIZE(BIG_SIZE(big));
hp = HAlloc(p, sz);
res = make_big(hp);
- while (sz--) {
- *hp++ = *big++;
- }
+ etermcpy(hp, big, sz);
erts_free(ERTS_ALC_T_TEMP_TERM, (void *) big_val(acc));
return res;
}
@@ -2574,7 +2572,6 @@ BIF_RETTYPE setelement_3(BIF_ALIST_3)
{
Eterm* ptr;
Eterm* hp;
- Eterm* resp;
Uint ix;
Uint size;
@@ -2592,30 +2589,28 @@ BIF_RETTYPE setelement_3(BIF_ALIST_3)
hp = HAlloc(BIF_P, size);
/* copy the tuple */
- resp = hp;
- sys_memcpy(hp, ptr, sizeof(Eterm)*size);
- resp[ix] = BIF_ARG_3;
- BIF_RET(make_tuple(resp));
+ etermcpy(hp, ptr, size);
+ hp[ix] = BIF_ARG_3;
+ BIF_RET(make_tuple(hp));
}
/**********************************************************************/
BIF_RETTYPE make_tuple_2(BIF_ALIST_2)
{
- Sint n;
- Eterm* hp;
- Eterm res;
+ if (is_small(BIF_ARG_1)) {
+ Sint n = signed_val(BIF_ARG_1);
- if (is_not_small(BIF_ARG_1) || (n = signed_val(BIF_ARG_1)) < 0 || n > ERTS_MAX_TUPLE_SIZE) {
- BIF_ERROR(BIF_P, BADARG);
- }
- hp = HAlloc(BIF_P, n+1);
- res = make_tuple(hp);
- *hp++ = make_arityval(n);
- while (n--) {
- *hp++ = BIF_ARG_2;
+ if (n >= 0 && n <= ERTS_MAX_TUPLE_SIZE) {
+ Eterm* hp = HAlloc(BIF_P, n + 1);
+ Eterm res = make_tuple(hp);
+
+ *hp = make_arityval(n);
+ etermset(hp + 1, BIF_ARG_2, n);
+ BIF_RET(res);
+ }
}
- BIF_RET(res);
+ BIF_ERROR(BIF_P, BADARG);
}
BIF_RETTYPE make_tuple_3(BIF_ALIST_3)
@@ -2624,47 +2619,44 @@ BIF_RETTYPE make_tuple_3(BIF_ALIST_3)
Uint limit;
Eterm* hp;
Eterm res;
- Eterm list = BIF_ARG_3;
- Eterm* tup;
+ Eterm list;
- if (is_not_small(BIF_ARG_1) || (n = signed_val(BIF_ARG_1)) < 0 || n > ERTS_MAX_TUPLE_SIZE) {
+ if (is_not_small(BIF_ARG_1))
error:
BIF_ERROR(BIF_P, BADARG);
- }
+
+ n = signed_val(BIF_ARG_1);
+ if (n < 0 || n > ERTS_MAX_TUPLE_SIZE)
+ goto error;
+
+ list = BIF_ARG_3;
limit = (Uint) n;
hp = HAlloc(BIF_P, n+1);
res = make_tuple(hp);
*hp++ = make_arityval(n);
- tup = hp;
- while (n--) {
- *hp++ = BIF_ARG_2;
- }
- while(is_list(list)) {
- Eterm* cons;
- Eterm hd;
+ etermset(hp, BIF_ARG_2, n);
+ while (is_list(list)) {
Eterm* tp;
Eterm index;
Uint index_val;
+ Eterm* cons = list_val(list);
+ Eterm hd = CAR(cons);
- cons = list_val(list);
- hd = CAR(cons);
- list = CDR(cons);
- if (is_not_tuple_arity(hd, 2)) {
+ if (is_not_tuple_arity(hd, 2))
goto error;
- }
tp = tuple_val(hd);
- if (is_not_small(index = tp[1])) {
+ index = tp[1];
+ if (is_not_small(index))
goto error;
- }
- if ((index_val = unsigned_val(index) - 1) < limit) {
- tup[index_val] = tp[2];
- } else {
+ index_val = unsigned_val(index) - 1;
+ if (index_val < limit)
+ hp[index_val] = tp[2];
+ else
goto error;
- }
+ list = CDR(cons);
}
- if (is_not_nil(list)) {
+ if (is_not_nil(list))
goto error;
- }
BIF_RET(res);
}
@@ -2690,11 +2682,18 @@ BIF_RETTYPE append_element_2(BIF_ALIST_2
hp = HAlloc(BIF_P, arity + 2);
res = make_tuple(hp);
- *hp = make_arityval(arity+1);
- while (arity--) {
- *++hp = *++ptr;
- }
- *++hp = BIF_ARG_2;
+ *hp = make_arityval(arity + 1);
+#ifdef ASM_OPT_X86
+ asm volatile (
+ "rep " MOVS_ETERM "\n\t"
+ "stos %3, %%es:(%1)"
+ : "=&S" (ptr), "=&D" (hp), "=&c" (arity), "=&a" (BIF_ARG_2)
+ : "0" (ptr + 1), "1" (hp + 1), "2" (arity), "3" (BIF_ARG_2)
+ : "memory");
+#else
+ etermcpy(++hp, ptr + 1, arity);
+ *(hp + arity) = BIF_ARG_2;
+#endif
BIF_RET(res);
}
@@ -2704,30 +2703,27 @@ BIF_RETTYPE insert_element_3(BIF_ALIST_3
Eterm* hp;
Uint arity;
Eterm res;
- Sint ix, c1, c2;
+ Sint ix;
- if (is_not_tuple(BIF_ARG_2) || is_not_small(BIF_ARG_1)) {
+ if (is_not_tuple(BIF_ARG_2) || is_not_small(BIF_ARG_1))
+ error:
BIF_ERROR(BIF_P, BADARG);
- }
ptr = tuple_val(BIF_ARG_2);
- arity = arityval(*ptr);
+ arity = arityval(*ptr) + 1;
ix = signed_val(BIF_ARG_1);
- if ((ix < 1) || (ix > (arity + 1))) {
- BIF_ERROR(BIF_P, BADARG);
- }
+ if (ix < 1 || ix > arity)
+ goto error;
- hp = HAlloc(BIF_P, arity + 1 + 1);
+ hp = HAlloc(BIF_P, arity + 1);
res = make_tuple(hp);
- *hp = make_arityval(arity + 1);
-
- c1 = ix - 1;
- c2 = arity - ix + 1;
+ *hp = make_arityval(arity);
- while (c1--) { *++hp = *++ptr; }
- *++hp = BIF_ARG_3;
- while (c2--) { *++hp = *++ptr; }
+ etermcpy(hp + 1, ptr + 1, ix - 1);
+ hp += ix;
+ *hp = BIF_ARG_3;
+ etermcpy(hp + 1, ptr + ix, arity - ix);
BIF_RET(res);
}
@@ -2738,30 +2734,30 @@ BIF_RETTYPE delete_element_2(BIF_ALIST_3
Eterm* hp;
Uint arity;
Eterm res;
- Sint ix, c1, c2;
+ Sint ix;
- if (is_not_tuple(BIF_ARG_2) || is_not_small(BIF_ARG_1)) {
+ if (is_not_tuple(BIF_ARG_2) || is_not_small(BIF_ARG_1))
+ error:
BIF_ERROR(BIF_P, BADARG);
- }
ptr = tuple_val(BIF_ARG_2);
arity = arityval(*ptr);
+
+ if (arity == 0)
+ goto error;
+
ix = signed_val(BIF_ARG_1);
- if ((ix < 1) || (ix > arity) || (arity == 0)) {
- BIF_ERROR(BIF_P, BADARG);
- }
+ if (ix < 1 || ix > arity)
+ goto error;
hp = HAlloc(BIF_P, arity + 1 - 1);
res = make_tuple(hp);
*hp = make_arityval(arity - 1);
- c1 = ix - 1;
- c2 = arity - ix;
-
- while (c1--) { *++hp = *++ptr; }
- ++ptr;
- while (c2--) { *++hp = *++ptr; }
+ ptr++;
+ etermcpy(hp + 1, ptr, ix - 1);
+ etermcpy(hp + ix, ptr + ix, arity - ix);
BIF_RET(res);
}
@@ -4189,18 +4185,21 @@ BIF_RETTYPE list_to_pid_1(BIF_ALIST_1)
cp = buf;
if (*cp++ != '<') goto bad;
- if (*cp < '0' || *cp > '9') goto bad;
- while(*cp >= '0' && *cp <= '9') { a = 10*a + (*cp - '0'); cp++; }
+ if (!isdigit(*cp)) goto bad;
+ for (; isdigit(*cp); cp++)
+ a = 10 * a + (*cp - '0');
if (*cp++ != '.') goto bad;
- if (*cp < '0' || *cp > '9') goto bad;
- while(*cp >= '0' && *cp <= '9') { b = 10*b + (*cp - '0'); cp++; }
+ if (!isdigit(*cp)) goto bad;
+ for (; isdigit(*cp); cp++)
+ b = 10 * b + (*cp - '0');
if (*cp++ != '.') goto bad;
- if (*cp < '0' || *cp > '9') goto bad;
- while(*cp >= '0' && *cp <= '9') { c = 10*c + (*cp - '0'); cp++; }
+ if (!isdigit(*cp)) goto bad;
+ for (; isdigit(*cp); cp++)
+ c = 10 * c + (*cp - '0');
if (*cp++ != '>') goto bad;
if (*cp != '\0') goto bad;
diff -Ndurp otp_src_18.0/erts/emulator/beam/bif.h otp_src_18.0-erts-bif-opt/erts/emulator/beam/bif.h
--- otp_src_18.0/erts/emulator/beam/bif.h 2015-06-23 11:24:27.000000000 +0300
+++ otp_src_18.0-erts-bif-opt/erts/emulator/beam/bif.h 2015-06-26 00:49:22.992924060 +0300
@@ -21,6 +21,8 @@
#ifndef __BIF_H__
#define __BIF_H__
+#include "sys.h"
+
extern Export *erts_await_result;
extern Export* erts_format_cpu_topology_trap;
extern Export *erts_convert_time_unit_trap;
@@ -518,6 +520,44 @@ BIF_RETTYPE hipe_wrapper_ ## BIF_NAME ##
#endif /* ERL_WANT_HIPE_BIF_WRAPPER__ */
+#ifdef ASM_OPTIMIZE
+#if defined(__i386__) || defined(__x86_64__)
+#define ASM_OPT_X86
+#if ERTS_SIZEOF_ETERM == 8
+#define MOVS_ETERM "movsq"
+#else
+#define MOVS_ETERM "movsl"
+#endif
+#endif
+#endif
+
+static inline void etermcpy(Eterm *dst, const Eterm *src, size_t size)
+{
+#ifdef ASM_OPT_X86
+ void *d;
+ asm volatile ("rep " MOVS_ETERM
+ : "=&S" (d), "=&D" (d), "=&c" (d)
+ : "0" (src), "1" (dst), "2" (size)
+ : "memory");
+#else
+ sys_memcpy(dst, src, size * sizeof(Eterm));
+#endif
+}
+
+static inline void etermset(Eterm *dst, const Eterm e, size_t size)
+{
+#ifdef ASM_OPT_X86
+ void *d;
+ asm volatile ("rep stos %2, %%es:(%0)"
+ : "=&D" (d), "=&c" (d), "=&a" (d)
+ : "0" (dst), "1" (size), "2" (e)
+ : "memory");
+#else
+ for (; size; size--, dst++)
+ *dst = e;
+#endif
+}
+
#include "erl_bif_table.h"
#endif
diff -Ndurp otp_src_18.0/erts/emulator/beam/erl_nif.c otp_src_18.0-erts-bif-opt/erts/emulator/beam/erl_nif.c
--- otp_src_18.0/erts/emulator/beam/erl_nif.c 2015-06-23 11:24:27.000000000 +0300
+++ otp_src_18.0-erts-bif-opt/erts/emulator/beam/erl_nif.c 2015-06-26 00:48:52.863926099 +0300
@@ -1035,9 +1035,7 @@ ERL_NIF_TERM enif_make_tuple_from_array(
const Eterm* src = arr;
*hp++ = make_arityval(cnt);
- while (cnt--) {
- *hp++ = *src++;
- }
+ etermcpy(hp, src, cnt);
return ret;
}
@@ -1063,11 +1061,10 @@ ERL_NIF_TERM enif_make_list(ErlNifEnv* e
va_list ap;
va_start(ap,cnt);
- while (cnt--) {
+ for (; cnt; hp++, cnt--) {
*last = make_list(hp);
*hp = va_arg(ap,Eterm);
last = ++hp;
- ++hp;
}
va_end(ap);
*last = NIL;
@@ -1079,14 +1076,13 @@ ERL_NIF_TERM enif_make_list_from_array(E
{
Eterm* hp = alloc_heap(env,cnt*2);
Eterm ret = make_list(hp);
- Eterm* last = &ret;
const Eterm* src = arr;
+ Eterm* last;
- while (cnt--) {
+ for (last = &ret; cnt; hp++, cnt--) {
*last = make_list(hp);
*hp = *src++;
last = ++hp;
- ++hp;
}
*last = NIL;
return ret;
@@ -2276,17 +2272,15 @@ static void add_taint(Eterm mod_atom)
Eterm erts_nif_taints(Process* p)
{
struct tainted_module_t* t;
- unsigned cnt = 0;
- Eterm list = NIL;
+ unsigned cnt;
+ Eterm list;
Eterm* hp;
- for (t=first_tainted_module ; t!=NULL; t=t->next) {
- cnt++;
- }
- hp = HAlloc(p,cnt*2);
- for (t=first_tainted_module ; t!=NULL; t=t->next) {
+
+ for (cnt = 0, t = first_tainted_module; t != NULL; cnt++, t = t->next);
+ for (list = NIL, hp = HAlloc(p, cnt * 2), t = first_tainted_module;
+ t != NULL;
+ hp += 2, t = t->next)
list = CONS(hp, t->module_atom, list);
- hp += 2;
- }
return list;
}