File 5822-erts-Start-using-bool-in-ETS-code-base.patch of Package erlang

From 5e1b9c190c34225bccca204cd900e14969fd9e0f Mon Sep 17 00:00:00 2001
From: Sverker Eriksson <sverker@erlang.org>
Date: Mon, 10 Jun 2024 14:22:16 +0200
Subject: [PATCH 2/3] erts: Start using 'bool' in ETS code base

---
 erts/emulator/beam/break.c            |   4 +-
 erts/emulator/beam/erl_db.c           | 124 ++++-----
 erts/emulator/beam/erl_db.h           |   8 +-
 erts/emulator/beam/erl_db_catree.c    |  88 +++---
 erts/emulator/beam/erl_db_catree.h    |  10 +-
 erts/emulator/beam/erl_db_hash.c      | 123 ++++----
 erts/emulator/beam/erl_db_hash.h      |  11 +-
 erts/emulator/beam/erl_db_tree.c      |  58 ++--
 erts/emulator/beam/erl_db_tree_util.h |  10 +-
 erts/emulator/beam/erl_db_util.c      | 385 +++++++++++++-------------
 erts/emulator/beam/erl_db_util.h      |  31 ++-
 erts/emulator/beam/erl_flxctr.c       |   9 +-
 erts/emulator/beam/erl_flxctr.h       |  15 +-
 erts/emulator/beam/erl_init.c         |   8 +-
 erts/emulator/beam/erl_node_tables.c  |   2 +-
 15 files changed, 450 insertions(+), 436 deletions(-)

diff --git a/erts/emulator/beam/break.c b/erts/emulator/beam/break.c
index 3e72576bda..c2154a1bca 100644
--- a/erts/emulator/beam/break.c
+++ b/erts/emulator/beam/break.c
@@ -639,7 +639,7 @@ do_break(void)
 	    distribution_info(ERTS_PRINT_STDOUT, NULL);
 	    return;
 	case 'D':
-	    db_info(ERTS_PRINT_STDOUT, NULL, 1);
+	    db_info(ERTS_PRINT_STDOUT, NULL, true);
 	    return; 
 	case 'k':
 	    process_killer();
@@ -1033,7 +1033,7 @@ erl_crash_dump_v(char *file, int line, const char* fmt, va_list args)
     info(to, to_arg); /* General system info */
     if (erts_ptab_initialized(&erts_proc))
 	process_info(to, to_arg); /* Info about each process and port */
-    db_info(to, to_arg, 0);
+    db_info(to, to_arg, false);
     erts_print_bif_timer_info(to, to_arg);
     distribution_info(to, to_arg);
     erts_cbprintf(to, to_arg, "=loaded_modules\n");
diff --git a/erts/emulator/beam/erl_db.c b/erts/emulator/beam/erl_db.c
index 9f15b855bf..654edec0c1 100644
--- a/erts/emulator/beam/erl_db.c
+++ b/erts/emulator/beam/erl_db.c
@@ -126,7 +126,7 @@ static BIF_RETTYPE db_bif_fail(Process* p, Uint freason,
  * "fixed_tabs": list of all fixed tables for a process
  */
 #ifdef DEBUG
-static int fixed_tabs_find(DbFixation* first, DbFixation* fix);
+static bool fixed_tabs_find(DbFixation* first, DbFixation* fix);
 #endif
 
 static void fixed_tabs_insert(Process* p, DbFixation* fix)
@@ -167,7 +167,7 @@ static void fixed_tabs_delete(Process *p, DbFixation* fix)
 }
 
 #ifdef DEBUG
-static int fixed_tabs_find(DbFixation* first, DbFixation* fix)
+static bool fixed_tabs_find(DbFixation* first, DbFixation* fix)
 {
     DbFixation* p;
 
@@ -193,7 +193,7 @@ static int fixed_tabs_find(DbFixation* first, DbFixation* fix)
 #define ERTS_RBT_PREFIX fixing_procs
 #define ERTS_RBT_T DbFixation
 #define ERTS_RBT_KEY_T Process*
-#define ERTS_RBT_FLAGS_T int
+#define ERTS_RBT_FLAGS_T bool
 #define ERTS_RBT_INIT_EMPTY_TNODE(T)                    \
     do {						\
 	(T)->procs.parent = NULL;			\
@@ -201,9 +201,9 @@ static int fixed_tabs_find(DbFixation* first, DbFixation* fix)
 	(T)->procs.left = NULL;				\
     } while (0)
 #define ERTS_RBT_IS_RED(T)        ((T)->procs.is_red)
-#define ERTS_RBT_SET_RED(T)       ((T)->procs.is_red = 1)
+#define ERTS_RBT_SET_RED(T)       ((T)->procs.is_red = true)
 #define ERTS_RBT_IS_BLACK(T)      (!(T)->procs.is_red)
-#define ERTS_RBT_SET_BLACK(T)     ((T)->procs.is_red = 0)
+#define ERTS_RBT_SET_BLACK(T)     ((T)->procs.is_red = false)
 #define ERTS_RBT_GET_FLAGS(T)     ((T)->procs.is_red)
 #define ERTS_RBT_SET_FLAGS(T, F)  ((T)->procs.is_red = (F))
 #define ERTS_RBT_GET_PARENT(T)    ((T)->procs.parent)
@@ -304,7 +304,7 @@ tid2tab(Eterm tid, Eterm *error_info_p)
     return tb;
 }
 
-static ERTS_INLINE int
+static ERTS_INLINE bool
 is_table_alive(DbTable *tb)
 {
     erts_atomic_t *tbref;
@@ -318,7 +318,7 @@ is_table_alive(DbTable *tb)
     return !!rtb;
 }
 
-static ERTS_INLINE int
+static ERTS_INLINE bool
 is_table_named(DbTable *tb)
 {
     return tb->common.type & DB_NAMED_TABLE;
@@ -413,8 +413,8 @@ extern DbTableMethod db_tree;
 extern DbTableMethod db_catree;
 
 int user_requested_db_max_tabs;
-int erts_ets_realloc_always_moves;
-int erts_ets_always_compress;
+bool erts_ets_realloc_always_moves;
+bool erts_ets_always_compress;
 static int db_max_tabs;
 
 /* 
@@ -429,7 +429,7 @@ static SWord free_fixations_locked(Process* p, DbTable *tb);
 
 static void delete_all_objects_continue(Process* p, DbTable* tb);
 static SWord free_table_continue(Process *p, DbTable *tb, SWord reds);
-static void print_table(fmtfn_t to, void *to_arg, int show,  DbTable* tb);
+static void print_table(fmtfn_t to, void *to_arg, bool show,  DbTable* tb);
 static BIF_RETTYPE ets_select_delete_trap_1(BIF_ALIST_1);
 static BIF_RETTYPE ets_select_count_1(BIF_ALIST_1);
 static BIF_RETTYPE ets_select_replace_1(BIF_ALIST_1);
@@ -674,7 +674,7 @@ static ERTS_INLINE void db_lock(DbTable* tb, db_lock_kind_t kind)
     if (tb->common.type & DB_FINE_LOCKED) {
         if (kind == LCK_WRITE) {
             erts_rwmtx_rwlock(&tb->common.rwlock);
-            tb->common.is_thread_safe = 1;
+            tb->common.is_thread_safe = true;
         }
         else {
             erts_rwmtx_rlock(&tb->common.rwlock);
@@ -702,7 +702,7 @@ static ERTS_INLINE void db_unlock(DbTable* tb, db_lock_kind_t kind)
     if (tb->common.type & DB_FINE_LOCKED) {
         if (kind == LCK_WRITE) {
             ASSERT(tb->common.is_thread_safe);
-            tb->common.is_thread_safe = 0;
+            tb->common.is_thread_safe = false;
             erts_rwmtx_rwunlock(&tb->common.rwlock);
         }
         else {
@@ -1782,7 +1782,7 @@ static int ets_insert_2_list_from_p_heap(DbTable* tb, Eterm list)
 
 /* This function is called both as is, and as YCF transformed. */
 static void ets_insert_2_list_destroy_copied_dbterms(DbTableMethod* meth,
-                                                     int compressed,
+                                                     bool compressed,
                                                      void* db_term_list)
 {
     void* lst = db_term_list;
@@ -1795,7 +1795,7 @@ static void ets_insert_2_list_destroy_copied_dbterms(DbTableMethod* meth,
 
 #ifdef YCF_FUNCTIONS
 static void* ets_insert_2_list_copy_term_list(DbTableMethod* meth,
-                                              int compress,
+                                              bool compress,
                                               int keypos,
                                               Eterm list)
 {
@@ -1946,7 +1946,7 @@ static BIF_RETTYPE ets_insert_2_list(Process* p,
     void* db_term_list = NULL;
     void* destroy_list = NULL;
     DbTableMethod* meth = tb->common.meth;
-    int compressed = tb->common.compress;
+    bool compressed = tb->common.compress;
     int keypos = tb->common.keypos;
     Uint32 tb_type = tb->common.type;
     Uint bif_ix = (is_insert_new ? BIF_ets_insert_new_2 : BIF_ets_insert_2);
@@ -2482,13 +2482,13 @@ BIF_RETTYPE ets_new_2(BIF_ALIST_2)
     UWord heir_data;
     Uint32 status;
     Sint keypos;
-    int is_named, is_compressed;
-    int is_fine_locked, frequent_read;
+    bool is_named, is_compressed;
+    bool is_fine_locked, frequent_read;
     UWord number_of_locks;
-    int is_decentralized_counters;
-    int is_decentralized_counters_option;
-    int is_explicit_lock_granularity;
-    int is_write_concurrency_auto;
+    bool is_decentralized_counters;
+    int decentralized_counters_option;
+    bool is_explicit_lock_granularity;
+    bool is_write_concurrency_auto;
     int cret;
     DbTableMethod* meth;
 
@@ -2501,17 +2501,17 @@ BIF_RETTYPE ets_new_2(BIF_ALIST_2)
 
     status = DB_SET | DB_PROTECTED;
     keypos = 1;
-    is_named = 0;
-    is_fine_locked = 0;
-    frequent_read = 0;
-    is_decentralized_counters = 0;
-    is_decentralized_counters_option = -1;
+    is_named = false;
+    is_fine_locked = false;
+    frequent_read = false;
+    is_decentralized_counters = false;
+    decentralized_counters_option = -1;
     heir = am_none;
     heir_data = (UWord) am_undefined;
     is_compressed = erts_ets_always_compress;
     number_of_locks = 0;
-    is_explicit_lock_granularity = 0;
-    is_write_concurrency_auto = 0;
+    is_explicit_lock_granularity = false;
+    is_write_concurrency_auto = false;
 
     list = BIF_ARG_2;
     while(is_list(list)) {
@@ -2525,7 +2525,7 @@ BIF_RETTYPE ets_new_2(BIF_ALIST_2)
 	    status &= ~(DB_SET | DB_BAG | DB_ORDERED_SET | DB_CA_ORDERED_SET);
 	}
 	else if (val == am_ordered_set) {
-            is_decentralized_counters = 1;
+            is_decentralized_counters = true;
 	    status |= DB_ORDERED_SET;
 	    status &= ~(DB_SET | DB_BAG | DB_DUPLICATE_BAG | DB_CA_ORDERED_SET);
 	}
@@ -2538,23 +2538,23 @@ BIF_RETTYPE ets_new_2(BIF_ALIST_2)
 		}
 		else if (tp[1] == am_write_concurrency) {
                     if (tp[2] == am_auto) {
-                        is_decentralized_counters = 1;
-                        is_write_concurrency_auto = 1;
-                        is_fine_locked = 1;
-                        is_explicit_lock_granularity = 0;
+                        is_decentralized_counters = true;
+                        is_write_concurrency_auto = true;
+                        is_fine_locked = true;
+                        is_explicit_lock_granularity = false;
                         number_of_locks = 0;
                     } else if (tp[2] == am_true) {
                         if (!(status & DB_ORDERED_SET)) {
-                            is_decentralized_counters = 0;
+                            is_decentralized_counters = false;
                         }
-                        is_fine_locked = 1;
-                        is_explicit_lock_granularity = 0;
-                        is_write_concurrency_auto = 0;
+                        is_fine_locked = true;
+                        is_explicit_lock_granularity = false;
+                        is_write_concurrency_auto = false;
                         number_of_locks = 0;
                     } else if (tp[2] == am_false) {
-                        is_fine_locked = 0;
-                        is_explicit_lock_granularity = 0;
-                        is_write_concurrency_auto = 0;
+                        is_fine_locked = false;
+                        is_explicit_lock_granularity = false;
+                        is_write_concurrency_auto = false;
                         number_of_locks = 0;
                     } else if (is_tuple(tp[2])) {
                         Eterm *stp = tuple_val(tp[2]);
@@ -2565,22 +2565,22 @@ BIF_RETTYPE ets_new_2(BIF_ALIST_2)
                             number_of_locks_param >= DB_WRITE_CONCURRENCY_MIN_LOCKS &&
                             number_of_locks_param <= DB_WRITE_CONCURRENCY_MAX_LOCKS) {
 
-                            is_decentralized_counters = 1;
-                            is_fine_locked = 1;
-                            is_explicit_lock_granularity = 1;
-                            is_write_concurrency_auto = 0;
+                            is_decentralized_counters = true;
+                            is_fine_locked = true;
+                            is_explicit_lock_granularity = true;
+                            is_write_concurrency_auto = false;
                             number_of_locks = number_of_locks_param;
 
                         } else break;
                     } else break;
                     if (DB_LOCK_FREE(NULL))
-			is_fine_locked = 0;
+			is_fine_locked = false;
 		}
 		else if (tp[1] == am_read_concurrency) {
 		    if (tp[2] == am_true) {
-			frequent_read = 1;
+			frequent_read = true;
 		    } else if (tp[2] == am_false) {
-			frequent_read = 0;
+			frequent_read = false;
 		    } else break;
 		}
 		else if (tp[1] == am_heir && tp[2] == am_none) {
@@ -2589,9 +2589,9 @@ BIF_RETTYPE ets_new_2(BIF_ALIST_2)
 		}
                 else if (tp[1] == am_decentralized_counters) {
 		    if (tp[2] == am_true) {
-			is_decentralized_counters_option = 1;
+			decentralized_counters_option = 1;
 		    } else if (tp[2] == am_false) {
-			is_decentralized_counters_option = 0;
+			decentralized_counters_option = 0;
 		    } else break;
                 }
 		else break;
@@ -2612,11 +2612,11 @@ BIF_RETTYPE ets_new_2(BIF_ALIST_2)
 	    status &= ~(DB_PROTECTED|DB_PUBLIC);
 	}
 	else if (val == am_named_table) {
-	    is_named = 1;
+	    is_named = true;
             status |= DB_NAMED_TABLE;
 	}
 	else if (val == am_compressed) {
-	    is_compressed = 1;
+	    is_compressed = true;
 	}
 	else if (val == am_set || val == am_protected)
 	    ;
@@ -2627,8 +2627,8 @@ BIF_RETTYPE ets_new_2(BIF_ALIST_2)
     if (is_not_nil(list)) { /* bad opt or not a well formed list */
 	BIF_ERROR(BIF_P, BADARG);
     }
-    if (-1 != is_decentralized_counters_option) {
-        is_decentralized_counters = is_decentralized_counters_option;
+    if (decentralized_counters_option != -1) {
+        is_decentralized_counters = decentralized_counters_option;
     }
     if (IS_TREE_TABLE(status) && is_fine_locked && !(status & DB_PRIVATE)) {
         meth = &db_catree;
@@ -4324,7 +4324,7 @@ BIF_RETTYPE ets_info_1(BIF_ALIST_1)
     Sint size = -1;
     Sint memory = -1;
     Eterm table;
-    int is_ctrs_read_result_set = 0;
+    bool is_ctrs_read_result_set = false;
     /*Process* rp = NULL;*/
     /* If/when we implement lockless private tables:
     Eterm owner;
@@ -4338,7 +4338,7 @@ BIF_RETTYPE ets_info_1(BIF_ALIST_1)
                                                           ERTS_DB_TABLE_NITEMS_COUNTER_ID);
         memory = erts_flxctr_get_snapshot_result_after_trap(counter_read_result,
                                                             ERTS_DB_TABLE_MEM_COUNTER_ID);
-        is_ctrs_read_result_set = 1;
+        is_ctrs_read_result_set = true;
     } else {
         table = BIF_ARG_1;
     }
@@ -4393,7 +4393,7 @@ BIF_RETTYPE ets_info_1(BIF_ALIST_1)
         } else {
             size = res.result[ERTS_DB_TABLE_NITEMS_COUNTER_ID];
             memory = res.result[ERTS_DB_TABLE_MEM_COUNTER_ID];
-            is_ctrs_read_result_set = 1;
+            is_ctrs_read_result_set = true;
         }
     }
     for (i = 0; i < sizeof(fields)/sizeof(Eterm); i++) {
@@ -5423,7 +5423,7 @@ static Eterm table_info(ErtsHeapFactory *hf, DbTable* tb, Eterm What)
      * For debugging purposes
      */
     else if (What == am_data) {
-	print_table(ERTS_PRINT_STDOUT, NULL, 1, tb);
+	print_table(ERTS_PRINT_STDOUT, NULL, true, tb);
 	ret = am_true;
     } else if (ERTS_IS_ATOM_STR("fixed",What)) {
 	if (IS_FIXED(tb))
@@ -5527,7 +5527,7 @@ static Eterm table_info(ErtsHeapFactory *hf, DbTable* tb, Eterm What)
     return ret;
 }
 
-static void print_table(fmtfn_t to, void *to_arg, int show,  DbTable* tb)
+static void print_table(fmtfn_t to, void *to_arg, bool show,  DbTable* tb)
 {
     Eterm tid;
     ErtsHeapFactory hf;
@@ -5565,7 +5565,7 @@ static void print_table(fmtfn_t to, void *to_arg, int show,  DbTable* tb)
 typedef struct {
     fmtfn_t to;
     void *to_arg;
-    int show;
+    bool show;
 } ErtsPrintDbInfo;
 
 static void
@@ -5577,7 +5577,7 @@ db_info_print(DbTable *tb, void *vpdbip)
     print_table(pdbip->to, pdbip->to_arg, pdbip->show, tb);
 }
 
-void db_info(fmtfn_t to, void *to_arg, int show)    /* Called by break handler */
+void db_info(fmtfn_t to, void *to_arg, bool show)    /* Called by break handler */
 {
     ErtsPrintDbInfo pdbi;
 
@@ -5585,7 +5585,7 @@ void db_info(fmtfn_t to, void *to_arg, int show)    /* Called by break handler *
     pdbi.to_arg = to_arg;
     pdbi.show = show;
 
-    erts_db_foreach_table(db_info_print, &pdbi, !0);
+    erts_db_foreach_table(db_info_print, &pdbi, true);
 }
 
 Uint
@@ -5598,7 +5598,7 @@ erts_get_ets_misc_mem_size(void)
 
 /* SMP Note: May only be used when system is locked */
 void
-erts_db_foreach_table(void (*func)(DbTable *, void *), void *arg, int alive_only)
+erts_db_foreach_table(void (*func)(DbTable *, void *), void *arg, bool alive_only)
 {
     int ix;
 
diff --git a/erts/emulator/beam/erl_db.h b/erts/emulator/beam/erl_db.h
index 19379dcdbe..313eecc18e 100644
--- a/erts/emulator/beam/erl_db.h
+++ b/erts/emulator/beam/erl_db.h
@@ -111,8 +111,8 @@ typedef enum {
 void init_db(ErtsDbSpinCount);
 int erts_db_process_exiting(Process *, ErtsProcLocks, void **);
 int erts_db_execute_free_fixation(Process*, DbFixation*);
-void db_info(fmtfn_t, void *, int);
-void erts_db_foreach_table(void (*)(DbTable *, void *), void *, int);
+void db_info(fmtfn_t, void *, bool);
+void erts_db_foreach_table(void (*)(DbTable *, void *), void *, bool);
 void erts_db_foreach_offheap(DbTable *,
 			     void (*func)(ErlOffHeap *, void *),
 			     void *);
@@ -121,8 +121,8 @@ void erts_db_foreach_thr_prgr_offheap(void (*func)(ErlOffHeap *, void *),
 
 extern int erts_ets_rwmtx_spin_count;
 extern int user_requested_db_max_tabs; /* set in erl_init */
-extern int erts_ets_realloc_always_moves;  /* set in erl_init */
-extern int erts_ets_always_compress;  /* set in erl_init */
+extern bool erts_ets_realloc_always_moves;  /* set in erl_init */
+extern bool erts_ets_always_compress;  /* set in erl_init */
 extern Export ets_select_delete_continue_exp;
 extern Export ets_select_count_continue_exp;
 extern Export ets_select_replace_continue_exp;
diff --git a/erts/emulator/beam/erl_db_catree.c b/erts/emulator/beam/erl_db_catree.c
index e441faf0bd..85c32a69da 100644
--- a/erts/emulator/beam/erl_db_catree.c
+++ b/erts/emulator/beam/erl_db_catree.c
@@ -114,7 +114,7 @@ static int db_prev_catree(Process *p, DbTable *tbl,
 static int db_prev_lookup_catree(Process *p, DbTable *tbl,
                           Eterm key,
                           Eterm *ret);
-static int db_put_catree(DbTable *tbl, Eterm obj, int key_clash_fail,
+static int db_put_catree(DbTable *tbl, Eterm obj, bool key_clash_fail,
                          SWord *consumed_reds_p);
 static int db_get_catree(Process *p, DbTable *tbl,
                          Eterm key,  Eterm *ret);
@@ -154,7 +154,7 @@ static int db_select_replace_continue_catree(Process *p, DbTable *tbl,
                                              enum DbIterSafety*);
 static int db_take_catree(Process *, DbTable *, Eterm, Eterm *);
 static void db_print_catree(fmtfn_t to, void *to_arg,
-                            int show, DbTable *tbl);
+                            bool show, DbTable *tbl);
 static int db_free_table_catree(DbTable *tbl);
 static SWord db_free_table_continue_catree(DbTable *tbl, SWord);
 static void db_foreach_offheap_catree(DbTable *,
@@ -166,14 +166,14 @@ static SWord db_delete_all_objects_catree(Process* p,
                                           Eterm* nitems_holder_wb);
 static Eterm db_delete_all_objects_get_nitems_from_holder_catree(Process* p,
                                                                  Eterm nitems_holder);
-static int
+static bool
 db_lookup_dbterm_catree(Process *, DbTable *, Eterm key, Eterm obj,
                         DbUpdateHandle*);
 static void db_finalize_dbterm_catree(int cret, DbUpdateHandle *);
 static int db_get_binary_info_catree(Process*, DbTable*, Eterm key, Eterm *ret);
 static int db_put_dbterm_catree(DbTable* tbl,
                                 void* obj,
-                                int key_clash_fail,
+                                bool key_clash_fail,
                                 SWord *consumed_reds_p);
 
 static void split_catree(DbTableCATree *tb,
@@ -497,7 +497,7 @@ static ERTS_INLINE int compute_tree_hight(TreeDbTerm * root)
  * Used by the join_trees function
  */
 static ERTS_INLINE
-TreeDbTerm* linkout_min_or_max_tree_node(TreeDbTerm **root, int is_min)
+TreeDbTerm* linkout_min_or_max_tree_node(TreeDbTerm **root, bool is_min)
 {
     TreeDbTerm **tstack[STACK_NEED];
     int tpos = 0;
@@ -543,8 +543,8 @@ TreeDbTerm* linkout_min_or_max_tree_node(TreeDbTerm **root, int is_min)
     return q;
 }
 
-#define LINKOUT_MIN_TREE_NODE(root) linkout_min_or_max_tree_node(root, 1)
-#define LINKOUT_MAX_TREE_NODE(root) linkout_min_or_max_tree_node(root, 0)
+#define LINKOUT_MIN_TREE_NODE(root) linkout_min_or_max_tree_node(root, true)
+#define LINKOUT_MAX_TREE_NODE(root) linkout_min_or_max_tree_node(root, false)
 
 /*
  * Joins two AVL trees where all the keys in the left one are smaller
@@ -907,7 +907,7 @@ void destroy_route_key(DbRouteKey* key)
 
 static ERTS_INLINE
 void init_root_iterator(DbTableCATree* tb, CATreeRootIterator* iter,
-                        int read_only)
+                        bool read_only)
 {
     iter->tb = tb;
     iter->read_only = read_only;
@@ -1036,7 +1036,7 @@ static DbTableCATreeNode *create_base_node(DbTableCATree *tb,
     p = erts_db_alloc(ERTS_ALC_T_DB_TABLE, (DbTable *) tb,
                       sizeof_base_node());
 
-    p->is_base_node = 1;
+    p->is_base_node = true;
     p->u.base.root = root;
     if (tb->common.type & DB_FREQ_READ)
         rwmtx_opt.type = ERTS_RWMTX_TYPE_FREQUENT_READ;
@@ -1050,7 +1050,7 @@ static DbTableCATreeNode *create_base_node(DbTableCATree *tb,
     ERTS_DB_ALC_MEM_UPDATE_((DbTable *) tb, 0, erts_rwmtx_size(&p->u.base.lock));
     BASE_NODE_STAT_SET(p, ((tb->common.status & DB_CATREE_FORCE_SPLIT)
                            ? INT_MAX : 0));
-    p->u.base.is_valid = 1;
+    p->u.base.is_valid = true;
     return p;
 }
 
@@ -1074,8 +1074,8 @@ create_route_node(DbTableCATree *tb,
                                          sizeof_route_node(key_size));
 
     copy_route_key(&p->u.route.key, key, key_size);
-    p->is_base_node = 0;
-    p->u.route.is_valid = 1;
+    p->is_base_node = false;
+    p->u.route.is_valid = true;
     erts_atomic_init_nob(&p->u.route.left, (erts_aint_t)left);
     erts_atomic_init_nob(&p->u.route.right, (erts_aint_t)right);
 #ifdef ERTS_ENABLE_LOCK_CHECK
@@ -1238,9 +1238,9 @@ static void join_catree(DbTableCATree *tb,
             return;
         } else {
             lock_route_node(parent);
-            parent->u.route.is_valid = 0;
-            neighbor->u.base.is_valid = 0;
-            thiz->u.base.is_valid = 0;
+            parent->u.route.is_valid = false;
+            neighbor->u.base.is_valid = false;
+            thiz->u.base.is_valid = false;
             gparent = NULL;
             do {
                 if (gparent != NULL) {
@@ -1288,9 +1288,9 @@ static void join_catree(DbTableCATree *tb,
             return;
         } else {
             lock_route_node(parent);
-            parent->u.route.is_valid = 0;
-            neighbor->u.base.is_valid = 0;
-            thiz->u.base.is_valid = 0;
+            parent->u.route.is_valid = false;
+            neighbor->u.base.is_valid = false;
+            thiz->u.base.is_valid = false;
             gparent = NULL;
             do {
                 if (gparent != NULL) {
@@ -1392,7 +1392,7 @@ static void split_catree(DbTableCATree *tb,
         } else {
             SET_RIGHT_RELB(parent, new_route);
         }
-        base->u.base.is_valid = 0;
+        base->u.base.is_valid = false;
         wunlock_base_node(base);
         erts_schedule_db_free(&tb->common,
                               do_free_base_node,
@@ -1418,7 +1418,7 @@ static SWord db_free_table_continue_catree(DbTable *tbl, SWord reds)
 
     if (!tb->deletion) {
         /* First call */
-        tb->deletion = 1;
+        tb->deletion = true;
         tb->nr_of_deleted_items = 0;
     }
 
@@ -1571,7 +1571,7 @@ int db_create_catree(Process *p, DbTable *tbl)
     DbTableCATreeNode *root;
 
     root = create_base_node(tb, NULL);
-    tb->deletion = 0;
+    tb->deletion = false;
     tb->nr_of_deleted_items = 0;
 #ifdef DEBUG
     tbl->common.status |= DB_CATREE_DEBUG_RANDOM_SPLIT_JOIN;
@@ -1586,7 +1586,7 @@ static int db_first_catree_common(Process *p, DbTable *tbl, Eterm *ret, Eterm (*
     CATreeRootIterator iter;
     int result;
 
-    init_root_iterator(&tbl->catree, &iter, 1);
+    init_root_iterator(&tbl->catree, &iter, true);
     root = *catree_find_first_root(&iter);
     if (!root) {
         TreeDbTerm **pp = catree_find_next_root(&iter, NULL);
@@ -1617,7 +1617,7 @@ static int db_next_catree_common(Process *p, DbTable *tbl, Eterm key, Eterm *ret
     CATreeRootIterator iter;
     int result;
 
-    init_root_iterator(&tbl->catree, &iter, 1);
+    init_root_iterator(&tbl->catree, &iter, true);
     iter.next_route_key = key;
     rootp = catree_find_next_root(&iter, NULL);
 
@@ -1650,7 +1650,7 @@ static int db_last_catree_common(Process *p, DbTable *tbl, Eterm *ret, Eterm (*f
     CATreeRootIterator iter;
     int result;
 
-    init_root_iterator(&tbl->catree, &iter, 1);
+    init_root_iterator(&tbl->catree, &iter, true);
     root = *catree_find_last_root(&iter);
     if (!root) {
         TreeDbTerm **pp = catree_find_prev_root(&iter, NULL);
@@ -1681,7 +1681,7 @@ static int db_prev_catree_common(Process *p, DbTable *tbl, Eterm key, Eterm *ret
     CATreeRootIterator iter;
     int result;
 
-    init_root_iterator(&tbl->catree, &iter, 1);
+    init_root_iterator(&tbl->catree, &iter, true);
     iter.next_route_key = key;
     rootp = catree_find_prev_root(&iter, NULL);
 
@@ -1710,7 +1710,7 @@ static int db_prev_lookup_catree(Process *p, DbTable *tbl, Eterm key, Eterm *ret
 
 static int db_put_dbterm_catree(DbTable* tbl,
                                 void* obj,
-                                int key_clash_fail,
+                                bool key_clash_fail,
                                 SWord *consumed_reds_p)
 {
     TreeDbTerm *value_to_insert = obj;
@@ -1727,7 +1727,7 @@ static int db_put_dbterm_catree(DbTable* tbl,
     return result;
 }
 
-static int db_put_catree(DbTable *tbl, Eterm obj, int key_clash_fail,
+static int db_put_catree(DbTable *tbl, Eterm obj, bool key_clash_fail,
                          SWord *consumed_reds_p)
 {
     DbTableCATree *tb = &tbl->catree;
@@ -2079,7 +2079,7 @@ static int db_slot_catree(Process *p, DbTable *tbl,
     int result;
     CATreeRootIterator iter;
 
-    init_root_iterator(&tbl->catree, &iter, 1);
+    init_root_iterator(&tbl->catree, &iter, true);
     result = db_slot_tree_common(p, tbl, *catree_find_first_root(&iter),
                                  slot_term, ret, NULL, &iter);
     destroy_root_iterator(&iter);
@@ -2095,7 +2095,7 @@ static int db_select_continue_catree(Process *p,
     int result;
     CATreeRootIterator iter;
 
-    init_root_iterator(&tbl->catree, &iter, 1);
+    init_root_iterator(&tbl->catree, &iter, true);
     result = db_select_continue_tree_common(p, &tbl->common,
                                             continuation, ret, NULL, &iter);
     destroy_root_iterator(&iter);
@@ -2109,7 +2109,7 @@ static int db_select_catree(Process *p, DbTable *tbl, Eterm tid,
     int result;
     CATreeRootIterator iter;
 
-    init_root_iterator(&tbl->catree, &iter, 1);
+    init_root_iterator(&tbl->catree, &iter, true);
     result = db_select_tree_common(p, tbl, tid, pattern, reverse, ret,
                                    NULL, &iter);
     destroy_root_iterator(&iter);
@@ -2125,7 +2125,7 @@ static int db_select_count_continue_catree(Process *p,
     int result;
     CATreeRootIterator iter;
 
-    init_root_iterator(&tbl->catree, &iter, 1);
+    init_root_iterator(&tbl->catree, &iter, true);
     result = db_select_count_continue_tree_common(p, tbl,
                                                   continuation, ret, NULL,
                                                   &iter);
@@ -2140,7 +2140,7 @@ static int db_select_count_catree(Process *p, DbTable *tbl, Eterm tid,
     int result;
     CATreeRootIterator iter;
 
-    init_root_iterator(&tbl->catree, &iter, 1);
+    init_root_iterator(&tbl->catree, &iter, true);
     result = db_select_count_tree_common(p, tbl,
                                          tid, pattern, ret, NULL, &iter);
     destroy_root_iterator(&iter);
@@ -2155,7 +2155,7 @@ static int db_select_chunk_catree(Process *p, DbTable *tbl, Eterm tid,
     int result;
     CATreeRootIterator iter;
 
-    init_root_iterator(&tbl->catree, &iter, 1);
+    init_root_iterator(&tbl->catree, &iter, true);
     result = db_select_chunk_tree_common(p, tbl,
                                          tid, pattern, chunk_size, reversed, ret,
                                          NULL, &iter);
@@ -2174,7 +2174,7 @@ static int db_select_delete_continue_catree(Process *p,
     int result;
     CATreeRootIterator iter;
 
-    init_root_iterator(&tbl->catree, &iter, 0);
+    init_root_iterator(&tbl->catree, &iter, false);
     init_tree_stack(&stack, stack_array, 0);
     result = db_select_delete_continue_tree_common(p, tbl, continuation, ret,
                                                    &stack, &iter);
@@ -2191,7 +2191,7 @@ static int db_select_delete_catree(Process *p, DbTable *tbl, Eterm tid,
     int result;
     CATreeRootIterator iter;
 
-    init_root_iterator(&tbl->catree, &iter, 0);
+    init_root_iterator(&tbl->catree, &iter, false);
     init_tree_stack(&stack, stack_array, 0);
     result = db_select_delete_tree_common(p, tbl,
                                           tid, pattern, ret, &stack,
@@ -2207,7 +2207,7 @@ static int db_select_replace_catree(Process *p, DbTable *tbl, Eterm tid,
     int result;
     CATreeRootIterator iter;
 
-    init_root_iterator(&tbl->catree, &iter, 0);
+    init_root_iterator(&tbl->catree, &iter, false);
     result = db_select_replace_tree_common(p, tbl,
                                            tid, pattern, ret, NULL, &iter);
     destroy_root_iterator(&iter);
@@ -2221,7 +2221,7 @@ static int db_select_replace_continue_catree(Process *p, DbTable *tbl,
     int result;
     CATreeRootIterator iter;
 
-    init_root_iterator(&tbl->catree, &iter, 0);
+    init_root_iterator(&tbl->catree, &iter, false);
     result = db_select_replace_continue_tree_common(p, tbl, continuation, ret,
                                                     NULL, &iter);
     destroy_root_iterator(&iter);
@@ -2246,12 +2246,12 @@ static int db_take_catree(Process *p, DbTable *tbl, Eterm key, Eterm *ret)
 
 /* Display tree contents (for dump) */
 static void db_print_catree(fmtfn_t to, void *to_arg,
-                            int show, DbTable *tbl)
+                            bool show, DbTable *tbl)
 {
     CATreeRootIterator iter;
     TreeDbTerm** root;
 
-    init_root_iterator(&tbl->catree, &iter, 1);
+    init_root_iterator(&tbl->catree, &iter, true);
     root = catree_find_first_root(&iter);
     do {
         db_print_tree_common(to, to_arg, show, *root, tbl);
@@ -2352,7 +2352,7 @@ static void db_foreach_offheap_catree(DbTable *tbl,
         ASSERT(tb->common.status & DB_DELETE);
         return;
     }
-    init_root_iterator(tb, &iter, 1);
+    init_root_iterator(tb, &iter, true);
     root = catree_find_first_root(&iter);
     do {
         db_foreach_offheap_tree_common(*root, func, arg);
@@ -2363,15 +2363,15 @@ static void db_foreach_offheap_catree(DbTable *tbl,
     do_for_route_nodes(GET_ROOT(tb), func, arg);
 }
 
-static int db_lookup_dbterm_catree(Process *p, DbTable *tbl, Eterm key, Eterm obj,
+static bool db_lookup_dbterm_catree(Process *p, DbTable *tbl, Eterm key, Eterm obj,
                                    DbUpdateHandle *handle)
 {
     DbTableCATree *tb = &tbl->catree;
     FindBaseNode fbn;
     DbTableCATreeNode* node = find_wlock_valid_base_node(tb, key, &fbn);
-    int res = db_lookup_dbterm_tree_common(p, tbl, &node->u.base.root, key,
+    bool res = db_lookup_dbterm_tree_common(p, tbl, &node->u.base.root, key,
                                            obj, handle, NULL);
-    if (res == 0) {
+    if (!res) {
         wunlock_adapt_base_node(tb, node, fbn.parent, fbn.current_level);
     } else {
         /* db_finalize_dbterm_catree will unlock */
@@ -2443,7 +2443,7 @@ void db_catree_force_split(DbTableCATree* tb, int on)
     CATreeRootIterator iter;
     TreeDbTerm** root;
 
-    init_root_iterator(tb, &iter, 1);
+    init_root_iterator(tb, &iter, true);
     root = catree_find_first_root(&iter);
     do {
         BASE_NODE_STAT_SET(iter.locked_bnode, (on ? INT_MAX : 0));
diff --git a/erts/emulator/beam/erl_db_catree.h b/erts/emulator/beam/erl_db_catree.h
index 9499b46f00..e9b3997b1d 100644
--- a/erts/emulator/beam/erl_db_catree.h
+++ b/erts/emulator/beam/erl_db_catree.h
@@ -43,7 +43,7 @@ typedef struct {
 typedef struct {
     erts_rwmtx_t lock; /* The lock for this base node */
     erts_atomic_t lock_statistics;
-    int is_valid; /* If this base node is still valid */
+    bool is_valid; /* If this base node is still valid */
     TreeDbTerm *root; /* The root of the sequential tree */
     ErtsThrPrgrLaterOp free_item; /* Used when freeing using thread progress */
 
@@ -56,14 +56,14 @@ typedef struct {
 #endif
     ErtsThrPrgrLaterOp free_item; /* Used when freeing using thread progress */
     erts_mtx_t lock; /* Used when joining route nodes */
-    int is_valid; /* If this route node is still valid */
+    bool is_valid; /* If this route node is still valid */
     erts_atomic_t left;
     erts_atomic_t right;
     DbRouteKey key;
 } DbTableCATreeRouteNode;
 
 typedef struct DbTableCATreeNode {
-    int is_base_node;
+    bool is_base_node;
     union {
         DbTableCATreeRouteNode route;
         DbTableCATreeBaseNode base;
@@ -81,7 +81,7 @@ typedef struct db_table_catree {
 
     /* CA Tree-specific fields */
     erts_atomic_t root;         /* The tree root (DbTableCATreeNode*) */
-    Uint deletion;		/* Being deleted */
+    bool deletion;		/* Being deleted */
     int is_routing_nodes_freed;
     /* The fields below are used by delete_all_objects and
        select_delete(DeleteAll)*/
@@ -95,7 +95,7 @@ typedef struct {
     DbTableCATreeNode* locked_bnode;
     DbTableCATreeNode* bnode_parent;
     int bnode_level;
-    int read_only;
+    bool read_only;
     DbRouteKey* search_key;
 } CATreeRootIterator;
 
diff --git a/erts/emulator/beam/erl_db_hash.c b/erts/emulator/beam/erl_db_hash.c
index d19289c252..9f50e1f577 100644
--- a/erts/emulator/beam/erl_db_hash.c
+++ b/erts/emulator/beam/erl_db_hash.c
@@ -71,6 +71,7 @@
 #  include "config.h"
 #endif
 
+#include <stdbool.h>
 #include "sys.h"
 #include "erl_vm.h"
 #include "global.h"
@@ -231,7 +232,7 @@ static ERTS_INLINE void free_fixdel(DbTableHash* tb, FixedDeletion* fixd)
     ERTS_ETS_MISC_MEM_ADD(-sizeof(FixedDeletion));
 }
 
-static ERTS_INLINE int link_fixdel(DbTableHash* tb,
+static ERTS_INLINE bool link_fixdel(DbTableHash* tb,
                                    FixedDeletion* fixd,
                                    erts_aint_t fixated_by_me)
 {
@@ -257,17 +258,17 @@ static ERTS_INLINE int link_fixdel(DbTableHash* tb,
  * Return false if we got raced by unfixing thread
  * and the object should be deleted for real.
  */
-static int add_fixed_deletion(DbTableHash* tb, int ix,
+static bool add_fixed_deletion(DbTableHash* tb, UWord ix,
                               erts_aint_t fixated_by_me)
 {
     FixedDeletion* fixd = alloc_fixdel(tb);
     fixd->slot = ix;
-    fixd->all = 0;
+    fixd->all = false;
     return link_fixdel(tb, fixd, fixated_by_me);
 }
 
 
-static ERTS_INLINE int is_pseudo_deleted(HashDbTerm* p)
+static ERTS_INLINE bool is_pseudo_deleted(HashDbTerm* p)
 {
     return p->pseudo_deleted;
 }
@@ -588,8 +589,8 @@ struct mp_prefound {
 };
 
 struct mp_info {
-    int something_can_match;	/* The match_spec is not "impossible" */
-    int key_given;
+    bool something_can_match;	/* The match_spec is not "impossible" */
+    bool key_given;
     struct mp_prefound dlists[10];  /* Default list of "pre-found" buckets */
     struct mp_prefound* lists;   /* Buckets to search if keys are given, 
 				  * = dlists initially */
@@ -632,8 +633,8 @@ typedef bool ExtraMatchValidatorF(int keypos, Eterm match, Eterm guard, Eterm bo
 /*
 ** Forward decl's (static functions)
 */
-static void alloc_seg(DbTableHash *tb, int activate_new_seg);
 static struct ext_segtab* alloc_ext_segtab(DbTableHash* tb, UWord seg_ix);
+static void alloc_seg(DbTableHash *tb, bool activate_new_seg);
 static int free_seg(DbTableHash *tb);
 static HashDbTerm* next_live(DbTableHash *tb, UWord *iptr, erts_rwmtx_t** lck_ptr,
 			     HashDbTerm *list);
@@ -711,7 +712,7 @@ static int db_select_replace_continue_hash(Process *p, DbTable *tbl,
 static int db_take_hash(Process *, DbTable *, Eterm, Eterm *);
 static void db_print_hash(fmtfn_t to,
 			  void *to_arg,
-			  int show,
+                          bool show,
 			  DbTable *tbl);
 static int db_free_empty_table_hash(DbTable *tbl);
 
@@ -731,19 +732,19 @@ static Eterm db_delete_all_objects_get_nitems_from_holder_hash(Process* p,
 #ifdef HARDDEBUG
 static void db_check_table_hash(DbTableHash *tb);
 #endif
-static int
+static bool
 db_lookup_dbterm_hash(Process *p, DbTable *tbl, Eterm key, Eterm obj,
                       DbUpdateHandle* handle);
 static void
 db_finalize_dbterm_hash(int cret, DbUpdateHandle* handle);
-static void* db_eterm_to_dbterm_hash(int compress, int keypos, Eterm obj);
+static void* db_eterm_to_dbterm_hash(bool compress, int keypos, Eterm obj);
 static void* db_dbterm_list_append_hash(void* last_term, void* db_term);
 static void* db_dbterm_list_remove_first_hash(void** list);
 static int db_put_dbterm_hash(DbTable* tb,
                               void* obj,
-                              int key_clash_fail,
+                              bool key_clash_fail,
                               SWord *consumed_reds_p);
-static void db_free_dbterm_hash(int compressed, void* obj);
+static void db_free_dbterm_hash(bool compressed, void* obj);
 static Eterm db_get_dbterm_key_hash(DbTable* tb, void* db_term);
 
 static int
@@ -760,7 +761,7 @@ static ERTS_INLINE void try_shrink(DbTableHash* tb, Sint nitems)
 
 /* Is this a live object (not pseodo-deleted) with the specified key? 
 */
-static ERTS_INLINE int has_live_key(DbTableHash* tb, HashDbTerm* b,
+static ERTS_INLINE bool has_live_key(DbTableHash* tb, HashDbTerm* b,
 				    Eterm key, HashValue hval)
 {
     if (b->hvalue != hval || is_pseudo_deleted(b))
@@ -774,7 +775,7 @@ static ERTS_INLINE int has_live_key(DbTableHash* tb, HashDbTerm* b,
 
 /* Has this object the specified key? Can be pseudo-deleted.
 */
-static ERTS_INLINE int has_key(DbTableHash* tb, HashDbTerm* b,
+static ERTS_INLINE bool has_key(DbTableHash* tb, HashDbTerm* b,
 			       Eterm key, HashValue hval)
 {
     if (b->hvalue != hval)
@@ -802,7 +803,7 @@ static ERTS_INLINE HashDbTerm* new_dbterm_hash(DbTableCommon* tb, Eterm obj)
  * This function only differ from new_dbterm_hash in that it does not
  * adjust the memory size of a given table.
  */
-static ERTS_INLINE HashDbTerm* new_dbterm_hash_no_tab(int compress, int keypos, Eterm obj)
+static ERTS_INLINE HashDbTerm* new_dbterm_hash_no_tab(bool compress, int keypos, Eterm obj)
 {
     HashDbTerm* p;
     if (compress) {
@@ -1240,7 +1241,7 @@ static ERTS_INLINE int db_terms_eq(DbTableCommon* tb, DbTerm* a, DbTerm* b,
 
 static int db_put_dbterm_hash(DbTable* tbl,
                               void* ob,
-                              int key_clash_fail,
+                              bool key_clash_fail,
                               SWord *consumed_reds_p)
 {
     DbTableHash *tb = &tbl->hash;
@@ -1280,7 +1281,7 @@ static int db_put_dbterm_hash(DbTable* tbl,
 	HashDbTerm* bnext = b->next;
 	if (is_pseudo_deleted(b)) {
             INC_NITEMS(tb, lck_ctr, hval);
-            b->pseudo_deleted = 0;
+            b->pseudo_deleted = false;
 	}
 	else if (key_clash_fail) {
 	    ret = DB_ERROR_BADKEY;
@@ -1315,7 +1316,7 @@ static int db_put_dbterm_hash(DbTable* tbl,
                             &tmp)) {
 		if (is_pseudo_deleted(q)) {
                     INC_NITEMS(tb, lck_ctr, hval);
-                    q->pseudo_deleted = 0;
+                    q->pseudo_deleted = false;
 		    ASSERT(q->hvalue == hval);
 		    if (q != b) { /* must move to preserve key insertion order */
 			*qp = q->next;
@@ -1338,7 +1339,7 @@ static int db_put_dbterm_hash(DbTable* tbl,
 Lnew:
     q = value_to_insert;
     q->hvalue = hval;
-    q->pseudo_deleted = 0;
+    q->pseudo_deleted = false;
     q->next = b;
     *bp = q;
     INC_NITEMS(tb, lck_ctr, hval);
@@ -1357,7 +1358,7 @@ Ldone:
     return ret;
 }
 
-int db_put_hash(DbTable *tbl, Eterm obj, int key_clash_fail,
+int db_put_hash(DbTable *tbl, Eterm obj, bool key_clash_fail,
                 SWord *consumed_reds_p)
 {
     DbTableHash *tb = &tbl->hash;
@@ -1394,7 +1395,7 @@ int db_put_hash(DbTable *tbl, Eterm obj, int key_clash_fail,
 	HashDbTerm* bnext = b->next;
 	if (is_pseudo_deleted(b)) {
             INC_NITEMS(tb, lck_ctr, hval);
-            b->pseudo_deleted = 0;
+            b->pseudo_deleted = false;
 	}
 	else if (key_clash_fail) {
 	    ret = DB_ERROR_BADKEY;
@@ -1423,7 +1424,7 @@ int db_put_hash(DbTable *tbl, Eterm obj, int key_clash_fail,
 	    if (db_eq(&tb->common,obj,&q->dbterm)) {
 		if (is_pseudo_deleted(q)) {
 		    INC_NITEMS(tb, lck_ctr, hval);
-                    q->pseudo_deleted = 0;
+                    q->pseudo_deleted = false;
 		    ASSERT(q->hvalue == hval);
 		    if (q != b) { /* must move to preserve key insertion order */
 			*qp = q->next;
@@ -1444,7 +1445,7 @@ int db_put_hash(DbTable *tbl, Eterm obj, int key_clash_fail,
 Lnew:
     q = new_dbterm(tb, obj);
     q->hvalue = hval;
-    q->pseudo_deleted = 0;
+    q->pseudo_deleted = false;
     q->next = b;
     *bp = q;
     INC_NITEMS(tb, lck_ctr, hval);
@@ -1630,7 +1631,7 @@ int db_erase_hash(DbTable *tbl, Eterm key, Eterm *ret)
 	    if (nitems_diff == -1 && IS_FIXED(tb)
                 && add_fixed_deletion(tb, ix, 0)) {
 		/* Pseudo remove (no need to keep several of same key) */
-		b->pseudo_deleted = 1;
+		b->pseudo_deleted = true;
 	    } else {
 		HashDbTerm* next = b->next;
                 b->next = free_us;
@@ -1689,7 +1690,7 @@ static int db_erase_object_hash(DbTable *tbl, Eterm object, Eterm *ret)
 	    if (db_eq(&tb->common,object, &b->dbterm)) {
 		--nitems_diff;
 		if (nkeys==1 && IS_FIXED(tb) && add_fixed_deletion(tb,ix,0)) {
-		    b->pseudo_deleted = 1;
+		    b->pseudo_deleted = true;
 		    bp = &b->next;
 		    b = b->next;
 		} else {
@@ -2077,7 +2078,7 @@ static ERTS_INLINE int on_simple_trap(Export* trap_function,
     Eterm egot;
     Eterm mpb;
     Eterm continuation;
-    int is_first_trap = (ctx->prev_continuation_tptr == NULL);
+    const bool is_first_trap = (ctx->prev_continuation_tptr == NULL);
     size_t base_halloc_sz = (is_first_trap ? ERTS_MAGIC_REF_THING_SIZE : 0);
 
     BUMP_ALL_REDS(ctx->p);
@@ -2114,7 +2115,7 @@ static ERTS_INLINE int on_simple_trap(Export* trap_function,
     return DB_ERROR_NONE;
 }
 
-static ERTS_INLINE int unpack_simple_continuation(Eterm continuation,
+static ERTS_INLINE bool unpack_simple_continuation(Eterm continuation,
                                                   Eterm** tptr_ptr,
                                                   Eterm* tid_ptr,
                                                   Sint* slot_ix_p,
@@ -2632,7 +2633,7 @@ static int select_delete_on_match_res(traverse_context_t* ctx_base, Sint slot_ix
                 goto do_erase;
             ctx->last_pseudo_delete = slot_ix;
         }
-        (*current_ptr)->pseudo_deleted = 1;
+        (*current_ptr)->pseudo_deleted = true;
     }
     else {
     do_erase:
@@ -2831,7 +2832,7 @@ static int select_replace_on_match_res(traverse_context_t* ctx, Sint slot_ix,
         new = new_dbterm(tb, match_res);
         new->next = next;
         new->hvalue = hval;
-        new->pseudo_deleted = 0;
+        new->pseudo_deleted = false;
         free_term(tb, **current_ptr_ptr);
         **current_ptr_ptr = new; /* replace 'next' pointer in previous object */
         *current_ptr_ptr = &((**current_ptr_ptr)->next); /* advance to next object */
@@ -2964,7 +2965,7 @@ static int db_take_hash(Process *p, DbTable *tbl, Eterm key, Eterm *ret)
                     && add_fixed_deletion(tb, ix, 0)) {
                     /* Pseudo remove (no need to keep several of same key) */
                     bp = &b->next;
-                    b->pseudo_deleted = 1;
+                    b->pseudo_deleted = true;
                     b = b->next;
                 } else {
                     HashDbTerm* next = b->next;
@@ -3017,7 +3018,7 @@ static SWord db_mark_all_deleted_hash(DbTable *tbl, SWord reds)
     }
     else {
         /* First call */
-        int ok;
+        bool ok;
         fixdel = alloc_fixdel(tb);
         ok = link_fixdel(tb, fixdel, 0);
         ASSERT(ok); (void)ok;
@@ -3027,31 +3028,31 @@ static SWord db_mark_all_deleted_hash(DbTable *tbl, SWord reds)
     do {
         HashDbTerm* b;
 	for (b = BUCKET(tb,i); b; b = b->next)
-            b->pseudo_deleted = 1;
+            b->pseudo_deleted = true;
     } while (++i < NACTIVE(tb) && --loops > 0);
 
     if (i < NACTIVE(tb)) {
          /* Yield */
         fixdel->slot = i;
-        fixdel->all = 1;
-        fixdel->trap = 1;
+        fixdel->all = true;
+        fixdel->trap = true;
         return -1;
     }
 
     fixdel->slot = NACTIVE(tb) - 1;
-    fixdel->all = 1;
-    fixdel->trap = 0;
+    fixdel->all = true;
+    fixdel->trap = false;
     RESET_NITEMS(tb);
     return loops < 0 ? 0 : loops / LOOPS_PER_REDUCTION;
 }
 
 
 /* Display hash table contents (for dump) */
-static void db_print_hash(fmtfn_t to, void *to_arg, int show, DbTable *tbl)
+static void db_print_hash(fmtfn_t to, void *to_arg, bool show, DbTable *tbl)
 {
     DbTableHash *tb = &tbl->hash;
     DbHashStats stats;
-    int was_thread_safe;
+    bool was_thread_safe;
 
     erts_print(to, to_arg, "Buckets: %d\n", NACTIVE(tb));
 
@@ -3059,7 +3060,7 @@ static void db_print_hash(fmtfn_t to, void *to_arg, int show, DbTable *tbl)
     /* If crash dumping we set table to thread safe in order to
        avoid taking any locks */
     if (ERTS_IS_CRASH_DUMPING)
-        tbl->common.is_thread_safe = 1;
+        tbl->common.is_thread_safe = true;
 
     db_calc_stats_hash(&tbl->hash, &stats);
 
@@ -3185,8 +3186,8 @@ static int analyze_pattern(DbTableHash *tb, Eterm pattern,
 
     mpi->lists = mpi->dlists;
     mpi->num_lists = 0;
-    mpi->key_given = 1;
-    mpi->something_can_match = 0;
+    mpi->key_given = true;
+    mpi->something_can_match = false;
     mpi->mp = NULL;
 
     for (lst = pattern; is_list(lst); lst = CDR(list_val(lst)))
@@ -3245,14 +3246,14 @@ static int analyze_pattern(DbTableHash *tb, Eterm pattern,
 	    continue;
 	}
 	if (tpl == am_Underscore || db_is_variable(tpl) != -1) {
-	    (mpi->key_given) = 0;
-	    (mpi->something_can_match) = 1;
+	    mpi->key_given = false;
+	    mpi->something_can_match = true;
 	} else {
 	    key = db_getkey(tb->common.keypos, tpl);
 	    if (is_value(key)) {
 		if (db_is_fully_bound(key)) {
 		    UWord ix;
-                    int search_slot;
+                    bool search_slot;
 		    HashDbTerm** bp;
 		    erts_rwmtx_t* lck;
 		    hval = MAKE_HASH(key);
@@ -3265,7 +3266,7 @@ static int analyze_pattern(DbTableHash *tb, Eterm pattern,
 			/* No point to verify if key exist now as there may be
 			   concurrent inserters/deleters anyway */
 			RUNLOCK_HASH(lck);
-			search_slot = 1;
+			search_slot = true;
 		    }
 		    if (search_slot) {
 			int j;
@@ -3282,11 +3283,11 @@ static int analyze_pattern(DbTableHash *tb, Eterm pattern,
 			    }
 			    ASSERT(mpi->lists[j].ix != ix);
 			}
-			mpi->something_can_match = 1;
+			mpi->something_can_match = true;
 		    }
 		} else {
-		    mpi->key_given = 0;
-		    mpi->something_can_match = 1;
+		    mpi->key_given = false;
+		    mpi->something_can_match = true;
 		}
 	    }
 	}
@@ -3344,7 +3345,7 @@ static struct ext_segtab* alloc_ext_segtab(DbTableHash* tb, UWord seg_ix)
 static void calc_shrink_limit(DbTableHash* tb)
 {
     erts_aint_t shrink_limit;
-    int sample_size_is_enough = 1;
+    bool sample_size_is_enough = true;
 
     if (IS_DECENTRALIZED_CTRS(tb)) {
         /*
@@ -3368,7 +3369,7 @@ static void calc_shrink_limit(DbTableHash* tb)
         /* } */
         const UWord needed_slots = 100 * NLOCKS_WITH_ITEM_COUNTERS;
         if (tb->nslots < needed_slots) {
-            sample_size_is_enough = 0;
+            sample_size_is_enough = false;
         }
     }
 
@@ -3400,7 +3401,7 @@ static void calc_shrink_limit(DbTableHash* tb)
 
 /* Extend table with one new segment
 */
-static void alloc_seg(DbTableHash *tb, int activate_buckets)
+static void alloc_seg(DbTableHash *tb, bool activate_buckets)
 {    
     UWord seg_ix = SLOT_IX_TO_SEG_IX(tb->nslots);
     struct segment** segtab;
@@ -3459,7 +3460,7 @@ struct dealloc_seg_ops {
 ** free_records: 1=free any records in segment, 0=assume segment is empty 
 ** ds_ops: (out) Instructions for dealloc_seg().
 */
-static int remove_seg(DbTableHash *tb, int free_records,
+static int remove_seg(DbTableHash *tb, bool free_records,
                       struct dealloc_seg_ops *ds_ops)
 {
     const UWord seg_ix = SLOT_IX_TO_SEG_IX(tb->nslots) - 1;
@@ -3571,7 +3572,7 @@ static int free_seg(DbTableHash *tb)
     struct dealloc_seg_ops ds_ops;
     int reds;
 
-    reds = remove_seg(tb, 1, &ds_ops);
+    reds = remove_seg(tb, true, &ds_ops);
     dealloc_seg(tb, &ds_ops);
     return reds;
 }
@@ -3616,7 +3617,7 @@ static Eterm build_term_list(Process* p, HashDbTerm* ptr1, HashDbTerm* ptr2,
     return list;
 }
 
-static ERTS_INLINE int
+static ERTS_INLINE bool
 begin_resizing(DbTableHash* tb)
 {
     if (DB_USING_FINE_LOCKING(tb)) {
@@ -3777,7 +3778,7 @@ static void shrink(DbTableHash* tb, UWord nitems)
             erts_atomic_set_relb(&tb->szm, low_szm);
         }
         if (tb->nslots - src_ix >= EXT_SEGSZ) {
-            remove_seg(tb, 0, &ds_ops);
+            remove_seg(tb, false, &ds_ops);
         }
         done_resizing(tb);
 
@@ -3862,7 +3863,7 @@ static HashDbTerm* next_live(DbTableHash *tb, UWord *iptr, erts_rwmtx_t** lck_pt
     return NULL;
 }
 
-static int
+static bool
 db_lookup_dbterm_hash(Process *p, DbTable *tbl, Eterm key, Eterm obj,
                       DbUpdateHandle* handle)
 {
@@ -3914,7 +3915,7 @@ db_lookup_dbterm_hash(Process *p, DbTable *tbl, Eterm key, Eterm obj,
             HashDbTerm *q = new_dbterm(tb, obj);
 
             q->hvalue = hval;
-            q->pseudo_deleted = 0;
+            q->pseudo_deleted = false;
             q->next = NULL;
             *bp = b = q;
             flags |= DB_INC_TRY_GROW;
@@ -3925,7 +3926,7 @@ db_lookup_dbterm_hash(Process *p, DbTable *tbl, Eterm key, Eterm obj,
             q = replace_dbterm(tb, b, obj);
             q->next = next;
             ASSERT(q->hvalue == hval);
-            q->pseudo_deleted = 0;
+            q->pseudo_deleted = false;
             *bp = b = q;
             INC_NITEMS(tb, lck_ctr, hval);
         }
@@ -3966,7 +3967,7 @@ db_finalize_dbterm_hash(int cret, DbUpdateHandle* handle)
     if (handle->flags & DB_NEW_OBJECT && cret != DB_ERROR_NONE) {
         if (IS_FIXED(tb) && add_fixed_deletion(tb, hash_to_ix(tb, b->hvalue),
                                                0)) {
-            b->pseudo_deleted = 1;
+            b->pseudo_deleted = true;
         } else {
             *bp = b->next;
             free_me = b;
@@ -4228,7 +4229,7 @@ static int db_raw_next_hash(Process *p, DbTable *tbl, Eterm key, Eterm *ret)
     return DB_ERROR_NONE;
 }
 
-static void* db_eterm_to_dbterm_hash(int compress, int keypos, Eterm obj)
+static void* db_eterm_to_dbterm_hash(bool compress, int keypos, Eterm obj)
 {
     HashDbTerm* term = new_dbterm_hash_no_tab(compress, keypos, obj);
     term->next = NULL;
@@ -4259,7 +4260,7 @@ static void* db_dbterm_list_remove_first_hash(void** list)
  * Frees a HashDbTerm without updating the memory footprint of the
  * table.
  */
-static void db_free_dbterm_hash(int compressed, void* obj)
+static void db_free_dbterm_hash(bool compressed, void* obj)
 {
     HashDbTerm* p = obj;
     db_free_term_no_tab(compressed, p, offsetof(HashDbTerm, dbterm));
diff --git a/erts/emulator/beam/erl_db_hash.h b/erts/emulator/beam/erl_db_hash.h
index 2c1b973ad2..7e6cbf5245 100644
--- a/erts/emulator/beam/erl_db_hash.h
+++ b/erts/emulator/beam/erl_db_hash.h
@@ -27,8 +27,8 @@ typedef struct fixed_deletion {
     UWord slot : sizeof(UWord)*8 - 2;
 
     /* Used by delete_all_objects: */
-    UWord all : 1;  /* marks [0 -> slot] */
-    UWord trap : 1;
+    bool all : 1;  /* marks [0 -> slot] */
+    bool trap : 1;
 
     struct fixed_deletion *next;
 } FixedDeletion;
@@ -39,7 +39,10 @@ typedef Uint32 HashVal;
 typedef struct hash_db_term {
     struct  hash_db_term* next;  /* next bucket */
     UWord hvalue : sizeof(UWord)*8 - 1;     /* stored hash value */
-    int pseudo_deleted : 1;
+    UWord pseudo_deleted : 1;               /* delete marked in fixed table */
+    /* Note: 'pseudo_deleted' could be bool if Windows compiler would
+     * pack it into same word as 'hvalue'. */
+
     DbTerm dbterm;         /* The actual term */
 } HashDbTerm;
 
@@ -112,7 +115,7 @@ Uint db_kept_items_hash(DbTableHash *tb);
 int db_create_hash(Process *p, 
 		   DbTable *tbl /* [in out] */);
 
-int db_put_hash(DbTable *tbl, Eterm obj, int key_clash_fail, SWord* consumed_reds_p);
+int db_put_hash(DbTable *tbl, Eterm obj, bool key_clash_fail, SWord* consumed_reds_p);
 
 int db_get_hash(Process *p, DbTable *tbl, Eterm key, Eterm *ret);
 
diff --git a/erts/emulator/beam/erl_db_tree.c b/erts/emulator/beam/erl_db_tree.c
index 040e6b0cfb..4660837300 100644
--- a/erts/emulator/beam/erl_db_tree.c
+++ b/erts/emulator/beam/erl_db_tree.c
@@ -150,7 +150,7 @@ static ERTS_INLINE TreeDbTerm* new_dbterm(DbTableCommon *tb, Eterm obj)
     return p;
 }
 
-static ERTS_INLINE TreeDbTerm* new_dbterm_no_tab(int compress, int keypos, Eterm obj)
+static ERTS_INLINE TreeDbTerm* new_dbterm_no_tab(bool compress, int keypos, Eterm obj)
 {
     TreeDbTerm* p;
     if (compress) {
@@ -282,7 +282,7 @@ struct select_delete_context {
     Uint accum;
     Binary *mp;
     Eterm end_condition;
-    int erase_lastterm;
+    bool erase_lastterm;
     TreeDbTerm *lastterm;
     Sint32 max;
     int keypos;
@@ -303,9 +303,6 @@ struct select_replace_context {
     Sint replaced;
 };
 
-/* Used by select_replace on analyze_pattern */
-typedef int (*extra_match_validator_t)(int keypos, Eterm match, Eterm guard, Eterm body);
-
 /*
 ** Forward declarations 
 */
@@ -320,7 +317,7 @@ int tree_balance_right(TreeDbTerm **this);
 static int delsub(TreeDbTerm **this); 
 static TreeDbTerm *slot_search(Process *p, TreeDbTerm *root, Sint slot,
                                DbTable *tb, DbTableTree *stack_container,
-                               CATreeRootIterator *iter, int* is_EOT);
+                               CATreeRootIterator *iter, bool* is_EOT);
 static TreeDbTerm *find_node(DbTableCommon *tb, TreeDbTerm *root,
                              Eterm key, DbTableTree *stack_container);
 static TreeDbTerm **find_node2(DbTableCommon *tb, TreeDbTerm **root, Eterm key);
@@ -364,8 +361,11 @@ static enum ms_key_boundness key_boundness(DbTableCommon *tb,
                                            Eterm pattern, Eterm *keyp);
 static Sint do_cmp_partly_bound(Eterm a, Eterm b, int *done);
 
+/* Used by select_replace on analyze_pattern */
+typedef bool ExtraMatchValidatorFn(int keypos, Eterm match, Eterm guard, Eterm body);
+
 static int analyze_pattern(DbTableCommon *tb, Eterm pattern,
-                           extra_match_validator_t extra_validator, /* Optional callback */
+                           ExtraMatchValidatorFn*, /* Optional callback */
                            struct mp_info *mpi);
 static int doit_select(DbTableCommon *tb,
                        TreeDbTerm *this,
@@ -418,7 +418,7 @@ static int db_prev_tree(Process *p, DbTable *tbl,
 static int db_prev_lookup_tree(Process *p, DbTable *tbl,
 			Eterm key,
 			Eterm *ret);
-static int db_put_tree(DbTable *tbl, Eterm obj, int key_clash_fail, SWord *consumed_reds_p);
+static int db_put_tree(DbTable *tbl, Eterm obj, bool key_clash_fail, SWord *consumed_reds_p);
 static int db_get_tree(Process *p, DbTable *tbl, 
 		       Eterm key,  Eterm *ret);
 static int db_member_tree(DbTable *tbl, Eterm key, Eterm *ret);
@@ -457,7 +457,7 @@ static int db_select_replace_continue_tree(Process *p, DbTable *tbl,
                                            enum DbIterSafety*);
 static int db_take_tree(Process *, DbTable *, Eterm, Eterm *);
 static void db_print_tree(fmtfn_t to, void *to_arg,
-			  int show, DbTable *tbl);
+			  bool show, DbTable *tbl);
 static int db_free_empty_table_tree(DbTable *tbl);
 
 static SWord db_free_table_continue_tree(DbTable *tbl, SWord);
@@ -475,7 +475,7 @@ static Eterm db_delete_all_objects_get_nitems_from_holder_tree(Process* p,
 #ifdef HARDDEBUG
 static void db_check_table_tree(DbTable *tbl);
 #endif
-static int
+static bool
 db_lookup_dbterm_tree(Process *, DbTable *, Eterm key, Eterm obj,
                       DbUpdateHandle*);
 static void
@@ -483,7 +483,7 @@ db_finalize_dbterm_tree(int cret, DbUpdateHandle *);
 static int db_get_binary_info_tree(Process*, DbTable*, Eterm key, Eterm *ret);
 static int db_put_dbterm_tree(DbTable* tbl, /* [in out] */
                               void* obj,
-                              int key_clash_fail,
+                              bool key_clash_fail,
                               SWord *consumed_reds_p);
 
 /*
@@ -765,7 +765,7 @@ static ERTS_INLINE int cmp_key_eq(DbTableCommon* tb, Eterm key, TreeDbTerm* obj)
 int db_put_dbterm_tree_common(DbTableCommon *tb,
                               TreeDbTerm **root,
                               TreeDbTerm *value_to_insert,
-                              int key_clash_fail,
+                              bool key_clash_fail,
                               DbTableTree *stack_container)
 {
     /* Non recursive insertion in AVL tree, building our own stack */
@@ -886,7 +886,7 @@ int db_put_dbterm_tree_common(DbTableCommon *tb,
 
 static int db_put_dbterm_tree(DbTable* tbl, /* [in out] */
                               void* obj,
-                              int key_clash_fail, /* DB_ERROR_BADKEY if key exists */
+                              bool key_clash_fail, /* DB_ERROR_BADKEY if key exists */
                               SWord *consumed_reds_p)
 {
     DbTableTree *tb = &tbl->tree;
@@ -894,7 +894,7 @@ static int db_put_dbterm_tree(DbTable* tbl, /* [in out] */
 }
 
 int db_put_tree_common(DbTableCommon *tb, TreeDbTerm **root, Eterm obj,
-                       int key_clash_fail, DbTableTree *stack_container)
+                       bool key_clash_fail, DbTableTree *stack_container)
 {
     /* Non recursive insertion in AVL tree, building our own stack */
     TreeDbTerm **tstack[STACK_NEED];
@@ -1007,7 +1007,7 @@ int db_put_tree_common(DbTableCommon *tb, TreeDbTerm **root, Eterm obj,
     return DB_ERROR_NONE;
 }
 
-static int db_put_tree(DbTable *tbl, Eterm obj, int key_clash_fail,
+static int db_put_tree(DbTable *tbl, Eterm obj, bool key_clash_fail,
                        SWord *consumed_reds_p)
 {
     DbTableTree *tb = &tbl->tree;
@@ -1143,7 +1143,7 @@ int db_slot_tree_common(Process *p, DbTable *tbl, TreeDbTerm *root,
     TreeDbTerm *st;
     Eterm *hp, *hend;
     Eterm copy;
-    int is_EOT = 0;
+    bool is_EOT = false;
     /*
      * The notion of a "slot" is not natural in a tree, but we try to
      * simulate it by giving the n'th node in the tree instead.
@@ -2016,7 +2016,7 @@ int db_select_delete_continue_tree_common(Process *p,
     lastkey = tptr[2];
     end_condition = tptr[3];
 
-    sc.erase_lastterm = 0; /* Before first RET_TO_BIF */
+    sc.erase_lastterm = false; /* Before first RET_TO_BIF */
     sc.lastterm = NULL;
 
     mp = erts_db_get_match_prog_binary_unchecked(tptr[4]);
@@ -2124,7 +2124,7 @@ int db_select_delete_tree_common(Process *p, DbTable *tbl,
     mpi.mp = NULL;
 
     sc.accum = 0;
-    sc.erase_lastterm = 0;
+    sc.erase_lastterm = false;
     sc.lastterm = NULL;
     sc.p = p;
     sc.max = 1000; 
@@ -2510,7 +2510,7 @@ void db_print_tree_common(fmtfn_t to, void *to_arg,
 
 /* Display tree contents (for dump) */
 static void db_print_tree(fmtfn_t to, void *to_arg,
-			  int show,
+                          bool show,
 			  DbTable *tbl)
 {
     DbTableTree *tb = &tbl->tree;
@@ -2752,7 +2752,7 @@ static TreeDbTerm *linkout_object_tree(DbTableCommon *tb,  TreeDbTerm **root,
 ** part of the tree should be searched. Also compiles the match program
 */
 static int analyze_pattern(DbTableCommon *tb, Eterm pattern,
-                           extra_match_validator_t extra_validator, /* Optional callback */
+                           ExtraMatchValidatorFn *extra_validator, /* Optional callback */
                            struct mp_info *mpi)
 {
     Eterm lst, tpl, ttpl;
@@ -3034,7 +3034,7 @@ static TreeDbTerm *slot_search(Process *p, TreeDbTerm *root,
                                Sint slot, DbTable *tb,
                                DbTableTree *stack_container,
                                CATreeRootIterator *iter,
-                               int* is_EOT)
+                               bool* is_EOT)
 {
     TreeDbTerm *this;
     TreeDbTerm *tmp;
@@ -3128,7 +3128,7 @@ static TreeDbTerm *slot_search(Process *p, TreeDbTerm *root,
 next_root:
         if (!iter) {
             if (stack->slot == (slot-1)) {
-                *is_EOT = 1;
+                *is_EOT = true;
             }
             break; /* EOT */
         }
@@ -3141,7 +3141,7 @@ next_root:
         pp = catree_find_next_root(iter, &lastkey);
         if (!pp) {
             if (stack->slot == (slot-1)) {
-                *is_EOT = 1;
+                *is_EOT = true;
             }
             break; /* EOT */
         }
@@ -3484,7 +3484,7 @@ static TreeDbTerm **find_ptr(DbTableCommon *tb, TreeDbTerm **root,
     return NULL;
 }
 
-int db_lookup_dbterm_tree_common(Process *p, DbTable *tbl, TreeDbTerm **root,
+bool db_lookup_dbterm_tree_common(Process *p, DbTable *tbl, TreeDbTerm **root,
                                  Eterm key, Eterm obj, DbUpdateHandle* handle,
                                  DbTableTree *stack_container)
 {
@@ -3527,7 +3527,7 @@ int db_lookup_dbterm_tree_common(Process *p, DbTable *tbl, TreeDbTerm **root,
     return 1;
 }
 
-static int
+static bool
 db_lookup_dbterm_tree(Process *p, DbTable *tbl, Eterm key, Eterm obj,
                       DbUpdateHandle* handle)
 {
@@ -3603,7 +3603,7 @@ Eterm db_binary_info_tree_common(Process* p, TreeDbTerm* this)
 }
 
 
-void* db_eterm_to_dbterm_tree_common(int compress, int keypos, Eterm obj)
+void* db_eterm_to_dbterm_tree_common(bool compress, int keypos, Eterm obj)
 {
     TreeDbTerm* term = new_dbterm_no_tab(compress, keypos, obj);
     term->left = NULL;
@@ -3635,7 +3635,7 @@ void* db_dbterm_list_remove_first_tree_common(void **list)
  * Frees a TreeDbTerm without updating the memory footprint of the
  * table.
  */
-void db_free_dbterm_tree_common(int compressed, void* obj)
+void db_free_dbterm_tree_common(bool compressed, void* obj)
 {
     TreeDbTerm* p = obj;
     db_free_term_no_tab(compressed, p, offsetof(TreeDbTerm, dbterm));
@@ -4220,7 +4220,7 @@ static int doit_select_delete(DbTableCommon *tb, TreeDbTerm *this,
 
     if (sc->erase_lastterm)
 	free_term((DbTable*)tb, sc->lastterm);
-    sc->erase_lastterm = 0;
+    sc->erase_lastterm = false;
     sc->lastterm = this;
     
     if (sc->end_condition != NIL && 
@@ -4231,7 +4231,7 @@ static int doit_select_delete(DbTableCommon *tb, TreeDbTerm *this,
     if (ret == am_true) {
 	key = GETKEY(sc->tb, this->dbterm.tpl);
 	linkout_tree(sc->tb, sc->common.root, key, sc->stack);
-	sc->erase_lastterm = 1;
+	sc->erase_lastterm = true;
 	++sc->accum;
     }
     if (--(sc->max) <= 0) {
diff --git a/erts/emulator/beam/erl_db_tree_util.h b/erts/emulator/beam/erl_db_tree_util.h
index 4cb238298f..8b2dd8e6f9 100644
--- a/erts/emulator/beam/erl_db_tree_util.h
+++ b/erts/emulator/beam/erl_db_tree_util.h
@@ -99,7 +99,7 @@ int db_prev_tree_common(Process *p, DbTable *tbl, TreeDbTerm *root, Eterm key,
                         Eterm *ret, DbTreeStack* stack,
                         Eterm (*func)(Process *, DbTable *, TreeDbTerm *));
 int db_put_tree_common(DbTableCommon *tb, TreeDbTerm **root, Eterm obj,
-                       int key_clash_fail, DbTableTree *stack_container);
+                       bool key_clash_fail, DbTableTree *stack_container);
 int db_get_tree_common(Process *p, DbTableCommon *tb, TreeDbTerm *root, Eterm key,
                        Eterm *ret, DbTableTree *stack_container);
 int db_get_element_tree_common(Process *p, DbTableCommon *tb, TreeDbTerm *root, Eterm key,
@@ -168,19 +168,19 @@ void db_print_tree_common(fmtfn_t to, void *to_arg,
 void db_foreach_offheap_tree_common(TreeDbTerm *root,
                                     void (*func)(ErlOffHeap *, void *),
                                     void * arg);
-int db_lookup_dbterm_tree_common(Process *p, DbTable *tbl, TreeDbTerm **root,
+bool db_lookup_dbterm_tree_common(Process *p, DbTable *tbl, TreeDbTerm **root,
                                  Eterm key, Eterm obj, DbUpdateHandle* handle,
                                  DbTableTree *stack_container);
 void db_finalize_dbterm_tree_common(int cret,
                                     DbUpdateHandle *handle,
                                     TreeDbTerm **root,
                                     DbTableTree *stack_container);
-void* db_eterm_to_dbterm_tree_common(int compress, int keypos, Eterm obj);
+void* db_eterm_to_dbterm_tree_common(bool compress, int keypos, Eterm obj);
 void* db_dbterm_list_append_tree_common(void* last_term, void* db_term);
 void* db_dbterm_list_remove_first_tree_common(void **list);
 int db_put_dbterm_tree_common(DbTableCommon *tb, TreeDbTerm **root, TreeDbTerm *value_to_insert,
-                              int key_clash_fail, DbTableTree *stack_container);
-void db_free_dbterm_tree_common(int compressed, void* obj);
+                              bool key_clash_fail, DbTableTree *stack_container);
+void db_free_dbterm_tree_common(bool compressed, void* obj);
 Eterm db_get_dbterm_key_tree_common(DbTable* tb, void* db_term);
 Sint cmp_partly_bound(Eterm partly_bound_key, Eterm bound_key);
 
diff --git a/erts/emulator/beam/erl_db_util.c b/erts/emulator/beam/erl_db_util.c
index 2029ed67ab..f062b8c0c8 100644
--- a/erts/emulator/beam/erl_db_util.c
+++ b/erts/emulator/beam/erl_db_util.c
@@ -364,8 +364,8 @@ DMC_DECLARE_STACK_TYPE(unsigned);
 */
 
 typedef struct DMCVariable {
-    int is_bound;
-    int is_in_body;
+    bool is_bound;
+    bool is_in_body;
 } DMCVariable;
 
 typedef struct DMCHeap {
@@ -400,8 +400,8 @@ typedef struct dmc_context {
     int num_match;
     int current_match;
     Uint cflags;
-    int is_guard; /* 1 if in guard, 0 if in body */
-    int special; /* 1 if the head in the match was a single expression */ 
+    bool is_guard; /* true if in guard, false if in body */
+    bool special;  /* true if the head in the match was a single expression */
     DMCErrInfo *err_info;
     char *stack_limit;
     Uint freason;
@@ -445,7 +445,7 @@ typedef struct {
 static erts_tsd_key_t match_pseudo_process_key;
 
 static ERTS_INLINE void
-cleanup_match_pseudo_process(ErtsMatchPseudoProcess *mpsp, int keep_heap)
+cleanup_match_pseudo_process(ErtsMatchPseudoProcess *mpsp, bool keep_heap)
 {
     if (mpsp->process.mbuf || mpsp->process.off_heap.first) {
 	erts_cleanup_empty_process(&mpsp->process);
@@ -501,7 +501,7 @@ get_match_pseudo_process(Process *c_p, Uint heap_size)
     if (mpsp) {
         ASSERT(mpsp == erts_tsd_get(match_pseudo_process_key));
         ASSERT(mpsp->process.scheduler_data == esdp);
-	cleanup_match_pseudo_process(mpsp, 0);
+	cleanup_match_pseudo_process(mpsp, false);
     }
     else {
 	ASSERT(erts_tsd_get(match_pseudo_process_key) == NULL);
@@ -527,7 +527,7 @@ destroy_match_pseudo_process(void)
     ErtsMatchPseudoProcess *mpsp;
     mpsp = (ErtsMatchPseudoProcess *)erts_tsd_get(match_pseudo_process_key);
     if (mpsp) {
-	cleanup_match_pseudo_process(mpsp, 0);
+	cleanup_match_pseudo_process(mpsp, false);
 	erts_free(ERTS_ALC_T_DB_MS_PSDO_PROC, (void *) mpsp);
 	erts_tsd_set(match_pseudo_process_key, (void *) NULL);
     }
@@ -983,8 +983,8 @@ static Eterm dmc_lookup_bif_reversed(void *f);
 static int cmp_uint(void *a, void *b);
 static int cmp_guard_bif(void *a, void *b);
 static int match_compact(ErlHeapFragment *expr, DMCErrInfo *err_info);
-static Uint my_size_object(Eterm t, int is_hashmap_node);
-static Eterm my_copy_struct(Eterm t, Eterm **hp, ErlOffHeap* off_heap, int);
+static Uint my_size_object(Eterm t, bool is_hashmap_node);
+static Eterm my_copy_struct(Eterm t, Eterm **hp, ErlOffHeap* off_heap, bool);
 
 /* Guard subroutines */
 static void
@@ -992,7 +992,7 @@ dmc_rearrange_constants(DMCContext *context, DMC_STACK_TYPE(UWord) *text,
                         int textpos, Eterm *p, Uint nelems);
 static DMCRet
 dmc_array(DMCContext *context, DMCHeap *heap, DMC_STACK_TYPE(UWord) *text,
-          Eterm *p, Uint nelems, int *constant);
+          Eterm *p, Uint nelems, bool *constant);
 /* Guard compilation */
 static void do_emit_constant(DMCContext *context, DMC_STACK_TYPE(UWord) *text,
 			     Eterm t);
@@ -1000,30 +1000,30 @@ static DMCRet dmc_list(DMCContext *context,
 		       DMCHeap *heap,
 		       DMC_STACK_TYPE(UWord) *text,
 		       Eterm t,
-		       int *constant);
+		       bool *constant);
 static DMCRet dmc_tuple(DMCContext *context,
 		       DMCHeap *heap,
 		       DMC_STACK_TYPE(UWord) *text,
 		       Eterm t,
-		       int *constant);
+                       bool *constant);
 static DMCRet
 dmc_map(DMCContext *context, DMCHeap *heap, DMC_STACK_TYPE(UWord) *text,
-        Eterm t, int *constant);
+        Eterm t, bool *constant);
 static DMCRet dmc_variable(DMCContext *context,
 			   DMCHeap *heap,
 			   DMC_STACK_TYPE(UWord) *text,
 			   Eterm t,
-			   int *constant);
+			   bool *constant);
 static DMCRet dmc_fun(DMCContext *context,
 		      DMCHeap *heap,
 		      DMC_STACK_TYPE(UWord) *text,
 		      Eterm t,
-		      int *constant);
+		      bool *constant);
 static DMCRet dmc_expr(DMCContext *context,
 		       DMCHeap *heap,
 		       DMC_STACK_TYPE(UWord) *text,
 		       Eterm t,
-		       int *constant);
+                       bool *constant);
 static DMCRet compile_guard_expr(DMCContext *context,
 				    DMCHeap *heap,
 				    DMC_STACK_TYPE(UWord) *text,
@@ -1052,7 +1052,7 @@ static void vadd_dmc_err(DMCErrInfo*, DMCErrorSeverity, int var, const char *str
 
 static Eterm dpm_array_to_list(Process *psp, Eterm *arr, int arity);
 
-static Eterm match_spec_test(Process *p, Eterm against, Eterm spec, int trace);
+static Eterm match_spec_test(Process *p, Eterm against, Eterm spec, bool trace);
 
 static Eterm seq_trace_fake(Process *p, Eterm arg1);
 
@@ -1302,7 +1302,7 @@ error:
  * Returns true if 'b' is guaranteed to always construct
  * the same term as 'a' has matched.
  */
-static int db_match_eq_body(Eterm a, Eterm b, int const_mode)
+static bool db_match_eq_body(Eterm a, Eterm b, bool const_mode)
 {
     DECLARE_ESTACK(s);
     Uint arity;
@@ -1313,7 +1313,7 @@ static int db_match_eq_body(Eterm a, Eterm b, int const_mode)
         switch(b & _TAG_PRIMARY_MASK) {
         case TAG_PRIMARY_LIST:
             if (!is_list(a))
-                return 0;
+                return false;
             ESTACK_PUSH2(s, CDR(list_val(a)), CDR(list_val(b)));
             a = CAR(list_val(a));
             b = CAR(list_val(b));
@@ -1328,20 +1328,20 @@ static int db_match_eq_body(Eterm a, Eterm b, int const_mode)
                     }
                     else if (bp[0] == make_arityval(2) && bp[1] == am_const) {
                         ESTACK_PUSH(s, CONST_MODE_OFF);
-                        const_mode = 1;   /* {const, term()} syntax */
+                        const_mode = true;   /* {const, term()} syntax */
                         b = bp[2];
                         continue; /* loop without pop */
                     }
                     else
-                        return 0; /* function call or invalid tuple syntax */
+                        return false; /* function call or invalid tuple syntax */
                 }
                 if (!is_tuple(a))
-                    return 0;
+                    return false;
 
                 ap = tuple_val(a);
                 bp = tuple_val(b);
                 if (ap[0] != bp[0])
-                    return 0;
+                    return false;
                 arity = arityval(ap[0]);
                 if (arity > 0) {
                     a = *(++ap);
@@ -1354,10 +1354,10 @@ static int db_match_eq_body(Eterm a, Eterm b, int const_mode)
             }
             else if (is_map(b)) {
                 /* We don't know what other pairs the matched map may contain */
-                return 0;
+                return false;
             }
             else if (!eq(a,b)) /* other boxed */
-                return 0;
+                return false;
             break;
 
         case TAG_PRIMARY_IMMED1:
@@ -1365,7 +1365,7 @@ static int db_match_eq_body(Eterm a, Eterm b, int const_mode)
                 || a == am_DollarUnderscore
                 || (const_mode && db_is_variable(a) >= 0)) {
 
-                return 0;
+                return false;
             }
             break;
         default:
@@ -1380,18 +1380,18 @@ pop_next:
         b = ESTACK_POP(s);
         if (b == CONST_MODE_OFF) {
             ASSERT(const_mode);
-            const_mode = 0;
+            const_mode = false;
             goto pop_next;
         }
         a = ESTACK_POP(s);
     }
 
     DESTROY_ESTACK(s);
-    return 1;
+    return true;
 }
 
 /* This is used by select_replace */
-int db_match_keeps_key(int keypos, Eterm match, Eterm guard, Eterm body)
+bool db_match_keeps_key(int keypos, Eterm match, Eterm guard, Eterm body)
 {
     Eterm match_key;
     Eterm* body_list;
@@ -1400,7 +1400,7 @@ int db_match_keeps_key(int keypos, Eterm match, Eterm guard, Eterm body)
     Eterm single_body_subterm;
     Eterm single_body_subterm_key;
     Eterm* single_body_subterm_key_tpl;
-    int const_mode;
+    bool const_mode;
 
     if (!is_list(body)) {
         return 0;
@@ -1432,12 +1432,12 @@ int db_match_keeps_key(int keypos, Eterm match, Eterm guard, Eterm body)
         single_body_term_tpl[1] == am_const) {
         /* {const, {"ets-tuple constant"}} */
         single_body_subterm = single_body_term_tpl[2];
-        const_mode = 1;
+        const_mode = true;
     }
     else if (*single_body_term_tpl == make_arityval(1)) {
         /* {{"ets-tuple construction"}} */
         single_body_subterm = single_body_term_tpl[1];
-        const_mode = 0;
+        const_mode = false;
     }
     else {
         /* not a tuple construction */
@@ -1690,7 +1690,7 @@ Binary *db_match_compile(Eterm *matchexpr,
     Eterm t;
     Uint i;
     Uint num_iters;
-    int structure_checked;
+    bool structure_checked;
     DMCRet res;
     int current_try_label;
     Binary *bp = NULL;
@@ -1726,7 +1726,7 @@ restart:
 	sys_memset(heap.vars, 0, heap.size * sizeof(*heap.vars));
 	t = context.matchexpr[context.current_match];
 	context.stack_used = 0;
-	structure_checked = 0;
+	structure_checked = false;
 	if (context.current_match < num_progs - 1) {
 	    DMC_PUSH(text,matchTryMeElse);
 	    current_try_label = DMC_STACK_NUM(text);
@@ -1744,7 +1744,7 @@ restart:
                     if (!structure_checked) {
                         DMC_PUSH2(text, matchMap, num_iters);
                     }
-                    structure_checked = 0;
+                    structure_checked = false;
                     for (i = 0; i < num_iters; ++i) {
                         Eterm key = flatmap_get_keys(flatmap_val(t))[i];
                         if (db_is_variable(key) >= 0) {
@@ -1792,7 +1792,7 @@ restart:
                     if (!structure_checked) {
                         DMC_PUSH2(text, matchMap, num_iters);
                     }
-                    structure_checked = 0;
+                    structure_checked = false;
 
                     hashmap_iterator_init(&wstack, t, 0);
 
@@ -1848,7 +1848,7 @@ restart:
 					     pop it */
 		    DMC_PUSH2(text, matchTuple, num_iters);
 		}
-		structure_checked = 0;
+		structure_checked = false;
 		for (i = 1; i <= num_iters; ++i) {
 		    if ((res = dmc_one_term(&context, 
 					    &heap, 
@@ -1868,7 +1868,7 @@ restart:
 		if (!structure_checked) {
 		    DMC_PUSH(text, matchList);
 		}
-		structure_checked = 0; /* Whatever it is, we did 
+		structure_checked = false; /* Whatever it is, we did
 					  not pop it */
 		if ((res = dmc_one_term(&context, &heap, &stack, 
 					&text, CAR(list_val(t))))
@@ -1883,7 +1883,7 @@ restart:
 			single terms as match 
 			expressions */
 	    simple_term:
-		structure_checked = 0;
+		structure_checked = false;
 		if ((res = dmc_one_term(&context, &heap, &stack, 
 					&text, t))
 		    != retOk) {
@@ -1908,10 +1908,10 @@ restart:
 		break;
 	    } else {
 		DMC_PUSH(text, matchPop);
-		structure_checked = 1; /* 
-					* Checked with matchPushT 
-					* or matchPushL
-					*/
+		structure_checked = true; /*
+					   * Checked with matchPushT
+					   * or matchPushL
+					   */
 		--(context.stack_used);
 	    }
 	}
@@ -1955,14 +1955,14 @@ restart:
 	/*
 	** ... and the guards
 	*/
-	context.is_guard = 1;
+	context.is_guard = true;
 	if (compile_guard_expr
 	    (&context,
 	     &heap,
 	     &text,
 	     context.guardexpr[context.current_match]) != retOk) 
 	    goto error;
-	context.is_guard = 0;
+	context.is_guard = false;
 	if ((context.cflags & DCOMP_TABLE) && 
 	    !is_list(context.bodyexpr[context.current_match])) {
 	    if (context.err_info) {
@@ -3065,7 +3065,7 @@ fail:
 			      lets restart, with the next match
 			      program */
 	pc = (prog->text) + fail_label;
-	cleanup_match_pseudo_process(mpsp, 1);
+	cleanup_match_pseudo_process(mpsp, true);
 	goto restart;
     }
     ret = THE_NON_VALUE;
@@ -3363,7 +3363,7 @@ Uint db_term_size(DbTable *tb, void* basep, Uint offset)
     }
 }
 
-void db_free_term_no_tab(int compress, void* basep, Uint offset)
+void db_free_term_no_tab(bool compress, void* basep, Uint offset)
 {
     DbTerm* db = (DbTerm*) ((byte*)basep + offset);
     Uint size;
@@ -3825,13 +3825,13 @@ void db_cleanup_offheap_comp(DbTerm* obj)
 #endif
 }
 
-int db_eq_comp(DbTableCommon* tb, Eterm a, DbTerm* b)
+bool db_eq_comp(DbTableCommon* tb, Eterm a, DbTerm* b)
 {
     ErlOffHeap tmp_offheap;
     Eterm* allocp;
     Eterm* hp;
     Eterm tmp_b;
-    int is_eq;
+    bool is_eq;
 
     ASSERT(tb->compress);
     hp = allocp = erts_alloc(ERTS_ALC_T_TMP, b->size*sizeof(Eterm));
@@ -3915,7 +3915,7 @@ int db_has_map(Eterm node) {
 }
 
 /* Check if obj is fully bound (contains no variables, underscores, or maps) */
-int db_is_fully_bound(Eterm node) {
+bool db_is_fully_bound(Eterm node) {
     DECLARE_ESTACK(s);
 
     ESTACK_PUSH(s,node);
@@ -3941,19 +3941,19 @@ int db_is_fully_bound(Eterm node) {
                  * map that has the given elements, so they must be considered
                  * variable. */
                 DESTROY_ESTACK(s);
-                return 0;
+                return false;
             }
 	    break;
 	case TAG_PRIMARY_IMMED1:
 	    if (node == am_Underscore || db_is_variable(node) >= 0) {
 		DESTROY_ESTACK(s);
-		return 0;
+		return false;
 	    }
 	    break;
 	}
     }
     DESTROY_ESTACK(s);
-    return 1;
+    return true;
 }
 
 /* 
@@ -4071,7 +4071,7 @@ static DMCRet dmc_one_term(DMCContext *context,
 		if (n >= heap->vars_used)
 		    heap->vars_used = n + 1;
 		DMC_PUSH2(*text, matchBind, n);
-		heap->vars[n].is_bound = 1;
+		heap->vars[n].is_bound = true;
 	    }
 	} else if (c == am_Underscore) {
 	    DMC_PUSH(*text, matchSkip);
@@ -4177,11 +4177,11 @@ static void do_emit_constant(DMCContext *context, DMC_STACK_TYPE(UWord) *text,
         if (is_immed(t)) {
 	    tmp = t;
 	} else {
-	    sz = my_size_object(t, 0);
+	    sz = my_size_object(t, false);
             if (sz) {
                 emb = new_message_buffer(sz);
                 hp = emb->mem;
-                tmp = my_copy_struct(t,&hp,&(emb->off_heap), 0);
+                tmp = my_copy_struct(t,&hp,&(emb->off_heap), false);
                 emb->next = context->save;
                 context->save = emb;
             }
@@ -4226,10 +4226,10 @@ static DMCRet dmc_list(DMCContext *context,
 		       DMCHeap *heap,
 		       DMC_STACK_TYPE(UWord) *text,
 		       Eterm t,
-		       int *constant)
+                       bool *constant)
 {
-    int c1;
-    int c2;
+    bool c1;
+    bool c2;
     int ret;
 
     if ((ret = dmc_expr(context, heap, text, CAR(list_val(t)), &c1)) != retOk)
@@ -4239,10 +4239,10 @@ static DMCRet dmc_list(DMCContext *context,
 	return ret;
 
     if (c1 && c2) {
-	*constant = 1;
+	*constant = true;
 	return retOk;
     } 
-    *constant = 0;
+    *constant = false;
     if (!c1) {
 	/* The CAR is not a constant, so if the CDR is, we just push it,
 	   otherwise it is already pushed. */
@@ -4279,9 +4279,9 @@ dmc_rearrange_constants(DMCContext *context, DMC_STACK_TYPE(UWord) *text,
 
 static DMCRet
 dmc_array(DMCContext *context, DMCHeap *heap, DMC_STACK_TYPE(UWord) *text,
-          Eterm *p, Uint nelems, int *constant)
+          Eterm *p, Uint nelems, bool *constant)
 {
-    int all_constant = 1;
+    bool all_constant = true;
     int textpos = DMC_STACK_NUM(*text);
     int preventive_bumps = 0;
     Uint i;
@@ -4294,14 +4294,14 @@ dmc_array(DMCContext *context, DMCHeap *heap, DMC_STACK_TYPE(UWord) *text,
     */
     for (i = nelems; i--;) {
         DMCRet ret;
-        int c;
+        bool c;
 
         ret = dmc_expr(context, heap, text, p[i], &c);
         if (ret != retOk) {
             return ret;
         }
         if (!c && all_constant) {
-            all_constant = 0;
+            all_constant = false;
             if (i < nelems - 1) {
                 /* Revert preventive stack bumps as they will now be done again
                  * for real by do_emit_constant() */
@@ -4338,9 +4338,9 @@ dmc_array(DMCContext *context, DMCHeap *heap, DMC_STACK_TYPE(UWord) *text,
 
 static DMCRet
 dmc_tuple(DMCContext *context, DMCHeap *heap, DMC_STACK_TYPE(UWord) *text,
-          Eterm t, int *constant)
+          Eterm t, bool *constant)
 {
-    int all_constant;
+    bool all_constant;
     Eterm *p = tuple_val(t);
     Uint nelems = arityval(*p);
     DMCRet ret;
@@ -4350,12 +4350,12 @@ dmc_tuple(DMCContext *context, DMCHeap *heap, DMC_STACK_TYPE(UWord) *text,
         return ret;
     }
     if (all_constant) {
-        *constant = 1;
+        *constant = true;
         return retOk;
     }
     DMC_PUSH2(*text, matchMkTuple, nelems);
     context->stack_used -= (nelems - 1);
-    *constant = 0;
+    *constant = false;
     return retOk;
 }
 
@@ -4365,12 +4365,12 @@ dmc_tuple(DMCContext *context, DMCHeap *heap, DMC_STACK_TYPE(UWord) *text,
  */
 static DMCRet
 dmc_map(DMCContext *context, DMCHeap *heap, DMC_STACK_TYPE(UWord) *text,
-        Eterm t, int *constant)
+        Eterm t, bool *constant)
 {
     int nelems;
     DMCRet ret;
     if (is_flatmap(t)) {
-        int constant_values, constant_keys;
+        bool constant_values, constant_keys;
         flatmap_t *m = (flatmap_t *)flatmap_val(t);
         Eterm *values = flatmap_get_values(m);
         int textpos = DMC_STACK_NUM(*text);
@@ -4398,7 +4398,7 @@ dmc_map(DMCContext *context, DMCHeap *heap, DMC_STACK_TYPE(UWord) *text,
         }
 
         if (constant_values && constant_keys) {
-            *constant = 1;
+            *constant = true;
             return retOk;
         }
 
@@ -4417,13 +4417,13 @@ dmc_map(DMCContext *context, DMCHeap *heap, DMC_STACK_TYPE(UWord) *text,
 
         DMC_PUSH2(*text, matchMkFlatMap, nelems);
         context->stack_used -= (nelems + 1) - 1;  /* n values + 1 key-tuple - 1 map ptr => 1 map */
-        *constant = 0;
+        *constant = false;
         return retOk;
     } else {
         DECLARE_WSTACK(wstack);
         DMC_STACK_TYPE(UWord) instr_save;
         Eterm *kv;
-        int c = 0;
+        bool c = false;
         int textpos = DMC_STACK_NUM(*text);
         int preventive_bumps = 0;
 
@@ -4464,7 +4464,7 @@ dmc_map(DMCContext *context, DMCHeap *heap, DMC_STACK_TYPE(UWord) *text,
            encountering any variables */
         if (c) {
             ASSERT(DMC_STACK_NUM(*text) == textpos);
-            *constant = 1;
+            *constant = true;
             DESTROY_WSTACK(wstack);
             return retOk;
         }
@@ -4547,7 +4547,7 @@ dmc_map(DMCContext *context, DMCHeap *heap, DMC_STACK_TYPE(UWord) *text,
         DMC_PUSH2(*text, matchMkHashMap, nelems);
         context->stack_used -= 2*nelems - 1;  /* n keys & values => 1 map */
         DESTROY_WSTACK(wstack);
-        *constant = 0;
+        *constant = false;
         return retOk;
     }
 }
@@ -4556,7 +4556,7 @@ static DMCRet dmc_whole_expression(DMCContext *context,
 				   DMCHeap *heap,
 				   DMC_STACK_TYPE(UWord) *text,
 				   Eterm t,
-				   int *constant)
+				   bool *constant)
 {
     if (context->cflags & DCOMP_TRACE) {
 	/* Hmmm, convert array to list... */
@@ -4573,7 +4573,7 @@ static DMCRet dmc_whole_expression(DMCContext *context,
     ++context->stack_used;
     if (context->stack_used > context->stack_need)
 	context->stack_need = context->stack_used;
-    *constant = 0;
+    *constant = false;
     return retOk;
 }
 
@@ -4589,7 +4589,7 @@ static void dmc_add_pushv_variant(DMCContext *context, DMCHeap *heap,
     if (!context->is_guard) {
         if(!v->is_in_body) {
 	    instr = matchPushVResult;
-	    v->is_in_body = 1;
+	    v->is_in_body = true;
 	}
     }
     DMC_PUSH(*text, instr);
@@ -4600,7 +4600,7 @@ static DMCRet dmc_variable(DMCContext *context,
 			   DMCHeap *heap,
 			   DMC_STACK_TYPE(UWord) *text,
 			   Eterm t,
-			   int *constant)
+			   bool *constant)
 {
     Uint n = db_is_variable(t);
 
@@ -4613,7 +4613,7 @@ static DMCRet dmc_variable(DMCContext *context,
     ++context->stack_used;
     if (context->stack_used > context->stack_need)
 	context->stack_need = context->stack_used;
-    *constant = 0;
+    *constant = false;
     return retOk;
 }
 
@@ -4621,7 +4621,7 @@ static DMCRet dmc_all_bindings(DMCContext *context,
 			       DMCHeap *heap,
 			       DMC_STACK_TYPE(UWord) *text,
 			       Eterm t,
-			       int *constant)
+			       bool *constant)
 {
     int i;
 
@@ -4636,7 +4636,7 @@ static DMCRet dmc_all_bindings(DMCContext *context,
     ++context->stack_used;
     if ((context->stack_used + 1) > context->stack_need)
 	context->stack_need = (context->stack_used + 1);
-    *constant = 0;
+    *constant = false;
     return retOk;
 }
 
@@ -4644,13 +4644,13 @@ static DMCRet dmc_const(DMCContext *context,
 		       DMCHeap *heap,
 		       DMC_STACK_TYPE(UWord) *text,
 		       Eterm t,
-		       int *constant)
+                       bool *constant)
 {
     if (tuple_val(t)[0] != make_arityval(2)) {
 	RETURN_TERM_ERROR("Special form 'const' called with more than one "
 			  "argument in %T.", t, context, *constant);
     }
-    *constant = 1;
+    *constant = true;
     return retOk;
 }
 
@@ -4658,19 +4658,19 @@ static DMCRet dmc_and(DMCContext *context,
 		      DMCHeap *heap,
 		      DMC_STACK_TYPE(UWord) *text,
 		      Eterm t,
-		      int *constant)
+                      bool *constant)
 {
     Eterm *p = tuple_val(t);
     Uint a = arityval(*p);
     DMCRet ret;
     int i;
-    int c;
+    bool c;
     
     if (a < 2) {
 	RETURN_TERM_ERROR("Special form 'and' called without arguments "
 			  "in %T.", t, context, *constant);
     }
-    *constant = 0;
+    *constant = false;
     for (i = a; i > 1; --i) {
 	if ((ret = dmc_expr(context, heap, text, p[i], &c)) != retOk)
 	    return ret;
@@ -4687,19 +4687,19 @@ static DMCRet dmc_or(DMCContext *context,
 		     DMCHeap *heap,
 		     DMC_STACK_TYPE(UWord) *text,
 		     Eterm t,
-		     int *constant)
+                     bool *constant)
 {
     Eterm *p = tuple_val(t);
     Uint a = arityval(*p);
     DMCRet ret;
     int i;
-    int c;
+    bool c;
     
     if (a < 2) {
 	RETURN_TERM_ERROR("Special form 'or' called without arguments "
 			  "in %T.", t, context, *constant);
     }
-    *constant = 0;
+    *constant = false;
     for (i = a; i > 1; --i) {
 	if ((ret = dmc_expr(context, heap, text, p[i], &c)) != retOk)
 	    return ret;
@@ -4717,13 +4717,13 @@ static DMCRet dmc_andalso(DMCContext *context,
 			  DMCHeap *heap,
 			  DMC_STACK_TYPE(UWord) *text,
 			  Eterm t,
-			  int *constant)
+                          bool *constant)
 {
     Eterm *p = tuple_val(t);
     Uint a = arityval(*p);
     DMCRet ret;
     int i;
-    int c;
+    bool c;
     Uint lbl;
     Uint lbl_next;
     Uint lbl_val;
@@ -4733,7 +4733,7 @@ static DMCRet dmc_andalso(DMCContext *context,
 			  " arguments "
 			  "in %T.", t, context, *constant);
     }
-    *constant = 0;
+    *constant = false;
     lbl = 0;
     for (i = 2; i <= a; ++i) {
 	if ((ret = dmc_expr(context, heap, text, p[i], &c)) != retOk)
@@ -4766,13 +4766,13 @@ static DMCRet dmc_orelse(DMCContext *context,
 			 DMCHeap *heap,
 			 DMC_STACK_TYPE(UWord) *text,
 			 Eterm t,
-			 int *constant)
+                         bool *constant)
 {
     Eterm *p = tuple_val(t);
     Uint a = arityval(*p);
     DMCRet ret;
     int i;
-    int c;
+    bool c;
     Uint lbl;
     Uint lbl_next;
     Uint lbl_val;
@@ -4781,7 +4781,7 @@ static DMCRet dmc_orelse(DMCContext *context,
 	RETURN_TERM_ERROR("Special form 'orelse' called without arguments "
 			  "in %T.", t, context, *constant);
     }
-    *constant = 0;
+    *constant = false;
     lbl = 0;
     for (i = 2; i <= a; ++i) {
 	if ((ret = dmc_expr(context, heap, text, p[i], &c)) != retOk)
@@ -4814,11 +4814,11 @@ static DMCRet dmc_message(DMCContext *context,
 			  DMCHeap *heap,
 			  DMC_STACK_TYPE(UWord) *text,
 			  Eterm t,
-			  int *constant)
+                          bool *constant)
 {
     Eterm *p = tuple_val(t);
     DMCRet ret;
-    int c;
+    bool c;
     
 
     if (!(context->cflags & DCOMP_TRACE)) {
@@ -4837,7 +4837,7 @@ static DMCRet dmc_message(DMCContext *context,
 			  "number of arguments in %T.", t, context, 
 			  *constant);
     }
-    *constant = 0;
+    *constant = false;
     if ((ret = dmc_expr(context, heap, text, p[2], &c)) != retOk) {
 	return ret;
     }
@@ -4855,7 +4855,7 @@ static DMCRet dmc_self(DMCContext *context,
 		     DMCHeap *heap,
 		     DMC_STACK_TYPE(UWord) *text,
 		     Eterm t,
-		     int *constant)
+                     bool *constant)
 {
     Eterm *p = tuple_val(t);
     
@@ -4863,7 +4863,7 @@ static DMCRet dmc_self(DMCContext *context,
 	RETURN_TERM_ERROR("Special form 'self' called with arguments "
 			  "in %T.", t, context, *constant);
     }
-    *constant = 0;
+    *constant = false;
     DMC_PUSH(*text, matchSelf);
     if (++context->stack_used > context->stack_need)
 	context->stack_need = context->stack_used;
@@ -4874,7 +4874,7 @@ static DMCRet dmc_return_trace(DMCContext *context,
 			       DMCHeap *heap,
 			       DMC_STACK_TYPE(UWord) *text,
 			       Eterm t,
-			       int *constant)
+			       bool *constant)
 {
     Eterm *p = tuple_val(t);
     
@@ -4892,7 +4892,7 @@ static DMCRet dmc_return_trace(DMCContext *context,
 	RETURN_TERM_ERROR("Special form 'return_trace' called with "
 			  "arguments in %T.", t, context, *constant);
     }
-    *constant = 0;
+    *constant = false;
     DMC_PUSH(*text, matchSetReturnTrace); /* Pushes 'true' on the stack */
     if (++context->stack_used > context->stack_need)
 	context->stack_need = context->stack_used;
@@ -4903,7 +4903,7 @@ static DMCRet dmc_exception_trace(DMCContext *context,
 			       DMCHeap *heap,
 			       DMC_STACK_TYPE(UWord) *text,
 			       Eterm t,
-			       int *constant)
+                               bool *constant)
 {
     Eterm *p = tuple_val(t);
     
@@ -4921,55 +4921,56 @@ static DMCRet dmc_exception_trace(DMCContext *context,
 	RETURN_TERM_ERROR("Special form 'exception_trace' called with "
 			  "arguments in %T.", t, context, *constant);
     }
-    *constant = 0;
+    *constant = false;
     DMC_PUSH(*text, matchSetExceptionTrace); /* Pushes 'true' on the stack */
     if (++context->stack_used > context->stack_need)
 	context->stack_need = context->stack_used;
     return retOk;
 }
 
-static int check_trace(const char* op,
+static bool check_trace(const char* op,
                        DMCContext *context,
-                       int *constant,
+                       bool *constant,
                        int need_cflags,
-                       int allow_in_guard,
+                       bool allow_in_guard,
                        DMCRet* retp)
 {
     if (!(context->cflags & DCOMP_TRACE)) {
 	*retp = RETURN_ERROR_X(-1, context, *constant, "Special form '%s' "
                                "used in wrong dialect.", op);
-        return 0;
+        return false;
     }
     if ((context->cflags & need_cflags) != need_cflags) {
         *retp = RETURN_ERROR_X(-1, context, *constant, "Special form '%s' "
                                "not allow for this trace event.", op);
-        return 0;
+        return false;
     }
     if (context->is_guard && !allow_in_guard) {
         *retp = RETURN_ERROR_X(-1, context, *constant, "Special form '%s' "
                                "called in guard context.", op);
-        return 0;
+        return false;
     }
-    return 1;
+    return true;
 }
 
 static DMCRet dmc_is_seq_trace(DMCContext *context,
 			       DMCHeap *heap,
 			       DMC_STACK_TYPE(UWord) *text,
 			       Eterm t,
-			       int *constant)
+                               bool *constant)
 {
     Eterm *p = tuple_val(t);
     DMCRet ret;
     
-    if (!check_trace("is_seq_trace", context, constant, DCOMP_ALLOW_TRACE_OPS, 1, &ret))
+    if (!check_trace("is_seq_trace", context, constant, DCOMP_ALLOW_TRACE_OPS,
+                     true, &ret))
         return ret;
 
     if (p[0] != make_arityval(1)) {
 	RETURN_TERM_ERROR("Special form 'is_seq_trace' called with "
 			  "arguments in %T.", t, context, *constant);
     }
-    *constant = 0;
+    *constant = false;
     DMC_PUSH(*text, matchIsSeqTrace); 
     /* Pushes 'true' or 'false' on the stack */
     if (++context->stack_used > context->stack_need)
@@ -4981,13 +4982,14 @@ static DMCRet dmc_set_seq_token(DMCContext *context,
 				DMCHeap *heap,
 				DMC_STACK_TYPE(UWord) *text,
 				Eterm t,
-				int *constant)
+                                bool *constant)
 {
     Eterm *p = tuple_val(t);
     DMCRet ret;
-    int c;
+    bool c;
     
-    if (!check_trace("set_seq_trace", context, constant, DCOMP_ALLOW_TRACE_OPS, 0, &ret))
+    if (!check_trace("set_seq_trace", context, constant, DCOMP_ALLOW_TRACE_OPS,
+                     false, &ret))
         return ret;
 
     if (p[0] != make_arityval(3)) {
@@ -4995,7 +4997,7 @@ static DMCRet dmc_set_seq_token(DMCContext *context,
 			  "number of arguments in %T.", t, context, 
 			  *constant);
     }
-    *constant = 0;
+    *constant = false;
     if ((ret = dmc_expr(context, heap, text, p[3], &c)) != retOk) {
 	return ret;
     }
@@ -5021,12 +5023,13 @@ static DMCRet dmc_get_seq_token(DMCContext *context,
 				DMCHeap *heap,
 				DMC_STACK_TYPE(UWord) *text,
 				Eterm t,
-				int *constant)
+				bool *constant)
 {
     Eterm *p = tuple_val(t);
     DMCRet ret;
 
-    if (!check_trace("get_seq_token", context, constant, DCOMP_ALLOW_TRACE_OPS, 0, &ret))
+    if (!check_trace("get_seq_token", context, constant, DCOMP_ALLOW_TRACE_OPS,
+                     false, &ret))
         return ret;
 
     if (p[0] != make_arityval(1)) {
@@ -5035,7 +5038,7 @@ static DMCRet dmc_get_seq_token(DMCContext *context,
 			  *constant);
     }
 
-    *constant = 0;
+    *constant = false;
     DMC_PUSH(*text, matchGetSeqToken);
     if (++context->stack_used > context->stack_need)
  	context->stack_need = context->stack_used;
@@ -5048,11 +5051,11 @@ static DMCRet dmc_display(DMCContext *context,
 			  DMCHeap *heap,
 			  DMC_STACK_TYPE(UWord) *text,
 			  Eterm t,
-			  int *constant)
+			  bool *constant)
 {
     Eterm *p = tuple_val(t);
     DMCRet ret;
-    int c;
+    bool c;
     
 
     if (!(context->cflags & DCOMP_TRACE)) {
@@ -5071,7 +5074,7 @@ static DMCRet dmc_display(DMCContext *context,
 			  "number of arguments in %T.", t, context, 
 			  *constant);
     }
-    *constant = 0;
+    *constant = false;
     if ((ret = dmc_expr(context, heap, text, p[2], &c)) != retOk) {
 	return ret;
     }
@@ -5087,19 +5090,20 @@ static DMCRet dmc_process_dump(DMCContext *context,
 			       DMCHeap *heap,
 			       DMC_STACK_TYPE(UWord) *text,
 			       Eterm t,
-			       int *constant)
+			       bool *constant)
 {
     Eterm *p = tuple_val(t);
     DMCRet ret;
 
-    if (!check_trace("process_dump", context, constant, DCOMP_ALLOW_TRACE_OPS, 0, &ret))
+    if (!check_trace("process_dump", context, constant, DCOMP_ALLOW_TRACE_OPS,
+                     false, &ret))
         return ret;
 
     if (p[0] != make_arityval(1)) {
 	RETURN_TERM_ERROR("Special form 'process_dump' called with "
 			  "arguments in %T.", t, context, *constant);
     }
-    *constant = 0;
+    *constant = false;
     DMC_PUSH(*text, matchProcessDump); /* Creates binary */
     if (++context->stack_used > context->stack_need)
 	context->stack_need = context->stack_used;
@@ -5110,19 +5114,20 @@ static DMCRet dmc_enable_trace(DMCContext *context,
 			       DMCHeap *heap,
 			       DMC_STACK_TYPE(UWord) *text,
 			       Eterm t,
-			       int *constant)
+			       bool *constant)
 {
     Eterm *p = tuple_val(t);
     Uint a = arityval(*p);
     DMCRet ret;
-    int c;
+    bool c;
     
-    if (!check_trace("enable_trace", context, constant, DCOMP_ALLOW_TRACE_OPS, 0, &ret))
+    if (!check_trace("enable_trace", context, constant, DCOMP_ALLOW_TRACE_OPS,
+                     false, &ret))
         return ret;
 
     switch (a) {
     case 2:
-	*constant = 0;
+	*constant = false;
 	if ((ret = dmc_expr(context, heap, text, p[2], &c)) != retOk) {
 	    return ret;
 	}
@@ -5133,7 +5138,7 @@ static DMCRet dmc_enable_trace(DMCContext *context,
 	/* Push as much as we remove, stack_need is untouched */
 	break;
     case 3:
-	*constant = 0;
+	*constant = false;
 	if ((ret = dmc_expr(context, heap, text, p[3], &c)) != retOk) {
 	    return ret;
 	}
@@ -5161,19 +5166,20 @@ static DMCRet dmc_disable_trace(DMCContext *context,
 				DMCHeap *heap,
 				DMC_STACK_TYPE(UWord) *text,
 				Eterm t,
-				int *constant)
+				bool *constant)
 {
     Eterm *p = tuple_val(t);
     Uint a = arityval(*p);
     DMCRet ret;
-    int c;
+    bool c;
 
-    if (!check_trace("disable_trace", context, constant, DCOMP_ALLOW_TRACE_OPS, 0, &ret))
+    if (!check_trace("disable_trace", context, constant, DCOMP_ALLOW_TRACE_OPS,
+                     false, &ret))
         return ret;
 
     switch (a) {
     case 2:
-	*constant = 0;
+	*constant = false;
 	if ((ret = dmc_expr(context, heap, text, p[2], &c)) != retOk) {
 	    return ret;
 	}
@@ -5184,7 +5190,7 @@ static DMCRet dmc_disable_trace(DMCContext *context,
 	/* Push as much as we remove, stack_need is untouched */
 	break;
     case 3:
-	*constant = 0;
+	*constant = false;
 	if ((ret = dmc_expr(context, heap, text, p[3], &c)) != retOk) {
 	    return ret;
 	}
@@ -5212,19 +5218,20 @@ static DMCRet dmc_trace(DMCContext *context,
 			DMCHeap *heap,
 			DMC_STACK_TYPE(UWord) *text,
 			Eterm t,
-			int *constant)
+			bool *constant)
 {
     Eterm *p = tuple_val(t);
     Uint a = arityval(*p);
     DMCRet ret;
-    int c;
+    bool c;
     
-    if (!check_trace("trace", context, constant, DCOMP_ALLOW_TRACE_OPS, 0, &ret))
+    if (!check_trace("trace", context, constant, DCOMP_ALLOW_TRACE_OPS,
+                     false, &ret))
         return ret;
 
     switch (a) {
     case 3:
-	*constant = 0;
+	*constant = false;
 	if ((ret = dmc_expr(context, heap, text, p[3], &c)) != retOk) {
 	    return ret;
 	}
@@ -5241,7 +5248,7 @@ static DMCRet dmc_trace(DMCContext *context,
 	--context->stack_used; /* Remove two and add one */
 	break;
     case 4:
-	*constant = 0;
+	*constant = false;
 	if ((ret = dmc_expr(context, heap, text, p[4], &c)) != retOk) {
 	    return ret;
 	}
@@ -5277,20 +5284,20 @@ static DMCRet dmc_caller(DMCContext *context,
  			 DMCHeap *heap,
 			 DMC_STACK_TYPE(UWord) *text,
  			 Eterm t,
- 			 int *constant)
+			 bool *constant)
 {
     Eterm *p = tuple_val(t);
     DMCRet ret;
      
     if (!check_trace("caller", context, constant,
-                     (DCOMP_CALL_TRACE|DCOMP_ALLOW_TRACE_OPS), 0, &ret))
+                     (DCOMP_CALL_TRACE|DCOMP_ALLOW_TRACE_OPS), false, &ret))
         return ret;
   
     if (p[0] != make_arityval(1)) {
  	RETURN_TERM_ERROR("Special form 'caller' called with "
  			  "arguments in %T.", t, context, *constant);
     }
-    *constant = 0;
+    *constant = false;
     DMC_PUSH(*text, matchCaller); /* Creates binary */
     if (++context->stack_used > context->stack_need)
  	context->stack_need = context->stack_used;
@@ -5301,20 +5308,20 @@ static DMCRet dmc_caller_line(DMCContext *context,
                          DMCHeap *heap,
                          DMC_STACK_TYPE(UWord) *text,
                          Eterm t,
-                         int *constant)
+                         bool *constant)
 {
     Eterm *p = tuple_val(t);
     DMCRet ret;
 
     if (!check_trace("caller_line", context, constant,
-                     (DCOMP_CALL_TRACE|DCOMP_ALLOW_TRACE_OPS), 0, &ret))
+                     (DCOMP_CALL_TRACE|DCOMP_ALLOW_TRACE_OPS), false, &ret))
         return ret;
 
     if (p[0] != make_arityval(1)) {
         RETURN_TERM_ERROR("Special form 'caller_line' called with "
                           "arguments in %T.", t, context, *constant);
     }
-    *constant = 0;
+    *constant = false;
     DMC_PUSH(*text, matchCallerLine); /* Creates binary */
     if (++context->stack_used > context->stack_need)
         context->stack_need = context->stack_used;
@@ -5325,7 +5332,7 @@ static DMCRet dmc_current_stacktrace(DMCContext *context,
                                     DMCHeap *heap,
                                     DMC_STACK_TYPE(UWord) *text,
                                     Eterm t,
-                                    int *constant)
+                                    bool *constant)
 {
     const Eterm *p = tuple_val(t);
     Uint a = arityval(*p);
@@ -5333,17 +5340,17 @@ static DMCRet dmc_current_stacktrace(DMCContext *context,
     int depth;
 
     if (!check_trace("current_stacktrace", context, constant,
-                    (DCOMP_CALL_TRACE|DCOMP_ALLOW_TRACE_OPS), 0, &ret))
+                    (DCOMP_CALL_TRACE|DCOMP_ALLOW_TRACE_OPS), false, &ret))
         return ret;
 
     switch (a) {
     case 1:
-        *constant = 0;
+        *constant = false;
         do_emit_constant(context, text, make_small(erts_backtrace_depth));
         DMC_PUSH(*text, matchCurrentStacktrace);
         break;
     case 2:
-        *constant = 0;
+        *constant = false;
 
         if (!is_small(p[2])) {
             RETURN_ERROR("Special form 'current_stacktrace' called with non "
@@ -5376,13 +5383,13 @@ static DMCRet dmc_silent(DMCContext *context,
  			 DMCHeap *heap,
 			 DMC_STACK_TYPE(UWord) *text,
  			 Eterm t,
- 			 int *constant)
+			 bool *constant)
 {
     Eterm *p = tuple_val(t);
     DMCRet ret;
-    int c;
+    bool c;
      
-    if (!check_trace("silent", context, constant, DCOMP_ALLOW_TRACE_OPS, 0, &ret))
+    if (!check_trace("silent", context, constant, DCOMP_ALLOW_TRACE_OPS, false, &ret))
         return ret;
   
     if (p[0] != make_arityval(2)) {
@@ -5390,7 +5397,7 @@ static DMCRet dmc_silent(DMCContext *context,
 			  "number of arguments in %T.", t, context, 
 			  *constant);
     }
-    *constant = 0;
+    *constant = false;
     if ((ret = dmc_expr(context, heap, text, p[2], &c)) != retOk) {
 	return ret;
     }
@@ -5410,11 +5417,11 @@ static DMCRet dmc_fun(DMCContext *context,
 		       DMCHeap *heap,
 		       DMC_STACK_TYPE(UWord) *text,
 		       Eterm t,
-		       int *constant)
+                       bool *constant)
 {
     Eterm *p = tuple_val(t);
     Uint a = arityval(*p);
-    int c;
+    bool c;
     int i;
     DMCRet ret;
     DMCGuardBif *b;
@@ -5506,7 +5513,7 @@ static DMCRet dmc_fun(DMCContext *context,
 	}
     }	
 
-    *constant = 0;
+    *constant = false;
 
     for (i = a; i > 1; --i) {
 	if ((ret = dmc_expr(context, heap, text, p[i], &c)) != retOk)
@@ -5542,7 +5549,7 @@ static DMCRet dmc_expr(DMCContext *context,
 		       DMCHeap *heap,
 		       DMC_STACK_TYPE(UWord) *text,
 		       Eterm t,
-		       int *constant)
+                       bool *constant)
 {
     DMCRet ret;
     Eterm tmp;
@@ -5603,7 +5610,7 @@ static DMCRet dmc_expr(DMCContext *context,
 	/* Fall through */
     default:
     simple_term:
-	*constant = 1;
+	*constant = true;
     }
     return retOk;
 }
@@ -5615,7 +5622,7 @@ static DMCRet compile_guard_expr(DMCContext *context,
 				 Eterm l)
 {
     DMCRet ret;
-    int constant;
+    bool constant;
     Eterm t;
 
     if (l != NIL) {
@@ -5626,7 +5633,7 @@ static DMCRet compile_guard_expr(DMCContext *context,
 	    DMC_PUSH(*text, matchCatch);
 	}
 	while (is_list(l)) {
-	    constant = 0;
+	    constant = false;
 	    t = CAR(list_val(l));
 	    if ((ret = dmc_expr(context, heap, text, t, &constant)) !=
 		retOk)
@@ -5784,14 +5791,14 @@ static int match_compact(ErlHeapFragment *expr, DMCErrInfo *err_info)
 /*
  ** Simple size object that takes care of function calls and constant tuples
  */
-static Uint my_size_object(Eterm t, int is_hashmap_node)
+static Uint my_size_object(Eterm t, bool is_hashmap_node)
 {
     Uint sum = 0;
     Eterm *p;
     switch (t & _TAG_PRIMARY_MASK) {
     case TAG_PRIMARY_LIST:
-	sum += 2 + my_size_object(CAR(list_val(t)), 0) +
-	    my_size_object(CDR(list_val(t)), 0);
+	sum += 2 + my_size_object(CAR(list_val(t)), false) +
+	    my_size_object(CDR(list_val(t)), false);
 	break;
     case TAG_PRIMARY_BOXED:
         if (is_tuple(t)) {
@@ -5816,7 +5823,7 @@ static Uint my_size_object(Eterm t, int is_hashmap_node)
             n = arityval(tpl[0]);
             sum += 1 + n;
             for (i = 1; i <= n; ++i)
-                sum += my_size_object(tpl[i], 0);
+                sum += my_size_object(tpl[i], false);
             break;
         } else if (is_map(t)) {
             if (is_flatmap(t)) {
@@ -5829,7 +5836,7 @@ static Uint my_size_object(Eterm t, int is_hashmap_node)
                 n = arityval(p[0]);
                 sum += 1 + n;
                 for (int i = 1; i <= n; ++i)
-                    sum += my_size_object(p[i], 0);
+                    sum += my_size_object(p[i], false);
 
                 /* Calculate size of values */
                 p = (Eterm *)mp;
@@ -5837,7 +5844,7 @@ static Uint my_size_object(Eterm t, int is_hashmap_node)
                 sum += n + 3;
                 p += 3; /* hdr + size + keys words */
                 while (n--) {
-                    sum += my_size_object(*p++, 0);
+                    sum += my_size_object(*p++, false);
                 }
             } else {
                 Eterm *head = (Eterm *)hashmap_val(t);
@@ -5849,7 +5856,7 @@ static Uint my_size_object(Eterm t, int is_hashmap_node)
                 head += 1 + header_arity(hdr);
 
                 while(sz-- > 0) {
-                    sum += my_size_object(head[sz], 1);
+                    sum += my_size_object(head[sz], true);
                 }
             }
             break;
@@ -5863,15 +5870,15 @@ static Uint my_size_object(Eterm t, int is_hashmap_node)
 }
 
 static Eterm my_copy_struct(Eterm t, Eterm **hp, ErlOffHeap* off_heap,
-                            int is_hashmap_node)
+                            bool is_hashmap_node)
 {
     Eterm ret = NIL, a, b;
     Eterm *p;
     Uint sz;
     switch (t & _TAG_PRIMARY_MASK) {
     case TAG_PRIMARY_LIST:
-	a = my_copy_struct(CAR(list_val(t)), hp, off_heap, 0);
-	b = my_copy_struct(CDR(list_val(t)), hp, off_heap, 0);
+	a = my_copy_struct(CAR(list_val(t)), hp, off_heap, false);
+	b = my_copy_struct(CDR(list_val(t)), hp, off_heap, false);
 	ret = CONS(*hp, a, b);
 	*hp += 2;
 	break;
@@ -5907,7 +5914,7 @@ static Eterm my_copy_struct(Eterm t, Eterm **hp, ErlOffHeap* off_heap,
                 *hp += n + 1;
                 *savep++ = tpl[0];
                 for(i = 1; i <= n; ++i)
-                    *savep++ = my_copy_struct(tpl[i], hp, off_heap, 0);
+                    *savep++ = my_copy_struct(tpl[i], hp, off_heap, false);
             }
 
         } else if (is_map(t)) {
@@ -5930,7 +5937,7 @@ static Eterm my_copy_struct(Eterm t, Eterm **hp, ErlOffHeap* off_heap,
                     *hp += n + 1;
                     *savep++ = make_arityval(n);
                     for(i = 1; i <= n; ++i)
-                        *savep++ = my_copy_struct(p[i], hp, off_heap, 0);
+                        *savep++ = my_copy_struct(p[i], hp, off_heap, false);
                 }
                 savep = *hp;
                 ret = make_flatmap(savep);
@@ -5942,7 +5949,7 @@ static Eterm my_copy_struct(Eterm t, Eterm **hp, ErlOffHeap* off_heap,
                 *savep++ = keys;
                 p += 3; /* hdr + size + keys words */
                 for (i = 0; i < n; i++)
-                    *savep++ = my_copy_struct(p[i], hp, off_heap, 0);
+                    *savep++ = my_copy_struct(p[i], hp, off_heap, false);
                 erts_usort_flatmap((flatmap_t*)flatmap_val(ret));
             } else {
                 Eterm *head = hashmap_val(t);
@@ -5959,7 +5966,7 @@ static Eterm my_copy_struct(Eterm t, Eterm **hp, ErlOffHeap* off_heap,
                     *savep++ = *head++;  /* map size */
 
                 for (int i = 0; i < sz; i++) {
-                    *savep++ = my_copy_struct(head[i],hp,off_heap, 1);
+                    *savep++ = my_copy_struct(head[i],hp,off_heap, true);
                 }
             }
 	} else {
@@ -6001,12 +6008,12 @@ BIF_RETTYPE match_spec_test_3(BIF_ALIST_3)
     } else
 #endif
     if (BIF_ARG_3 == am_trace) {
-	res = match_spec_test(BIF_P, BIF_ARG_1, BIF_ARG_2, 1);
+	res = match_spec_test(BIF_P, BIF_ARG_1, BIF_ARG_2, true);
 	if (is_value(res)) {
 	    BIF_RET(res);
 	}
     } else if (BIF_ARG_3 == am_table) {
-	res = match_spec_test(BIF_P, BIF_ARG_1, BIF_ARG_2, 0);
+	res = match_spec_test(BIF_P, BIF_ARG_1, BIF_ARG_2, false);
 	if (is_value(res)) {
 	    BIF_RET(res);
 	}
@@ -6014,7 +6021,7 @@ BIF_RETTYPE match_spec_test_3(BIF_ALIST_3)
     BIF_ERROR(BIF_P, BADARG);
 }
 
-static Eterm match_spec_test(Process *p, Eterm against, Eterm spec, int trace)
+static Eterm match_spec_test(Process *p, Eterm against, Eterm spec, bool trace)
 {
     Eterm lint_res;
     Binary *mps;
@@ -6183,7 +6190,7 @@ void db_match_dis(Binary *bp)
     UWord *t = prog->text;
     Uint n;
     Eterm p;
-    int first;
+    bool first;
     ErlHeapFragment *tmp;
 
     while (t < prog->prog_end) {
@@ -6290,10 +6297,10 @@ void db_match_dis(Binary *bp)
 		}
 
 		erts_printf("EqRef\t(%d) {", (int) ERTS_REF_NUMBERS);
-		first = 1;
+		first = true;
 		for (ri = 0; ri < ERTS_REF_NUMBERS; ++ri) {
 		    if (first)
-			first = 0;
+			first = false;
 		    else
 			erts_printf(", ");
 #if defined(ARCH_64)
@@ -6312,11 +6319,11 @@ void db_match_dis(Binary *bp)
 		Eterm *et = (Eterm *) t;
 		t += n+1;
 		erts_printf("EqBig\t(%d) {", (int) n);
-		first = 1;
+		first = true;
 		++n;
 		while (n--) {
 		    if (first)
-			first = 0;
+			first = false;
 		    else
 			erts_printf(", ");
 #if defined(ARCH_64)
@@ -6554,10 +6561,10 @@ void db_match_dis(Binary *bp)
 	}
     }
     erts_printf("\n\nterm_save: {");
-    first = 1;
+    first = true;
     for (tmp = prog->term_save; tmp; tmp = tmp->next) {
 	if (first)
-	    first = 0;
+	    first = false;
 	else
 	    erts_printf(", ");
 	erts_printf("%p", tmp);
diff --git a/erts/emulator/beam/erl_db_util.h b/erts/emulator/beam/erl_db_util.h
index 3398759733..badc80b81c 100644
--- a/erts/emulator/beam/erl_db_util.h
+++ b/erts/emulator/beam/erl_db_util.h
@@ -21,6 +21,7 @@
 #ifndef _DB_UTIL_H
 #define _DB_UTIL_H
 
+#include <stdbool.h>
 #include "erl_flxctr.h"
 #include "global.h"
 #include "erl_message.h"
@@ -137,7 +138,7 @@ typedef struct db_table_method
 		   Eterm* ret);
     int (*db_put)(DbTable* tb, /* [in out] */ 
 		  Eterm obj,
-		  int key_clash_fail, /* DB_ERROR_BADKEY if key exists */
+                  bool key_clash_fail, /* DB_ERROR_BADKEY if key exists */
                   SWord *consumed_reds_p);
     int (*db_get)(Process* p, 
 		  DbTable* tb, /* [in out] */ 
@@ -227,7 +228,7 @@ typedef struct db_table_method
     
     void (*db_print)(fmtfn_t to,
 		     void* to_arg, 
-		     int show, 
+                     bool show,
 		     DbTable* tb /* [in out] */ );
 
     void (*db_foreach_offheap)(DbTable* db,  /* [in out] */ 
@@ -235,21 +236,21 @@ typedef struct db_table_method
 			       void *arg);
 
     /* Lookup a dbterm for updating. Return false if not found. */
-    int (*db_lookup_dbterm)(Process *, DbTable *, Eterm key, Eterm obj,
+    bool (*db_lookup_dbterm)(Process *, DbTable *, Eterm key, Eterm obj,
                             DbUpdateHandle* handle);
 
     /* Must be called for each db_lookup_dbterm that returned true, even if
     ** dbterm was not updated. If the handle was of a new object and cret is
     ** not DB_ERROR_NONE, the object is removed from the table. */
     void (*db_finalize_dbterm)(int cret, DbUpdateHandle* handle);
-    void* (*db_eterm_to_dbterm)(int compress, int keypos, Eterm obj);
+    void* (*db_eterm_to_dbterm)(bool compress, int keypos, Eterm obj);
     void* (*db_dbterm_list_append)(void* last_term, void* db_term);
     void* (*db_dbterm_list_remove_first)(void** list);
     int (*db_put_dbterm)(DbTable* tb, /* [in out] */
                          void* obj,
-                         int key_clash_fail, /* DB_ERROR_BADKEY if key exists */
+                         bool key_clash_fail, /* DB_ERROR_BADKEY if key exists */
                          SWord *consumed_reds_p);
-    void (*db_free_dbterm)(int compressed, void* obj);
+    void (*db_free_dbterm)(bool compressed, void* obj);
     Eterm (*db_get_dbterm_key)(DbTable* tb, void* db_term);
     int (*db_get_binary_info)(Process*, DbTable* tb, Eterm key, Eterm* ret);
     /* Raw first/next same as first/next but also return pseudo deleted keys.
@@ -283,7 +284,7 @@ typedef struct db_fixation {
     /* Node in fixing_procs tree */
     struct {
         struct db_fixation *left, *right, *parent;
-        int is_red;
+        bool is_red;
         Process* p;
     } procs;
 
@@ -316,7 +317,7 @@ typedef struct db_table_common {
     DbTableList owned;
     erts_rwmtx_t rwlock;  /* rw lock on table */
     erts_mtx_t fixlock;   /* Protects fixing_procs and time */
-    int is_thread_safe;       /* No fine locking inside table needed */
+    bool is_thread_safe;       /* No fine locking inside table needed */
     Uint32 type;              /* table type, *read only* after creation */
     Eterm owner;              /* Pid of the creator */
     Eterm heir;               /* Pid of the heir */
@@ -339,7 +340,7 @@ typedef struct db_table_common {
     /* All 32-bit fields */
     Uint32 status;            /* bit masks defined  below */
     int keypos;               /* defaults to 1 */
-    int compress;
+    bool compress;
 
     /* For unfinished operations that needs to be helped */
     struct ets_insert_2_list_info* continuation_ctx;
@@ -393,13 +394,13 @@ typedef struct db_table_common {
 ERTS_GLB_INLINE Eterm db_copy_key(Process* p, DbTable* tb, DbTerm* obj);
 Eterm db_copy_from_comp(DbTableCommon* tb, DbTerm* bp, Eterm** hpp,
 			ErlOffHeap* off_heap);
-int db_eq_comp(DbTableCommon* tb, Eterm a, DbTerm* b);
+bool db_eq_comp(DbTableCommon* tb, Eterm a, DbTerm* b);
 DbTerm* db_alloc_tmp_uncompressed(DbTableCommon* tb, DbTerm* org);
 void db_free_tmp_uncompressed(DbTerm* obj);
 
 ERTS_GLB_INLINE Eterm db_copy_object_from_ets(DbTableCommon* tb, DbTerm* bp,
 					      Eterm** hpp, ErlOffHeap* off_heap);
-ERTS_GLB_INLINE int db_eq(DbTableCommon* tb, Eterm a, DbTerm* b);
+ERTS_GLB_INLINE bool db_eq(DbTableCommon* tb, Eterm a, DbTerm* b);
 Eterm db_do_read_element(DbUpdateHandle* handle, Sint position);
 
 #if ERTS_GLB_INLINE_INCL_FUNC_DEF
@@ -428,7 +429,7 @@ ERTS_GLB_INLINE Eterm db_copy_object_from_ets(DbTableCommon* tb, DbTerm* bp,
     }
 }
 
-ERTS_GLB_INLINE int db_eq(DbTableCommon* tb, Eterm a, DbTerm* b)
+ERTS_GLB_INLINE bool db_eq(DbTableCommon* tb, Eterm a, DbTerm* b)
 {
     if (!tb->compress) {
 	return EQ(a, make_tuple(b->tpl));
@@ -462,7 +463,7 @@ void db_initialize_util(void);
 Eterm db_getkey(int keypos, Eterm obj);
 void db_cleanup_offheap_comp(DbTerm* p);
 void db_free_term(DbTable *tb, void* basep, Uint offset);
-void db_free_term_no_tab(int compress, void* basep, Uint offset);
+void db_free_term_no_tab(bool compress, void* basep, Uint offset);
 Uint db_term_size(DbTable *tb, void* basep, Uint offset);
 void* db_store_term(DbTableCommon *tb, DbTerm* old, Uint offset, Eterm obj);
 void* db_store_term_comp(DbTableCommon *tb, /*May be NULL*/
@@ -472,7 +473,7 @@ void* db_store_term_comp(DbTableCommon *tb, /*May be NULL*/
 Eterm db_copy_element_from_ets(DbTableCommon* tb, Process* p, DbTerm* obj,
 			       Uint pos, Eterm** hpp, Uint extra);
 int db_has_map(Eterm obj);
-int db_is_fully_bound(Eterm obj);
+bool db_is_fully_bound(Eterm obj);
 int db_is_variable(Eterm obj);
 void db_do_update_element(DbUpdateHandle* handle,
 			  Sint position,
@@ -481,7 +482,7 @@ void db_finalize_resize(DbUpdateHandle* handle, Uint offset);
 Eterm db_add_counter(Eterm** hpp, Eterm counter, Eterm incr);
 Binary *db_match_set_compile(Process *p, Eterm matchexpr, 
 			     Uint flags, Uint *freasonp);
-int db_match_keeps_key(int keypos, Eterm match, Eterm guard, Eterm body);
+bool db_match_keeps_key(int keypos, Eterm match, Eterm guard, Eterm body);
 int erts_db_match_prog_destructor(Binary *);
 
 typedef struct match_prog {
diff --git a/erts/emulator/beam/erl_flxctr.c b/erts/emulator/beam/erl_flxctr.c
index 35c4de1a27..e2224e2fd6 100644
--- a/erts/emulator/beam/erl_flxctr.c
+++ b/erts/emulator/beam/erl_flxctr.c
@@ -215,7 +215,7 @@ void erts_flxctr_setup(int decentralized_counter_groups)
 }
 
 void erts_flxctr_init(ErtsFlxCtr* c,
-                      int is_decentralized,
+                      bool is_decentralized,
                       Uint nr_of_counters,
                       ErtsAlcType_t alloc_type)
 {
@@ -341,12 +341,13 @@ Sint erts_flxctr_get_snapshot_result_after_trap(Eterm result_holder,
     return data->result[counter_nr];
 }
 
-int erts_flxctr_is_snapshot_result(Eterm term)
+bool erts_flxctr_is_snapshot_result(Eterm term)
 {
     if (is_internal_magic_ref(term)) {
         Binary* bin = erts_magic_ref2bin(term);
         return ERTS_MAGIC_BIN_DESTRUCTOR(bin) ==  erts_flxctr_read_ctx_bin_dtor;
-    } else return 0;
+    } else
+        return false;
 }
 
 Sint erts_flxctr_read_approx(ErtsFlxCtr* c,
@@ -365,7 +366,7 @@ Sint erts_flxctr_read_approx(ErtsFlxCtr* c,
     }
 }
 
-int erts_flxctr_is_snapshot_ongoing(ErtsFlxCtr* c)
+bool erts_flxctr_is_snapshot_ongoing(ErtsFlxCtr* c)
 {
     return c->is_decentralized &&
         (ERTS_FLXCTR_SNAPSHOT_NOT_ONGOING !=
diff --git a/erts/emulator/beam/erl_flxctr.h b/erts/emulator/beam/erl_flxctr.h
index 6065a5cb3a..b1924c4c75 100644
--- a/erts/emulator/beam/erl_flxctr.h
+++ b/erts/emulator/beam/erl_flxctr.h
@@ -48,6 +48,7 @@
 #include "erl_binary.h"
 #include "bif.h"
 #include <stddef.h>
+#include <stdbool.h>
 
 /* Public Interface */
 
@@ -56,7 +57,7 @@
 
 typedef struct {
     int nr_of_counters;
-    int is_decentralized;
+    bool is_decentralized;
     union {
         erts_atomic_t counters_ptr;
         erts_atomic_t counters[1];
@@ -82,13 +83,13 @@ void erts_flxctr_setup(int decentralized_counter_groups);
  * ErtsFlxCtr that should be operated on.
  *
  * @param c The counter to initialize
- * @param is_decentralized Non-zero value to make c decentralized
+ * @param is_decentralized true to make c decentralized
  * @param nr_of_counters The number of counters included in c
  *                       (max ERTS_FLXCTR_ATOMICS_PER_CACHE_LINE)
  * @param alloc_type 
  */
 void erts_flxctr_init(ErtsFlxCtr* c,
-                      int is_decentralized,
+                      bool is_decentralized,
                       Uint nr_of_counters,
                       ErtsAlcType_t alloc_type);
 
@@ -243,9 +244,9 @@ erts_flxctr_snapshot(ErtsFlxCtr* c,
  *
  * @param term The term to check 
  *
- * @return A nonzero value iff the term is a snapshot result
+ * @return true iff the term is a snapshot result
  */
-int erts_flxctr_is_snapshot_result(Eterm term);
+bool erts_flxctr_is_snapshot_result(Eterm term);
 
 /**
  * @brief Returns the result of a snapshot for a counter given a
@@ -269,10 +270,10 @@ void erts_flxctr_reset(ErtsFlxCtr* c,
  * @brief Checks if a snapshot operation is active (snapshots are
  * initiated with the erts_flxctr_snapshot function).
  *
- * @return nonzero value iff a snapshot was active at some point
+ * @return true iff a snapshot was active at some point
  * between the invocation and return of the function
  */
-int erts_flxctr_is_snapshot_ongoing(ErtsFlxCtr* c);
+bool erts_flxctr_is_snapshot_ongoing(ErtsFlxCtr* c);
 
 /**
  * @brief This function checks if a snapshot operation is ongoing
diff --git a/erts/emulator/beam/erl_init.c b/erts/emulator/beam/erl_init.c
index 45c10d1e23..26884fcfda 100644
--- a/erts/emulator/beam/erl_init.c
+++ b/erts/emulator/beam/erl_init.c
@@ -1279,8 +1279,8 @@ early_init(int *argc, char **argv) /*
     /* Creates threads on Windows that depend on the arguments, so has to be after erl_sys_args */
     erl_sys_init();
 
-    erts_ets_realloc_always_moves = 0;
-    erts_ets_always_compress = 0;
+    erts_ets_realloc_always_moves = false;
+    erts_ets_always_compress = false;
     erts_dist_buf_busy_limit = ERTS_DE_BUSY_LIMIT;
 
     return ncpu;
@@ -1649,7 +1649,7 @@ erl_start(int argc, char **argv)
 
 	case 'e':
 	    if (sys_strcmp("c", argv[i]+2) == 0) {
-		erts_ets_always_compress = 1;
+		erts_ets_always_compress = true;
 	    }
 	    else {
 		/* set maximum number of ets tables */
@@ -2244,7 +2244,7 @@ erl_start(int argc, char **argv)
 		/* already handled */
 	    }
 	    else {
-		erts_ets_realloc_always_moves = 1;
+		erts_ets_realloc_always_moves = true;
 	    }
 	    break;
 	}
diff --git a/erts/emulator/beam/erl_node_tables.c b/erts/emulator/beam/erl_node_tables.c
index a249ecb538..0e4b9f6a2d 100644
--- a/erts/emulator/beam/erl_node_tables.c
+++ b/erts/emulator/beam/erl_node_tables.c
@@ -2176,7 +2176,7 @@ setup_reference_table(void)
     }
 
     /* Insert all ets tables */
-    erts_db_foreach_table(insert_ets_table, NULL, 0);
+    erts_db_foreach_table(insert_ets_table, NULL, false);
     erts_db_foreach_thr_prgr_offheap(insert_ets_offheap_thr_prgr, NULL);
 
     /* Insert all bif timers */
-- 
2.35.3

openSUSE Build Service is sponsored by