Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:23
erlang
2041-Drop-old-code-for-handling-pre-R15-abstrac...
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 2041-Drop-old-code-for-handling-pre-R15-abstract-format.patch of Package erlang
From 7d1b3d15a86516c3720b53ab7bb7553a31254e0a Mon Sep 17 00:00:00 2001 From: Richard Carlsson <carlsson.richard@gmail.com> Date: Tue, 12 May 2020 13:07:57 +0200 Subject: [PATCH] Drop old code for handling pre-R15 abstract format --- erts/doc/src/absform.xml | 4 +-- lib/stdlib/examples/erl_id_trans.erl | 4 --- lib/stdlib/src/erl_lint.erl | 4 --- lib/stdlib/src/erl_pp.erl | 8 ------ lib/syntax_tools/src/erl_syntax.erl | 8 ------ lib/tools/src/xref_reader.erl | 9 ------ lib/tools/test/xref_SUITE.erl | 26 ++---------------- .../test/xref_SUITE_data/fun_mfa_r14.beam | Bin 1116 -> 0 bytes .../test/xref_SUITE_data/fun_mfa_r14.erl | 18 ------------ 9 files changed, 3 insertions(+), 78 deletions(-) delete mode 100644 lib/tools/test/xref_SUITE_data/fun_mfa_r14.beam delete mode 100644 lib/tools/test/xref_SUITE_data/fun_mfa_r14.erl diff --git a/erts/doc/src/absform.xml b/erts/doc/src/absform.xml index d3ba0932b7..65538a80f6 100644 --- a/erts/doc/src/absform.xml +++ b/erts/doc/src/absform.xml @@ -375,9 +375,7 @@ </item> <item> <p>If E is a fun expression <c>fun Module:Name/Arity</c>, then Rep(E) = - <c>{'fun',ANNO,{function,Rep(Module),Rep(Name),Rep(Arity)}}</c>. - (Before Erlang/OTP R15: Rep(E) = - <c>{'fun',ANNO,{function,Module,Name,Arity}}</c>.)</p> + <c>{'fun',ANNO,{function,Rep(Module),Rep(Name),Rep(Arity)}}</c>.</p> </item> <item> <p>If E is a fun expression <c>fun Fc_1 ; ... ; Fc_k end</c>, diff --git a/lib/stdlib/examples/erl_id_trans.erl b/lib/stdlib/examples/erl_id_trans.erl index a707c45eb9..f18e13a565 100644 --- a/lib/stdlib/examples/erl_id_trans.erl +++ b/lib/stdlib/examples/erl_id_trans.erl @@ -480,11 +480,7 @@ expr({'fun',Line,Body}) -> {'fun',Line,{clauses,Cs1}}; {function,F,A} -> {'fun',Line,{function,F,A}}; - {function,M,F,A} when is_atom(M), is_atom(F), is_integer(A) -> - %% R10B-6: fun M:F/A. (Backward compatibility) - {'fun',Line,{function,M,F,A}}; {function,M0,F0,A0} -> - %% R15: fun M:F/A with variables. M = expr(M0), F = expr(F0), A = expr(A0), diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index 7c717e47d1..442ea01da0 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -2426,11 +2426,7 @@ expr({'fun',Line,Body}, Vt, St) -> true -> {[],St}; false -> {[],call_function(Line, F, A, St)} end; - {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. expr_list([M,F,A], Vt, St) end; expr({named_fun,_,'_',Cs}, Vt, St) -> diff --git a/lib/stdlib/src/erl_pp.erl b/lib/stdlib/src/erl_pp.erl index 651c601bb0..2ccd6c53b5 100644 --- a/lib/stdlib/src/erl_pp.erl +++ b/lib/stdlib/src/erl_pp.erl @@ -623,15 +623,7 @@ lexpr({'fun',_,{function,F,A}}, _Prec, _Opts) -> [leaf("fun "),{atom,F},leaf(format("/~w", [A]))]; lexpr({'fun',L,{function,_,_}=Func,Extra}, Prec, Opts) -> {force_nl,fun_info(Extra),lexpr({'fun',L,Func}, Prec, Opts)}; -lexpr({'fun',L,{function,M,F,A}}, Prec, Opts) - when is_atom(M), is_atom(F), is_integer(A) -> - %% For backward compatibility with pre-R15 abstract format. - Mod = erl_parse:abstract(M), - Fun = erl_parse:abstract(F), - Arity = erl_parse:abstract(A), - lexpr({'fun',L,{function,Mod,Fun,Arity}}, Prec, Opts); lexpr({'fun',_,{function,M,F,A}}, _Prec, Opts) -> - %% New format in R15. NameItem = lexpr(M, Opts), CallItem = lexpr(F, Opts), ArityItem = lexpr(A, Opts), diff --git a/lib/syntax_tools/src/erl_syntax.erl b/lib/syntax_tools/src/erl_syntax.erl index ed94bd383c..087ce72ded 100644 --- a/lib/syntax_tools/src/erl_syntax.erl +++ b/lib/syntax_tools/src/erl_syntax.erl @@ -6872,15 +6872,7 @@ implicit_fun_name(Node) -> {'fun', Pos, {function, Atom, Arity}} -> arity_qualifier(set_pos(atom(Atom), Pos), set_pos(integer(Arity), Pos)); - {'fun', Pos, {function, Module, Atom, Arity}} - when is_atom(Module), is_atom(Atom), is_integer(Arity) -> - %% Backward compatibility with pre-R15 abstract format. - module_qualifier(set_pos(atom(Module), Pos), - arity_qualifier( - set_pos(atom(Atom), Pos), - set_pos(integer(Arity), Pos))); {'fun', _Pos, {function, Module, Atom, Arity}} -> - %% New in R15: fun M:F/A. %% XXX: Perhaps set position for this as well? module_qualifier(Module, arity_qualifier(Atom, Arity)); Node1 -> diff --git a/lib/tools/src/xref_reader.erl b/lib/tools/src/xref_reader.erl index d28bdb78db..c145b98972 100644 --- a/lib/tools/src/xref_reader.erl +++ b/lib/tools/src/xref_reader.erl @@ -171,15 +171,6 @@ expr({'try',_Line,Es,Scs,Ccs,As}, S) -> S2 = clauses(Scs, S1), S3 = clauses(Ccs, S2), expr(As, S3); -expr({'fun', Line, {function,M,F,A}}, S) - when is_atom(M), is_atom(F), is_integer(A) -> - %% This is the old format for external funs, generated by a pre-R15 - %% compiler. Exposed in OTP 20 because sys_pre_expand is no longer - %% run. - Fun = {'fun', Line, {function, {atom,Line,M}, - {atom,Line,F}, - {integer,Line,A}}}, - expr(Fun, S); expr({'fun', Line, {function, {atom,_,Mod}, {atom,_,Name}, {integer,_,Arity}}}, S) -> diff --git a/lib/tools/test/xref_SUITE.erl b/lib/tools/test/xref_SUITE.erl index d258966bc2..4ed8130dc0 100644 --- a/lib/tools/test/xref_SUITE.erl +++ b/lib/tools/test/xref_SUITE.erl @@ -45,7 +45,7 @@ -export([add/1, default/1, info/1, lib/1, read/1, read2/1, remove/1, replace/1, update/1, deprecated/1, trycatch/1, - fun_mfa/1, fun_mfa_r14/1, + fun_mfa/1, fun_mfa_vars/1, qlc/1]). -export([analyze/1, basic/1, md/1, q/1, variables/1, unused_locals/1, @@ -81,7 +81,7 @@ groups() -> {files, [], [add, default, info, lib, read, read2, remove, replace, update, deprecated, trycatch, fun_mfa, - fun_mfa_r14, fun_mfa_vars, qlc]}, + fun_mfa_vars, qlc]}, {analyses, [], [analyze, basic, md, q, variables, unused_locals, behaviour]}, @@ -1677,28 +1677,6 @@ fun_mfa(Conf) when is_list(Conf) -> ok = file:delete(Beam), ok. -%% Same as the previous test case, except that we use a BEAM file -%% that was compiled by an R14 compiler to test backward compatibility. -fun_mfa_r14(Conf) when is_list(Conf) -> - Dir = proplists:get_value(data_dir, Conf), - MFile = fname(Dir, "fun_mfa_r14"), - - A = fun_mfa_r14, - {ok, _} = xref:start(s), - {ok, A} = xref:add_module(s, MFile, {warnings,false}), - {ok, [{{{A,t,0},{'$M_EXPR','$F_EXPR',0}},[7]}, - {{{A,t,0},{A,t,0}},[6]}, - {{{A,t1,0},{'$M_EXPR','$F_EXPR',0}},[11]}, - {{{A,t1,0},{A,t,0}},[10]}, - {{{A,t2,0},{A,t,0}},[14]}, - {{{A,t3,0},{A,t3,0}},[17]}]} = - xref:q(s, "(Lin) E"), - - ok = check_state(s), - xref:stop(s), - - ok. - %% fun M:F/A with variables. fun_mfa_vars(Conf) when is_list(Conf) -> Dir = ?copydir, diff --git a/lib/tools/test/xref_SUITE_data/fun_mfa_r14.beam b/lib/tools/test/xref_SUITE_data/fun_mfa_r14.beam deleted file mode 100644 index 46455256904b541073bc78cc724f989072d8f37b..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 1116 zcmZ?s4>Dw6U<q+@b@X*C$<JkAU<d(XF7C9_y!hO-#P}jZ6UGv@)S{fkymXG-#O%~~ zpbS%qAybJFQ;9KmZhlH>PHKE+URpkXdTL2L5}!x6#8BTr7pPp<K-W1xB^7Ay6d)D= zVh~6NVtycIXB1!(Qet3K;9+2JP!e`vRCW+zW;bB)W)NZ!W;9?D3SwY%0LrC9MFN<F zk{B2hu&OR#5-MU~Y+z$(Wt_ky)WpEJ0BDw<fB@qLAWwktfCIBINI*e>@dA_3A_m3> zYz(T*!6ii?KQnmd7Jz6CAZCVQ79=(&kj)6?gV;>26=3x~KsFl?a{w_&9_TPI8%Qy5 z0Wmv>0R$j<kU9_m(X3z=Fz|si6O_&5R+<NLgA5RZ%mV2L0X_%?bXev_0iXP2kQz`p zqNs5!DJcSqX*B16WHOji7?{h7^T3=u0S3Vyxs0Fx7{c^a5-e}%%*e{ha`wzi11huu zt7ieJXU{Jv$;{6y2I*l28<1R{lFeYPpOcbVoUNafm0y&npI=g-pOcxSUy`4nQ><T- zT3n)EQIwh%9~|l#;u@clSdyrZlz2d<u;rJQq+}LRW>5+PS4wJ9X*xKqWr1B=mReK{ zbZ#~StBIbuo+(I-r6e;qHG?e)80@zbxe}!lc@s?%CBTj-&Mz%WPR(ZUrocDIKGOqc ziY&*Z;u2sO3N{A-BXL5-oYsl8Ma>EVN5%IGJyz+xT&<FP%lM1bIk$od32y{^s{c5d zge*1w%N=oV-}mOHjIH9W@v8IkqY{^%u2y7BIIGO1nYDIS@p?%iuE4t<$C|mHv?t$< zKfUc(km!5%Whz4P^R~#oRb4#6_Xu}nM#`Jtn}ctqx!pM+(3^1GLHzvLmpdz+1#FgW zFzcI|w@dq&bMsrZZ)z)5zL~de6xb$qW6uuP*g~Hjp4{(O7#RA>_fP(4_%-8^#c|of z9)(o_UNM&aQ@;u%HBRokBj^9>bIzRWX~#aV@UM8rGV}GRe=0Zn<ev%Vurqzi-da3y rcm4hYr*HOu{!sKS&hK5(r=yqKI;FCW?@lN+-Pa{AEw}y~Fa-esrN%q- diff --git a/lib/tools/test/xref_SUITE_data/fun_mfa_r14.erl b/lib/tools/test/xref_SUITE_data/fun_mfa_r14.erl deleted file mode 100644 index 293bd83a8b..0000000000 --- a/lib/tools/test/xref_SUITE_data/fun_mfa_r14.erl +++ /dev/null @@ -1,18 +0,0 @@ --module(fun_mfa_r14). - --export([t/0, t1/0, t2/0, t3/0]). - -t() -> - F = fun ?MODULE:t/0, - (F)(). - -t1() -> - F = fun t/0, - (F)(). - -t2() -> - fun ?MODULE:t/0(). - -t3() -> - fun t3/0(). - -- 2.26.2
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor