Skip to content

Commit

Permalink
Merge branch 'bjorn/remove-is_constant-vestiges/OTP-6454' into maint
Browse files Browse the repository at this point in the history
* bjorn/remove-is_constant-vestiges/OTP-6454:
  HiPE: Remove support for is_constant/1
  erl_lint: Remove handling of constant/1
  erl_bif_types: Remove type for is_constant/1
  erl_eval: Remove support for is_constant/1
  Remove support for is_constant/1 in ms_transform
  Remove references to is_constant/1 from the match spec documentation
  • Loading branch information
bjorng committed Feb 9, 2012
2 parents 2907d80 + ad4a686 commit 34c9724
Show file tree
Hide file tree
Showing 14 changed files with 11 additions and 47 deletions.
6 changes: 3 additions & 3 deletions erts/doc/src/match_spec.xml
Expand Up @@ -75,7 +75,7 @@
<item>MatchCondition ::= { GuardFunction } |
{ GuardFunction, ConditionExpression, ... }
</item>
<item>BoolFunction ::= <c><![CDATA[is_atom]]></c> | <c><![CDATA[is_constant]]></c> |
<item>BoolFunction ::= <c><![CDATA[is_atom]]></c> |
<c><![CDATA[is_float]]></c> | <c><![CDATA[is_integer]]></c> | <c><![CDATA[is_list]]></c> |
<c><![CDATA[is_number]]></c> | <c><![CDATA[is_pid]]></c> | <c><![CDATA[is_port]]></c> |
<c><![CDATA[is_reference]]></c> | <c><![CDATA[is_tuple]]></c> | <c><![CDATA[is_binary]]></c> |
Expand Down Expand Up @@ -133,7 +133,7 @@
<item>MatchCondition ::= { GuardFunction } |
{ GuardFunction, ConditionExpression, ... }
</item>
<item>BoolFunction ::= <c><![CDATA[is_atom]]></c> | <c><![CDATA[is_constant]]></c> |
<item>BoolFunction ::= <c><![CDATA[is_atom]]></c> |
<c><![CDATA[is_float]]></c> | <c><![CDATA[is_integer]]></c> | <c><![CDATA[is_list]]></c> |
<c><![CDATA[is_number]]></c> | <c><![CDATA[is_pid]]></c> | <c><![CDATA[is_port]]></c> |
<c><![CDATA[is_reference]]></c> | <c><![CDATA[is_tuple]]></c> | <c><![CDATA[is_binary]]></c> |
Expand Down Expand Up @@ -172,7 +172,7 @@
<title>Functions allowed in all types of match specifications</title>
<p>The different functions allowed in <c><![CDATA[match_spec]]></c> work like this:
</p>
<p><em>is_atom, is_constant, is_float, is_integer, is_list, is_number, is_pid, is_port, is_reference, is_tuple, is_binary, is_function: </em> Like the corresponding guard tests in
<p><em>is_atom, is_float, is_integer, is_list, is_number, is_pid, is_port, is_reference, is_tuple, is_binary, is_function: </em> Like the corresponding guard tests in
Erlang, return <c><![CDATA[true]]></c> or <c><![CDATA[false]]></c>.
</p>
<p><em>is_record: </em>Takes an additional parameter, which SHALL
Expand Down
1 change: 0 additions & 1 deletion lib/hipe/cerl/cerl_hipe_primops.hrl
Expand Up @@ -59,7 +59,6 @@
-define(PRIMOP_IS_ATOM, 'is_atom'). % arity 1
-define(PRIMOP_IS_BIGNUM, 'is_bignum'). % arity 1
-define(PRIMOP_IS_BINARY, 'is_binary'). % arity 1
-define(PRIMOP_IS_CONSTANT, 'is_constant'). % arity 1
-define(PRIMOP_IS_FIXNUM, 'is_fixnum'). % arity 1
-define(PRIMOP_IS_FLOAT, 'is_float'). % arity 1
-define(PRIMOP_IS_FUNCTION, 'is_function'). % arity 1
Expand Down
1 change: 0 additions & 1 deletion lib/hipe/cerl/cerl_hipeify.erl
Expand Up @@ -392,7 +392,6 @@ call_to_primop(erlang, '=<', 2) -> {yes, ?PRIMOP_LE};
call_to_primop(erlang, '>=', 2) -> {yes, ?PRIMOP_GE};
call_to_primop(erlang, is_atom, 1) -> {yes, ?PRIMOP_IS_ATOM};
call_to_primop(erlang, is_binary, 1) -> {yes, ?PRIMOP_IS_BINARY};
call_to_primop(erlang, is_constant, 1) -> {yes, ?PRIMOP_IS_CONSTANT};
call_to_primop(erlang, is_float, 1) -> {yes, ?PRIMOP_IS_FLOAT};
call_to_primop(erlang, is_function, 1) -> {yes, ?PRIMOP_IS_FUNCTION};
call_to_primop(erlang, is_integer, 1) -> {yes, ?PRIMOP_IS_INTEGER};
Expand Down
1 change: 0 additions & 1 deletion lib/hipe/cerl/cerl_messagean.erl
Expand Up @@ -1083,7 +1083,6 @@ is_imm_op(erlang, is_alive, 0) -> true;
is_imm_op(erlang, is_atom, 1) -> true;
is_imm_op(erlang, is_binary, 1) -> true;
is_imm_op(erlang, is_builtin, 3) -> true;
is_imm_op(erlang, is_constant, 1) -> true;
is_imm_op(erlang, is_float, 1) -> true;
is_imm_op(erlang, is_function, 1) -> true;
is_imm_op(erlang, is_integer, 1) -> true;
Expand Down
3 changes: 0 additions & 3 deletions lib/hipe/cerl/cerl_to_icode.erl
Expand Up @@ -88,7 +88,6 @@
-define(TYPE_IS_ATOM, atom).
-define(TYPE_IS_BIGNUM, bignum).
-define(TYPE_IS_BINARY, binary).
-define(TYPE_IS_CONSTANT, constant).
-define(TYPE_IS_FIXNUM, fixnum).
-define(TYPE_IS_FLOAT, float).
-define(TYPE_IS_FUNCTION, function).
Expand Down Expand Up @@ -2051,7 +2050,6 @@ is_record_test(T, A, N, True, False, Ctxt, Env, S) ->
type_test(?PRIMOP_IS_ATOM) -> ?TYPE_IS_ATOM;
type_test(?PRIMOP_IS_BIGNUM) -> ?TYPE_IS_BIGNUM;
type_test(?PRIMOP_IS_BINARY) -> ?TYPE_IS_BINARY;
type_test(?PRIMOP_IS_CONSTANT) -> ?TYPE_IS_CONSTANT;
type_test(?PRIMOP_IS_FIXNUM) -> ?TYPE_IS_FIXNUM;
type_test(?PRIMOP_IS_FLOAT) -> ?TYPE_IS_FLOAT;
type_test(?PRIMOP_IS_FUNCTION) -> ?TYPE_IS_FUNCTION;
Expand Down Expand Up @@ -2082,7 +2080,6 @@ is_bool_op(Op, A) when is_atom(Op), is_integer(A) -> false.
is_type_test(?PRIMOP_IS_ATOM, 1) -> true;
is_type_test(?PRIMOP_IS_BIGNUM, 1) -> true;
is_type_test(?PRIMOP_IS_BINARY, 1) -> true;
is_type_test(?PRIMOP_IS_CONSTANT, 1) -> true;
is_type_test(?PRIMOP_IS_FIXNUM, 1) -> true;
is_type_test(?PRIMOP_IS_FLOAT, 1) -> true;
is_type_test(?PRIMOP_IS_FUNCTION, 1) -> true;
Expand Down
9 changes: 0 additions & 9 deletions lib/hipe/cerl/erl_bif_types.erl
Expand Up @@ -54,7 +54,6 @@
t_cons/2,
t_cons_hd/1,
t_cons_tl/1,
t_constant/0,
t_fixnum/0,
t_non_neg_fixnum/0,
t_pos_fixnum/0,
Expand All @@ -81,7 +80,6 @@
t_is_bitstr/1,
t_is_boolean/1,
t_is_cons/1,
t_is_constant/1,
t_is_float/1,
t_is_float/1,
t_is_fun/1,
Expand Down Expand Up @@ -845,11 +843,6 @@ type(erlang, is_boolean, 1, Xs) ->
strict(arg_types(erlang, is_boolean, 1), Xs, Fun);
type(erlang, is_builtin, 3, Xs) ->
strict(arg_types(erlang, is_builtin, 3), Xs, fun (_) -> t_boolean() end);
type(erlang, is_constant, 1, Xs) ->
Fun = fun (X) ->
check_guard(X, fun (Y) -> t_is_constant(Y) end, t_constant())
end,
strict(arg_types(erlang, is_constant, 1), Xs, Fun);
type(erlang, is_float, 1, Xs) ->
Fun = fun (X) ->
check_guard(X, fun (Y) -> t_is_float(Y) end, t_float())
Expand Down Expand Up @@ -3567,8 +3560,6 @@ arg_types(erlang, is_boolean, 1) ->
[t_any()];
arg_types(erlang, is_builtin, 3) ->
[t_atom(), t_atom(), t_arity()];
arg_types(erlang, is_constant, 1) ->
[t_any()];
arg_types(erlang, is_float, 1) ->
[t_any()];
arg_types(erlang, is_function, 1) ->
Expand Down
4 changes: 0 additions & 4 deletions lib/hipe/icode/hipe_beam_to_icode.erl
Expand Up @@ -465,10 +465,6 @@ trans_fun([{test,is_nil,{f,Lbl},[Arg]}|Instructions], Env) ->
trans_fun([{test,is_binary,{f,Lbl},[Arg]}|Instructions], Env) ->
{Code,Env1} = trans_type_test(binary,Lbl,Arg,Env),
[Code | trans_fun(Instructions,Env1)];
%%--- is_constant ---
trans_fun([{test,is_constant,{f,Lbl},[Arg]}|Instructions], Env) ->
{Code,Env1} = trans_type_test(constant,Lbl,Arg,Env),
[Code | trans_fun(Instructions,Env1)];
%%--- is_list ---
trans_fun([{test,is_list,{f,Lbl},[Arg]}|Instructions], Env) ->
{Code,Env1} = trans_type_test(list,Lbl,Arg,Env),
Expand Down
3 changes: 1 addition & 2 deletions lib/hipe/icode/hipe_icode_inline_bifs.erl
Expand Up @@ -29,7 +29,7 @@

%% Currently inlined BIFs:
%% and, or, xor, not, <, >, >=, =<, ==, /=, =/=, =:=
%% is_atom, is_boolean, is_binary, is_constant, is_float, is_function,
%% is_atom, is_boolean, is_binary, is_float, is_function,
%% is_integer, is_list, is_pid, is_port, is_reference, is_tuple

-module(hipe_icode_inline_bifs).
Expand Down Expand Up @@ -131,7 +131,6 @@ is_type_test(Name) ->
is_boolean -> {true, boolean};
is_function -> {true, function};
is_reference -> {true, reference};
is_constant -> {true, constant};
is_port -> {true, port};
_ -> false
end.
Expand Down
6 changes: 1 addition & 5 deletions lib/hipe/icode/hipe_icode_type.erl
Expand Up @@ -899,9 +899,7 @@ test_type0(list, T) ->
test_type0(cons, T) ->
t_is_cons(T);
test_type0(nil, T) ->
t_is_nil(T);
test_type0(constant, T) ->
t_is_constant(T).
t_is_nil(T).


true_branch_info(integer) ->
Expand Down Expand Up @@ -940,8 +938,6 @@ true_branch_info(nil) ->
t_nil();
true_branch_info(boolean) ->
t_boolean();
true_branch_info(constant) ->
t_constant();
true_branch_info(T) ->
exit({?MODULE,unknown_typetest,T}).

Expand Down
4 changes: 2 additions & 2 deletions lib/stdlib/doc/src/ms_transform.xml
Expand Up @@ -308,7 +308,7 @@ ets:select(emp_tab, ets:fun2ms(
Erlang code. Also arithmetics is allowed, as well as ordinary guard
bif's. Here's a list of bif's and expressions:</p>
<list type="bulleted">
<item>The type tests: is_atom, is_constant, is_float, is_integer,
<item>The type tests: is_atom, is_float, is_integer,
is_list, is_number, is_pid, is_port, is_reference, is_tuple,
is_binary, is_function, is_record</item>
<item>The boolean operators: not, and, or, andalso, orelse </item>
Expand All @@ -318,7 +318,7 @@ ets:select(emp_tab, ets:fun2ms(
<item>The guard bif's: abs, element, hd, length, node, round, size, tl,
trunc, self</item>
<item>The obsolete type test (only in guards):
atom, constant, float, integer,
atom, float, integer,
list, number, pid, port, reference, tuple,
binary, function, record</item>
</list>
Expand Down
1 change: 0 additions & 1 deletion lib/stdlib/src/erl_eval.erl
Expand Up @@ -947,7 +947,6 @@ type_test(integer) -> is_integer;
type_test(float) -> is_float;
type_test(number) -> is_number;
type_test(atom) -> is_atom;
type_test(constant) -> is_constant;
type_test(list) -> is_list;
type_test(tuple) -> is_tuple;
type_test(pid) -> is_pid;
Expand Down
12 changes: 3 additions & 9 deletions lib/stdlib/src/erl_lint.erl
Expand Up @@ -3436,17 +3436,11 @@ obsolete_guard({call,Line,{atom,Lr,F},As}, St0) ->
false ->
deprecated_function(Line, erlang, F, As, St0);
true ->
St1 = case F of
constant ->
deprecated_function(Lr, erlang, is_constant, As, St0);
_ ->
St0
end,
case is_warn_enabled(obsolete_guard, St1) of
case is_warn_enabled(obsolete_guard, St0) of
true ->
add_warning(Lr,{obsolete_guard, {F, Arity}}, St1);
add_warning(Lr,{obsolete_guard, {F, Arity}}, St0);
false ->
St1
St0
end
end;
obsolete_guard(_G, St) ->
Expand Down
2 changes: 0 additions & 2 deletions lib/stdlib/src/ms_transform.erl
Expand Up @@ -881,7 +881,6 @@ translate_language_element(Atom) ->
end.

old_bool_test(atom,1) -> is_atom;
old_bool_test(constant,1) -> is_constant;
old_bool_test(float,1) -> is_float;
old_bool_test(integer,1) -> is_integer;
old_bool_test(list,1) -> is_list;
Expand All @@ -896,7 +895,6 @@ old_bool_test(record,2) -> is_record;
old_bool_test(_,_) -> undefined.

bool_test(is_atom,1) -> true;
bool_test(is_constant,1) -> true;
bool_test(is_float,1) -> true;
bool_test(is_integer,1) -> true;
bool_test(is_list,1) -> true;
Expand Down
5 changes: 1 addition & 4 deletions lib/stdlib/test/ms_transform_SUITE.erl
Expand Up @@ -455,7 +455,6 @@ old_guards(Config) when is_list(Config) ->
?line setup(Config),
Tests = [
{atom,is_atom},
{constant,is_constant},
{float,is_float},
{integer,is_integer},
{list,is_list},
Expand Down Expand Up @@ -490,7 +489,6 @@ old_guards(Config) when is_list(Config) ->
?line [{'$1',[{is_integer,'$1'},
{is_float,'$1'},
{is_atom,'$1'},
{is_constant,'$1'},
{is_list,'$1'},
{is_number,'$1'},
{is_pid,'$1'},
Expand All @@ -502,7 +500,7 @@ old_guards(Config) when is_list(Config) ->
[true]}] =
compile_and_run(RD, <<
"ets:fun2ms(fun(X) when integer(X),"
"float(X), atom(X), constant(X),"
"float(X), atom(X),"
"list(X), number(X), pid(X),"
"port(X), reference(X), tuple(X),"
"binary(X), record(X,a) -> true end)"
Expand Down Expand Up @@ -530,7 +528,6 @@ autoimported(Config) when is_list(Config) ->
{self,0},
%{float,1}, see float_1_function/1
{is_atom,1},
{is_constant,1},
{is_float,1},
{is_integer,1},
{is_list,1},
Expand Down

0 comments on commit 34c9724

Please sign in to comment.