File 2053-erts-Beautify-away-ifdef-DEBUG.patch of Package erlang

From 50459bca9fd60733f9b354b2a2a4672fd8dc77e9 Mon Sep 17 00:00:00 2001
From: Sverker Eriksson <sverker@erlang.org>
Date: Fri, 7 Sep 2018 19:35:15 +0200
Subject: [PATCH] erts: Beautify away #ifdef DEBUG

"(void)result" will silence warning about unused variable
and compiler will optimize away such unused variables.
---
 erts/emulator/beam/bif.c          | 29 ++++--------------
 erts/emulator/beam/dist.c         | 22 +++-----------
 erts/emulator/beam/erl_bif_info.c |  2 --
 erts/emulator/beam/erl_bif_re.c   | 64 ++++++++-------------------------------
 erts/emulator/beam/erl_db_util.c  |  9 ++----
 erts/emulator/beam/erl_process.c  | 32 +++-----------------
 erts/emulator/beam/erl_unicode.c  |  4 +--
 7 files changed, 31 insertions(+), 131 deletions(-)

diff --git a/erts/emulator/beam/bif.c b/erts/emulator/beam/bif.c
index 56ac072449..9ec863f259 100644
--- a/erts/emulator/beam/bif.c
+++ b/erts/emulator/beam/bif.c
@@ -218,11 +218,8 @@ BIF_RETTYPE link_1(BIF_ALIST_1)
              * We have (pending) connection.
              * Setup link and enqueue link signal.
              */
-#ifdef DEBUG
-            int inserted =
-#endif
-                erts_link_dist_insert(&ldp->b, dep->mld);
-            ASSERT(inserted);
+            int inserted = erts_link_dist_insert(&ldp->b, dep->mld);
+            ASSERT(inserted); (void)inserted;
             erts_de_runlock(dep);
 
             code = erts_dsig_send_link(&dsd, BIF_P->common.id, BIF_ARG_1);
@@ -567,12 +564,8 @@ BIF_RETTYPE monitor_2(BIF_ALIST_2)
 
             case ERTS_DSIG_PREP_PENDING:
             case ERTS_DSIG_PREP_CONNECTED: {
-#ifdef DEBUG
-                int inserted =
-#endif
-
-                erts_monitor_dist_insert(&mdp->target, dep->mld);
-                ASSERT(inserted);
+                int inserted = erts_monitor_dist_insert(&mdp->target, dep->mld);
+                ASSERT(inserted); (void)inserted;
                 erts_de_runlock(dep);
 
                 code = erts_dsig_send_monitor(&dsd, BIF_P->common.id, target, ref);
@@ -2745,9 +2738,7 @@ BIF_RETTYPE atom_to_list_1(BIF_ALIST_1)
     Uint num_chars, num_built, num_eaten;
     byte* err_pos;
     Eterm res;
-#ifdef DEBUG
     int ares;
-#endif
 
     if (is_not_atom(BIF_ARG_1))
 	BIF_ERROR(BIF_P, BADARG);
@@ -2757,11 +2748,9 @@ BIF_RETTYPE atom_to_list_1(BIF_ALIST_1)
     if (ap->len == 0)
 	BIF_RET(NIL);	/* the empty atom */
 
-#ifdef DEBUG
     ares =
-#endif
 	erts_analyze_utf8(ap->name, ap->len, &err_pos, &num_chars, NULL);
-    ASSERT(ares == ERTS_UTF8_OK);
+    ASSERT(ares == ERTS_UTF8_OK); (void)ares;
     
     res = erts_utf8_to_list(BIF_P, num_chars, ap->name, ap->len, ap->len,
 			    &num_built, &num_eaten, NIL);
diff --git a/erts/emulator/beam/dist.c b/erts/emulator/beam/dist.c
index db594a23a0..9232781687 100644
--- a/erts/emulator/beam/dist.c
+++ b/erts/emulator/beam/dist.c
@@ -570,9 +570,7 @@ int erts_do_net_exits(DistEntry *dep, Eterm reason)
         }
 
 	if (dep->state == ERTS_DE_STATE_EXITING) {
-#ifdef DEBUG
 	    ASSERT(erts_atomic32_read_nob(&dep->qflgs) & ERTS_DE_QFLG_EXIT);
-#endif
 	}
 	else {
 	    dep->state = ERTS_DE_STATE_EXITING;
@@ -3943,28 +3935,22 @@ monitor_node(Process* p, Eterm Node, Eterm Bool, Eterm Options)
                                                   Node);
             mdep = (ErtsMonitorDataExtended *) erts_monitor_to_data(mon);
             if (created) {
-#ifdef DEBUG
                 int inserted =
-#endif
                     erts_monitor_dist_insert(&mdep->md.target, dep->mld);
-                ASSERT(inserted);
+                ASSERT(inserted); (void)inserted;
                 ASSERT(mdep->dist->connection_id == dep->connection_id);
             }
             else if (mdep->dist->connection_id != dep->connection_id) {
                 ErtsMonitorDataExtended *mdep2;
                 ErtsMonitor *mon2;
-#ifdef DEBUG
                 int inserted;
-#endif
                 mdep2 = ((ErtsMonitorDataExtended *)
                          erts_monitor_create(ERTS_MON_TYPE_NODE, NIL,
                                              p->common.id, Node, NIL));
                 mon2 = &mdep2->md.origin;
-#ifdef DEBUG
                 inserted =
-#endif
                     erts_monitor_dist_insert(&mdep->md.target, dep->mld);
-                ASSERT(inserted);
+                ASSERT(inserted); (void)inserted;
                 ASSERT(mdep2->dist->connection_id == dep->connection_id);
 
                 mdep2->uptr.node_monitors = mdep->uptr.node_monitors;
diff --git a/erts/emulator/beam/erl_bif_info.c b/erts/emulator/beam/erl_bif_info.c
index 7fada0d548..2a8e7e8858 100644
--- a/erts/emulator/beam/erl_bif_info.c
+++ b/erts/emulator/beam/erl_bif_info.c
@@ -2705,9 +2705,7 @@ BIF_RETTYPE system_info_1(BIF_ALIST_1)
 	    goto bld_instruction_counts;
 	}
 
-#ifdef DEBUG
 	ASSERT(endp == hp);
-#endif
 
 	BIF_RET(res);
 #endif /* #ifndef ERTS_OPCODE_COUNTER_SUPPORT */
diff --git a/erts/emulator/beam/erl_bif_re.c b/erts/emulator/beam/erl_bif_re.c
index bbc64eb9aa..e0b9202fe7 100644
--- a/erts/emulator/beam/erl_bif_re.c
+++ b/erts/emulator/beam/erl_bif_re.c
@@ -532,10 +532,7 @@ re_compile(Process* p, Eterm arg1, Eterm arg2)
     int options = 0;
     int pflags = 0;
     int unicode = 0;
-#ifdef DEBUG
     int buffres;
-#endif
-
 
     if (parse_options(arg2,&options,NULL,&pflags,NULL,NULL,NULL,NULL)
 	< 0) {
@@ -556,12 +553,8 @@ re_compile(Process* p, Eterm arg1, Eterm arg2)
         BIF_ERROR(p,BADARG);
     }
     expr = erts_alloc(ERTS_ALC_T_RE_TMP_BUF, slen + 1);
-#ifdef DEBUG
-    buffres =
-#endif
-    erts_iolist_to_buf(arg1, expr, slen);
-
-    ASSERT(buffres >= 0);
+    buffres = erts_iolist_to_buf(arg1, expr, slen);
+    ASSERT(buffres >= 0); (void)buffres;
 
     expr[slen]='\0';
     result = erts_pcre_compile2(expr, options, &errcode, 
@@ -1052,9 +1045,7 @@ build_capture(Eterm capture_spec[CAPSPEC_SIZE], const pcre *code)
 			tmpb[ap->len] = '\0';
 		    } else {
 			ErlDrvSizeT slen;
-#ifdef DEBUG
 			int buffres;
-#endif
 
 			if (erts_iolist_size(val, &slen)) {
 			    goto error;
@@ -1068,11 +1059,8 @@ build_capture(Eterm capture_spec[CAPSPEC_SIZE], const pcre *code)
 			    }
 			}
 
-#ifdef DEBUG
-			buffres =
-#endif
-			erts_iolist_to_buf(val, tmpb, slen);
-			ASSERT(buffres >= 0);
+			buffres = erts_iolist_to_buf(val, tmpb, slen);
+			ASSERT(buffres >= 0); (void)buffres;
 			tmpb[slen] = '\0';
 		    }
 		    build_one_capture(code,&ri,&sallocated,has_dupnames,tmpb);
@@ -1145,9 +1133,7 @@ re_run(Process *p, Eterm arg1, Eterm arg2, Eterm arg3)
 	    const char *errstr = "";
 	    int errofset = 0;
 	    int capture_count;
-#ifdef DEBUG
 	    int buffres;
-#endif
 
 	    if (pflags & PARSE_FLAG_UNICODE && 
 		(!is_binary(arg2) || !is_binary(arg1) ||
@@ -1161,12 +1147,8 @@ re_run(Process *p, Eterm arg1, Eterm arg2, Eterm arg3)
 	    
 	    expr = erts_alloc(ERTS_ALC_T_RE_TMP_BUF, slen + 1);
 	    
-#ifdef DEBUG
-	    buffres =
-#endif
-	    erts_iolist_to_buf(arg2, expr, slen);
-
-	    ASSERT(buffres >= 0);
+	    buffres = erts_iolist_to_buf(arg2, expr, slen);
+	    ASSERT(buffres >= 0); (void)buffres;
 
 	    expr[slen]='\0';
 	    result = erts_pcre_compile2(expr, comp_options, &errcode, 
@@ -1317,9 +1299,7 @@ re_run(Process *p, Eterm arg1, Eterm arg2, Eterm arg3)
 	restart.subject = (char *) (pb->bytes+offset);
 	restart.flags |= RESTART_FLAG_SUBJECT_IN_BINARY;
     } else {
-#ifdef DEBUG
 	int buffres;
-#endif
 handle_iolist:
 	if (erts_iolist_size(arg1, &slength)) {
 	    erts_free(ERTS_ALC_T_RE_SUBJECT, restart.ovector);
@@ -1331,11 +1311,8 @@ handle_iolist:
 	}
 	restart.subject = erts_alloc(ERTS_ALC_T_RE_SUBJECT, slength);
 
-#ifdef DEBUG
-	buffres =
-#endif
-	erts_iolist_to_buf(arg1, restart.subject, slength);
-	ASSERT(buffres >= 0);
+	buffres = erts_iolist_to_buf(arg1, restart.subject, slength);
+	ASSERT(buffres >= 0); (void)buffres;
     }
 
     if (pflags & PARSE_FLAG_REPORT_ERRORS) {
@@ -1457,10 +1434,7 @@ re_inspect_2(BIF_ALIST_2)
     Eterm res;
     const pcre *code;
     byte *temp_alloc = NULL;
-#ifdef DEBUG
-    int infores;
-#endif
-    
+    int infores;    
 
     if (is_not_tuple(BIF_ARG_1) || (arityval(*tuple_val(BIF_ARG_1)) != 5)) {
 	goto error;
@@ -1484,12 +1458,8 @@ re_inspect_2(BIF_ALIST_2)
     if (erts_pcre_fullinfo(code, NULL, PCRE_INFO_OPTIONS, &options) != 0)
 	goto error;
 
-#ifdef DEBUG
-    infores =
-#endif
-    erts_pcre_fullinfo(code, NULL, PCRE_INFO_NAMECOUNT, &top);
-
-    ASSERT(infores == 0);
+    infores = erts_pcre_fullinfo(code, NULL, PCRE_INFO_NAMECOUNT, &top);
+    ASSERT(infores == 0); (void)infores;
 
     if (top <= 0) {
 	hp = HAlloc(BIF_P, 3);
@@ -1497,18 +1467,10 @@ re_inspect_2(BIF_ALIST_2)
 	erts_free_aligned_binary_bytes(temp_alloc);
 	BIF_RET(res);
     }
-#ifdef DEBUG
-    infores =
-#endif
-    erts_pcre_fullinfo(code, NULL, PCRE_INFO_NAMEENTRYSIZE, &entrysize);
-
+    infores = erts_pcre_fullinfo(code, NULL, PCRE_INFO_NAMEENTRYSIZE, &entrysize);
     ASSERT(infores == 0);
 
-#ifdef DEBUG
-    infores =
-#endif
-    erts_pcre_fullinfo(code, NULL, PCRE_INFO_NAMETABLE, &nametable);
-
+    infores = erts_pcre_fullinfo(code, NULL, PCRE_INFO_NAMETABLE, &nametable);
     ASSERT(infores == 0);
     
     has_dupnames = ((options & PCRE_DUPNAMES) != 0);
diff --git a/erts/emulator/beam/erl_db_util.c b/erts/emulator/beam/erl_db_util.c
index f1d47326b4..a78623f490 100644
--- a/erts/emulator/beam/erl_db_util.c
+++ b/erts/emulator/beam/erl_db_util.c
@@ -3118,9 +3118,7 @@ void* db_store_term_comp(DbTableCommon *tb, DbTerm* old, Uint offset, Eterm obj)
     Uint new_sz = offset + db_size_dbterm_comp(tb, obj);
     byte* basep;
     DbTerm* newp;
-#ifdef DEBUG
     byte* top;
-#endif
 
     ASSERT(tb->compress);
     if (old != 0) {
@@ -3142,11 +3140,8 @@ void* db_store_term_comp(DbTableCommon *tb, DbTerm* old, Uint offset, Eterm obj)
     }
 
     newp->size = size_object(obj);
-#ifdef DEBUG
-    top = 
-#endif
-	copy_to_comp(tb, obj, newp, new_sz);
-    ASSERT(top <= basep + new_sz);
+    top = copy_to_comp(tb, obj, newp, new_sz);
+    ASSERT(top <= basep + new_sz); (void)top;
 
     /* ToDo: Maybe realloc if ((basep+new_sz) - top) > WASTED_SPACE_LIMIT */
 
diff --git a/erts/emulator/beam/erl_process.c b/erts/emulator/beam/erl_process.c
index 9f3dfd6c37..3aa04d825e 100644
--- a/erts/emulator/beam/erl_process.c
+++ b/erts/emulator/beam/erl_process.c
@@ -4022,9 +4022,7 @@ schedule_bound_processes(ErtsRunQueue *rq,
 static ERTS_INLINE void
 clear_proc_dirty_queue_bit(Process *p, ErtsRunQueue *rq, int prio_bit)
 {
-#ifdef DEBUG
     erts_aint32_t old;
-#endif
     erts_aint32_t qb = prio_bit;
     if (rq == ERTS_DIRTY_CPU_RUNQ)
 	qb <<= ERTS_PDSFLGS_IN_CPU_PRQ_MASK_OFFSET;
@@ -4032,13 +4030,8 @@ clear_proc_dirty_queue_bit(Process *p, ErtsRunQueue *rq, int prio_bit)
 	ASSERT(rq == ERTS_DIRTY_IO_RUNQ);
 	qb <<= ERTS_PDSFLGS_IN_IO_PRQ_MASK_OFFSET;
     }
-#ifdef DEBUG
-    old = (int)
-#else
-	(void)
-#endif
-	erts_atomic32_read_band_mb(&p->dirty_state, ~qb);
-    ASSERT(old & qb);
+    old = (int) erts_atomic32_read_band_mb(&p->dirty_state, ~qb);
+    ASSERT(old & qb); (void)old;
 }
 
 
@@ -7175,9 +7168,7 @@ msb_scheduler_type_switch(ErtsSchedType sched_type,
     Uint32 nrml_prio, dcpu_prio, dio_prio;
     ErtsSchedType exec_type;
     ErtsRunQueue *exec_rq;
-#ifdef DEBUG
     erts_aint32_t dbg_val;
-#endif
 
     ASSERT(schdlr_sspnd.msb.ongoing);
 
@@ -7292,16 +7283,12 @@ msb_scheduler_type_switch(ErtsSchedType sched_type,
      * Suspend this scheduler and wake up scheduler
      * number one of another type...
      */
-#ifdef DEBUG
     dbg_val =
-#else
-    (void)
-#endif
         erts_atomic32_read_bset_mb(&esdp->ssi->flags,
                                        (ERTS_SSI_FLG_SUSPENDED
                                         | ERTS_SSI_FLG_MSB_EXEC),
                                        ERTS_SSI_FLG_SUSPENDED);
-    ASSERT(dbg_val & ERTS_SSI_FLG_MSB_EXEC);
+    ASSERT(dbg_val & ERTS_SSI_FLG_MSB_EXEC); (void)dbg_val;
 
     switch (exec_type) {
     case ERTS_SCHED_NORMAL:
@@ -7319,11 +7306,7 @@ msb_scheduler_type_switch(ErtsSchedType sched_type,
         break;
     }
 
-#ifdef DEBUG
     dbg_val =
-#else
-    (void)
-#endif
         erts_atomic32_read_bset_mb(&exec_rq->scheduler->ssi->flags,
                                        (ERTS_SSI_FLG_SUSPENDED
                                         | ERTS_SSI_FLG_MSB_EXEC),
@@ -8888,11 +8871,8 @@ erts_suspend(Process* c_p, ErtsProcLocks c_p_locks, Port *busy_port)
 	suspend = 1;
 
     if (suspend) {
-#ifdef DEBUG
-	int res =
-#endif
-	    suspend_process(c_p, c_p);
-	ASSERT(res);
+	int res = suspend_process(c_p, c_p);
+	ASSERT(res); (void)res;
     }
 
     if (!(c_p_locks & ERTS_PROC_LOCK_STATUS))
@@ -12490,9 +12470,7 @@ erts_continue_exit_process(Process *p)
 
  yield:
 
-#ifdef DEBUG
     ASSERT(yield_allowed);
-#endif
 
     ERTS_LC_ASSERT(curr_locks == erts_proc_lc_my_proc_locks(p));
     ERTS_LC_ASSERT(ERTS_PROC_LOCK_MAIN & curr_locks);
diff --git a/erts/emulator/beam/erl_unicode.c b/erts/emulator/beam/erl_unicode.c
index d225916ac5..1d6869a7cd 100644
--- a/erts/emulator/beam/erl_unicode.c
+++ b/erts/emulator/beam/erl_unicode.c
@@ -1358,11 +1358,9 @@ Uint erts_atom_to_string_length(Eterm atom)
     else {
         byte* err_pos;
         Uint num_chars;
-#ifdef DEBUG
         int ares =
-#endif
             erts_analyze_utf8(ap->name, ap->len, &err_pos, &num_chars, NULL);
-        ASSERT(ares == ERTS_UTF8_OK);
+        ASSERT(ares == ERTS_UTF8_OK); (void)ares;
 
         return num_chars;
     }
-- 
2.16.4

openSUSE Build Service is sponsored by