From f143990aea3ed5dd62952c1ed3d0a052f011626f Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= Date: Mon, 3 Dec 2012 11:46:04 +0100 Subject: [PATCH] compiler: Remove support for packages --- lib/compiler/src/compile.erl | 6 +- lib/compiler/src/sys_pre_expand.erl | 66 +++---------------- lib/compiler/test/compilation_SUITE.erl | 3 +- .../bad_functional_value.erl | 28 -------- lib/compiler/test/compile_SUITE.erl | 30 +-------- 5 files changed, 14 insertions(+), 119 deletions(-) delete mode 100644 lib/compiler/test/compilation_SUITE_data/bad_functional_value.erl diff --git a/lib/compiler/src/compile.erl b/lib/compiler/src/compile.erl index a3120eb917da..10e7f5e9ce94 100644 --- a/lib/compiler/src/compile.erl +++ b/lib/compiler/src/compile.erl @@ -1342,16 +1342,12 @@ save_binary(#compile{code=none}=St) -> {ok,St}; save_binary(#compile{module=Mod,ofile=Outfile, options=Opts}=St) -> %% Test that the module name and output file name match. - %% We must take care to not completely break a packaged module - %% (even though packages still is as an experimental, unsupported - %% feature) - so we will extract the last part of a packaged - %% module name and compare only that. case member(no_error_module_mismatch, Opts) of true -> save_binary_1(St); false -> Base = filename:rootname(filename:basename(Outfile)), - case lists:last(packages:split(Mod)) of + case atom_to_list(Mod) of Base -> save_binary_1(St); _ -> diff --git a/lib/compiler/src/sys_pre_expand.erl b/lib/compiler/src/sys_pre_expand.erl index e55fb2a03732..a8c69c3cb166 100644 --- a/lib/compiler/src/sys_pre_expand.erl +++ b/lib/compiler/src/sys_pre_expand.erl @@ -35,10 +35,8 @@ -record(expand, {module=[], %Module name parameters=undefined, %Module parameters - package="", %Module package exports=[], %Exports imports=[], %Imports - mod_imports, %Module Imports compile=[], %Compile flags attributes=[], %Attributes callbacks=[], %Callbacks @@ -67,12 +65,8 @@ module(Fs0, Opts0) -> %% Set pre-defined exported functions. PreExp = [{module_info,0},{module_info,1}], - %% Set pre-defined module imports. - PreModImp = [{erlang,erlang},{packages,packages}], - %% Build initial expand record. St0 = #expand{exports=PreExp, - mod_imports=dict:from_list(PreModImp), compile=Opts, defined=PreExp, bitdefault = erl_bits:system_bitdefault(), @@ -242,14 +236,12 @@ forms([], St) -> {[],St}. %% Process an attribute, this just affects the state. attribute(module, {Module, As}, _L, St) -> - M = package_to_string(Module), - St#expand{module=list_to_atom(M), - package=packages:strip_last(M), + true = is_atom(Module), + St#expand{module=Module, parameters=As}; attribute(module, Module, _L, St) -> - M = package_to_string(Module), - St#expand{module=list_to_atom(M), - package=packages:strip_last(M)}; + true = is_atom(Module), + St#expand{module=Module}; attribute(export, Es, _L, St) -> St#expand{exports=union(from_list(Es), St#expand.exports)}; attribute(import, Is, _L, St) -> @@ -312,8 +304,6 @@ pattern({tuple,Line,Ps}, St0) -> %%pattern({struct,Line,Tag,Ps}, St0) -> %% {TPs,TPsvs,St1} = pattern_list(Ps, St0), %% {{tuple,Line,[{atom,Line,Tag}|TPs]},TPsvs,St1}; -pattern({record_field,_,_,_}=M, St) -> - {expand_package(M, St),St}; % must be a package name pattern({bin,Line,Es0}, St0) -> {Es1,St1} = pattern_bin(Es0, St0), {{bin,Line,Es1},St1}; @@ -404,8 +394,6 @@ expr({tuple,Line,Es0}, St0) -> %%expr({struct,Line,Tag,Es0}, Vs, St0) -> %% {Es1,Esvs,Esus,St1} = expr_list(Es0, Vs, St0), %% {{tuple,Line,[{atom,Line,Tag}|Es1]},Esvs,Esus,St1}; -expr({record_field,_,_,_}=M, St) -> - {expand_package(M, St),St}; % must be a package name expr({bin,Line,Es0}, St0) -> {Es1,St1} = expr_bin(Es0, St0), {{bin,Line,Es1},St1}; @@ -448,12 +436,9 @@ expr({call,Line,{atom,La,N}=Atom,As0}, St0) -> end end end; -expr({call,Line,{record_field,_,_,_}=M,As0}, St0) -> - expr({call,Line,expand_package(M, St0),As0}, St0); -expr({call,Line,{remote,Lr,M,F},As0}, St0) -> - M1 = expand_package(M, St0), - {[M2,F1|As1],St1} = expr_list([M1,F|As0], St0), - {{call,Line,{remote,Lr,M2,F1},As1},St1}; +expr({call,Line,{remote,Lr,M0,F},As0}, St0) -> + {[M1,F1|As1],St1} = expr_list([M0,F|As0], St0), + {{call,Line,{remote,Lr,M1,F1},As1},St1}; expr({call,Line,F,As0}, St0) -> {[Fun1|As1],St1} = expr_list([F|As0], St0), {{call,Line,Fun1,As1},St1}; @@ -666,32 +651,6 @@ string_to_conses(Line, Cs, Tail) -> foldr(fun (C, T) -> {cons,Line,{char,Line,C},T} end, Tail, Cs). -%% In syntax trees, module/package names are atoms or lists of atoms. - -package_to_string(A) when is_atom(A) -> atom_to_list(A); -package_to_string(L) when is_list(L) -> packages:concat(L). - -expand_package({atom,L,A} = M, St) -> - case dict:find(A, St#expand.mod_imports) of - {ok, A1} -> - {atom,L,A1}; - error -> - case packages:is_segmented(A) of - true -> - M; - false -> - M1 = packages:concat(St#expand.package, A), - {atom,L,list_to_atom(M1)} - end - end; -expand_package(M, _St) -> - case erl_parse:package_segments(M) of - error -> - M; - M1 -> - {atom,element(2,M),list_to_atom(package_to_string(M1))} - end. - %% import(Line, Imports, State) -> %% State' %% imported(Name, Arity, State) -> @@ -699,15 +658,10 @@ expand_package(M, _St) -> %% Handle import declarations and test for imported functions. No need to %% check when building imports as code is correct. -import({Mod0,Fs}, St) -> - Mod = list_to_atom(package_to_string(Mod0)), +import({Mod,Fs}, St) -> + true = is_atom(Mod), Mfs = from_list(Fs), - St#expand{imports=add_imports(Mod, Mfs, St#expand.imports)}; -import(Mod0, St) -> - Mod = package_to_string(Mod0), - Key = list_to_atom(packages:last(Mod)), - St#expand{mod_imports=dict:store(Key, list_to_atom(Mod), - St#expand.mod_imports)}. + St#expand{imports=add_imports(Mod, Mfs, St#expand.imports)}. add_imports(Mod, [F|Fs], Is) -> add_imports(Mod, Fs, orddict:store(F, Mod, Is)); diff --git a/lib/compiler/test/compilation_SUITE.erl b/lib/compiler/test/compilation_SUITE.erl index bec97b01995f..f8f74e6f7aad 100644 --- a/lib/compiler/test/compilation_SUITE.erl +++ b/lib/compiler/test/compilation_SUITE.erl @@ -44,7 +44,7 @@ groups() -> {group,vsn},otp_2380,otp_2141,otp_2173,otp_4790, const_list_256,bin_syntax_1,bin_syntax_2, bin_syntax_3,bin_syntax_4,bin_syntax_5,bin_syntax_6, - live_var,convopts,bad_functional_value, + live_var,convopts, catch_in_catch,redundant_case,long_string,otp_5076, complex_guard,otp_5092,otp_5151,otp_5235,otp_5244, trycatch_4,opt_crash,otp_5404,otp_5436,otp_5481, @@ -143,7 +143,6 @@ split({int, N}, <>) -> ?comp(live_var). ?comp(trycatch_4). -?comp(bad_functional_value). ?comp(catch_in_catch). diff --git a/lib/compiler/test/compilation_SUITE_data/bad_functional_value.erl b/lib/compiler/test/compilation_SUITE_data/bad_functional_value.erl deleted file mode 100644 index 126a573e83b0..000000000000 --- a/lib/compiler/test/compilation_SUITE_data/bad_functional_value.erl +++ /dev/null @@ -1,28 +0,0 @@ -%% -%% %CopyrightBegin% -%% -%% Copyright Ericsson AB 2003-2009. 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(bad_functional_value). - --export([?MODULE/0,a/0]). - -?MODULE() -> - ok. - -a() -> - .list_to_atom("ok"). - diff --git a/lib/compiler/test/compile_SUITE.erl b/lib/compiler/test/compile_SUITE.erl index 2cd75944f48f..229e5a98a1c8 100644 --- a/lib/compiler/test/compile_SUITE.erl +++ b/lib/compiler/test/compile_SUITE.erl @@ -27,7 +27,7 @@ app_test/1, file_1/1, forms_2/1, module_mismatch/1, big_file/1, outdir/1, binary/1, makedep/1, cond_and_ifdef/1, listings/1, listings_big/1, - other_output/1, package_forms/1, encrypted_abstr/1, + other_output/1, encrypted_abstr/1, bad_record_use1/1, bad_record_use2/1, strict_record/1, missing_testheap/1, cover/1, env/1, core/1, asm/1, sys_pre_attributes/1]). @@ -44,7 +44,7 @@ all() -> test_lib:recompile(?MODULE), [app_test, file_1, forms_2, module_mismatch, big_file, outdir, binary, makedep, cond_and_ifdef, listings, listings_big, - other_output, package_forms, encrypted_abstr, + other_output, encrypted_abstr, {group, bad_record_use}, strict_record, missing_testheap, cover, env, core, asm, sys_pre_attributes]. @@ -410,32 +410,6 @@ other_output(Config) when is_list(Config) -> ?line test_server:timetrap_cancel(Dog), ok. -package_forms(Config) when is_list(Config) -> - Fs = [{attribute,1,file,{"./p.erl",1}}, - {attribute,1,module,[p,p]}, - {attribute,3,compile,export_all}, - {attribute,1,file, - {"/clearcase/otp/erts/lib/stdlib/include/qlc.hrl",1}}, - {attribute,6,file,{"./p.erl",6}}, - {function,7,q,0, - [{clause,7,[],[], - [{call,8, - {remote,8,{atom,8,qlc},{atom,8,q}}, - [{tuple,-8, - [{atom,-8,qlc_lc}, - {'fun',-8, - {clauses, - [{clause,-8,[],[], - [{tuple,-8, - [{atom,-8,simple_v1}, - {atom,-8,'X'}, - {'fun',-8,{clauses,[{clause,-8,[],[],[{nil,8}]}]}}, - {integer,-8,8}]}]}]}}, - {atom,-8,undefined}]}]}]}]}, - {eof,9}], - {ok,'p.p',_} = compile:forms(Fs, ['S',report]), - ok. - encrypted_abstr(Config) when is_list(Config) -> ?line Dog = test_server:timetrap(test_server:minutes(10)), ?line {Simple,Target} = files(Config, "encrypted_abstr"),