aboutsummaryrefslogtreecommitdiffstats
path: root/lib/hipe/cerl/erl_types.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/hipe/cerl/erl_types.erl')
-rw-r--r--lib/hipe/cerl/erl_types.erl333
1 files changed, 86 insertions, 247 deletions
diff --git a/lib/hipe/cerl/erl_types.erl b/lib/hipe/cerl/erl_types.erl
index 2b290b2f23..d61cd8664c 100644
--- a/lib/hipe/cerl/erl_types.erl
+++ b/lib/hipe/cerl/erl_types.erl
@@ -66,7 +66,6 @@
t_find_opaque_mismatch/3,
t_find_unknown_opaque/3,
t_fixnum/0,
- t_map/2,
t_non_neg_fixnum/0,
t_pos_fixnum/0,
t_float/0,
@@ -108,13 +107,14 @@
t_is_bitstr/1, t_is_bitstr/2,
t_is_bitwidth/1,
t_is_boolean/1, t_is_boolean/2,
- %% t_is_byte/1,
- %% t_is_char/1,
+ t_is_byte/1,
+ t_is_char/1,
t_is_cons/1, t_is_cons/2,
t_is_equal/2,
t_is_fixnum/1,
t_is_float/1, t_is_float/2,
t_is_fun/1, t_is_fun/2,
+ t_is_identifier/1,
t_is_instance/2,
t_is_integer/1, t_is_integer/2,
t_is_list/1,
@@ -204,6 +204,7 @@
t_unopaque/1, t_unopaque/2,
t_var/1,
t_var_name/1,
+ t_widen_to_number/1,
%% t_assign_variables_to_subtype/2,
type_is_defined/4,
record_field_diffs_to_string/2,
@@ -216,18 +217,7 @@
cache__new/0
]).
-%%-define(DO_ERL_TYPES_TEST, true).
--compile({no_auto_import,[min/2,max/2]}).
-
--ifdef(DO_ERL_TYPES_TEST).
--export([test/0]).
--else.
--define(NO_UNUSED, true).
--endif.
-
--ifndef(NO_UNUSED).
--export([t_is_identifier/1]).
--endif.
+-compile({no_auto_import,[min/2,max/2,map_get/2]}).
-export_type([erl_type/0, opaques/0, type_table/0,
var_table/0, cache/0]).
@@ -1190,12 +1180,10 @@ is_fun(_) -> false.
t_identifier() ->
?identifier(?any).
--ifdef(DO_ERL_TYPES_TEST).
--spec t_is_identifier(erl_type()) -> erl_type().
+-spec t_is_identifier(erl_type()) -> boolean().
t_is_identifier(?identifier(_)) -> true;
t_is_identifier(_) -> false.
--endif.
%%------------------------------------
@@ -1366,7 +1354,6 @@ is_integer1(_) -> false.
t_byte() ->
?byte.
--ifdef(DO_ERL_TYPES_TEST).
-spec t_is_byte(erl_type()) -> boolean().
t_is_byte(?int_range(neg_inf, _)) -> false;
@@ -1376,7 +1363,6 @@ t_is_byte(?int_range(From, To))
t_is_byte(?int_set(Set)) ->
(set_min(Set) >= 0) andalso (set_max(Set) =< ?MAX_BYTE);
t_is_byte(_) -> false.
--endif.
%%------------------------------------
@@ -1608,6 +1594,50 @@ lift_list_to_pos_empty(?nil) -> ?nil;
lift_list_to_pos_empty(?list(Content, Termination, _)) ->
?list(Content, Termination, ?unknown_qual).
+-spec t_widen_to_number(erl_type()) -> erl_type().
+
+%% Widens integers and floats to t_number().
+%% Used by erl_bif_types:key_comparison_fail().
+
+t_widen_to_number(?any) -> ?any;
+t_widen_to_number(?none) -> ?none;
+t_widen_to_number(?unit) -> ?unit;
+t_widen_to_number(?atom(_Set) = T) -> T;
+t_widen_to_number(?bitstr(_Unit, _Base) = T) -> T;
+t_widen_to_number(?float) -> t_number();
+t_widen_to_number(?function(Domain, Range)) ->
+ ?function(t_widen_to_number(Domain), t_widen_to_number(Range));
+t_widen_to_number(?identifier(_Types) = T) -> T;
+t_widen_to_number(?int_range(_From, _To)) -> t_number();
+t_widen_to_number(?int_set(_Set)) -> t_number();
+t_widen_to_number(?integer(_Types)) -> t_number();
+t_widen_to_number(?list(Type, Tail, Size)) ->
+ ?list(t_widen_to_number(Type), t_widen_to_number(Tail), Size);
+t_widen_to_number(?map(Pairs, DefK, DefV)) ->
+ L = [{t_widen_to_number(K), MNess, t_widen_to_number(V)} ||
+ {K, MNess, V} <- Pairs],
+ t_map(L, t_widen_to_number(DefK), t_widen_to_number(DefV));
+t_widen_to_number(?matchstate(_P, _Slots) = T) -> T;
+t_widen_to_number(?nil) -> ?nil;
+t_widen_to_number(?number(_Set, _Tag)) -> t_number();
+t_widen_to_number(?opaque(Set)) ->
+ L = [Opaque#opaque{struct = t_widen_to_number(S)} ||
+ #opaque{struct = S} = Opaque <- set_to_list(Set)],
+ ?opaque(ordsets:from_list(L));
+t_widen_to_number(?product(Types)) ->
+ ?product(list_widen_to_number(Types));
+t_widen_to_number(?tuple(?any, _, _) = T) -> T;
+t_widen_to_number(?tuple(Types, Arity, Tag)) ->
+ ?tuple(list_widen_to_number(Types), Arity, Tag);
+t_widen_to_number(?tuple_set(_) = Tuples) ->
+ t_sup([t_widen_to_number(T) || T <- t_tuple_subtypes(Tuples)]);
+t_widen_to_number(?union(List)) ->
+ ?union(list_widen_to_number(List));
+t_widen_to_number(?var(_Id)= T) -> T.
+
+list_widen_to_number(List) ->
+ [t_widen_to_number(E) || E <- List].
+
%%-----------------------------------------------------------------------------
%% Maps
%%
@@ -3118,9 +3148,18 @@ is_compat_arg(?list(Contents1, Termination1, Size1),
is_compat_arg(?product(Types1), ?product(Types2)) ->
is_compat_list(Types1, Types2);
is_compat_arg(?map(Pairs1, DefK1, DefV1), ?map(Pairs2, DefK2, DefV2)) ->
- (is_compat_list(Pairs1, Pairs2) andalso
- is_compat_arg(DefK1, DefK2) andalso
- is_compat_arg(DefV1, DefV2));
+ {Ks1, _, Vs1} = lists:unzip3(Pairs1),
+ {Ks2, _, Vs2} = lists:unzip3(Pairs2),
+ Key1 = t_sup([DefK1 | Ks1]),
+ Key2 = t_sup([DefK2 | Ks2]),
+ case is_compat_arg(Key1, Key2) of
+ true ->
+ Value1 = t_sup([DefV1 | Vs1]),
+ Value2 = t_sup([DefV2 | Vs2]),
+ is_compat_arg(Value1, Value2);
+ false ->
+ false
+ end;
is_compat_arg(?tuple(?any, ?any, ?any), ?tuple(_, _, _)) -> false;
is_compat_arg(?tuple(_, _, _), ?tuple(?any, ?any, ?any)) -> false;
is_compat_arg(?tuple(Elements1, Arity, _),
@@ -4170,39 +4209,6 @@ t_abstract_records(?opaque(_)=Type, RecDict) ->
t_abstract_records(T, _RecDict) ->
T.
-%% Map over types. Depth first. Used by the contract checker. ?list is
-%% not fully implemented so take care when changing the type in Termination.
-
--spec t_map(fun((erl_type()) -> erl_type()), erl_type()) -> erl_type().
-
-t_map(Fun, ?list(Contents, Termination, Size)) ->
- Fun(?list(t_map(Fun, Contents), t_map(Fun, Termination), Size));
-t_map(Fun, ?function(Domain, Range)) ->
- Fun(?function(t_map(Fun, Domain), t_map(Fun, Range)));
-t_map(Fun, ?product(Types)) ->
- Fun(?product([t_map(Fun, T) || T <- Types]));
-t_map(Fun, ?union(Types)) ->
- Fun(t_sup([t_map(Fun, T) || T <- Types]));
-t_map(Fun, ?tuple(?any, ?any, ?any) = T) ->
- Fun(T);
-t_map(Fun, ?tuple(Elements, _Arity, _Tag)) ->
- Fun(t_tuple([t_map(Fun, E) || E <- Elements]));
-t_map(Fun, ?tuple_set(_) = Tuples) ->
- Fun(t_sup([t_map(Fun, T) || T <- t_tuple_subtypes(Tuples)]));
-t_map(Fun, ?opaque(Set)) ->
- L = [Opaque#opaque{struct = NewS} ||
- #opaque{struct = S} = Opaque <- set_to_list(Set),
- not t_is_none(NewS = t_map(Fun, S))],
- Fun(case L of
- [] -> ?none;
- _ -> ?opaque(ordsets:from_list(L))
- end);
-t_map(Fun, ?map(Pairs,DefK,DefV)) ->
- %% TODO:
- Fun(t_map(Pairs, Fun(DefK), Fun(DefV)));
-t_map(Fun, T) ->
- Fun(T).
-
%%=============================================================================
%%
%% Prettyprinter
@@ -4257,13 +4263,13 @@ t_to_string(?identifier(Set), _RecDict) ->
case Set of
?any -> "identifier()";
_ ->
- string:join([flat_format("~w()", [T]) || T <- set_to_list(Set)], " | ")
+ flat_join([flat_format("~w()", [T]) || T <- set_to_list(Set)], " | ")
end;
t_to_string(?opaque(Set), RecDict) ->
- string:join([opaque_type(Mod, Name, Args, S, RecDict) ||
- #opaque{mod = Mod, name = Name, struct = S, args = Args}
- <- set_to_list(Set)],
- " | ");
+ flat_join([opaque_type(Mod, Name, Args, S, RecDict) ||
+ #opaque{mod = Mod, name = Name, struct = S, args = Args}
+ <- set_to_list(Set)],
+ " | ");
t_to_string(?matchstate(Pres, Slots), RecDict) ->
flat_format("ms(~ts,~ts)", [t_to_string(Pres, RecDict),
t_to_string(Slots,RecDict)]);
@@ -4354,9 +4360,9 @@ t_to_string(?map(Pairs0,DefK,DefV), RecDict) ->
end end,
StrMand = [{Tos(K),Tos(V)}||{K,?mand,V}<-Pairs],
StrOpt = [{Tos(K),Tos(V)}||{K,?opt,V}<-Pairs],
- "#{" ++ string:join([K ++ ":=" ++ V||{K,V}<-StrMand]
- ++ [K ++ "=>" ++ V||{K,V}<-StrOpt]
- ++ ExtraEl, ", ") ++ "}";
+ "#{" ++ flat_join([K ++ ":=" ++ V||{K,V}<-StrMand]
+ ++ [K ++ "=>" ++ V||{K,V}<-StrOpt]
+ ++ ExtraEl, ", ") ++ "}";
t_to_string(?tuple(?any, ?any, ?any), _RecDict) -> "tuple()";
t_to_string(?tuple(Elements, _Arity, ?any), RecDict) ->
"{" ++ comma_sequence(Elements, RecDict) ++ "}";
@@ -4379,7 +4385,7 @@ t_to_string(?var(Id), _RecDict) when is_integer(Id) ->
record_to_string(Tag, [_|Fields], FieldNames, RecDict) ->
FieldStrings = record_fields_to_string(Fields, FieldNames, RecDict, []),
- "#" ++ atom_to_string(Tag) ++ "{" ++ string:join(FieldStrings, ",") ++ "}".
+ "#" ++ atom_to_string(Tag) ++ "{" ++ flat_join(FieldStrings, ",") ++ "}".
record_fields_to_string([F|Fs], [{FName, _Abstr, DefType}|FDefs],
RecDict, Acc) ->
@@ -4405,7 +4411,7 @@ record_field_diffs_to_string(?tuple([_|Fs], Arity, Tag), RecDict) ->
{ok, FieldNames} = lookup_record(TagAtom, Arity-1, RecDict),
%% io:format("RecCElems = ~p\nRecTypes = ~p\n", [Fs, FieldNames]),
FieldDiffs = field_diffs(Fs, FieldNames, RecDict, []),
- string:join(FieldDiffs, " and ").
+ flat_join(FieldDiffs, " and ").
field_diffs([F|Fs], [{FName, _Abstr, DefType}|FDefs], RecDict, Acc) ->
%% Don't care about opacity for now.
@@ -4425,11 +4431,11 @@ comma_sequence(Types, RecDict) ->
true -> "_";
false -> t_to_string(T, RecDict)
end || T <- Types],
- string:join(List, ",").
+ flat_join(List, ",").
union_sequence(Types, RecDict) ->
List = [t_to_string(T, RecDict) || T <- Types],
- string:join(List, " | ").
+ flat_join(List, " | ").
-ifdef(DEBUG).
opaque_type(Mod, Name, _Args, S, RecDict) ->
@@ -5269,7 +5275,7 @@ t_form_to_string({ann_type, _L, [Var, Type]}) ->
t_form_to_string({paren_type, _L, [Type]}) ->
flat_format("(~ts)", [t_form_to_string(Type)]);
t_form_to_string({remote_type, _L, [{atom, _, Mod}, {atom, _, Name}, Args]}) ->
- ArgString = "(" ++ string:join(t_form_to_string_list(Args), ",") ++ ")",
+ ArgString = "(" ++ flat_join(t_form_to_string_list(Args), ",") ++ ")",
flat_format("~w:~tw", [Mod, Name]) ++ ArgString;
t_form_to_string({type, _L, arity, []}) -> "arity()";
t_form_to_string({type, _L, binary, []}) -> "binary()";
@@ -5292,7 +5298,7 @@ t_form_to_string({type, _L, 'fun', []}) -> "fun()";
t_form_to_string({type, _L, 'fun', [{type, _, any}, Range]}) ->
"fun(...) -> " ++ t_form_to_string(Range);
t_form_to_string({type, _L, 'fun', [{type, _, product, Domain}, Range]}) ->
- "fun((" ++ string:join(t_form_to_string_list(Domain), ",") ++ ") -> "
+ "fun((" ++ flat_join(t_form_to_string_list(Domain), ",") ++ ") -> "
++ t_form_to_string(Range) ++ ")";
t_form_to_string({type, _L, iodata, []}) -> "iodata()";
t_form_to_string({type, _L, iolist, []}) -> "iolist()";
@@ -5300,7 +5306,7 @@ t_form_to_string({type, _L, list, [Type]}) ->
"[" ++ t_form_to_string(Type) ++ "]";
t_form_to_string({type, _L, map, any}) -> "map()";
t_form_to_string({type, _L, map, Args}) ->
- "#{" ++ string:join(t_form_to_string_list(Args), ",") ++ "}";
+ "#{" ++ flat_join(t_form_to_string_list(Args), ",") ++ "}";
t_form_to_string({type, _L, map_field_assoc, [Key, Val]}) ->
t_form_to_string(Key) ++ "=>" ++ t_form_to_string(Val);
t_form_to_string({type, _L, map_field_exact, [Key, Val]}) ->
@@ -5312,7 +5318,7 @@ t_form_to_string({type, _L, nonempty_list, [Type]}) ->
"[" ++ t_form_to_string(Type) ++ ",...]";
t_form_to_string({type, _L, nonempty_string, []}) -> "nonempty_string()";
t_form_to_string({type, _L, product, Elements}) ->
- "<" ++ string:join(t_form_to_string_list(Elements), ",") ++ ">";
+ "<" ++ flat_join(t_form_to_string_list(Elements), ",") ++ ">";
t_form_to_string({type, _L, range, [From, To]} = Type) ->
case {erl_eval:partial_eval(From), erl_eval:partial_eval(To)} of
{{integer, _, FromVal}, {integer, _, ToVal}} ->
@@ -5322,7 +5328,7 @@ t_form_to_string({type, _L, range, [From, To]} = Type) ->
t_form_to_string({type, _L, record, [{atom, _, Name}]}) ->
flat_format("#~tw{}", [Name]);
t_form_to_string({type, _L, record, [{atom, _, Name}|Fields]}) ->
- FieldString = string:join(t_form_to_string_list(Fields), ","),
+ FieldString = flat_join(t_form_to_string_list(Fields), ","),
flat_format("#~tw{~ts}", [Name, FieldString]);
t_form_to_string({type, _L, field_type, [{atom, _, Name}, Type]}) ->
flat_format("~tw::~ts", [Name, t_form_to_string(Type)]);
@@ -5330,9 +5336,9 @@ t_form_to_string({type, _L, term, []}) -> "term()";
t_form_to_string({type, _L, timeout, []}) -> "timeout()";
t_form_to_string({type, _L, tuple, any}) -> "tuple()";
t_form_to_string({type, _L, tuple, Args}) ->
- "{" ++ string:join(t_form_to_string_list(Args), ",") ++ "}";
+ "{" ++ flat_join(t_form_to_string_list(Args), ",") ++ "}";
t_form_to_string({type, _L, union, Args}) ->
- string:join(t_form_to_string_list(Args), " | ");
+ flat_join(t_form_to_string_list(Args), " | ");
t_form_to_string({type, _L, Name, []} = T) ->
try
M = mod,
@@ -5350,7 +5356,7 @@ t_form_to_string({type, _L, Name, []} = T) ->
end;
t_form_to_string({user_type, _L, Name, List}) ->
flat_format("~tw(~ts)",
- [Name, string:join(t_form_to_string_list(List), ",")]);
+ [Name, flat_join(t_form_to_string_list(List), ",")]);
t_form_to_string({type, L, Name, List}) ->
%% Compatibility: modules compiled before Erlang/OTP 18.0.
t_form_to_string({user_type, L, Name, List}).
@@ -5611,7 +5617,7 @@ set_to_string(Set) ->
true -> io_lib:write_string(atom_to_list(X), $'); % stupid emacs '
false -> flat_format("~tw", [X])
end || X <- set_to_list(Set)],
- string:join(L, " | ").
+ flat_join(L, " | ").
set_min([H|_]) -> H.
@@ -5621,6 +5627,9 @@ set_max(Set) ->
flat_format(F, S) ->
lists:flatten(io_lib:format(F, S)).
+flat_join(List, Sep) ->
+ lists:flatten(lists:join(Sep, List)).
+
%%=============================================================================
%%
%% Utilities for the binary type
@@ -5690,173 +5699,3 @@ family(L) ->
var_table__new() ->
maps:new().
-
-%%=============================================================================
-%% Consistency-testing function(s) below
-%%=============================================================================
-
--ifdef(DO_ERL_TYPES_TEST).
-
-test() ->
- Atom1 = t_atom(),
- Atom2 = t_atom(foo),
- Atom3 = t_atom(bar),
- true = t_is_atom(Atom2),
-
- True = t_atom(true),
- False = t_atom(false),
- Bool = t_boolean(),
- true = t_is_boolean(True),
- true = t_is_boolean(Bool),
- false = t_is_boolean(Atom1),
-
- Binary = t_binary(),
- true = t_is_binary(Binary),
-
- Bitstr = t_bitstr(),
- true = t_is_bitstr(Bitstr),
-
- Bitstr1 = t_bitstr(7, 3),
- true = t_is_bitstr(Bitstr1),
- false = t_is_binary(Bitstr1),
-
- Bitstr2 = t_bitstr(16, 8),
- true = t_is_bitstr(Bitstr2),
- true = t_is_binary(Bitstr2),
-
- ?bitstr(8, 16) = t_subtract(t_bitstr(4, 12), t_bitstr(8, 12)),
- ?bitstr(8, 16) = t_subtract(t_bitstr(4, 12), t_bitstr(8, 12)),
-
- Int1 = t_integer(),
- Int2 = t_integer(1),
- Int3 = t_integer(16#ffffffff),
- true = t_is_integer(Int2),
- true = t_is_byte(Int2),
- false = t_is_byte(Int3),
- false = t_is_byte(t_from_range(-1, 1)),
- true = t_is_byte(t_from_range(1, ?MAX_BYTE)),
-
- Tuple1 = t_tuple(),
- Tuple2 = t_tuple(3),
- Tuple3 = t_tuple([Atom1, Int1]),
- Tuple4 = t_tuple([Tuple1, Tuple2]),
- Tuple5 = t_tuple([Tuple3, Tuple4]),
- Tuple6 = t_limit(Tuple5, 2),
- Tuple7 = t_limit(Tuple5, 3),
- true = t_is_tuple(Tuple1),
-
- Port = t_port(),
- Pid = t_pid(),
- Ref = t_reference(),
- Identifier = t_identifier(),
- false = t_is_reference(Port),
- true = t_is_identifier(Port),
-
- Function1 = t_fun(),
- Function2 = t_fun(Pid),
- Function3 = t_fun([], Pid),
- Function4 = t_fun([Port, Pid], Pid),
- Function5 = t_fun([Pid, Atom1], Int2),
- true = t_is_fun(Function3),
-
- List1 = t_list(),
- List2 = t_list(t_boolean()),
- List3 = t_cons(t_boolean(), List2),
- List4 = t_cons(t_boolean(), t_atom()),
- List5 = t_cons(t_boolean(), t_nil()),
- List6 = t_cons_tl(List5),
- List7 = t_sup(List4, List5),
- List8 = t_inf(List7, t_list()),
- List9 = t_cons(),
- List10 = t_cons_tl(List9),
- true = t_is_boolean(t_cons_hd(List5)),
- true = t_is_list(List5),
- false = t_is_list(List4),
-
- Product1 = t_product([Atom1, Atom2]),
- Product2 = t_product([Atom3, Atom1]),
- Product3 = t_product([Atom3, Atom2]),
-
- Union1 = t_sup(Atom2, Atom3),
- Union2 = t_sup(Tuple2, Tuple3),
- Union3 = t_sup(Int2, Atom3),
- Union4 = t_sup(Port, Pid),
- Union5 = t_sup(Union4, Int1),
- Union6 = t_sup(Function1, Function2),
- Union7 = t_sup(Function4, Function5),
- Union8 = t_sup(True, False),
- true = t_is_boolean(Union8),
- Union9 = t_sup(Int2, t_integer(2)),
- true = t_is_byte(Union9),
- Union10 = t_sup(t_tuple([t_atom(true), ?any]),
- t_tuple([t_atom(false), ?any])),
-
- ?any = t_sup(Product3, Function5),
-
- Atom3 = t_inf(Union3, Atom1),
- Union2 = t_inf(Union2, Tuple1),
- Int2 = t_inf(Int1, Union3),
- Union4 = t_inf(Union4, Identifier),
- Port = t_inf(Union5, Port),
- Function4 = t_inf(Union7, Function4),
- ?none = t_inf(Product2, Atom1),
- Product3 = t_inf(Product1, Product2),
- Function5 = t_inf(Union7, Function5),
- true = t_is_byte(t_inf(Union9, t_number())),
- true = t_is_char(t_inf(Union9, t_number())),
-
- io:format("3? ~p ~n", [?int_set([3])]),
-
- RecDict = dict:store({foo, 2}, [bar, baz], dict:new()),
- Record1 = t_from_term({foo, [1,2], {1,2,3}}),
-
- Types = [
- Atom1,
- Atom2,
- Atom3,
- Binary,
- Int1,
- Int2,
- Tuple1,
- Tuple2,
- Tuple3,
- Tuple4,
- Tuple5,
- Tuple6,
- Tuple7,
- Ref,
- Port,
- Pid,
- Identifier,
- List1,
- List2,
- List3,
- List4,
- List5,
- List6,
- List7,
- List8,
- List9,
- List10,
- Function1,
- Function2,
- Function3,
- Function4,
- Function5,
- Product1,
- Product2,
- Record1,
- Union1,
- Union2,
- Union3,
- Union4,
- Union5,
- Union6,
- Union7,
- Union8,
- Union10,
- t_inf(Union10, t_tuple([t_atom(true), t_integer()]))
- ],
- io:format("~p\n", [[t_to_string(X, RecDict) || X <- Types]]).
-
--endif.