diff options
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r-- | lib/stdlib/src/c.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/src/dict.erl | 5 | ||||
-rw-r--r-- | lib/stdlib/src/edlin.erl | 7 | ||||
-rw-r--r-- | lib/stdlib/src/erl_eval.erl | 45 | ||||
-rw-r--r-- | lib/stdlib/src/erl_expand_records.erl | 7 | ||||
-rw-r--r-- | lib/stdlib/src/erl_lint.erl | 293 | ||||
-rw-r--r-- | lib/stdlib/src/erl_parse.yrl | 64 | ||||
-rw-r--r-- | lib/stdlib/src/erl_scan.erl | 25 | ||||
-rw-r--r-- | lib/stdlib/src/filename.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/src/gb_sets.erl | 3 | ||||
-rw-r--r-- | lib/stdlib/src/gb_trees.erl | 3 | ||||
-rw-r--r-- | lib/stdlib/src/io_lib.erl | 23 | ||||
-rw-r--r-- | lib/stdlib/src/otp_internal.erl | 43 | ||||
-rw-r--r-- | lib/stdlib/src/qlc_pt.erl | 10 | ||||
-rw-r--r-- | lib/stdlib/src/sets.erl | 5 | ||||
-rw-r--r-- | lib/stdlib/src/shell.erl | 61 | ||||
-rw-r--r-- | lib/stdlib/src/string.erl | 3 |
17 files changed, 156 insertions, 445 deletions
diff --git a/lib/stdlib/src/c.erl b/lib/stdlib/src/c.erl index a920921a5e..4c1c0f904b 100644 --- a/lib/stdlib/src/c.erl +++ b/lib/stdlib/src/c.erl @@ -116,7 +116,7 @@ machine_load(Mod, File, Opts) -> File2 = filename:join(Dir, filename:basename(File, ".erl")), case compile:output_generated(Opts) of true -> - Base = packages:last(Mod), + Base = atom_to_list(Mod), case filename:basename(File, ".erl") of Base -> code:purge(Mod), diff --git a/lib/stdlib/src/dict.erl b/lib/stdlib/src/dict.erl index 2e9eba4bfa..4f8d45dc8d 100644 --- a/lib/stdlib/src/dict.erl +++ b/lib/stdlib/src/dict.erl @@ -1,7 +1,8 @@ +%% -*- coding: utf-8 -*- %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2000-2011. All Rights Reserved. +%% Copyright Ericsson AB 2000-2012. 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 @@ -17,7 +18,7 @@ %% %CopyrightEnd% %% -%% We use the dynamic hashing techniques by Per-�ke Larsson as +%% We use the dynamic hashing techniques by Per-Åke Larsson as %% described in "The Design and Implementation of Dynamic Hashing for %% Sets and Tables in Icon" by Griswold and Townsend. Much of the %% terminology comes from that paper as well. diff --git a/lib/stdlib/src/edlin.erl b/lib/stdlib/src/edlin.erl index 026bd9038f..1164ee49eb 100644 --- a/lib/stdlib/src/edlin.erl +++ b/lib/stdlib/src/edlin.erl @@ -1,7 +1,8 @@ +%% -*- coding: utf-8 -*- %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2010. All Rights Reserved. +%% Copyright Ericsson AB 1996-2012. 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 @@ -317,9 +318,9 @@ over_non_word([], Stack, N) -> {[],Stack,N}. word_char(C) when C >= $A, C =< $Z -> true; -word_char(C) when C >= $�, C =< $�, C =/= $� -> true; +word_char(C) when C >= $À, C =< $Þ, C =/= $× -> true; word_char(C) when C >= $a, C =< $z -> true; -word_char(C) when C >= $�, C =< $�, C =/= $� -> true; +word_char(C) when C >= $ß, C =< $ÿ, C =/= $÷ -> true; word_char(C) when C >= $0, C =< $9 -> true; word_char(C) when C =:= $_ -> true; word_char(C) when C =:= $. -> true; % accept dot-separated names diff --git a/lib/stdlib/src/erl_eval.erl b/lib/stdlib/src/erl_eval.erl index 95ba6b1096..8471ae6b64 100644 --- a/lib/stdlib/src/erl_eval.erl +++ b/lib/stdlib/src/erl_eval.erl @@ -227,13 +227,6 @@ expr({bc,_,E,Qs}, Bs, Lf, Ef, RBs) -> expr({tuple,_,Es}, Bs0, Lf, Ef, RBs) -> {Vs,Bs} = expr_list(Es, Bs0, Lf, Ef), ret_expr(list_to_tuple(Vs), Bs, RBs); -expr({record_field,_,_,_}=Mod, Bs, _Lf, _Ef, RBs) -> - case expand_module_name(Mod, Bs) of - {atom,_,A} -> - ret_expr(A, Bs, RBs); %% This is the "x.y" syntax - _ -> - erlang:raise(error, {badexpr, '.'}, stacktrace()) - end; expr({record_field,_,_,Name,_}, _Bs, _Lf, _Ef, _RBs) -> erlang:raise(error, {undef_record,Name}, stacktrace()); expr({record_index,_,Name,_}, _Bs, _Lf, _Ef, _RBs) -> @@ -332,8 +325,7 @@ expr({call,L1,{remote,L2,{record_field,_,{atom,_,''},{atom,_,qlc}=Mod}, Bs, Lf, Ef, RBs) when length(As0) =< 1 -> expr({call,L1,{remote,L2,Mod,Func},As}, Bs, Lf, Ef, RBs); expr({call,_,{remote,_,Mod,Func},As0}, Bs0, Lf, Ef, RBs) -> - Mod1 = expand_module_name(Mod, Bs0), - {value,M,Bs1} = expr(Mod1, Bs0, Lf, Ef, none), + {value,M,Bs1} = expr(Mod, Bs0, Lf, Ef, none), {value,F,Bs2} = expr(Func, Bs0, Lf, Ef, none), {As,Bs3} = expr_list(As0, merge_bindings(Bs1, Bs2), Lf, Ef), %% M could be a parameterized module (not an atom). @@ -1210,41 +1202,6 @@ ret_expr(_Old, New) -> line(Expr) -> element(2, Expr). -%% In syntax trees, module/package names are atoms or lists of atoms. - -expand_module_name({atom,L,A} = M, Bs) -> - case binding({module,A}, Bs) of - {value, A1} -> - {atom,L,A1}; - unbound -> - case packages:is_segmented(A) of - true -> - M; - false -> -%%% P = case binding({module,'$package'}, Bs) of -%%% {value, P1} -> P1; -%%% unbound -> "" -%%% end, -%%% A1 = list_to_atom(packages:concat(P, A)), -%%% {atom,L,list_to_atom(A1)} - {atom,L,A} - end - end; -expand_module_name(M, _) -> - case erl_parse:package_segments(M) of - error -> - M; - M1 -> - L = element(2,M), - Mod = packages:concat(M1), - case packages:is_valid(Mod) of - true -> - {atom,L,list_to_atom(Mod)}; - false -> - erlang:raise(error, {bad_module_name, Mod}, stacktrace()) - end - end. - %% {?MODULE,expr,3} is still the stacktrace, despite the %% fact that expr() now takes two, three or four arguments... stacktrace() -> [{?MODULE,expr,3}]. diff --git a/lib/stdlib/src/erl_expand_records.erl b/lib/stdlib/src/erl_expand_records.erl index 85defacc43..d05f630d8e 100644 --- a/lib/stdlib/src/erl_expand_records.erl +++ b/lib/stdlib/src/erl_expand_records.erl @@ -135,8 +135,6 @@ pattern({tuple,Line,Ps}, St0) -> %%pattern({struct,Line,Tag,Ps}, St0) -> %% {TPs,TPsvs,St1} = pattern_list(Ps, St0), %% {{struct,Line,Tag,TPs},TPsvs,St1}; -pattern({record_field,_,_,_}=M, St) -> - {M,St}; % must be a package name pattern({record_index,Line,Name,Field}, St) -> {index_expr(Line, Field, Name, record_fields(Name, St)),St}; pattern({record,Line,Name,Pfs}, St0) -> @@ -306,8 +304,6 @@ expr({tuple,Line,Es0}, St0) -> %%expr({struct,Line,Tag,Es0}, Vs, St0) -> %% {Es1,Esvs,Esus,St1} = expr_list(Es0, Vs, St0), %% {{struct,Line,Tag,Es1},Esvs,Esus,St1}; -expr({record_field,_,_,_}=M, St) -> - {M,St}; % must be a package name expr({record_index,Line,Name,F}, St) -> I = index_expr(Line, F, Name, record_fields(Name, St)), expr(I, St); @@ -375,9 +371,6 @@ expr({call,Line,{atom,_La,N}=Atom,As0}, St0) -> end end end; -expr({call,Line,{record_field,_,_,_}=M,As0}, St0) -> - {As,St1} = expr_list(As0, St0), - {{call,Line,M,As},St1}; expr({call,Line,{remote,Lr,M,F},As0}, St0) -> {[M1,F1 | As1],St1} = expr_list([M,F | As0], St0), {{call,Line,{remote,Lr,M1,F1},As1},St1}; diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index 0a442d950f..9a01e85006 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -94,12 +94,9 @@ 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 - package="", %Module package - extends=[], %Extends behaviour=[], %Behaviour exports=gb_sets:empty() :: gb_set(), %Exports imports=[], %Imports - mod_imports=dict:new() :: dict(), %Module Imports compile=[], %Compile flags records=dict:new() :: dict(), %Record definitions locals=gb_sets:empty() :: gb_set(), %All defined functions (prescanned) @@ -114,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 @@ -144,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]); @@ -168,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}}) -> @@ -539,7 +529,6 @@ start(File, Opts) -> end, #lint{state = start, exports = gb_sets:from_list([{module_info,0},{module_info,1}]), - mod_imports = dict:from_list([{erlang,erlang}]), compile = Opts, %% Internal pseudo-functions must appear as defined/reached. defined = gb_sets:from_list(pseudolocals()), @@ -625,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 @@ -681,51 +668,15 @@ form(Form, #lint{state=State}=St) -> %% start_state(Form, State) -> State' -start_state({attribute,L,module,{M,Ps}}, St) -> - St1 = set_module(M, L, St), - 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,L,module,M}, St) -> - St1 = set_module(M, L, St), - St1#lint{state=attribute, extends=[]}; +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}; start_state(Form, St) -> St1 = add_error(element(2, Form), undefined_module, St), - attribute_state(Form, St1#lint{state=attribute, extends=[]}). - -set_module(M, L, St) -> - M1 = package_to_string(M), - case packages:is_valid(M1) of - true -> - St#lint{module=list_to_atom(M1), - package=packages:strip_last(M1)}; - false -> - add_error(L, {bad_module_name, M1}, St) - end. - -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' @@ -734,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) -> @@ -1007,9 +949,9 @@ check_imports(Forms, St0) -> true -> Usage = St0#lint.usage, Unused = ordsets:subtract(St0#lint.imports, Usage#usage.imported), - Imports = [{{FA,list_to_atom(package_to_string(Mod))},L} - || {attribute,L,import,{Mod,Fs}} <- Forms, - FA <- lists:usort(Fs)], + Imports = [{{FA,Mod},L} || + {attribute,L,import,{Mod,Fs}} <- Forms, + FA <- lists:usort(Fs)], Bad = [{FM,L} || FM <- Unused, {FM2,L} <- Imports, FM =:= FM2], func_line_warning(unused_import, Bad, St0) end. @@ -1222,73 +1164,46 @@ export_type(Line, ETs, #lint{usage = Usage, exp_types = ETs0} = St0) -> -spec import(line(), import(), lint_state()) -> lint_state(). import(Line, {Mod,Fs}, St) -> - Mod1 = package_to_string(Mod), - case packages:is_valid(Mod1) of - true -> - Mfs = ordsets:from_list(Fs), - case check_imports(Line, Mfs, St#lint.imports) of - [] -> - St#lint{imports=add_imports(list_to_atom(Mod1), Mfs, - St#lint.imports)}; - Efs -> - {Err, St1} = - foldl(fun ({bif,{F,A},_}, {Err,St0}) -> - %% BifClash - import directive - Warn = is_warn_enabled(bif_clash, St0) - and (not bif_clash_specifically_disabled(St0,{F,A})), - AutoImpSup = is_autoimport_suppressed(St0#lint.no_auto,{F,A}), - OldBif = erl_internal:old_bif(F,A), - {Err,if - Warn and (not AutoImpSup) and OldBif -> - add_error - (Line, - {redefine_old_bif_import, {F,A}}, - St0); - Warn and (not AutoImpSup) -> - add_warning - (Line, - {redefine_bif_import, {F,A}}, - St0); - true -> - St0 - end}; - (Ef, {_Err,St0}) -> - {true,add_error(Line, - {redefine_import,Ef}, - St0)} - end, - {false,St}, Efs), - if - not Err -> - St1#lint{imports= - add_imports(list_to_atom(Mod1), Mfs, + Mfs = ordsets:from_list(Fs), + case check_imports(Line, Mfs, St#lint.imports) of + [] -> + St#lint{imports=add_imports(Mod, Mfs, + St#lint.imports)}; + Efs -> + {Err, St1} = + foldl(fun ({bif,{F,A},_}, {Err,St0}) -> + %% BifClash - import directive + Warn = is_warn_enabled(bif_clash, St0) andalso + (not bif_clash_specifically_disabled(St0,{F,A})), + AutoImpSup = is_autoimport_suppressed(St0#lint.no_auto,{F,A}), + OldBif = erl_internal:old_bif(F,A), + {Err,if + Warn and (not AutoImpSup) and OldBif -> + add_error + (Line, + {redefine_old_bif_import, {F,A}}, + St0); + Warn and (not AutoImpSup) -> + add_warning + (Line, + {redefine_bif_import, {F,A}}, + St0); + true -> + St0 + end}; + (Ef, {_Err,St0}) -> + {true,add_error(Line, + {redefine_import,Ef}, + St0)} + end, + {false,St}, Efs), + if + not Err -> + St1#lint{imports=add_imports(Mod, Mfs, St#lint.imports)}; - true -> - St1 - end - end; - false -> - add_error(Line, {bad_module_name, Mod1}, St) - end; -import(Line, Mod, St) -> - Mod1 = package_to_string(Mod), - case packages:is_valid(Mod1) of - true -> - Key = list_to_atom(packages:last(Mod1)), - Imps = St#lint.mod_imports, -%%% case dict:is_key(Key, Imps) of -%%% true -> -%%% M = packages:last(Mod1), -%%% P = packages:strip_last(Mod1), -%%% add_error(Line, {redefine_mod_import, M, P}, St); -%%% false -> -%%% St#lint{mod_imports = -%%% dict:store(Key, list_to_atom(Mod1), Imps)} -%%% end; - St#lint{mod_imports = dict:store(Key, list_to_atom(Mod1), - Imps)}; - false -> - add_error(Line, {bad_module_name, Mod1}, St) + true -> + St1 + end end. check_imports(_Line, Fs, Is) -> @@ -1362,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(). @@ -1389,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)), @@ -1463,13 +1377,6 @@ pattern({record_index,Line,Name,Field}, _Vt, _Old, _Bvt, St) -> pattern_field(Field, Name, Dfs, St1) end), {Vt1,[],St1}; -pattern({record_field,Line,_,_}=M, _Vt, _Old, _Bvt, St0) -> - case expand_package(M, St0) of - {error, St1} -> - {[],[],add_error(Line, illegal_expr, St1)}; - {_, St1} -> - {[],[],St1} - end; pattern({record,Line,Name,Pfs}, Vt, Old, Bvt, St) -> case dict:find(Name, St#lint.records) of {ok,{_Line,Fields}} -> @@ -1851,13 +1758,6 @@ gexpr({tuple,_Line,Es}, Vt, St) -> gexpr({record_index,Line,Name,Field}, _Vt, St) -> check_record(Line, Name, St, fun (Dfs, St1) -> record_field(Field, Name, Dfs, St1) end ); -gexpr({record_field,Line,_,_}=M, _Vt, St0) -> - case expand_package(M, St0) of - {error, St1} -> - {[],add_error(Line, illegal_expr, St1)}; - {_, St1} -> - {[], St1} - end; gexpr({record_field,Line,Rec,Name,Field}, Vt, St0) -> {Rvt,St1} = gexpr(Rec, Vt, St0), {Fvt,St2} = check_record(Line, Name, St1, @@ -1996,8 +1896,6 @@ is_gexpr({tuple,_L,Es}, RDs) -> is_gexpr_list(Es, RDs); %% is_gexpr_list(Es, RDs); is_gexpr({record_index,_L,_Name,Field}, RDs) -> is_gexpr(Field, RDs); -is_gexpr({record_field,_L,_,_}=M, _RDs) -> - erl_parse:package_segments(M) =/= error; is_gexpr({record_field,_L,Rec,_Name,Field}, RDs) -> is_gexpr_list([Rec,Field], RDs); is_gexpr({record,L,Name,Inits}, RDs) -> @@ -2086,13 +1984,6 @@ expr({record,Line,Name,Inits}, Vt, St) -> fun (Dfs, St1) -> init_fields(Inits, Line, Name, Dfs, Vt, St1) end); -expr({record_field,Line,_,_}=M, _Vt, St0) -> - case expand_package(M, St0) of - {error, St1} -> - {[],add_error(Line, illegal_expr, St1)}; - {_, St1} -> - {[], St1} - end; expr({record_field,Line,Rec,Name,Field}, Vt, St0) -> {Rvt,St1} = record_expr(Line, Rec, Vt, St0), {Fvt,St2} = check_record(Line, Name, St1, @@ -2163,20 +2054,14 @@ expr({call,Line,{remote,_Lr,{atom,_Lm,erlang},{atom,Lf,is_record}},[E,A]}, expr({call,Line,{atom,Lf,is_record},[E,A]}, Vt, St0); expr({call,L,{tuple,Lt,[{atom,Lm,erlang},{atom,Lf,is_record}]},As}, Vt, St) -> expr({call,L,{remote,Lt,{atom,Lm,erlang},{atom,Lf,is_record}},As}, Vt, St); +expr({call,Line,{remote,_Lr,{atom,_Lm,M},{atom,Lf,F}},As}, Vt, St0) -> + St1 = keyword_warning(Lf, F, St0), + St2 = check_remote_function(Line, M, F, As, St1), + expr_list(As, Vt, St2); expr({call,Line,{remote,_Lr,M,F},As}, Vt, St0) -> - case expand_package(M, St0) of - {error, _} -> - expr_list([M,F|As], Vt, St0); - {{atom,_La,M1}, St1} -> - case F of - {atom,Lf,F1} -> - St2 = keyword_warning(Lf, F1, St1), - St3 = check_remote_function(Line, M1, F1, As, St2), - expr_list(As, Vt, St3); - _ -> - expr_list([F|As], Vt, St1) - end - end; + St1 = keyword_warning(Line, M, St0), + St2 = keyword_warning(Line, F, St1), + expr_list([M,F|As], Vt, St2); expr({call,Line,{atom,La,F},As}, Vt, St0) -> St1 = keyword_warning(La, F, St0), {Asvt,St2} = expr_list(As, Vt, St1), @@ -2232,13 +2117,6 @@ expr({call,Line,{atom,La,F},As}, Vt, St0) -> end end} end; -expr({call,Line,{record_field,_,_,_}=F,As}, Vt, St0) -> - case expand_package(F, St0) of - {error, _} -> - expr_list([F|As], Vt, St0); - {A, St1} -> - expr({call,Line,A,As}, Vt, St1) - end; expr({call,Line,F,As}, Vt, St0) -> St = warn_invalid_call(Line,F,St0), expr_list([F|As], Vt, St); %They see the same variables @@ -3658,49 +3536,6 @@ control_type($n, Need) -> Need; control_type($i, Need) -> [term|Need]; control_type(_C, _Need) -> error. -%% 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, St0) -> - St1 = keyword_warning(L, A, St0), - case dict:find(A, St1#lint.mod_imports) of - {ok, A1} -> - {{atom,L,A1}, St1}; - error -> - Name = atom_to_list(A), - case packages:is_valid(Name) of - true -> - case packages:is_segmented(Name) of - true -> - {M, St1}; - false -> - M1 = packages:concat(St1#lint.package, - Name), - {{atom,L,list_to_atom(M1)}, St1} - end; - false -> - St2 = add_error(L, {bad_module_name, Name}, St1), - {error, St2} - end - end; -expand_package(M, St0) -> - L = element(2, M), - case erl_parse:package_segments(M) of - error -> - {error, St0}; - M1 -> - Name = package_to_string(M1), - case packages:is_valid(Name) of - true -> - {{atom,L,list_to_atom(Name)}, St0}; - false -> - St1 = add_error(L, {bad_module_name, Name}, St0), - {error, St1} - end - end. - %% Prebuild set of local functions (to override auto-import) local_functions(Forms) -> diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl index 27a2ba80eb..002abc11e8 100644 --- a/lib/stdlib/src/erl_parse.yrl +++ b/lib/stdlib/src/erl_parse.yrl @@ -26,7 +26,7 @@ attribute attr_val function function_clauses function_clause clause_args clause_guard clause_body expr expr_100 expr_150 expr_160 expr_200 expr_300 expr_400 expr_500 -expr_600 expr_700 expr_800 expr_900 +expr_600 expr_700 expr_800 expr_max list tail list_comprehension lc_expr lc_exprs @@ -253,15 +253,9 @@ expr_700 -> function_call : '$1'. expr_700 -> record_expr : '$1'. expr_700 -> expr_800 : '$1'. -expr_800 -> expr_900 ':' expr_max : +expr_800 -> expr_max ':' expr_max : {remote,?line('$2'),'$1','$3'}. -expr_800 -> expr_900 : '$1'. - -expr_900 -> '.' atom : - {record_field,?line('$1'),{atom,?line('$1'),''},'$2'}. -expr_900 -> expr_900 '.' atom : - {record_field,?line('$2'),'$1','$3'}. -expr_900 -> expr_max : '$1'. +expr_800 -> expr_max : '$1'. expr_max -> var : '$1'. expr_max -> atomic : '$1'. @@ -510,7 +504,7 @@ Erlang code. -export([parse_form/1,parse_exprs/1,parse_term/1]). -export([normalise/1,abstract/1,tokens/1,tokens/2]). --export([abstract/2, package_segments/1]). +-export([abstract/2]). -export([inop_prec/1,preop_prec/1,func_prec/0,max_prec/0]). -export([set_line/2,get_attribute/2,get_attributes/1]). @@ -679,20 +673,6 @@ build_attribute({atom,La,module}, Val) -> {attribute,La,module,Module}; [{atom,_Lm,Module},ExpList] -> {attribute,La,module,{Module,var_list(ExpList)}}; - [Name] -> - case package_segments(Name) of - error -> - error_bad_decl(La, module); - Module -> - {attribute,La,module,Module} - end; - [Name,ExpList] -> - case package_segments(Name) of - error -> - error_bad_decl(La, module); - Module -> - {attribute,La,module,{Module,var_list(ExpList)}} - end; _Other -> error_bad_decl(La, module) end; @@ -704,22 +684,8 @@ build_attribute({atom,La,export}, Val) -> end; build_attribute({atom,La,import}, Val) -> case Val of - [Name] -> - case package_segments(Name) of - error -> - error_bad_decl(La, import); - Module -> - {attribute,La,import,Module} - end; [{atom,_Lm,Mod},ImpList] -> {attribute,La,import,{Mod,farity_list(ImpList)}}; - [Name, ImpList] -> - case package_segments(Name) of - error -> - error_bad_decl(La, import); - Module -> - {attribute,La,import,{Module,farity_list(ImpList)}} - end; _Other -> error_bad_decl(La, import) end; build_attribute({atom,La,record}, Val) -> @@ -820,18 +786,6 @@ term(Expr) -> catch _:_R -> ret_err(?line(Expr), "bad attribute") end. -package_segments(Name) -> - package_segments(Name, [], []). - -package_segments({record_field, _, F1, F2}, Fs, As) -> - package_segments(F1, [F2 | Fs], As); -package_segments({atom, _, A}, [F | Fs], As) -> - package_segments(F, Fs, [A | As]); -package_segments({atom, _, A}, [], As) -> - lists:reverse([A | As]); -package_segments(_, _, _) -> - error. - %% build_function([Clause]) -> {function,Line,Name,Arity,[Clause]} build_function(Cs) -> @@ -900,12 +854,6 @@ normalise({cons,_,Head,Tail}) -> [normalise(Head)|normalise(Tail)]; normalise({tuple,_,Args}) -> list_to_tuple(normalise_list(Args)); -%% Atom dot-notation, as in 'foo.bar.baz' -normalise({record_field,_,_,_}=A) -> - case package_segments(A) of - error -> erlang:error({badarg, A}); - As -> list_to_atom(packages:concat(As)) - end; %% Special case for unary +/-. normalise({op,_,'+',{char,_,I}}) -> I; normalise({op,_,'+',{integer,_,I}}) -> I; @@ -1083,9 +1031,9 @@ preop_prec('#') -> {700,800}. func_prec() -> {800,700}. --spec max_prec() -> 1000. +-spec max_prec() -> 900. -max_prec() -> 1000. +max_prec() -> 900. %%% [Experimental]. The parser just copies the attributes of the %%% scanner tokens to the abstract format. This design decision has diff --git a/lib/stdlib/src/erl_scan.erl b/lib/stdlib/src/erl_scan.erl index 20eb341c31..e5bb287c45 100644 --- a/lib/stdlib/src/erl_scan.erl +++ b/lib/stdlib/src/erl_scan.erl @@ -1,3 +1,4 @@ +%% -*- coding: utf-8 -*- %% %% %CopyrightBegin% %% @@ -32,19 +33,19 @@ %% 173 - 176 { - ~ punctuation %% 177 DEL control %% 200 - 237 control -%% 240 - 277 NBSP - � punctuation -%% 300 - 326 � - � uppercase -%% 327 � punctuation -%% 330 - 336 � - � uppercase -%% 337 - 366 � - � lowercase -%% 367 � punctuation -%% 370 - 377 � - � lowercase +%% 240 - 277 NBSP - ¿ punctuation +%% 300 - 326 À - Ö uppercase +%% 327 × punctuation +%% 330 - 336 Ø - Þ uppercase +%% 337 - 366 ß - ö lowercase +%% 367 ÷ punctuation +%% 370 - 377 ø - ÿ lowercase %% %% Many punctuation characters have special meaning: %% $\s, $_, $", $$, $%, $', $. %% DEL is a punctuation. %% -%% Must watch using � \327, very close to x \170. +%% Must watch using × \327, very close to x \170. -module(erl_scan). @@ -535,9 +536,9 @@ scan1([$$|Cs], St, Line, Col, Toks) -> scan_char(Cs, St, Line, Col, Toks); scan1([$\r|Cs], St, Line, Col, Toks) when St#erl_scan.ws -> white_space_end(Cs, St, Line, Col, Toks, 1, "\r"); -scan1([C|Cs], St, Line, Col, Toks) when C >= $�, C =< $�, C =/= $� -> +scan1([C|Cs], St, Line, Col, Toks) when C >= $ß, C =< $ÿ, C =/= $÷ -> scan_atom(Cs, St, Line, Col, Toks, [C]); -scan1([C|Cs], St, Line, Col, Toks) when C >= $�, C =< $�, C /= $� -> +scan1([C|Cs], St, Line, Col, Toks) when C >= $À, C =< $Þ, C /= $× -> scan_variable(Cs, St, Line, Col, Toks, [C]); scan1([$\t|Cs], St, Line, Col, Toks) when St#erl_scan.ws -> scan_tabs(Cs, St, Line, Col, Toks, 1); @@ -704,9 +705,9 @@ scan_name([C|Cs], Ncs) when ?DIGIT(C) -> scan_name(Cs, [C|Ncs]); scan_name([$@=C|Cs], Ncs) -> scan_name(Cs, [C|Ncs]); -scan_name([C|Cs], Ncs) when C >= $�, C =< $�, C =/= $� -> +scan_name([C|Cs], Ncs) when C >= $ß, C =< $ÿ, C =/= $÷ -> scan_name(Cs, [C|Ncs]); -scan_name([C|Cs], Ncs) when C >= $�, C =< $�, C =/= $� -> +scan_name([C|Cs], Ncs) when C >= $À, C =< $Þ, C =/= $× -> scan_name(Cs, [C|Ncs]); scan_name([], Ncs) -> {more,Ncs}; diff --git a/lib/stdlib/src/filename.erl b/lib/stdlib/src/filename.erl index 59d6de5d10..0c50eb34e6 100644 --- a/lib/stdlib/src/filename.erl +++ b/lib/stdlib/src/filename.erl @@ -878,7 +878,7 @@ filter_options(_Base, [], Result) -> %% Gets the source file given path of object code and module name. get_source_file(Obj, Mod, Rules) -> - source_by_rules(dirname(Obj), packages:last(Mod), Rules). + source_by_rules(dirname(Obj), atom_to_list(Mod), Rules). source_by_rules(Dir, Base, [{From, To}|Rest]) -> case try_rule(Dir, Base, From, To) of diff --git a/lib/stdlib/src/gb_sets.erl b/lib/stdlib/src/gb_sets.erl index 391f1cff64..ba35a7170a 100644 --- a/lib/stdlib/src/gb_sets.erl +++ b/lib/stdlib/src/gb_sets.erl @@ -1,3 +1,4 @@ +%% -*- coding: utf-8 -*- %% %% %CopyrightBegin% %% @@ -165,7 +166,7 @@ -export([new/0, is_element/2, add_element/2, del_element/2, subtract/2]). -%% GB-trees adapted from Sven-Olof Nystr�m's implementation for +%% GB-trees adapted from Sven-Olof Nyström's implementation for %% representation of sets. %% %% Data structures: diff --git a/lib/stdlib/src/gb_trees.erl b/lib/stdlib/src/gb_trees.erl index 258713c90f..de0c239e26 100644 --- a/lib/stdlib/src/gb_trees.erl +++ b/lib/stdlib/src/gb_trees.erl @@ -1,3 +1,4 @@ +%% -*- coding: utf-8 -*- %% %% %CopyrightBegin% %% @@ -19,7 +20,7 @@ %% ===================================================================== %% General Balanced Trees - highly efficient dictionaries. %% -%% Copyright (C) 1999-2001 Sven-Olof Nystr�m, Richard Carlsson +%% Copyright (C) 1999-2001 Sven-Olof Nyström, Richard Carlsson %% %% An efficient implementation of Prof. Arne Andersson's General %% Balanced Trees. These have no storage overhead compared to plain diff --git a/lib/stdlib/src/io_lib.erl b/lib/stdlib/src/io_lib.erl index 44c1d2132a..5ad505f683 100644 --- a/lib/stdlib/src/io_lib.erl +++ b/lib/stdlib/src/io_lib.erl @@ -1,3 +1,4 @@ +%% -*- coding: utf-8 -*- %% %% %CopyrightBegin% %% @@ -46,16 +47,16 @@ %% 173 - 176 { - ~ punctuation %% 177 DEL control %% 200 - 237 control -%% 240 - 277 NBSP - � punctuation -%% 300 - 326 � - � uppercase -%% 327 � punctuation -%% 330 - 336 � - � uppercase -%% 337 - 366 � - � lowercase -%% 367 � punctuation -%% 370 - 377 � - � lowercase +%% 240 - 277 NBSP - ¿ punctuation +%% 300 - 326 À - Ö uppercase +%% 327 × punctuation +%% 330 - 336 Ø - Þ uppercase +%% 337 - 366 ß - ö lowercase +%% 367 ÷ punctuation +%% 370 - 377 ø - ÿ lowercase %% %% Many punctuation characters region have special meaning. Must -%% watch using � \327, very close to x \170 +%% watch using × \327, very close to x \170 -module(io_lib). @@ -317,7 +318,7 @@ quote_atom(Atom, Cs0) -> case Cs0 of [C|Cs] when C >= $a, C =< $z -> not name_chars(Cs); - [C|Cs] when C >= $�, C =< $�, C =/= $� -> + [C|Cs] when C >= $ß, C =< $ÿ, C =/= $÷ -> not name_chars(Cs); _ -> true end @@ -331,9 +332,9 @@ name_chars([C|Cs]) -> name_chars([]) -> true. name_char(C) when C >= $a, C =< $z -> true; -name_char(C) when C >= $�, C =< $�, C =/= $� -> true; +name_char(C) when C >= $ß, C =< $ÿ, C =/= $÷ -> true; name_char(C) when C >= $A, C =< $Z -> true; -name_char(C) when C >= $�, C =< $�, C =/= $� -> true; +name_char(C) when C >= $À, C =< $Þ, C =/= $× -> true; name_char(C) when C >= $0, C =< $9 -> true; name_char($_) -> true; name_char($@) -> true; diff --git a/lib/stdlib/src/otp_internal.erl b/lib/stdlib/src/otp_internal.erl index 88985ea1d0..9257953071 100644 --- a/lib/stdlib/src/otp_internal.erl +++ b/lib/stdlib/src/otp_internal.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1999-2012. All Rights Reserved. +%% Copyright Ericsson AB 1999-2013. 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 @@ -347,7 +347,7 @@ obsolete_1(docb_xml_check, _, _) -> obsolete_1(asn1rt, F, _) when F == load_driver; F == unload_driver -> {deprecated,"deprecated (will be removed in R16A); has no effect as drivers are no longer used."}; obsolete_1(ssl, pid, 1) -> - {deprecated,"deprecated (will be removed in R17); is no longer needed"}; + {removed,"was removed in R16; is no longer needed"}; obsolete_1(inviso, _, _) -> {removed,"the inviso application was removed in R16"}; @@ -359,6 +359,45 @@ obsolete_1(ssh, sign_data, 2) -> "and public_key:sign/3 instead"}; obsolete_1(ssh, verify_data, 3) -> {deprecated,"deprecated (will be removed in R16A); use public_key:ssh_decode/1, and public_key:verify/4 instead"}; + +%% Added in R16 +obsolete_1(wxCalendarCtrl, enableYearChange, _) -> %% wx bug documented? + {deprecated,"deprecated function not available in wxWidgets-2.9 and later"}; +obsolete_1(wxDC, computeScaleAndOrigin, 1) -> + {deprecated,"deprecated function not available in wxWidgets-2.9 and later"}; +obsolete_1(wxClientDC, new, 0) -> + {deprecated,"deprecated function not available in wxWidgets-2.9 and later"}; +obsolete_1(wxPaintDC, new, 0) -> + {deprecated,"deprecated function not available in wxWidgets-2.9 and later"}; +obsolete_1(wxWindowDC, new, 0) -> + {deprecated,"deprecated function not available in wxWidgets-2.9 and later"}; +obsolete_1(wxGraphicsContext, createLinearGradientBrush, 7) -> + {deprecated,"deprecated function not available in wxWidgets-2.9 and later"}; +obsolete_1(wxGraphicsContext, createRadialGradientBrush, 8) -> + {deprecated,"deprecated function not available in wxWidgets-2.9 and later"}; +obsolete_1(wxGraphicsRenderer, createLinearGradientBrush, 7) -> + {deprecated,"deprecated function not available in wxWidgets-2.9 and later"}; +obsolete_1(wxGraphicsRenderer, createRadialGradientBrush, 8) -> + {deprecated,"deprecated function not available in wxWidgets-2.9 and later"}; +obsolete_1(wxGridCellEditor, endEdit, 4) -> + {deprecated,"deprecated function not available in wxWidgets-2.9 and later"}; +obsolete_1(wxGridCellEditor, paintBackground, 3) -> + {deprecated,"deprecated function not available in wxWidgets-2.9 and later"}; +obsolete_1(wxIdleEvent, canSend, 1) -> + {deprecated,"deprecated function not available in wxWidgets-2.9 and later"}; +obsolete_1(wxMDIClientWindow, new, 1) -> + {deprecated,"deprecated function not available in wxWidgets-2.9 and later"}; +obsolete_1(wxMDIClientWindow, new, 2) -> + {deprecated,"deprecated function not available in wxWidgets-2.9 and later"}; +obsolete_1(wxPostScriptDC, getResolution, 0) -> + {deprecated,"deprecated function not available in wxWidgets-2.9 and later"}; +obsolete_1(wxPostScriptDC, setResolution, 1) -> + {deprecated,"deprecated function not available in wxWidgets-2.9 and later"}; +obsolete_1(wxCursor, new, 3) -> + {deprecated,"deprecated function not available in wxWidgets-2.9 and later"}; +obsolete_1(wxCursor, new, 4) -> + {deprecated,"deprecated function not available in wxWidgets-2.9 and later"}; + obsolete_1(_, _, _) -> no. diff --git a/lib/stdlib/src/qlc_pt.erl b/lib/stdlib/src/qlc_pt.erl index ad25fd559c..d441f38e44 100644 --- a/lib/stdlib/src/qlc_pt.erl +++ b/lib/stdlib/src/qlc_pt.erl @@ -31,9 +31,6 @@ %% Also in qlc.erl. -define(QLC_Q(L1, L2, L3, L4, LC, Os), {call,L1,{remote,L2,{atom,L3,?APIMOD},{atom,L4,?Q}},[LC | Os]}). --define(QLC_QQ(L1, L2, L3, L4, L5, L6, LC, Os), % packages... - {call,L1,{remote,L2,{record_field,L3,{atom,L4,''}, - {atom,L5,?APIMOD}},{atom,L6,?Q}},[LC | Os]}). -define(IMP_Q(L1, L2, LC, Os), {call,L,{atom,L2,?Q},[LC | Os]}). %% Also in qlc.erl. @@ -2475,13 +2472,6 @@ qlcmf(?QLC_Q(L1, L2, L3, L4, LC0, Os0), F, Imp, A0, No0) when length(Os0) < 2 -> NL = make_lcid(L1, No), {T, A} = F(NL, LC, A2), {?QLC_Q(L1, L2, L3, L4, T, Os), A, No + 1}; -qlcmf(?QLC_QQ(L1, L2, L3, L4, L5, L6, LC0, Os0), - F, Imp, A0, No0) when length(Os0) < 2 -> - {Os, A1, No1} = qlcmf(Os0, F, Imp, A0, No0), - {LC, A2, No} = qlcmf(LC0, F, Imp, A1, No1), % nested... - NL = make_lcid(L1, No), - {T, A} = F(NL, LC, A2), - {?QLC_QQ(L1, L2, L3, L4, L5, L6, T, Os), A, No + 1}; qlcmf(?IMP_Q(L1, L2, LC0, Os0), F, Imp=true, A0, No0) when length(Os0) < 2 -> {Os, A1, No1} = qlcmf(Os0, F, Imp, A0, No0), {LC, A2, No} = qlcmf(LC0, F, Imp, A1, No1), % nested... diff --git a/lib/stdlib/src/sets.erl b/lib/stdlib/src/sets.erl index 3fd6c81e5f..e6f05b71d4 100644 --- a/lib/stdlib/src/sets.erl +++ b/lib/stdlib/src/sets.erl @@ -1,7 +1,8 @@ +%% -*- coding: utf-8 -*- %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2000-2011. All Rights Reserved. +%% Copyright Ericsson AB 2000-2012. 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 @@ -17,7 +18,7 @@ %% %CopyrightEnd% %% -%% We use the dynamic hashing techniques by Per-�ke Larsson as +%% We use the dynamic hashing techniques by Per-Åke Larsson as %% described in "The Design and Implementation of Dynamic Hashing for %% Sets and Tables in Icon" by Griswold and Townsend. Much of the %% terminology comes from that paper as well. diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl index 688492d724..5c929d2f51 100644 --- a/lib/stdlib/src/shell.erl +++ b/lib/stdlib/src/shell.erl @@ -139,16 +139,6 @@ stop_restricted() -> application:unset_env(stdlib, restricted_shell), exit(restricted_shell_stopped). -default_packages() -> - []. -%%% ['erl','erl.lang']. - -default_modules() -> - []. -%%% [{pdict, 'erl.lang.proc.pdict'}, -%%% {keylist, 'erl.lang.list.keylist'}, -%%% {debug, 'erl.system.debug'}]. - -spec server(boolean(), boolean()) -> 'terminated'. server(NoCtrlG, StartSync) -> @@ -183,15 +173,7 @@ server(StartSync) -> end end, %% Our spawner has fixed the process groups. - Bs0 = erl_eval:new_bindings(), - Bs = lists:foldl(fun ({K, V}, D) -> - erl_eval:add_binding({module,K}, V, D) - end, - lists:foldl(fun (P, D) -> - import_all(P, D) - end, - Bs0, default_packages()), - default_modules()), + Bs = erl_eval:new_bindings(), %% Use an Ets table for record definitions. It takes too long to %% send a huge term to and from the evaluator. Ets makes it @@ -1032,38 +1014,6 @@ local_func(which, [{atom,_,M}], Bs, _Shell, _RT, _Lf, _Ef) -> end; local_func(which, [_Other], _Bs, _Shell, _RT, _Lf, _Ef) -> erlang:raise(error, function_clause, [{shell,which,1}]); -local_func(import, [M], Bs, _Shell, _RT, _Lf, _Ef) -> - case erl_parse:package_segments(M) of - error -> erlang:raise(error, function_clause, [{shell,import,1}]); - M1 -> - Mod = packages:concat(M1), - case packages:is_valid(Mod) of - true -> - Key = list_to_atom(packages:last(Mod)), - Mod1 = list_to_atom(Mod), - {value,ok,erl_eval:add_binding({module,Key}, Mod1, Bs)}; - false -> - exit({{bad_module_name, Mod}, [{shell,import,1}]}) - end - end; -local_func(import_all, [P], Bs0, _Shell, _RT, _Lf, _Ef) -> - case erl_parse:package_segments(P) of - error -> erlang:raise(error, function_clause, [{shell,import_all,1}]); - P1 -> - Name = packages:concat(P1), - case packages:is_valid(Name) of - true -> - Bs1 = import_all(Name, Bs0), - {value,ok,Bs1}; - false -> - exit({{bad_package_name, Name}, - [{shell,import_all,1}]}) - end - end; -local_func(use, [M], Bs, Shell, RT, Lf, Ef) -> - local_func(import, [M], Bs, Shell, RT, Lf, Ef); -local_func(use_all, [M], Bs, Shell, RT, Lf, Ef) -> - local_func(import_all, [M], Bs, Shell, RT, Lf, Ef); local_func(history, [{integer,_,N}], Bs, _Shell, _RT, _Lf, _Ef) -> {value,history(N),Bs}; local_func(history, [_Other], _Bs, _Shell, _RT, _Lf, _Ef) -> @@ -1343,15 +1293,6 @@ record_attrs(Forms) -> %%% End of reading record information from file(s) -import_all(P, Bs0) -> - Ms = packages:find_modules(P), - lists:foldl(fun (M, Bs) -> - Key = list_to_atom(M), - M1 = list_to_atom(packages:concat(P, M)), - erl_eval:add_binding({module,Key}, M1, Bs) - end, - Bs0, Ms). - shell_req(Shell, Req) -> Shell ! {shell_req,self(),Req}, receive diff --git a/lib/stdlib/src/string.erl b/lib/stdlib/src/string.erl index fc029a582f..03f0a19f14 100644 --- a/lib/stdlib/src/string.erl +++ b/lib/stdlib/src/string.erl @@ -1,3 +1,4 @@ +%% -*- coding: utf-8 -*- %% %% %CopyrightBegin% %% @@ -257,7 +258,7 @@ chars(C, N, Tail) when N > 0 -> chars(C, 0, Tail) when is_integer(C) -> Tail. -%% Torbj�rn's bit. +%% Torbjörn's bit. %%% COPIES %%% |