File 2238-erts-Implement-halt-0-and-halt-1-in-Erlang.patch of Package erlang

From f9cb80861f169743a96099a06d68149a91f18dfa Mon Sep 17 00:00:00 2001
From: Sverker Eriksson <sverker@erlang.org>
Date: Fri, 20 May 2016 15:58:04 +0200
Subject: [PATCH 4/7] erts: Implement halt/0 and halt/1 in Erlang

just to make things simpler.
---
 erts/emulator/beam/bif.c        | 50 +----------------------------------------
 erts/emulator/beam/bif.tab      |  2 --
 erts/preloaded/src/erlang.erl   |  8 +++----
 erts/preloaded/src/init.erl     |  1 +
 lib/hipe/cerl/erl_bif_types.erl |  6 -----
 lib/stdlib/src/erl_compile.erl  |  1 +
 lib/stdlib/src/escript.erl      |  1 +
 7 files changed, 7 insertions(+), 62 deletions(-)

diff --git a/erts/emulator/beam/bif.c b/erts/emulator/beam/bif.c
index 2a3bd4a..8147742 100644
--- a/erts/emulator/beam/bif.c
+++ b/erts/emulator/beam/bif.c
@@ -3836,59 +3836,11 @@ BIF_RETTYPE display_nl_0(BIF_ALIST_0)
 
 /**********************************************************************/
 
-/* stop the system */
-/* ARGSUSED */
-BIF_RETTYPE halt_0(BIF_ALIST_0)
-{
-    VERBOSE(DEBUG_SYSTEM,("System halted by BIF halt()\n"));
-    erts_halt(0);
-    ERTS_BIF_YIELD1(bif_export[BIF_halt_1], BIF_P, am_undefined);
-}
-
-/**********************************************************************/
 
 #define HALT_MSG_SIZE	200
 static char halt_msg[HALT_MSG_SIZE];
 
-/* stop the system with exit code */
-/* ARGSUSED */
-BIF_RETTYPE halt_1(BIF_ALIST_1)
-{
-    Uint code;
-    
-    if (term_to_Uint_mask(BIF_ARG_1, &code)) {
-	int pos_int_code = (int) (code & INT_MAX);
-	VERBOSE(DEBUG_SYSTEM,("System halted by BIF halt(%T)\n", BIF_ARG_1));
-	erts_halt(pos_int_code);
-	ERTS_BIF_YIELD1(bif_export[BIF_halt_1], BIF_P, am_undefined);
-    }
-    else if (ERTS_IS_ATOM_STR("abort", BIF_ARG_1)) {
-	VERBOSE(DEBUG_SYSTEM,("System halted by BIF halt(%T)\n", BIF_ARG_1));
-	erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
-	erts_exit(ERTS_ABORT_EXIT, "");
-    }
-    else if (is_string(BIF_ARG_1) || BIF_ARG_1 == NIL) {
-	Sint i;
-
-	if ((i = intlist_to_buf(BIF_ARG_1, halt_msg, HALT_MSG_SIZE-1)) < 0) {
-	    goto error;
-	}
-	halt_msg[i] = '\0';
-	VERBOSE(DEBUG_SYSTEM,("System halted by BIF halt(%T)\n", BIF_ARG_1));
-	erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
-	erts_exit(ERTS_DUMP_EXIT, "%s\n", halt_msg);
-    }
-    else
-	goto error;
-    return NIL;  /* Pedantic (lint does not know about erts_exit) */
- error:
-	BIF_ERROR(BIF_P, BADARG);
-}
-
-/**********************************************************************/
-
 /* stop the system with exit code and flags */
-/* ARGSUSED */
 BIF_RETTYPE halt_2(BIF_ALIST_2)
 {
     Uint code;
@@ -3924,7 +3876,7 @@ BIF_RETTYPE halt_2(BIF_ALIST_2)
 		("System halted by BIF halt(%T, %T)\n", BIF_ARG_1, BIF_ARG_2));
 	if (flush) {
 	    erts_halt(pos_int_code);
-	    ERTS_BIF_YIELD1(bif_export[BIF_halt_1], BIF_P, am_undefined);
+	    ERTS_BIF_YIELD2(bif_export[BIF_halt_2], BIF_P, am_undefined, am_undefined);
 	}
 	else {
 	    erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
diff --git a/erts/emulator/beam/bif.tab b/erts/emulator/beam/bif.tab
index 872f0f9..0650185 100644
--- a/erts/emulator/beam/bif.tab
+++ b/erts/emulator/beam/bif.tab
@@ -72,8 +72,6 @@ bif erlang:get/1
 bif erlang:get_keys/1
 bif erlang:group_leader/0
 bif erlang:group_leader/2
-bif erlang:halt/0
-bif erlang:halt/1
 bif erlang:halt/2
 bif erlang:phash/2
 bif erlang:phash2/1
diff --git a/erts/preloaded/src/erlang.erl b/erts/preloaded/src/erlang.erl
index 3d152c4..4c456bb 100644
--- a/erts/preloaded/src/erlang.erl
+++ b/erts/preloaded/src/erlang.erl
@@ -977,17 +977,15 @@ group_leader(_GroupLeader, _Pid) ->
     erlang:nif_error(undefined).
 
 %% halt/0
-%% Shadowed by erl_bif_types: erlang:halt/0
 -spec halt() -> no_return().
 halt() ->
-    erlang:nif_error(undefined).
+    erlang:halt(0, []).
 
 %% halt/1
-%% Shadowed by erl_bif_types: erlang:halt/1
 -spec halt(Status) -> no_return() when
       Status :: non_neg_integer() | 'abort' | string().
-halt(_Status) ->
-    erlang:nif_error(undefined).
+halt(Status) ->
+    erlang:halt(Status, []).
 
 %% halt/2
 %% Shadowed by erl_bif_types: erlang:halt/2
diff --git a/erts/preloaded/src/init.erl b/erts/preloaded/src/init.erl
index 04c5210..e8f02f5 100644
--- a/erts/preloaded/src/init.erl
+++ b/erts/preloaded/src/init.erl
@@ -316,6 +316,7 @@ limit_halt_string(String) ->
 %% List = [string() | atom() | pid() | number()]
 %% Any other items in List, such as tuples, are ignored when creating
 %% the string used as argument to erlang:halt/1.
+-spec crash(_, _) -> no_return().
 crash(String, List) ->
     halt(halt_string(String, List)).
 
diff --git a/lib/hipe/cerl/erl_bif_types.erl b/lib/hipe/cerl/erl_bif_types.erl
index 9453ca6..f649c6e 100644
--- a/lib/hipe/cerl/erl_bif_types.erl
+++ b/lib/hipe/cerl/erl_bif_types.erl
@@ -154,8 +154,6 @@ type(M, F, A, Xs) ->
               erl_types:erl_type().
 
 %%-- erlang -------------------------------------------------------------------
-type(erlang, halt, 0, _, _) -> t_none();
-type(erlang, halt, 1, _, _) -> t_none();
 type(erlang, halt, 2, _, _) -> t_none();
 type(erlang, exit, 1, _, _) -> t_none();
 type(erlang, error, 1, _, _) -> t_none();
@@ -2341,10 +2339,6 @@ arg_types(erlang, bit_size, 1) ->
 %% Guard bif, needs to be here.
 arg_types(erlang, byte_size, 1) ->
   [t_bitstr()];
-arg_types(erlang, halt, 0) ->
-  [];
-arg_types(erlang, halt, 1) ->
-  [t_sup([t_non_neg_fixnum(), t_atom('abort'), t_string()])];
 arg_types(erlang, halt, 2) ->
   [t_sup([t_non_neg_fixnum(), t_atom('abort'), t_string()]),
    t_list(t_tuple([t_atom('flush'), t_boolean()]))];
diff --git a/lib/stdlib/src/erl_compile.erl b/lib/stdlib/src/erl_compile.erl
index ef54076..a6ae398 100644
--- a/lib/stdlib/src/erl_compile.erl
+++ b/lib/stdlib/src/erl_compile.erl
@@ -60,6 +60,7 @@ compile_cmdline() ->
 	_ -> my_halt(2)
     end.
 
+-spec my_halt(_) -> no_return().
 my_halt(Reason) ->
     erlang:halt(Reason).
 
diff --git a/lib/stdlib/src/escript.erl b/lib/stdlib/src/escript.erl
index b8ce311..f53b0e2 100644
--- a/lib/stdlib/src/escript.erl
+++ b/lib/stdlib/src/escript.erl
@@ -906,6 +906,7 @@ anno(L) ->
 fatal(Str) ->
     throw(Str).
 
+-spec my_halt(_) -> no_return().
 my_halt(Reason) ->
     erlang:halt(Reason).
 
-- 
2.1.4

openSUSE Build Service is sponsored by