aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorBjörn Gustavsson <[email protected]>2012-10-08 15:51:57 +0200
committerBjörn Gustavsson <[email protected]>2013-01-18 11:48:06 +0100
commitcdf80608685750e9e09069d8299a5b44ed53b2a0 (patch)
tree8b2cc3f5ea9c3684515744b62985a8954e1aa0a0
parentce467a4676fa9c6d501adff800a86ad1b93baa95 (diff)
downloadotp-cdf80608685750e9e09069d8299a5b44ed53b2a0.tar.gz
otp-cdf80608685750e9e09069d8299a5b44ed53b2a0.tar.bz2
otp-cdf80608685750e9e09069d8299a5b44ed53b2a0.zip
Remove support for parameterized modules
-rw-r--r--lib/compiler/src/Makefile1
-rw-r--r--lib/compiler/src/compile.erl1
-rw-r--r--lib/compiler/src/compiler.app.src1
-rw-r--r--lib/compiler/src/sys_expand_pmod.erl433
-rw-r--r--lib/compiler/src/sys_pre_expand.erl85
-rw-r--r--lib/compiler/test/Makefile1
-rw-r--r--lib/compiler/test/pmod_SUITE.erl121
-rw-r--r--lib/compiler/test/pmod_SUITE_data/pmod_basic.erl83
-rw-r--r--lib/stdlib/src/erl_lint.erl72
-rw-r--r--lib/stdlib/test/erl_lint_SUITE.erl22
10 files changed, 21 insertions, 799 deletions
diff --git a/lib/compiler/src/Makefile b/lib/compiler/src/Makefile
index cbcbf79839..3229752be1 100644
--- a/lib/compiler/src/Makefile
+++ b/lib/compiler/src/Makefile
@@ -82,7 +82,6 @@ MODULES = \
sys_core_dsetel \
sys_core_fold \
sys_core_inline \
- sys_expand_pmod \
sys_pre_attributes \
sys_pre_expand \
v3_codegen \
diff --git a/lib/compiler/src/compile.erl b/lib/compiler/src/compile.erl
index 10e7f5e9ce..7596a2cac8 100644
--- a/lib/compiler/src/compile.erl
+++ b/lib/compiler/src/compile.erl
@@ -895,7 +895,6 @@ foldl_core_transforms(St, []) -> {ok,St}.
%%% Fetches the module name from a list of forms. The module attribute must
%%% be present.
-get_module([{attribute,_,module,{M,_As}} | _]) -> M;
get_module([{attribute,_,module,M} | _]) -> M;
get_module([_ | Rest]) ->
get_module(Rest).
diff --git a/lib/compiler/src/compiler.app.src b/lib/compiler/src/compiler.app.src
index 94c78e68f9..9a02121d8b 100644
--- a/lib/compiler/src/compiler.app.src
+++ b/lib/compiler/src/compiler.app.src
@@ -57,7 +57,6 @@
sys_core_dsetel,
sys_core_fold,
sys_core_inline,
- sys_expand_pmod,
sys_pre_attributes,
sys_pre_expand,
v3_codegen,
diff --git a/lib/compiler/src/sys_expand_pmod.erl b/lib/compiler/src/sys_expand_pmod.erl
deleted file mode 100644
index da644b4f0b..0000000000
--- a/lib/compiler/src/sys_expand_pmod.erl
+++ /dev/null
@@ -1,433 +0,0 @@
-%%
-%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 2004-2011. All Rights Reserved.
-%%
-%% The contents of this file are subject to the Erlang Public License,
-%% Version 1.1, (the "License"); you may not use this file except in
-%% compliance with the License. You should have received a copy of the
-%% Erlang Public License along with this software. If not, it can be
-%% retrieved online at http://www.erlang.org/.
-%%
-%% Software distributed under the License is distributed on an "AS IS"
-%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
-%% the License for the specific language governing rights and limitations
-%% under the License.
-%%
-%% %CopyrightEnd%
-%%
--module(sys_expand_pmod).
-
-%% Expand function definition forms of parameterized module. We assume
-%% all record definitions, imports, queries, etc., have been expanded
-%% away. Any calls on the form 'foo(...)' must be calls to local
-%% functions. Auto-generated functions (module_info,...) have not yet
-%% been added to the function definitions, but are listed in 'defined'
-%% and 'exports'. The automatic 'new/N' function is neither added to the
-%% definitions nor to the 'exports'/'defines' lists yet.
-
--export([forms/4]).
-
--record(pmod, {parameters, exports, defined, predef}).
-
-%% TODO: more abstract handling of predefined/static functions.
-
-forms(Fs0, Ps, Es0, Ds0) ->
- PreDef = [{module_info,0},{module_info,1}],
- forms(Fs0, Ps, Es0, Ds0, PreDef).
-
-forms(Fs0, Ps, Es0, Ds0, PreDef) ->
- St0 = #pmod{parameters=Ps,exports=Es0,defined=Ds0, predef=PreDef},
- {Fs1, St1} = forms(Fs0, St0),
- Es1 = update_function_names(Es0, St1),
- Ds1 = update_function_names(Ds0, St1),
- Fs2 = update_forms(Fs1, St1),
- {Fs2,Es1,Ds1}.
-
-%% This is extremely simplistic for now; all functions get an extra
-%% parameter, whether they need it or not, except for static functions.
-
-update_function_names(Es, St) ->
- [update_function_name(E, St) || E <- Es].
-
-update_function_name(E={F,A}, St) when F =/= new ->
- case ordsets:is_element(E, St#pmod.predef) of
- true -> E;
- false -> {F, A + 1}
- end;
-update_function_name(E, _St) ->
- E.
-
-update_forms([{function,L,N,A,Cs}|Fs],St) when N =/= new ->
- [{function,L,N,A+1,Cs}|update_forms(Fs,St)];
-update_forms([F|Fs],St) ->
- [F|update_forms(Fs,St)];
-update_forms([],_St) ->
- [].
-
-%% Process the program forms.
-
-forms([F0|Fs0],St0) ->
- {F1,St1} = form(F0,St0),
- {Fs1,St2} = forms(Fs0,St1),
- {[F1|Fs1],St2};
-forms([], St0) ->
- {[], St0}.
-
-%% Only function definitions are of interest here. State is not updated.
-form({function,Line,Name0,Arity0,Clauses0},St) when Name0 =/= new ->
- {Name,Arity,Clauses} = function(Name0, Arity0, Clauses0, St),
- {{function,Line,Name,Arity,Clauses},St};
-%% Pass anything else through
-form(F,St) -> {F,St}.
-
-function(Name, Arity, Clauses0, St) ->
- Clauses1 = clauses(Clauses0,St),
- {Name,Arity,Clauses1}.
-
-clauses([C|Cs],St) ->
- {clause,L,H,G,B} = clause(C,St),
- T = {tuple,L,[{var,L,V} || V <- ['_'|St#pmod.parameters]]},
- [{clause,L,H++[{match,L,T,{var,L,'THIS'}}],G,B}|clauses(Cs,St)];
-clauses([],_St) -> [].
-
-clause({clause,Line,H0,G0,B0},St) ->
- H1 = head(H0,St),
- G1 = guard(G0,St),
- B1 = exprs(B0,St),
- {clause,Line,H1,G1,B1}.
-
-head(Ps,St) -> patterns(Ps,St).
-
-patterns([P0|Ps],St) ->
- P1 = pattern(P0,St),
- [P1|patterns(Ps,St)];
-patterns([],_St) -> [].
-
-string_to_conses([], _Line, Tail) ->
- Tail;
-string_to_conses([E|Rest], Line, Tail) ->
- {cons, Line, {integer, Line, E}, string_to_conses(Rest, Line, Tail)}.
-
-pattern({var,_Line,_V}=Var,_St) -> Var;
-pattern({match,Line,L0,R0},St) ->
- L1 = pattern(L0,St),
- R1 = pattern(R0,St),
- {match,Line,L1,R1};
-pattern({integer,_Line,_I}=Integer,_St) -> Integer;
-pattern({char,_Line,_C}=Char,_St) -> Char;
-pattern({float,_Line,_F}=Float,_St) -> Float;
-pattern({atom,_Line,_A}=Atom,_St) -> Atom;
-pattern({string,_Line,_S}=String,_St) -> String;
-pattern({nil,_Line}=Nil,_St) -> Nil;
-pattern({cons,Line,H0,T0},St) ->
- H1 = pattern(H0,St),
- T1 = pattern(T0,St),
- {cons,Line,H1,T1};
-pattern({tuple,Line,Ps0},St) ->
- Ps1 = pattern_list(Ps0,St),
- {tuple,Line,Ps1};
-pattern({bin,Line,Fs},St) ->
- Fs2 = pattern_grp(Fs,St),
- {bin,Line,Fs2};
-pattern({op,_Line,'++',{nil,_},R},St) ->
- pattern(R,St);
-pattern({op,_Line,'++',{cons,Li,{char,_C2,_I}=Char,T},R},St) ->
- pattern({cons,Li,Char,{op,Li,'++',T,R}},St);
-pattern({op,_Line,'++',{cons,Li,{integer,_L2,_I}=Integer,T},R},St) ->
- pattern({cons,Li,Integer,{op,Li,'++',T,R}},St);
-pattern({op,_Line,'++',{string,Li,L},R},St) ->
- pattern(string_to_conses(L, Li, R),St);
-pattern({op,_Line,_Op,_A}=Op4,_St) -> Op4;
-pattern({op,_Line,_Op,_L,_R}=Op5,_St) -> Op5.
-
-pattern_grp([{bin_element,L1,E1,S1,T1} | Fs],St) ->
- S2 = case S1 of
- default ->
- default;
- _ ->
- expr(S1,St)
- end,
- T2 = case T1 of
- default ->
- default;
- _ ->
- bit_types(T1)
- end,
- [{bin_element,L1,expr(E1,St),S2,T2} | pattern_grp(Fs,St)];
-pattern_grp([],_St) ->
- [].
-
-bit_types([]) ->
- [];
-bit_types([Atom | Rest]) when is_atom(Atom) ->
- [Atom | bit_types(Rest)];
-bit_types([{Atom, Integer} | Rest]) when is_atom(Atom), is_integer(Integer) ->
- [{Atom, Integer} | bit_types(Rest)].
-
-pattern_list([P0|Ps],St) ->
- P1 = pattern(P0,St),
- [P1|pattern_list(Ps,St)];
-pattern_list([],_St) -> [].
-
-guard([G0|Gs],St) when is_list(G0) ->
- [guard0(G0,St) | guard(Gs,St)];
-guard(L,St) ->
- guard0(L,St).
-
-guard0([G0|Gs],St) ->
- G1 = guard_test(G0,St),
- [G1|guard0(Gs,St)];
-guard0([],_St) -> [].
-
-guard_test(Expr={call,Line,{atom,La,F},As0},St) ->
- case erl_internal:type_test(F, length(As0)) of
- true ->
- As1 = gexpr_list(As0,St),
- {call,Line,{atom,La,F},As1};
- _ ->
- gexpr(Expr,St)
- end;
-guard_test(Any,St) ->
- gexpr(Any,St).
-
-gexpr({var,_L,_V}=Var,_St) -> Var;
-% %% alternative implementation of accessing module parameters
-% case index(V,St#pmod.parameters) of
-% N when N > 0 ->
-% {call,L,{remote,L,{atom,L,erlang},{atom,L,element}},
-% [{integer,L,N+1},{var,L,'THIS'}]};
-% _ ->
-% Var
-% end;
-gexpr({integer,_Line,_I}=Integer,_St) -> Integer;
-gexpr({char,_Line,_C}=Char,_St) -> Char;
-gexpr({float,_Line,_F}=Float,_St) -> Float;
-gexpr({atom,_Line,_A}=Atom,_St) -> Atom;
-gexpr({string,_Line,_S}=String,_St) -> String;
-gexpr({nil,_Line}=Nil,_St) -> Nil;
-gexpr({cons,Line,H0,T0},St) ->
- H1 = gexpr(H0,St),
- T1 = gexpr(T0,St),
- {cons,Line,H1,T1};
-gexpr({tuple,Line,Es0},St) ->
- Es1 = gexpr_list(Es0,St),
- {tuple,Line,Es1};
-gexpr({call,Line,{atom,_La,F}=Atom,As0},St) ->
- true = erl_internal:guard_bif(F, length(As0)),
- As1 = gexpr_list(As0,St),
- {call,Line,Atom,As1};
-%% Pre-expansion generated calls to erlang:is_record/3 must also be handled
-gexpr({call,Line,{remote,La,{atom,Lb,erlang},{atom,Lc,is_record}},[_,_,_]=As0},St) ->
- As1 = gexpr_list(As0,St),
- {call,Line,{remote,La,{atom,Lb,erlang},{atom,Lc,is_record}},As1};
-%% Guard BIFs can be remote, but only in the module erlang...
-gexpr({call,Line,{remote,La,{atom,Lb,erlang},{atom,Lc,F}},As0},St) ->
- A = length(As0),
- true =
- erl_internal:guard_bif(F, A) orelse erl_internal:arith_op(F, A) orelse
- erl_internal:comp_op(F, A) orelse erl_internal:bool_op(F, A),
- As1 = gexpr_list(As0,St),
- {call,Line,{remote,La,{atom,Lb,erlang},{atom,Lc,F}},As1};
-%% Unfortunately, writing calls as {M,F}(...) is also allowed.
-gexpr({call,Line,{tuple,La,[{atom,Lb,erlang},{atom,Lc,F}]},As0},St) ->
- A = length(As0),
- true =
- erl_internal:guard_bif(F, A) orelse erl_internal:arith_op(F, A) orelse
- erl_internal:comp_op(F, A) orelse erl_internal:bool_op(F, A),
- As1 = gexpr_list(As0,St),
- {call,Line,{tuple,La,[{atom,Lb,erlang},{atom,Lc,F}]},As1};
-gexpr({bin,Line,Fs},St) ->
- Fs2 = pattern_grp(Fs,St),
- {bin,Line,Fs2};
-gexpr({op,Line,Op,A0},St) ->
- true = erl_internal:arith_op(Op, 1) orelse erl_internal:bool_op(Op, 1),
- A1 = gexpr(A0,St),
- {op,Line,Op,A1};
-gexpr({op,Line,Op,L0,R0},St) ->
- true =
- Op =:= 'andalso' orelse Op =:= 'orelse' orelse
- erl_internal:arith_op(Op, 2) orelse
- erl_internal:bool_op(Op, 2) orelse erl_internal:comp_op(Op, 2),
- L1 = gexpr(L0,St),
- R1 = gexpr(R0,St),
- {op,Line,Op,L1,R1}.
-
-gexpr_list([E0|Es],St) ->
- E1 = gexpr(E0,St),
- [E1|gexpr_list(Es,St)];
-gexpr_list([],_St) -> [].
-
-exprs([E0|Es],St) ->
- E1 = expr(E0,St),
- [E1|exprs(Es,St)];
-exprs([],_St) -> [].
-
-expr({var,_L,_V}=Var,_St) ->
- Var;
-% case index(V,St#pmod.parameters) of
-% N when N > 0 ->
-% {call,L,{remote,L,{atom,L,erlang},{atom,L,element}},
-% [{integer,L,N+1},{var,L,'THIS'}]};
-% _ ->
-% Var
-% end;
-expr({integer,_Line,_I}=Integer,_St) -> Integer;
-expr({float,_Line,_F}=Float,_St) -> Float;
-expr({atom,_Line,_A}=Atom,_St) -> Atom;
-expr({string,_Line,_S}=String,_St) -> String;
-expr({char,_Line,_C}=Char,_St) -> Char;
-expr({nil,_Line}=Nil,_St) -> Nil;
-expr({cons,Line,H0,T0},St) ->
- H1 = expr(H0,St),
- T1 = expr(T0,St),
- {cons,Line,H1,T1};
-expr({lc,Line,E0,Qs0},St) ->
- Qs1 = lc_bc_quals(Qs0,St),
- E1 = expr(E0,St),
- {lc,Line,E1,Qs1};
-expr({bc,Line,E0,Qs0},St) ->
- Qs1 = lc_bc_quals(Qs0,St),
- E1 = expr(E0,St),
- {bc,Line,E1,Qs1};
-expr({tuple,Line,Es0},St) ->
- Es1 = expr_list(Es0,St),
- {tuple,Line,Es1};
-expr({block,Line,Es0},St) ->
- Es1 = exprs(Es0,St),
- {block,Line,Es1};
-expr({'if',Line,Cs0},St) ->
- Cs1 = icr_clauses(Cs0,St),
- {'if',Line,Cs1};
-expr({'case',Line,E0,Cs0},St) ->
- E1 = expr(E0,St),
- Cs1 = icr_clauses(Cs0,St),
- {'case',Line,E1,Cs1};
-expr({'receive',Line,Cs0},St) ->
- Cs1 = icr_clauses(Cs0,St),
- {'receive',Line,Cs1};
-expr({'receive',Line,Cs0,To0,ToEs0},St) ->
- To1 = expr(To0,St),
- ToEs1 = exprs(ToEs0,St),
- Cs1 = icr_clauses(Cs0,St),
- {'receive',Line,Cs1,To1,ToEs1};
-expr({'try',Line,Es0,Scs0,Ccs0,As0},St) ->
- Es1 = exprs(Es0,St),
- Scs1 = icr_clauses(Scs0,St),
- Ccs1 = icr_clauses(Ccs0,St),
- As1 = exprs(As0,St),
- {'try',Line,Es1,Scs1,Ccs1,As1};
-expr({'fun',_,{function,_,_,_}}=ExtFun,_St) ->
- ExtFun;
-expr({'fun',Line,Body,Info},St) ->
- case Body of
- {clauses,Cs0} ->
- Cs1 = fun_clauses(Cs0,St),
- {'fun',Line,{clauses,Cs1},Info};
- {function,F,A} = Function ->
- {F1,A1} = update_function_name({F,A},St),
- if A1 =:= A ->
- {'fun',Line,Function,Info};
- true ->
- %% Must rewrite local fun-name to a fun that does a
- %% call with the extra THIS parameter.
- As = make_vars(A, Line),
- As1 = As ++ [{var,Line,'THIS'}],
- Call = {call,Line,{atom,Line,F1},As1},
- Cs = [{clause,Line,As,[],[Call]}],
- {'fun',Line,{clauses,Cs},Info}
- end;
- {function,_M,_F,_A} = Fun4 -> %This is an error in lint!
- {'fun',Line,Fun4,Info}
- end;
-expr({call,Lc,{atom,_,instance}=Name,As0},St) ->
- %% All local functions 'instance(...)' are static by definition,
- %% so they do not take a 'THIS' argument when called
- As1 = expr_list(As0,St),
- {call,Lc,Name,As1};
-expr({call,Lc,{atom,_,new}=Name,As0},St) ->
- %% All local functions 'new(...)' are static by definition,
- %% so they do not take a 'THIS' argument when called
- As1 = expr_list(As0,St),
- {call,Lc,Name,As1};
-expr({call,Lc,{atom,_,module_info}=Name,As0},St)
- when length(As0) =:= 0; length(As0) =:= 1 ->
- %% The module_info/0 and module_info/1 functions are also static.
- As1 = expr_list(As0,St),
- {call,Lc,Name,As1};
-expr({call,Lc,{atom,_Lf,_F}=Atom,As0},St) ->
- %% Local function call - needs THIS parameter.
- As1 = expr_list(As0,St),
- {call,Lc,Atom,As1 ++ [{var,0,'THIS'}]};
-expr({call,Line,F0,As0},St) ->
- %% Other function call
- F1 = expr(F0,St),
- As1 = expr_list(As0,St),
- {call,Line,F1,As1};
-expr({'catch',Line,E0},St) ->
- E1 = expr(E0,St),
- {'catch',Line,E1};
-expr({match,Line,P0,E0},St) ->
- E1 = expr(E0,St),
- P1 = pattern(P0,St),
- {match,Line,P1,E1};
-expr({bin,Line,Fs},St) ->
- Fs2 = pattern_grp(Fs,St),
- {bin,Line,Fs2};
-expr({op,Line,Op,A0},St) ->
- A1 = expr(A0,St),
- {op,Line,Op,A1};
-expr({op,Line,Op,L0,R0},St) ->
- L1 = expr(L0,St),
- R1 = expr(R0,St),
- {op,Line,Op,L1,R1};
-%% The following are not allowed to occur anywhere!
-expr({remote,Line,M0,F0},St) ->
- M1 = expr(M0,St),
- F1 = expr(F0,St),
- {remote,Line,M1,F1}.
-
-expr_list([E0|Es],St) ->
- E1 = expr(E0,St),
- [E1|expr_list(Es,St)];
-expr_list([],_St) -> [].
-
-icr_clauses([C0|Cs],St) ->
- C1 = clause(C0,St),
- [C1|icr_clauses(Cs,St)];
-icr_clauses([],_St) -> [].
-
-lc_bc_quals([{generate,Line,P0,E0}|Qs],St) ->
- E1 = expr(E0,St),
- P1 = pattern(P0,St),
- [{generate,Line,P1,E1}|lc_bc_quals(Qs,St)];
-lc_bc_quals([{b_generate,Line,P0,E0}|Qs],St) ->
- E1 = expr(E0,St),
- P1 = pattern(P0,St),
- [{b_generate,Line,P1,E1}|lc_bc_quals(Qs,St)];
-lc_bc_quals([E0|Qs],St) ->
- E1 = expr(E0,St),
- [E1|lc_bc_quals(Qs,St)];
-lc_bc_quals([],_St) -> [].
-
-fun_clauses([C0|Cs],St) ->
- C1 = clause(C0,St),
- [C1|fun_clauses(Cs,St)];
-fun_clauses([],_St) -> [].
-
-%% %% Return index from 1 upwards, or 0 if not in the list.
-%%
-%% index(X,Ys) -> index(X,Ys,1).
-%%
-%% index(X,[X|Ys],A) -> A;
-%% index(X,[Y|Ys],A) -> index(X,Ys,A+1);
-%% index(X,[],A) -> 0.
-
-make_vars(N, L) ->
- make_vars(1, N, L).
-
-make_vars(N, M, L) when N =< M ->
- V = list_to_atom("X"++integer_to_list(N)),
- [{var,L,V} | make_vars(N + 1, M, L)];
-make_vars(_, _, _) ->
- [].
diff --git a/lib/compiler/src/sys_pre_expand.erl b/lib/compiler/src/sys_pre_expand.erl
index a8c69c3cb1..7d918a55ed 100644
--- a/lib/compiler/src/sys_pre_expand.erl
+++ b/lib/compiler/src/sys_pre_expand.erl
@@ -28,13 +28,12 @@
%% Main entry point.
-export([module/2]).
--import(ordsets, [from_list/1,add_element/2,union/2]).
+-import(ordsets, [from_list/1,union/2]).
-import(lists, [member/2,foldl/3,foldr/3]).
-include("../include/erl_bits.hrl").
-record(expand, {module=[], %Module name
- parameters=undefined, %Module parameters
exports=[], %Exports
imports=[], %Imports
compile=[], %Compile flags
@@ -74,88 +73,20 @@ module(Fs0, Opts0) ->
},
%% Expand the functions.
{Tfs,St1} = forms(Fs, define_functions(Fs, St0)),
- {Efs,St2} = expand_pmod(Tfs, St1),
%% Get the correct list of exported functions.
- Exports = case member(export_all, St2#expand.compile) of
- true -> gb_sets:to_list(St2#expand.defined);
- false -> St2#expand.exports
+ Exports = case member(export_all, St1#expand.compile) of
+ true -> gb_sets:to_list(St1#expand.defined);
+ false -> St1#expand.exports
end,
%% Generate all functions from stored info.
- {Ats,St3} = module_attrs(St2#expand{exports = Exports}),
+ {Ats,St3} = module_attrs(St1#expand{exports = Exports}),
{Mfs,St4} = module_predef_funcs(St3),
- {St4#expand.module, St4#expand.exports, Ats ++ Efs ++ Mfs,
+ {St4#expand.module, St4#expand.exports, Ats ++ Tfs ++ Mfs,
St4#expand.compile}.
compiler_options(Forms) ->
lists:flatten([C || {attribute,_,compile,C} <- Forms]).
-expand_pmod(Fs0, St0) ->
- case St0#expand.parameters of
- undefined ->
- {Fs0,St0};
- Ps0 ->
- Base = get_base(St0#expand.attributes),
- Ps = if is_atom(Base) ->
- ['BASE' | Ps0];
- true ->
- Ps0
- end,
- Def = gb_sets:to_list(St0#expand.defined),
- {Fs1,Xs,Ds} = sys_expand_pmod:forms(Fs0, Ps,
- St0#expand.exports,
- Def),
- St1 = St0#expand{exports=Xs,defined=gb_sets:from_list(Ds)},
- {Fs2,St2} = add_instance(Ps, Fs1, St1),
- {Fs3,St3} = ensure_new(Base, Ps0, Fs2, St2),
- {Fs3,St3#expand{attributes = [{abstract, 0, [true]}
- | St3#expand.attributes]}}
- end.
-
-get_base(As) ->
- case lists:keyfind(extends, 1, As) of
- {extends,_,[Base]} when is_atom(Base) ->
- Base;
- _ ->
- []
- end.
-
-ensure_new(Base, Ps, Fs, St) ->
- case has_new(Fs) of
- true ->
- {Fs, St};
- false ->
- add_new(Base, Ps, Fs, St)
- end.
-
-has_new([{function,_L,new,_A,_Cs} | _Fs]) ->
- true;
-has_new([_ | Fs]) ->
- has_new(Fs);
-has_new([]) ->
- false.
-
-add_new(Base, Ps, Fs, St) ->
- Vs = [{var,0,V} || V <- Ps],
- As = if is_atom(Base) ->
- [{call,0,{remote,0,{atom,0,Base},{atom,0,new}},Vs} | Vs];
- true ->
- Vs
- end,
- Body = [{call,0,{atom,0,instance},As}],
- add_func(new, Vs, Body, Fs, St).
-
-add_instance(Ps, Fs, St) ->
- Vs = [{var,0,V} || V <- Ps],
- AbsMod = [{tuple,0,[{atom,0,St#expand.module}|Vs]}],
- add_func(instance, Vs, AbsMod, Fs, St).
-
-add_func(Name, Args, Body, Fs, St) ->
- A = length(Args),
- F = {function,0,Name,A,[{clause,0,Args,[],Body}]},
- NA = {Name,A},
- {[F|Fs],St#expand{exports=add_element(NA, St#expand.exports),
- defined=gb_sets:add_element(NA, St#expand.defined)}}.
-
%% define_function(Form, State) -> State.
%% Add function to defined if form is a function.
@@ -235,10 +166,6 @@ forms([], St) -> {[],St}.
%% attribute(Attribute, Value, Line, State) -> State'.
%% Process an attribute, this just affects the state.
-attribute(module, {Module, As}, _L, St) ->
- true = is_atom(Module),
- St#expand{module=Module,
- parameters=As};
attribute(module, Module, _L, St) ->
true = is_atom(Module),
St#expand{module=Module};
diff --git a/lib/compiler/test/Makefile b/lib/compiler/test/Makefile
index 3b065ec3b9..b9c5be09ce 100644
--- a/lib/compiler/test/Makefile
+++ b/lib/compiler/test/Makefile
@@ -29,7 +29,6 @@ MODULES= \
match_SUITE \
misc_SUITE \
num_bif_SUITE \
- pmod_SUITE \
receive_SUITE \
record_SUITE \
trycatch_SUITE \
diff --git a/lib/compiler/test/pmod_SUITE.erl b/lib/compiler/test/pmod_SUITE.erl
deleted file mode 100644
index 5dd09a7245..0000000000
--- a/lib/compiler/test/pmod_SUITE.erl
+++ /dev/null
@@ -1,121 +0,0 @@
-%%
-%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 2004-2011. All Rights Reserved.
-%%
-%% The contents of this file are subject to the Erlang Public License,
-%% Version 1.1, (the "License"); you may not use this file except in
-%% compliance with the License. You should have received a copy of the
-%% Erlang Public License along with this software. If not, it can be
-%% retrieved online at http://www.erlang.org/.
-%%
-%% Software distributed under the License is distributed on an "AS IS"
-%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
-%% the License for the specific language governing rights and limitations
-%% under the License.
-%%
-%% %CopyrightEnd%
-%%
--module(pmod_SUITE).
-
--export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
- init_per_group/2,end_per_group/2,
- init_per_testcase/2,end_per_testcase/2,
- basic/1, otp_8447/1]).
-
--include_lib("test_server/include/test_server.hrl").
-
-suite() -> [{ct_hooks,[ts_install_cth]}].
-
-all() ->
- test_lib:recompile(?MODULE),
- [basic, otp_8447].
-
-groups() ->
- [].
-
-init_per_suite(Config) ->
- Config.
-
-end_per_suite(_Config) ->
- ok.
-
-init_per_group(_GroupName, Config) ->
- Config.
-
-end_per_group(_GroupName, Config) ->
- Config.
-
-
-init_per_testcase(Case, Config) when is_atom(Case), is_list(Config) ->
- Dog = test_server:timetrap(?t:minutes(1)),
- [{watchdog,Dog}|Config].
-
-end_per_testcase(Case, Config) when is_atom(Case), is_list(Config) ->
- Dog = ?config(watchdog, Config),
- ?t:timetrap_cancel(Dog),
- ok.
-
-basic(Config) when is_list(Config) ->
- ?line basic_1(Config, []),
- ?line basic_1(Config, [inline]),
- ?line basic_1(Config, [{inline,500},inline]),
- ok.
-
-basic_1(Config, Opts) ->
- io:format("Options: ~p\n", [Opts]),
- ?line ok = compile_load(pmod_basic, Config, Opts),
-
- ?line Prop1 = pmod_basic:new([{a,xb},{b,true},{c,false}]),
- ?line Prop2 = pmod_basic:new([{y,zz}]),
- ?line io:format("Prop1 = ~p\n", [Prop1]),
- ?line io:format("Prop2 = ~p\n", [Prop2]),
-
- ?line {a,xb} = Prop1:lookup(a),
- ?line none = Prop1:lookup(glurf),
- ?line false = Prop1:or_props([]),
- ?line true = Prop1:or_props([b,c]),
- ?line true = Prop1:or_props([b,d]),
- ?line false = Prop1:or_props([d]),
-
- ?line none = Prop2:lookup(kalle),
- ?line {y,zz} = Prop2:lookup(y),
- ?line {a,xb} = Prop1:lookup(a),
-
- ?line Prop3 = Prop1:prepend({blurf,true}),
- ?line io:format("Prop3 = ~p\n", [Prop3]),
- ?line {blurf,true} = Prop3:lookup(blurf),
-
- Prop4 = Prop3:append(42),
- ?line io:format("Prop4 = ~p\n", [Prop4]),
- ?line {42,5} = Prop4:stupid_sum(),
-
- %% Some record guards.
- ?line ok = Prop4:bar({s,0}),
- ?line ok = Prop4:bar_bar({s,blurf}),
- ?line error = Prop4:bar_bar({s,a,b}),
- ?line error = Prop4:bar_bar([]),
-
- %% Call from a fun.
- Fun = fun(Arg) -> Prop4:bar(Arg) end,
- ?line ok = Fun({s,0}),
-
- [{y,[1,2]},{x,[5,19]}] = Prop4:collapse([{y,[2,1]},{x,[19,5]}]),
- ok.
-
-otp_8447(Config) when is_list(Config) ->
- ?line P = pmod_basic:new(foo),
- ?line [0,0,1,1,1,0,0,1] = P:bc1(),
- ?line <<10:4>> = P:bc2(),
- ok.
-
-compile_load(Module, Conf, Opts) ->
- ?line Dir = ?config(data_dir,Conf),
- ?line Src = filename:join(Dir, atom_to_list(Module)),
- ?line Out = ?config(priv_dir,Conf),
- ?line CompRc = compile:file(Src, [report,{outdir,Out}|Opts]),
- ?line {ok,Module} = CompRc,
- ?line code:purge(Module),
- ?line {module,Module} =
- code:load_abs(filename:join(Out, atom_to_list(Module))),
- ok.
diff --git a/lib/compiler/test/pmod_SUITE_data/pmod_basic.erl b/lib/compiler/test/pmod_SUITE_data/pmod_basic.erl
deleted file mode 100644
index 19cce452dc..0000000000
--- a/lib/compiler/test/pmod_SUITE_data/pmod_basic.erl
+++ /dev/null
@@ -1,83 +0,0 @@
-%%
-%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 2004-2011. All Rights Reserved.
-%%
-%% The contents of this file are subject to the Erlang Public License,
-%% Version 1.1, (the "License"); you may not use this file except in
-%% compliance with the License. You should have received a copy of the
-%% Erlang Public License along with this software. If not, it can be
-%% retrieved online at http://www.erlang.org/.
-%%
-%% Software distributed under the License is distributed on an "AS IS"
-%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
-%% the License for the specific language governing rights and limitations
-%% under the License.
-%%
-%% %CopyrightEnd%
-%%
--module(pmod_basic, [Props]).
-
--export([lookup/1,or_props/1,prepend/1,append/1,stupid_sum/0]).
--export([bar/1,bar_bar/1]).
--export([bc1/0, bc2/0]).
--export([collapse/1]).
-
-lookup(Key) ->
- proplists:lookup(Key, Props).
-
-or_props(Keys) ->
- Res = or_props_1(Keys, false),
- true = is_bool(Res), %is_bool/1 does not use Props.
- Res.
-
-prepend(Term) ->
- new([Term|Props]).
-
-append(Term) ->
- pmod_basic:new(Props++[Term]).
-
-or_props_1([K|Ks], Acc) ->
- or_props_1(Ks, proplists:get_bool(K, Props) or Acc);
-or_props_1([], Acc) -> Acc.
-
-is_bool(true) -> true;
-is_bool(false) -> true;
-is_bool(_) -> false.
-
-stupid_sum() ->
- put(counter, 0),
- Res = stupid_sum_1(Props, 0),
- {Res,get(counter)}.
-
-stupid_sum_1([H|T], Sum0) ->
- try add(Sum0, H) of
- Sum -> stupid_sum_1(T, Sum)
- catch
- error:_ -> stupid_sum_1(T, Sum0)
- after
- bump()
- end;
-stupid_sum_1([], Sum) -> Sum.
-
-bump() ->
- put(counter, get(counter)+1).
-
-add(A, B) ->
- A+B.
-
--record(s, {a}).
-
-bar(S) when S#s.a == 0 -> ok.
-
-bar_bar(S) when is_record(S, s) -> ok;
-bar_bar(_) -> error.
-
-bc1() ->
- [A || <<A:1>> <= <<"9">> ].
-
-bc2() ->
- << <<A:1>> || A <- [1,0,1,0] >>.
-
-collapse(L) ->
- lists:keymap(fun lists:sort/1, 2, L).
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index d24e2fff44..9a01e85006 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -94,7 +94,6 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) ->
%% the other function collections contain {Function, Arity}.
-record(lint, {state=start :: 'start' | 'attribute' | 'function',
module=[], %Module
- extends=[], %Extends
behaviour=[], %Behaviour
exports=gb_sets:empty() :: gb_set(), %Exports
imports=[], %Imports
@@ -112,7 +111,6 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) ->
enabled_warnings=[], %All enabled warnings (ordset).
errors=[], %Current errors
warnings=[], %Current warnings
- global_vt=[], %The global VarTable
file = "" :: string(), %From last file attribute
recdef_top=false :: boolean(), %true in record initialisation
%outside any fun or lc
@@ -142,10 +140,8 @@ format_error({bad_module_name, M}) ->
io_lib:format("bad module name '~s'", [M]);
format_error(redefine_module) ->
"redefining module";
-format_error(redefine_extends) ->
- "redefining extends attribute";
-format_error(extends_self) ->
- "cannot extend from self";
+format_error(pmod_unsupported) ->
+ "parameterized modules are no longer supported";
%% format_error({redefine_mod_import, M, P}) ->
%% io_lib:format("module '~s' already imported from package '~s'", [M, P]);
@@ -166,10 +162,6 @@ format_error({bad_inline,{F,A}}) ->
io_lib:format("inlined function ~w/~w undefined", [F,A]);
format_error({invalid_deprecated,D}) ->
io_lib:format("badly formed deprecated attribute ~w", [D]);
-format_error(invalid_extends) ->
- "badly formed extends attribute";
-format_error(define_instance) ->
- "defining instance function not allowed in abstract module";
format_error({bad_deprecated,{F,A}}) ->
io_lib:format("deprecated function ~w/~w undefined or not exported", [F,A]);
format_error({bad_nowarn_unused_function,{F,A}}) ->
@@ -622,8 +614,6 @@ forms(Forms0, St0) ->
pre_scan([{function,_L,new,_A,_Cs} | Fs], St) ->
pre_scan(Fs, St#lint{new=true});
-pre_scan([{attribute,_L,extends,M} | Fs], St) when is_atom(M) ->
- pre_scan(Fs, St#lint{extends=true});
pre_scan([{attribute,L,compile,C} | Fs], St) ->
case is_warn_enabled(export_all, St) andalso
member(export_all, lists:flatten([C])) of
@@ -678,41 +668,15 @@ form(Form, #lint{state=State}=St) ->
%% start_state(Form, State) -> State'
-start_state({attribute,_,module,{M,Ps}}, St0) ->
- St1 = St0#lint{module=M},
- Arity = length(Ps),
- Ps1 = if is_atom(St1#lint.extends) ->
- ['BASE', 'THIS' | Ps];
- true ->
- ['THIS' | Ps]
- end,
- Vt = orddict:from_list([{V, {bound, used, []}} || V <- Ps1]),
- St2 = add_instance(Arity, St1),
- St3 = ensure_new(Arity, St2),
- St3#lint{state=attribute, extends=[], global_vt=Vt};
+start_state({attribute,Line,module,{_,_}}=Form, St0) ->
+ St1 = add_error(Line, pmod_unsupported, St0),
+ attribute_state(Form, St1#lint{state=attribute});
start_state({attribute,_,module,M}, St0) ->
St1 = St0#lint{module=M},
- St1#lint{state=attribute, extends=[]};
+ St1#lint{state=attribute};
start_state(Form, St) ->
St1 = add_error(element(2, Form), undefined_module, St),
- attribute_state(Form, St1#lint{state=attribute, extends=[]}).
-
-ensure_new(Arity, St) ->
- case St#lint.new of
- true ->
- St;
- false ->
- add_func(new, Arity, St)
- end.
-
-add_instance(Arity, St) ->
- A = Arity + (if is_atom(St#lint.extends) -> 1; true -> 0 end),
- add_func(instance, A, St).
-
-add_func(Name, Arity, St) ->
- F = {Name, Arity},
- St#lint{exports = gb_sets:add_element(F, St#lint.exports),
- defined = gb_sets:add_element(F, St#lint.defined)}.
+ attribute_state(Form, St1#lint{state=attribute}).
%% attribute_state(Form, State) ->
%% State'
@@ -721,15 +685,6 @@ attribute_state({attribute,_L,module,_M}, #lint{module=[]}=St) ->
St;
attribute_state({attribute,L,module,_M}, St) ->
add_error(L, redefine_module, St);
-attribute_state({attribute,L,extends,M}, #lint{module=M}=St) when is_atom(M) ->
- add_error(L, extends_self, St);
-attribute_state({attribute,_L,extends,M}, #lint{extends=[]}=St)
- when is_atom(M) ->
- St#lint{extends=M};
-attribute_state({attribute,L,extends,M}, St) when is_atom(M) ->
- add_error(L, redefine_extends, St);
-attribute_state({attribute,L,extends,_M}, St) ->
- add_error(L, invalid_extends, St);
attribute_state({attribute,L,export,Es}, St) ->
export(L, Es, St);
attribute_state({attribute,L,export_type,Es}, St) ->
@@ -1322,11 +1277,9 @@ call_function(Line, F, A, #lint{usage=Usage0,called=Cd,func=Func}=St) ->
%% function(Line, Name, Arity, Clauses, State) -> State.
-function(Line, instance, _Arity, _Cs, St) when St#lint.global_vt =/= [] ->
- add_error(Line, define_instance, St);
function(Line, Name, Arity, Cs, St0) ->
St1 = define_function(Line, Name, Arity, St0#lint{func={Name,Arity}}),
- clauses(Cs, St1#lint.global_vt, St1).
+ clauses(Cs, St1).
-spec define_function(line(), atom(), arity(), lint_state()) -> lint_state().
@@ -1349,15 +1302,16 @@ function_check_max_args(Line, Arity, St) when Arity > ?MAX_ARGUMENTS ->
add_error(Line, {too_many_arguments,Arity}, St);
function_check_max_args(_, _, St) -> St.
-%% clauses([Clause], VarTable, State) -> {VarTable, State}.
+%% clauses([Clause], State) -> {VarTable, State}.
-clauses(Cs, Vt, St) ->
+clauses(Cs, St) ->
foldl(fun (C, St0) ->
- {_,St1} = clause(C, Vt, St0),
+ {_,St1} = clause(C, St0),
St1
end, St, Cs).
-clause({clause,_Line,H,G,B}, Vt0, St0) ->
+clause({clause,_Line,H,G,B}, St0) ->
+ Vt0 = [],
{Hvt,Binvt,St1} = head(H, Vt0, St0),
%% Cannot ignore BinVt since "binsize variables" may have been used.
Vt1 = vtupdate(Hvt, vtupdate(Binvt, Vt0)),
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index 774229fca9..564f27a512 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -2187,27 +2187,9 @@ otp_5878(Config) when is_list(Config) ->
?line [] = run(Config, Ts),
Abstr = <<"-module(lint_test, [A, B]).
-
- -export([args/1]).
-
- -record(r, {a = A, b = THIS}). % A and THIS are unbound
-
- %% param:args(compile,param:new(1,2)).
-
- args(C) ->
- X = local(C),
- Z = new(A, B),
- F = fun(THIS) -> {x, A} end, % THIS unused and shadowed
- {X, Z, THIS, F, #r{}}.
-
- local(C) ->
- module_info(C).
">>,
- ?line {error,[{5,erl_lint,{unbound_var,'A'}},
- {5,erl_lint,{unbound_var,'THIS'}}],
- [{12,erl_lint,{unused_var,'THIS'}},
- {12,erl_lint,{shadowed_var,'THIS','fun'}}]}
- = run_test2(Config, Abstr, [warn_unused_record]),
+ {errors,[{1,erl_lint,pmod_unsupported}],[]} =
+ run_test2(Config, Abstr, [warn_unused_record]),
QLC1 = <<"-module(lint_test).
-include_lib(\"stdlib/include/qlc.hrl\").