aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/erl_expand_records.erl
diff options
context:
space:
mode:
authorBjörn Gustavsson <[email protected]>2016-08-24 14:09:46 +0200
committerBjörn Gustavsson <[email protected]>2016-09-01 15:16:03 +0200
commit44c5d0a729387273a604f687fa2a9d50989f87d3 (patch)
tree27b566fbc0765e2272f7a193095e4d53394d4f37 /lib/stdlib/src/erl_expand_records.erl
parent04c67da5b455416c71fe9bc4c70fe61ceb7aad79 (diff)
downloadotp-44c5d0a729387273a604f687fa2a9d50989f87d3.tar.gz
otp-44c5d0a729387273a604f687fa2a9d50989f87d3.tar.bz2
otp-44c5d0a729387273a604f687fa2a9d50989f87d3.zip
Teach erl_expand_records to translate module-less calls
As the next step in eliminating sys_pre_expand, teach erl_expand_records to handle calls without explicit module name. If such call refer to a BIF or imported function, add an explicit module name. That means that any subsequent pass will know that a call without a module name is always to a local function defined in the module.
Diffstat (limited to 'lib/stdlib/src/erl_expand_records.erl')
-rw-r--r--lib/stdlib/src/erl_expand_records.erl84
1 files changed, 58 insertions, 26 deletions
diff --git a/lib/stdlib/src/erl_expand_records.erl b/lib/stdlib/src/erl_expand_records.erl
index ebcbc54ab1..ab47f05320 100644
--- a/lib/stdlib/src/erl_expand_records.erl
+++ b/lib/stdlib/src/erl_expand_records.erl
@@ -17,7 +17,8 @@
%%
%% %CopyrightEnd%
%%
-%% Purpose : Expand records into tuples.
+%% Purpose: Expand records into tuples. Also add explicit module
+%% names to calls to imported functions and BIFs.
%% N.B. Although structs (tagged tuples) are not yet allowed in the
%% language there is code included in pattern/2 and expr/3 (commented out)
@@ -31,7 +32,7 @@
-record(exprec, {compile=[], % Compile flags
vcount=0, % Variable counter
- imports=[], % Imports
+ calltype=#{}, % Call types
records=dict:new(), % Record definitions
strict_ra=[], % strict record accesses
checked_ra=[] % successfully accessed records
@@ -46,22 +47,34 @@
%% erl_lint without errors.
module(Fs0, Opts0) ->
Opts = compiler_options(Fs0) ++ Opts0,
- St0 = #exprec{compile = Opts},
+ Calltype = init_calltype(Fs0),
+ St0 = #exprec{compile = Opts, calltype = Calltype},
{Fs,_St} = forms(Fs0, St0),
Fs.
compiler_options(Forms) ->
lists:flatten([C || {attribute,_,compile,C} <- Forms]).
+init_calltype(Forms) ->
+ Locals = [{{Name,Arity},local} || {function,_,Name,Arity,_} <- Forms],
+ Ctype = maps:from_list(Locals),
+ init_calltype_imports(Forms, Ctype).
+
+init_calltype_imports([{attribute,_,import,{Mod,Fs}}|T], Ctype0) ->
+ true = is_atom(Mod),
+ Ctype = foldl(fun(FA, Acc) ->
+ Acc#{FA=>{imported,Mod}}
+ end, Ctype0, Fs),
+ init_calltype_imports(T, Ctype);
+init_calltype_imports([_|T], Ctype) ->
+ init_calltype_imports(T, Ctype);
+init_calltype_imports([], Ctype) -> Ctype.
+
forms([{attribute,_,record,{Name,Defs}}=Attr | Fs], St0) ->
NDefs = normalise_fields(Defs),
St = St0#exprec{records=dict:store(Name, NDefs, St0#exprec.records)},
{Fs1, St1} = forms(Fs, St),
{[Attr | Fs1], St1};
-forms([{attribute,L,import,Is} | Fs0], St0) ->
- St1 = import(Is, St0),
- {Fs,St2} = forms(Fs0, St1),
- {[{attribute,L,import,Is} | Fs], St2};
forms([{function,L,N,A,Cs0} | Fs0], St0) ->
{Cs,St1} = clauses(Cs0, St0),
{Fs,St2} = forms(Fs0, St1),
@@ -334,8 +347,16 @@ expr({'receive',Line,Cs0,To0,ToEs0}, St0) ->
{ToEs,St2} = exprs(ToEs0, St1),
{Cs,St3} = clauses(Cs0, St2),
{{'receive',Line,Cs,To,ToEs},St3};
-expr({'fun',_,{function,_F,_A}}=Fun, St) ->
- {Fun,St};
+expr({'fun',Lf,{function,F,A}}=Fun0, St0) ->
+ case erl_internal:bif(F, A) of
+ true ->
+ {As,St1} = new_vars(A, Lf, St0),
+ Cs = [{clause,Lf,As,[],[{call,Lf,{atom,Lf,F},As}]}],
+ Fun = {'fun',Lf,{clauses,Cs}},
+ expr(Fun, St1);
+ false ->
+ {Fun0,St0}
+ end;
expr({'fun',_,{function,_M,_F,_A}}=Fun, St) ->
{Fun,St};
expr({'fun',Line,{clauses,Cs0}}, St0) ->
@@ -352,14 +373,30 @@ expr({call,Line,{remote,_,{atom,_,erlang},{atom,_,is_record}},
expr({call,Line,{tuple,_,[{atom,_,erlang},{atom,_,is_record}]},
[A,{atom,_,Name}]}, St) ->
record_test(Line, A, Name, St);
+expr({call,Line,{atom,_La,record_info},[_,_]=As0}, St0) ->
+ {As,St1} = expr_list(As0, St0),
+ record_info_call(Line, As, St1);
expr({call,Line,{atom,_La,N}=Atom,As0}, St0) ->
{As,St1} = expr_list(As0, St0),
Ar = length(As),
- case {N,Ar} =:= {record_info,2} andalso not imported(N, Ar, St1) of
- true ->
- record_info_call(Line, As, St1);
- false ->
- {{call,Line,Atom,As},St1}
+ NA = {N,Ar},
+ case St0#exprec.calltype of
+ #{NA := local} ->
+ {{call,Line,Atom,As},St1};
+ #{NA := {imported,Module}} ->
+ ModAtom = {atom,Line,Module},
+ {{call,Line,{remote,Line,ModAtom,Atom},As},St1};
+ _ ->
+ case erl_internal:bif(N, Ar) of
+ true ->
+ ModAtom = {atom,Line,erlang},
+ {{call,Line,{remote,Line,ModAtom,Atom},As},St1};
+ false ->
+ %% Call to a module_info/0,1 or one of the
+ %% pseudo-functions in the shell. Leave it as
+ %% a local call.
+ {{call,Line,Atom,As},St1}
+ end
end;
expr({call,Line,{remote,Lr,M,F},As0}, St0) ->
{[M1,F1 | As1],St1} = expr_list([M,F | As0], St0),
@@ -769,6 +806,13 @@ bin_element({bin_element,Line,Expr,Size,Type}, {Es,St0}) ->
end,
{[{bin_element,Line,Expr1,Size1,Type} | Es],St2}.
+new_vars(N, L, St) -> new_vars(N, L, St, []).
+
+new_vars(N, L, St0, Vs) when N > 0 ->
+ {V,St1} = new_var(L, St0),
+ new_vars(N-1, L, St1, [V|Vs]);
+new_vars(0, _L, St, Vs) -> {Vs,St}.
+
new_var(L, St0) ->
{New,St1} = new_var_name(St0),
{{var,L,New},St1}.
@@ -783,18 +827,6 @@ make_list(Ts, Line) ->
call_error(L, R) ->
{call,L,{remote,L,{atom,L,erlang},{atom,L,error}},[R]}.
-import({Mod,Fs}, St) ->
- St#exprec{imports=add_imports(Mod, Fs, St#exprec.imports)};
-import(_Mod0, St) ->
- St.
-
-add_imports(Mod, [F | Fs], Is) ->
- add_imports(Mod, Fs, orddict:store(F, Mod, Is));
-add_imports(_, [], Is) -> Is.
-
-imported(F, A, St) ->
- orddict:is_key({F,A}, St#exprec.imports).
-
%%%
%%% Replace is_record/3 in guards with matching if possible.
%%%