File 2024-erts-Remove-old-unused-functions.patch of Package erlang

From e6437e926340c3024449b83826f8013d187caaed Mon Sep 17 00:00:00 2001
From: Lukas Larsson <lukas@erlang.org>
Date: Wed, 3 May 2017 17:18:44 +0200
Subject: [PATCH] erts: Remove old unused functions

The functions have been found using: https://github.com/caolanm/callcatcher
---
 erts/emulator/beam/big.c              | 25 ----------------------
 erts/emulator/beam/big.h              |  2 --
 erts/emulator/beam/erl_alloc.c        | 22 --------------------
 erts/emulator/beam/erl_alloc.h        |  7 -------
 erts/emulator/beam/erl_cpu_topology.c | 11 ----------
 erts/emulator/beam/erl_cpu_topology.h |  8 -------
 erts/emulator/beam/erl_db_util.c      |  5 -----
 erts/emulator/beam/erl_gc.c           |  2 +-
 erts/emulator/beam/erl_init.c         | 24 ---------------------
 erts/emulator/beam/erl_port_task.c    |  7 -------
 erts/emulator/beam/erl_port_task.h    |  1 -
 erts/emulator/beam/erl_process.c      | 39 -----------------------------------
 erts/emulator/beam/erl_process.h      |  7 -------
 erts/emulator/beam/global.h           |  2 --
 14 files changed, 1 insertion(+), 161 deletions(-)

diff --git a/erts/emulator/beam/big.c b/erts/emulator/beam/big.c
index 4baee7900..1f6feade1 100644
--- a/erts/emulator/beam/big.c
+++ b/erts/emulator/beam/big.c
@@ -2266,21 +2266,6 @@ Eterm big_minus(Eterm x, Eterm y, Eterm *r)
 }
 
 /*
-** Subtract a digit from big number
-*/
-Eterm big_minus_small(Eterm x, Eterm y, Eterm *r)
-{
-    Eterm* xp = big_val(x);
-
-    if (BIG_SIGN(xp))
-	return big_norm(r, D_add(BIG_V(xp),BIG_SIZE(xp), (ErtsDigit) y, BIG_V(r)), 
-			(short) BIG_SIGN(xp));
-    else
-	return big_norm(r, D_sub(BIG_V(xp),BIG_SIZE(xp), (ErtsDigit) y, BIG_V(r)), 
-			(short) BIG_SIGN(xp));
-}
-
-/*
 ** Multiply smallnums
 */
 
@@ -2412,16 +2397,6 @@ Eterm big_rem(Eterm x, Eterm y, Eterm *r)
     }
 }
 
-Eterm big_neg(Eterm x, Eterm *r)
-{
-    Eterm* xp = big_val(x);
-    dsize_t xsz = BIG_SIZE(xp);
-    short xsgn = BIG_SIGN(xp);
-    
-    MOVE_DIGITS(BIG_V(r), BIG_V(xp), xsz);
-    return big_norm(r, xsz, (short) !xsgn);
-}
-
 Eterm big_band(Eterm x, Eterm y, Eterm *r)
 {
     Eterm* xp = big_val(x);
diff --git a/erts/emulator/beam/big.h b/erts/emulator/beam/big.h
index 4a96d971c..258038a15 100644
--- a/erts/emulator/beam/big.h
+++ b/erts/emulator/beam/big.h
@@ -118,9 +118,7 @@ Eterm big_minus(Eterm, Eterm, Eterm*);
 Eterm big_times(Eterm, Eterm, Eterm*);
 Eterm big_div(Eterm, Eterm, Eterm*);
 Eterm big_rem(Eterm, Eterm, Eterm*);
-Eterm big_neg(Eterm, Eterm*);
 
-Eterm big_minus_small(Eterm, Uint, Eterm*);
 Eterm big_plus_small(Eterm, Uint, Eterm*);
 Eterm big_times_small(Eterm, Uint, Eterm*);
 
diff --git a/erts/emulator/beam/erl_alloc.c b/erts/emulator/beam/erl_alloc.c
index 71957b225..5aea917dd 100644
--- a/erts/emulator/beam/erl_alloc.c
+++ b/erts/emulator/beam/erl_alloc.c
@@ -3512,28 +3512,6 @@ void erts_allctr_wrapper_pre_unlock(void)
 }
 
 
-
-/* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *\
- * Deprecated functions                                                    *
- *                                                                         *
- * These functions are still defined since "non-OTP linked in drivers" may *
- * contain (illegal) calls to them.                                        *
-\*                                                                         */
-
-/* --- DO *NOT* USE THESE FUNCTIONS --- */
-
-void *sys_alloc(Uint sz)
-{ return erts_alloc_fnf(ERTS_ALC_T_UNDEF, sz); }
-void *sys_realloc(void *ptr, Uint sz)
-{ return erts_realloc_fnf(ERTS_ALC_T_UNDEF, ptr, sz); }
-void sys_free(void *ptr)
-{ erts_free(ERTS_ALC_T_UNDEF, ptr); }
-void *safe_alloc(Uint sz)
-{ return erts_alloc(ERTS_ALC_T_UNDEF, sz); }
-void *safe_realloc(void *ptr, Uint sz)
-{ return erts_realloc(ERTS_ALC_T_UNDEF, ptr, sz); }
-
-
 /* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *\
  * NOTE: erts_alc_test() is only supposed to be used for testing.            *
  *                                                                           *
diff --git a/erts/emulator/beam/erl_alloc.h b/erts/emulator/beam/erl_alloc.h
index 56a3b73bf..758d529f8 100644
--- a/erts/emulator/beam/erl_alloc.h
+++ b/erts/emulator/beam/erl_alloc.h
@@ -173,13 +173,6 @@ __decl_noreturn void erts_realloc_n_enomem(ErtsAlcType_t,void*,Uint)
 __decl_noreturn void erts_alc_fatal_error(int,int,ErtsAlcType_t,...)	
      __noreturn;
 
-/* --- DO *NOT* USE THESE DEPRECATED FUNCTIONS ---    Instead use:       */
-void *safe_alloc(Uint)               __deprecated; /* erts_alloc()       */
-void *safe_realloc(void *, Uint)     __deprecated; /* erts_realloc()     */
-void  sys_free(void *)               __deprecated; /* erts_free()        */
-void *sys_alloc(Uint )               __deprecated; /* erts_alloc_fnf()   */
-void *sys_realloc(void *, Uint)      __deprecated; /* erts_realloc_fnf() */
-
 #undef ERTS_HAVE_IS_IN_LITERAL_RANGE
 #if defined(ARCH_32) || defined(ERTS_HAVE_OS_PHYSICAL_MEMORY_RESERVATION)
 #  define ERTS_HAVE_IS_IN_LITERAL_RANGE
diff --git a/erts/emulator/beam/erl_cpu_topology.c b/erts/emulator/beam/erl_cpu_topology.c
index 28aaeeb47..4347f9f2b 100644
--- a/erts/emulator/beam/erl_cpu_topology.c
+++ b/erts/emulator/beam/erl_cpu_topology.c
@@ -827,17 +827,6 @@ erts_sched_bind_atfork_child(int unbind)
     return 0;
 }
 
-char *
-erts_sched_bind_atvfork_child(int unbind)
-{
-    if (unbind) {
-	ERTS_SMP_LC_ASSERT(erts_lc_rwmtx_is_rlocked(&cpuinfo_rwmtx)
-			   || erts_lc_rwmtx_is_rwlocked(&cpuinfo_rwmtx));
-	return erts_get_unbind_from_cpu_str(cpuinfo);
-    }
-    return "false";
-}
-
 void
 erts_sched_bind_atfork_parent(int unbind)
 {
diff --git a/erts/emulator/beam/erl_cpu_topology.h b/erts/emulator/beam/erl_cpu_topology.h
index 45324ac4a..cf139d95a 100644
--- a/erts/emulator/beam/erl_cpu_topology.h
+++ b/erts/emulator/beam/erl_cpu_topology.h
@@ -85,22 +85,14 @@ void erts_sched_bind_atthrcreate_parent(int unbind);
 
 int erts_sched_bind_atfork_prepare(void);
 int erts_sched_bind_atfork_child(int unbind);
-char *erts_sched_bind_atvfork_child(int unbind);
 void erts_sched_bind_atfork_parent(int unbind);
 
 Eterm erts_fake_scheduler_bindings(Process *p, Eterm how);
 Eterm erts_debug_cpu_groups_map(Process *c_p, int groups);
 
-
 typedef void (*erts_cpu_groups_callback_t)(int,
 					   ErtsSchedulerData *,
 					   int,
 					   void *);
 
-void erts_add_cpu_groups(int groups,
-			 erts_cpu_groups_callback_t callback,
-			 void *arg);
-void erts_remove_cpu_groups(erts_cpu_groups_callback_t callback,
-			    void *arg);
-
 #endif
diff --git a/erts/emulator/beam/erl_db_util.c b/erts/emulator/beam/erl_db_util.c
index 24b22eafb..d69035cf6 100644
--- a/erts/emulator/beam/erl_db_util.c
+++ b/erts/emulator/beam/erl_db_util.c
@@ -1290,11 +1290,6 @@ int db_match_keeps_key(int keypos, Eterm match, Eterm guard, Eterm body)
     return NULL;
 }
 
-/* This is used when tracing */
-Eterm erts_match_set_lint(Process *p, Eterm matchexpr) {
-    return db_match_set_lint(p, matchexpr, DCOMP_TRACE);
-}
-
 Eterm db_match_set_lint(Process *p, Eterm matchexpr, Uint flags) 
 {
     Eterm l;
diff --git a/erts/emulator/beam/erl_gc.c b/erts/emulator/beam/erl_gc.c
index a991c2c16..6ec6be5a0 100644
--- a/erts/emulator/beam/erl_gc.c
+++ b/erts/emulator/beam/erl_gc.c
@@ -439,7 +439,7 @@ Eterm
 erts_gc_after_bif_call(Process* p, Eterm result, Eterm* regs, Uint arity)
 {
     return erts_gc_after_bif_call_lhf(p, ERTS_INVALID_HFRAG_PTR,
-				      result, regs, arity);
+                                      result, regs, arity);
 }
 
 static ERTS_INLINE void reset_active_writer(Process *p)
diff --git a/erts/emulator/beam/erl_init.c b/erts/emulator/beam/erl_init.c
index eaaf5c911..2527732eb 100644
--- a/erts/emulator/beam/erl_init.c
+++ b/erts/emulator/beam/erl_init.c
@@ -309,30 +309,6 @@ void erl_error(char *fmt, va_list args)
 
 static int early_init(int *argc, char **argv);
 
-void
-erts_short_init(void)
-{
-    
-    int ncpu;
-    int time_correction;
-    ErtsTimeWarpMode time_warp_mode;
-
-    set_default_time_adj(&time_correction,
-			 &time_warp_mode);
-    ncpu = early_init(NULL, NULL);
-    erl_init(ncpu,
-	     ERTS_DEFAULT_MAX_PROCESSES,
-	     0,
-	     ERTS_DEFAULT_MAX_PORTS,
-	     0,
-	     0,
-	     time_correction,
-	     time_warp_mode,
-	     ERTS_NODE_TAB_DELAY_GC_DEFAULT,
-	     ERTS_DB_SPNCNT_NORMAL);
-    erts_initialized = 1;
-}
-
 static void
 erl_init(int ncpu,
 	 int proc_tab_sz,
diff --git a/erts/emulator/beam/erl_port_task.c b/erts/emulator/beam/erl_port_task.c
index 4836b9e2d..55526e1d5 100644
--- a/erts/emulator/beam/erl_port_task.c
+++ b/erts/emulator/beam/erl_port_task.c
@@ -2161,13 +2161,6 @@ begin_port_cleanup(Port *pp, ErtsPortTask **execqp, int *processing_busy_q_p)
 #endif
 }
 
-int
-erts_port_is_scheduled(Port *pp)
-{
-    erts_aint32_t flags = erts_smp_atomic32_read_acqb(&pp->sched.flags);
-    return (flags & (ERTS_PTS_FLG_IN_RUNQ|ERTS_PTS_FLG_EXEC)) != 0;
-}
-
 #ifdef ERTS_SMP
 
 void
diff --git a/erts/emulator/beam/erl_port_task.h b/erts/emulator/beam/erl_port_task.h
index e3550e878..a48b492ba 100644
--- a/erts/emulator/beam/erl_port_task.h
+++ b/erts/emulator/beam/erl_port_task.h
@@ -265,7 +265,6 @@ int erts_port_task_schedule(Eterm,
 			    ErtsPortTaskType,
 			    ...);
 void erts_port_task_free_port(Port *);
-int erts_port_is_scheduled(Port *);
 ErtsProc2PortSigData *erts_port_task_alloc_p2p_sig_data(void);
 ErtsProc2PortSigData *erts_port_task_alloc_p2p_sig_data_extra(size_t extra, void **extra_ptr);
 void erts_port_task_free_p2p_sig_data(ErtsProc2PortSigData *sigdp);
diff --git a/erts/emulator/beam/erl_process.c b/erts/emulator/beam/erl_process.c
index 9947e33f4..a59457879 100644
--- a/erts/emulator/beam/erl_process.c
+++ b/erts/emulator/beam/erl_process.c
@@ -1538,12 +1538,6 @@ proclist_destroy(ErtsProcList *plp)
 }
 
 ErtsProcList *
-erts_proclist_copy(ErtsProcList *plp)
-{
-    return proclist_copy(plp);
-}
-
-ErtsProcList *
 erts_proclist_create(Process *p)
 {
     return proclist_create(p);
@@ -3275,13 +3269,6 @@ thr_prgr_fin_wait(void *vssi)
 
 static void init_aux_work_data(ErtsAuxWorkData *awdp, ErtsSchedulerData *esdp, char *dawwp);
 
-void
-erts_interupt_aux_thread_timed(ErtsMonotonicTime timeout_time)
-{
-    /* TODO only poke when needed (based on timeout_time) */
-    erts_sched_poke(ERTS_SCHED_SLEEP_INFO_IX(-1));
-}
-
 static void *
 aux_thread(void *unused)
 {
@@ -9316,17 +9303,6 @@ erts_pid2proc_not_running(Process *c_p, ErtsProcLocks c_p_locks,
 }
 
 /*
- * Like erts_pid2proc_not_running(), but hands over the process
- * in a suspended state unless (c_p is looked up).
- */
-Process *
-erts_pid2proc_suspend(Process *c_p, ErtsProcLocks c_p_locks,
-		      Eterm pid, ErtsProcLocks pid_locks)
-{
-    return pid2proc_not_running(c_p, c_p_locks, pid, pid_locks, 1);
-}
-
-/*
  * erts_pid2proc_nropt() is normally the same as
  * erts_pid2proc_not_running(). However it is only
  * to be used when 'not running' is a pure optimization,
@@ -9444,21 +9420,6 @@ handle_pend_bif_async_suspend(Process *suspendee,
     }
 }
 
-#else
-
-/*
- * Non-smp version of erts_pid2proc_suspend().
- */
-Process *
-erts_pid2proc_suspend(Process *c_p, ErtsProcLocks c_p_locks,
-		      Eterm pid, ErtsProcLocks pid_locks)
-{
-    Process *rp = erts_pid2proc(c_p, c_p_locks, pid, pid_locks);
-    if (rp)
-	erts_suspend(rp, pid_locks, NULL);
-    return rp;
-}
-
 #endif /* ERTS_SMP */
 
 /*
diff --git a/erts/emulator/beam/erl_process.h b/erts/emulator/beam/erl_process.h
index 5b35dc3c7..d6d7750a3 100644
--- a/erts/emulator/beam/erl_process.h
+++ b/erts/emulator/beam/erl_process.h
@@ -1606,7 +1606,6 @@ Uint64 erts_ensure_later_proc_interval(Uint64);
 int erts_check_nif_export_in_area(Process *p, char *start, Uint size);
 
 ErtsProcList *erts_proclist_create(Process *);
-ErtsProcList *erts_proclist_copy(ErtsProcList *);
 void erts_proclist_destroy(ErtsProcList *);
 
 ERTS_GLB_INLINE int erts_proclist_same(ErtsProcList *, Process *);
@@ -2556,10 +2555,6 @@ ERTS_TIME2REDS_IMPL__(ErtsMonotonicTime start, ErtsMonotonicTime end)
 }
 #endif
 
-Process *erts_pid2proc_suspend(Process *,
-			       ErtsProcLocks,
-			       Eterm,
-			       ErtsProcLocks);
 #ifdef ERTS_SMP
 
 Process *erts_pid2proc_not_running(Process *,
@@ -2601,8 +2596,6 @@ extern int erts_disable_proc_not_running_opt;
 
 void erts_smp_notify_inc_runq(ErtsRunQueue *runq);
 
-void erts_interupt_aux_thread_timed(ErtsMonotonicTime timeout_time);
-
 #ifdef ERTS_SMP
 void erts_sched_finish_poke(ErtsSchedulerSleepInfo *, erts_aint32_t);
 ERTS_GLB_INLINE void erts_sched_poke(ErtsSchedulerSleepInfo *ssi);
diff --git a/erts/emulator/beam/global.h b/erts/emulator/beam/global.h
index bb4d44224..d6a66ce7c 100644
--- a/erts/emulator/beam/global.h
+++ b/erts/emulator/beam/global.h
@@ -1132,7 +1132,6 @@ extern erts_tid_t erts_main_thread;
 #endif
 extern int erts_compat_rel;
 extern int erts_use_sender_punish;
-void erts_short_init(void);
 void erl_start(int, char**);
 void erts_usage(void);
 Eterm erts_preloaded(Process* p);
@@ -1439,7 +1438,6 @@ do {								\
 #define MatchSetGetSource(MPSP) erts_match_set_get_source(MPSP)
 
 extern Binary *erts_match_set_compile(Process *p, Eterm matchexpr, Eterm MFA);
-Eterm erts_match_set_lint(Process *p, Eterm matchexpr); 
 extern void erts_match_set_release_result(Process* p);
 ERTS_GLB_INLINE void erts_match_set_release_result_trace(Process* p, Eterm);
 
-- 
2.13.0

openSUSE Build Service is sponsored by