aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/ms_transform.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src/ms_transform.erl')
-rw-r--r--lib/stdlib/src/ms_transform.erl91
1 files changed, 55 insertions, 36 deletions
diff --git a/lib/stdlib/src/ms_transform.erl b/lib/stdlib/src/ms_transform.erl
index b67b6f75d7..6d243e1bec 100644
--- a/lib/stdlib/src/ms_transform.erl
+++ b/lib/stdlib/src/ms_transform.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2002-2015. All Rights Reserved.
+%% Copyright Ericsson AB 2002-2018. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -91,12 +91,12 @@ format_error(?ERR_GUARDMATCH) ->
"fun with guard matching ('=' in guard) is illegal as match_spec as well";
format_error({?ERR_GUARDLOCALCALL, Name, Arithy}) ->
lists:flatten(io_lib:format("fun containing the local function call "
- "'~w/~w' (called in guard) "
+ "'~tw/~w' (called in guard) "
"cannot be translated into match_spec",
[Name, Arithy]));
format_error({?ERR_GUARDREMOTECALL, Module, Name, Arithy}) ->
lists:flatten(io_lib:format("fun containing the remote function call "
- "'~w:~w/~w' (called in guard) "
+ "'~w:~tw/~w' (called in guard) "
"cannot be translated into match_spec",
[Module,Name,Arithy]));
format_error({?ERR_GUARDELEMENT, Str}) ->
@@ -117,12 +117,12 @@ format_error(?ERR_BODYMATCH) ->
"fun with body matching ('=' in body) is illegal as match_spec";
format_error({?ERR_BODYLOCALCALL, Name, Arithy}) ->
lists:flatten(io_lib:format("fun containing the local function "
- "call '~w/~w' (called in body) "
+ "call '~tw/~w' (called in body) "
"cannot be translated into match_spec",
[Name,Arithy]));
format_error({?ERR_BODYREMOTECALL, Module, Name, Arithy}) ->
lists:flatten(io_lib:format("fun containing the remote function call "
- "'~w:~w/~w' (called in body) "
+ "'~w:~tw/~w' (called in body) "
"cannot be translated into match_spec",
[Module,Name,Arithy]));
format_error({?ERR_BODYELEMENT, Str}) ->
@@ -147,15 +147,15 @@ format_error({?ERR_UNBOUND_VARIABLE, Str}) ->
"into match_spec", [Str]));
format_error({?ERR_HEADBADREC,Name}) ->
lists:flatten(
- io_lib:format("fun head contains unknown record type ~w",[Name]));
+ io_lib:format("fun head contains unknown record type ~tw",[Name]));
format_error({?ERR_HEADBADFIELD,RName,FName}) ->
lists:flatten(
- io_lib:format("fun head contains reference to unknown field ~w in "
- "record type ~w",[FName, RName]));
+ io_lib:format("fun head contains reference to unknown field ~tw in "
+ "record type ~tw",[FName, RName]));
format_error({?ERR_HEADMULTIFIELD,RName,FName}) ->
lists:flatten(
- io_lib:format("fun head contains already defined field ~w in "
- "record type ~w",[FName, RName]));
+ io_lib:format("fun head contains already defined field ~tw in "
+ "record type ~tw",[FName, RName]));
format_error({?ERR_HEADDOLLARATOM,Atom}) ->
lists:flatten(
io_lib:format("fun head contains atom ~w, which conflics with reserved "
@@ -166,28 +166,28 @@ format_error({?ERR_HEADBINMATCH,Atom}) ->
"which cannot be translated into match_spec", [Atom]));
format_error({?ERR_GUARDBADREC,Name}) ->
lists:flatten(
- io_lib:format("fun guard contains unknown record type ~w",[Name]));
+ io_lib:format("fun guard contains unknown record type ~tw",[Name]));
format_error({?ERR_GUARDBADFIELD,RName,FName}) ->
lists:flatten(
- io_lib:format("fun guard contains reference to unknown field ~w in "
- "record type ~w",[FName, RName]));
+ io_lib:format("fun guard contains reference to unknown field ~tw in "
+ "record type ~tw",[FName, RName]));
format_error({?ERR_GUARDMULTIFIELD,RName,FName}) ->
lists:flatten(
- io_lib:format("fun guard contains already defined field ~w in "
- "record type ~w",[FName, RName]));
+ io_lib:format("fun guard contains already defined field ~tw in "
+ "record type ~tw",[FName, RName]));
format_error({?ERR_BODYBADREC,Name}) ->
lists:flatten(
- io_lib:format("fun body contains unknown record type ~w",[Name]));
+ io_lib:format("fun body contains unknown record type ~tw",[Name]));
format_error({?ERR_BODYBADFIELD,RName,FName}) ->
lists:flatten(
- io_lib:format("fun body contains reference to unknown field ~w in "
- "record type ~w",[FName, RName]));
+ io_lib:format("fun body contains reference to unknown field ~tw in "
+ "record type ~tw",[FName, RName]));
format_error({?ERR_BODYMULTIFIELD,RName,FName}) ->
lists:flatten(
- io_lib:format("fun body contains already defined field ~w in "
- "record type ~w",[FName, RName]));
+ io_lib:format("fun body contains already defined field ~tw in "
+ "record type ~tw",[FName, RName]));
format_error(Else) ->
- lists:flatten(io_lib:format("Unknown error code ~w",[Else])).
+ lists:flatten(io_lib:format("Unknown error code ~tw",[Else])).
%%
%% Called when translating in shell
@@ -224,9 +224,12 @@ transform_from_shell(Dialect, Clauses, BoundEnvironment) ->
%% Called when translating during compiling
%%
--spec parse_transform(Forms, Options) -> Forms when
- Forms :: [erl_parse:abstract_form()],
- Options :: term().
+-spec parse_transform(Forms, Options) -> Forms2 | Errors | Warnings when
+ Forms :: [erl_parse:abstract_form() | erl_parse:form_info()],
+ Forms2 :: [erl_parse:abstract_form() | erl_parse:form_info()],
+ Options :: term(),
+ Errors :: {error, ErrInfo :: [tuple()], WarnInfo :: []},
+ Warnings :: {warning, Forms2, WarnInfo :: [tuple()]}.
parse_transform(Forms, _Options) ->
SaveFilename = setup_filename(),
@@ -307,15 +310,18 @@ cleanup_filename({Old,OldRec,OldWarnings}) ->
add_record_definition({Name,FieldList}) ->
{KeyList,_} = lists:foldl(
- fun({record_field,_,{atom,Line0,FieldName}},{L,C}) ->
- {[{FieldName,C,{atom,Line0,undefined}}|L],C+1};
- ({record_field,_,{atom,_,FieldName},Def},{L,C}) ->
- {[{FieldName,C,Def}|L],C+1}
- end,
+ fun(F, {L,C}) -> {[record_field(F, C)|L],C+1} end,
{[],2},
FieldList),
put_records([{Name,KeyList}|get_records()]).
+record_field({record_field,_,{atom,Line0,FieldName}}, C) ->
+ {FieldName,C,{atom,Line0,undefined}};
+record_field({record_field,_,{atom,_,FieldName},Def}, C) ->
+ {FieldName,C,Def};
+record_field({typed_record_field,Field,_Type}, C) ->
+ record_field(Field, C).
+
forms([F0|Fs0]) ->
F1 = form(F0),
Fs1 = forms(Fs0),
@@ -447,6 +453,8 @@ check_type(_,[{record,_,_,_}],ets) ->
ok;
check_type(_,[{cons,_,_,_}],dbg) ->
ok;
+check_type(_,[{nil,_}],dbg) ->
+ ok;
check_type(Line0,[{match,_,{var,_,_},X}],Any) ->
check_type(Line0,[X],Any);
check_type(Line0,[{match,_,X,{var,_,_}}],Any) ->
@@ -495,10 +503,20 @@ tg0(Line,[H|T],B) ->
tg({match,Line,_,_},B) ->
throw({error,Line,?ERR_GENMATCH+B#tgd.eb});
-tg({op, Line, Operator, O1, O2}, B) ->
- {tuple, Line, [{atom, Line, Operator}, tg(O1,B), tg(O2,B)]};
-tg({op, Line, Operator, O1}, B) ->
- {tuple, Line, [{atom, Line, Operator}, tg(O1,B)]};
+tg({op, Line, Operator, O1, O2}=Expr, B) ->
+ case erl_eval:partial_eval(Expr) of
+ Expr ->
+ {tuple, Line, [{atom, Line, Operator}, tg(O1, B), tg(O2, B)]};
+ Value ->
+ Value
+ end;
+tg({op, Line, Operator, O1}=Expr, B) ->
+ case erl_eval:partial_eval(Expr) of
+ Expr ->
+ {tuple, Line, [{atom, Line, Operator}, tg(O1, B)]};
+ Value ->
+ Value
+ end;
tg({call, _Line, {atom, Line2, bindings},[]},_B) ->
{atom, Line2, '$*'};
tg({call, _Line, {atom, Line2, object},[]},_B) ->
@@ -717,7 +735,7 @@ tg(T,B) when is_tuple(T), tuple_size(T) >= 2 ->
throw({error,Line,{?ERR_GENELEMENT+B#tgd.eb,
translate_language_element(Element)}});
tg(Other,B) ->
- Element = io_lib:format("unknown element ~w", [Other]),
+ Element = io_lib:format("unknown element ~tw", [Other]),
throw({error,unknown,{?ERR_GENELEMENT+B#tgd.eb,Element}}).
transform_head([V],OuterBound) ->
@@ -913,6 +931,7 @@ bool_test(is_port,1) -> true;
bool_test(is_reference,1) -> true;
bool_test(is_tuple,1) -> true;
bool_test(is_map,1) -> true;
+bool_test(is_map_key, 2) -> true;
bool_test(is_binary,1) -> true;
bool_test(is_function,1) -> true;
bool_test(is_record,2) -> true;
@@ -927,7 +946,9 @@ real_guard_function(node,0) -> true;
real_guard_function(node,1) -> true;
real_guard_function(round,1) -> true;
real_guard_function(size,1) -> true;
+real_guard_function(bit_size,1) -> true;
real_guard_function(map_size,1) -> true;
+real_guard_function(map_get,2) -> true;
real_guard_function(tl,1) -> true;
real_guard_function(trunc,1) -> true;
real_guard_function(self,0) -> true;
@@ -1099,5 +1120,3 @@ normalise_list([H|T]) ->
[normalise(H)|normalise_list(T)];
normalise_list([]) ->
[].
-
-