aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r--lib/stdlib/src/erl_eval.erl3
-rw-r--r--lib/stdlib/src/erl_lint.erl9
-rw-r--r--lib/stdlib/src/erl_parse.yrl12
-rw-r--r--lib/stdlib/src/erl_pp.erl10
-rw-r--r--lib/stdlib/src/qlc.erl5
5 files changed, 31 insertions, 8 deletions
diff --git a/lib/stdlib/src/erl_eval.erl b/lib/stdlib/src/erl_eval.erl
index 4f4fa16040..88a0094d57 100644
--- a/lib/stdlib/src/erl_eval.erl
+++ b/lib/stdlib/src/erl_eval.erl
@@ -256,7 +256,8 @@ expr({'receive',_,Cs}, Bs, Lf, Ef, RBs) ->
expr({'receive',_, Cs, E, TB}, Bs0, Lf, Ef, RBs) ->
{value,T,Bs} = expr(E, Bs0, Lf, Ef, none),
receive_clauses(T, Cs, {TB,Bs}, Bs0, Lf, Ef, [], RBs);
-expr({'fun',_Line,{function,Mod,Name,Arity}}, Bs, _Lf, _Ef, RBs) ->
+expr({'fun',_Line,{function,Mod0,Name0,Arity0}}, Bs0, Lf, Ef, RBs) ->
+ {[Mod,Name,Arity],Bs} = expr_list([Mod0,Name0,Arity0], Bs0, Lf, Ef),
F = erlang:make_fun(Mod, Name, Arity),
ret_expr(F, Bs, RBs);
expr({'fun',_Line,{function,Name,Arity}}, _Bs0, _Lf, _Ef, _RBs) -> % R8
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index 78b996d94b..5d45260fe9 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -2127,8 +2127,13 @@ expr({'fun',Line,Body}, Vt, St) ->
true -> {[],St};
false -> {[],call_function(Line, F, A, St)}
end;
- {function,_M,_F,_A} ->
- {[],St}
+ {function,M,F,A} when is_atom(M), is_atom(F), is_integer(A) ->
+ %% Compatibility with pre-R15 abstract format.
+ {[],St};
+ {function,M,F,A} ->
+ %% New in R15.
+ {Bvt, St1} = expr_list([M,F,A], Vt, St),
+ {vtupdate(Bvt, Vt),St1}
end;
expr({call,_Line,{atom,_Lr,is_record},[E,{atom,Ln,Name}]}, Vt, St0) ->
{Rvt,St1} = expr(E, Vt, St0),
diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl
index 709bd83e6f..928c10f7f2 100644
--- a/lib/stdlib/src/erl_parse.yrl
+++ b/lib/stdlib/src/erl_parse.yrl
@@ -35,7 +35,7 @@ tuple
%struct
record_expr record_tuple record_field record_fields
if_expr if_clause if_clauses case_expr cr_clause cr_clauses receive_expr
-fun_expr fun_clause fun_clauses
+fun_expr fun_clause fun_clauses atom_or_var integer_or_var
try_expr try_catch try_clause try_clauses query_expr
function_call argument_list
exprs guard
@@ -395,11 +395,17 @@ receive_expr -> 'receive' cr_clauses 'after' expr clause_body 'end' :
fun_expr -> 'fun' atom '/' integer :
{'fun',?line('$1'),{function,element(3, '$2'),element(3, '$4')}}.
-fun_expr -> 'fun' atom ':' atom '/' integer :
- {'fun',?line('$1'),{function,element(3, '$2'),element(3, '$4'),element(3,'$6')}}.
+fun_expr -> 'fun' atom_or_var ':' atom_or_var '/' integer_or_var :
+ {'fun',?line('$1'),{function,'$2','$4','$6'}}.
fun_expr -> 'fun' fun_clauses 'end' :
build_fun(?line('$1'), '$2').
+atom_or_var -> atom : '$1'.
+atom_or_var -> var : '$1'.
+
+integer_or_var -> integer : '$1'.
+integer_or_var -> var : '$1'.
+
fun_clauses -> fun_clause : ['$1'].
fun_clauses -> fun_clause ';' fun_clauses : ['$1' | '$3'].
diff --git a/lib/stdlib/src/erl_pp.erl b/lib/stdlib/src/erl_pp.erl
index 7dc19f2e9b..6b5aa951cf 100644
--- a/lib/stdlib/src/erl_pp.erl
+++ b/lib/stdlib/src/erl_pp.erl
@@ -457,8 +457,16 @@ lexpr({'fun',_,{function,F,A}}, _Prec, _Hook) ->
leaf(format("fun ~w/~w", [F,A]));
lexpr({'fun',_,{function,F,A},Extra}, _Prec, _Hook) ->
{force_nl,fun_info(Extra),leaf(format("fun ~w/~w", [F,A]))};
-lexpr({'fun',_,{function,M,F,A}}, _Prec, _Hook) ->
+lexpr({'fun',_,{function,M,F,A}}, _Prec, _Hook)
+ when is_atom(M), is_atom(F), is_integer(A) ->
+ %% For backward compatibility with pre-R15 abstract format.
leaf(format("fun ~w:~w/~w", [M,F,A]));
+lexpr({'fun',_,{function,M,F,A}}, _Prec, Hook) ->
+ %% New format in R15.
+ NameItem = lexpr(M, Hook),
+ CallItem = lexpr(F, Hook),
+ ArityItem = lexpr(A, Hook),
+ ["fun ",NameItem,$:,CallItem,$/,ArityItem];
lexpr({'fun',_,{clauses,Cs}}, _Prec, Hook) ->
{list,[{first,'fun',fun_clauses(Cs, Hook)},'end']};
lexpr({'fun',_,{clauses,Cs},Extra}, _Prec, Hook) ->
diff --git a/lib/stdlib/src/qlc.erl b/lib/stdlib/src/qlc.erl
index f5e180b4bd..2b691e6abf 100644
--- a/lib/stdlib/src/qlc.erl
+++ b/lib/stdlib/src/qlc.erl
@@ -1272,7 +1272,10 @@ abstr_term(Fun, Line) when is_function(Fun) ->
case erlang:fun_info(Fun, type) of
{type, external} ->
{module, Module} = erlang:fun_info(Fun, module),
- {'fun', Line, {function,Module,Name,Arity}};
+ {'fun', Line, {function,
+ {atom,Line,Module},
+ {atom,Line,Name},
+ {integer,Line,Arity}}};
{type, local} ->
{'fun', Line, {function,Name,Arity}}
end