diff options
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r-- | lib/stdlib/src/dict.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/src/erl_compile.erl | 225 | ||||
-rw-r--r-- | lib/stdlib/src/erl_eval.erl | 4 | ||||
-rw-r--r-- | lib/stdlib/src/erl_lint.erl | 44 | ||||
-rw-r--r-- | lib/stdlib/src/erl_tar.erl | 4 | ||||
-rw-r--r-- | lib/stdlib/src/filelib.erl | 4 | ||||
-rw-r--r-- | lib/stdlib/src/gen_server.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/src/io_lib.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/src/lists.erl | 4 | ||||
-rw-r--r-- | lib/stdlib/src/string.erl | 4 |
10 files changed, 211 insertions, 84 deletions
diff --git a/lib/stdlib/src/dict.erl b/lib/stdlib/src/dict.erl index e3bfb6c2e2..32a7878da4 100644 --- a/lib/stdlib/src/dict.erl +++ b/lib/stdlib/src/dict.erl @@ -386,7 +386,7 @@ merge(F, D1, D2) -> update(K, fun (V1) -> F(K, V1, V2) end, V2, D) end, D1, D2). - + %% get_slot(Hashdb, Key) -> Slot. %% Get the slot. First hash on the new range, if we hit a bucket %% which has not been split use the unsplit buddy bucket. diff --git a/lib/stdlib/src/erl_compile.erl b/lib/stdlib/src/erl_compile.erl index 8c3d59467b..ed8fea5d78 100644 --- a/lib/stdlib/src/erl_compile.erl +++ b/lib/stdlib/src/erl_compile.erl @@ -21,10 +21,12 @@ -include("erl_compile.hrl"). -include("file.hrl"). --export([compile_cmdline/1]). +-export([compile_cmdline/0]). -export_type([cmd_line_arg/0]). +-define(STDERR, standard_error). %Macro to avoid misspellings. + %% Mapping from extension to {M,F} to run the correct compiler. compiler(".erl") -> {compile, compile}; @@ -47,9 +49,10 @@ compiler(_) -> no. -type cmd_line_arg() :: atom() | string(). --spec compile_cmdline([cmd_line_arg()]) -> no_return(). +-spec compile_cmdline() -> no_return(). -compile_cmdline(List) -> +compile_cmdline() -> + List = init:get_plain_arguments(), case compile(List) of ok -> my_halt(0); error -> my_halt(1); @@ -67,8 +70,12 @@ compile(List) -> receive {'EXIT', Pid, {compiler_result, Result}} -> Result; + {'EXIT', Pid, {compiler_error, Error}} -> + io:put_chars(?STDERR, Error), + io:nl(?STDERR), + error; {'EXIT', Pid, Reason} -> - io:format("Runtime error: ~tp~n", [Reason]), + io:format(?STDERR, "Runtime error: ~tp~n", [Reason]), error end. @@ -83,66 +90,178 @@ compiler_runner(List) -> %% Parses the first part of the option list. -compile1(['@cwd', Cwd|Rest]) -> - CwdL = atom_to_list(Cwd), - compile1(Rest, CwdL, #options{outdir=CwdL, cwd=CwdL}); compile1(Args) -> - %% From R13B02, the @cwd argument is optional. {ok, Cwd} = file:get_cwd(), - compile1(Args, Cwd, #options{outdir=Cwd, cwd=Cwd}). + compile1(Args, #options{outdir=Cwd,cwd=Cwd}). %% Parses all options. -compile1(['@i', Dir|Rest], Cwd, Opts) -> +compile1(["--"|Files], Opts) -> + compile2(Files, Opts); +compile1(["-"++Option|T], Opts) -> + parse_generic_option(Option, T, Opts); +compile1(["+"++Option|Rest], Opts) -> + Term = make_term(Option), + Specific = Opts#options.specific, + compile1(Rest, Opts#options{specific=[Term|Specific]}); +compile1(Files, Opts) -> + compile2(Files, Opts). + +parse_generic_option("b"++Opt, T0, Opts) -> + {OutputType,T} = get_option("b", Opt, T0), + compile1(T, Opts#options{output_type=list_to_atom(OutputType)}); +parse_generic_option("D"++Opt, T0, #options{defines=Defs}=Opts) -> + {Val0,T} = get_option("D", Opt, T0), + {Key0,Val1} = split_at_equals(Val0, []), + Key = list_to_atom(Key0), + case Val1 of + [] -> + compile1(T, Opts#options{defines=[Key|Defs]}); + Val2 -> + Val = make_term(Val2), + compile1(T, Opts#options{defines=[{Key,Val}|Defs]}) + end; +parse_generic_option("help", _, _Opts) -> + usage(); +parse_generic_option("I"++Opt, T0, #options{cwd=Cwd}=Opts) -> + {Dir,T} = get_option("I", Opt, T0), AbsDir = filename:absname(Dir, Cwd), - compile1(Rest, Cwd, Opts#options{includes=[AbsDir|Opts#options.includes]}); -compile1(['@outdir', Dir|Rest], Cwd, Opts) -> + compile1(T, Opts#options{includes=[AbsDir|Opts#options.includes]}); +parse_generic_option("M"++Opt, T0, #options{specific=Spec}=Opts) -> + case parse_dep_option(Opt, T0) of + error -> + error; + {SpecOpts,T} -> + compile1(T, Opts#options{specific=SpecOpts++Spec}) + end; +parse_generic_option("o"++Opt, T0, #options{cwd=Cwd}=Opts) -> + {Dir,T} = get_option("o", Opt, T0), AbsName = filename:absname(Dir, Cwd), case file_or_directory(AbsName) of file -> - compile1(Rest, Cwd, Opts#options{outfile=AbsName}); + compile1(T, Opts#options{outfile=AbsName}); directory -> - compile1(Rest, Cwd, Opts#options{outdir=AbsName}) + compile1(T, Opts#options{outdir=AbsName}) end; -compile1(['@d', Name|Rest], Cwd, Opts) -> - Defines = Opts#options.defines, - compile1(Rest, Cwd, Opts#options{defines=[Name|Defines]}); -compile1(['@dv', Name, Term|Rest], Cwd, Opts) -> - Defines = Opts#options.defines, - Value = make_term(atom_to_list(Term)), - compile1(Rest, Cwd, Opts#options{defines=[{Name, Value}|Defines]}); -compile1(['@warn', Level0|Rest], Cwd, Opts) -> - case catch list_to_integer(atom_to_list(Level0)) of - Level when is_integer(Level) -> - compile1(Rest, Cwd, Opts#options{warning=Level}); +parse_generic_option("O"++Opt, T, Opts) -> + case Opt of + "" -> + compile1(T, Opts#options{optimize=1}); _ -> - compile1(Rest, Cwd, Opts) + Term = make_term(Opt), + compile1(T, Opts#options{optimize=Term}) end; -compile1(['@verbose', false|Rest], Cwd, Opts) -> - compile1(Rest, Cwd, Opts#options{verbose=false}); -compile1(['@verbose', true|Rest], Cwd, Opts) -> - compile1(Rest, Cwd, Opts#options{verbose=true}); -compile1(['@optimize', Atom|Rest], Cwd, Opts) -> - Term = make_term(atom_to_list(Atom)), - compile1(Rest, Cwd, Opts#options{optimize=Term}); -compile1(['@option', Atom|Rest], Cwd, Opts) -> - Term = make_term(atom_to_list(Atom)), - Specific = Opts#options.specific, - compile1(Rest, Cwd, Opts#options{specific=[Term|Specific]}); -compile1(['@output_type', OutputType|Rest], Cwd, Opts) -> - compile1(Rest, Cwd, Opts#options{output_type=OutputType}); -compile1(['@files'|Rest], Cwd, Opts) -> - Includes = lists:reverse(Opts#options.includes), - compile2(Rest, Cwd, Opts#options{includes=Includes}). - -compile2(Files, Cwd, Opts) -> - case {Opts#options.outfile, length(Files)} of +parse_generic_option("v", T, Opts) -> + compile1(T, Opts#options{verbose=true}); +parse_generic_option("W"++Warn, T, #options{specific=Spec}=Opts) -> + case Warn of + "all" -> + compile1(T, Opts#options{warning=999}); + "error" -> + compile1(T, Opts#options{specific=[warnings_as_errors|Spec]}); + "" -> + compile1(T, Opts#options{warning=1}); + _ -> + try list_to_integer(Warn) of + Level -> + compile1(T, Opts#options{warning=Level}) + catch + error:badarg -> + usage() + end + end; +parse_generic_option("E", T, #options{specific=Spec}=Opts) -> + compile1(T, Opts#options{specific=['E'|Spec]}); +parse_generic_option("P", T, #options{specific=Spec}=Opts) -> + compile1(T, Opts#options{specific=['P'|Spec]}); +parse_generic_option("S", T, #options{specific=Spec}=Opts) -> + compile1(T, Opts#options{specific=['S'|Spec]}); +parse_generic_option(Option, _T, _Opts) -> + io:format(?STDERR, "Unknown option: -~s\n", [Option]), + usage(). + +parse_dep_option("", T) -> + {[makedep,{makedep_output,standard_io}],T}; +parse_dep_option("D", T) -> + {[makedep],T}; +parse_dep_option("F"++Opt, T0) -> + {File,T} = get_option("MF", Opt, T0), + {[makedep,{makedep_output,File}],T}; +parse_dep_option("G", T) -> + {[makedep_add_missing],T}; +parse_dep_option("P", T) -> + {[makedep_phony],T}; +parse_dep_option("Q"++Opt, T0) -> + {Target,T} = get_option("MT", Opt, T0), + {[makedep_quote_target,{makedep_target,Target}],T}; +parse_dep_option("T"++Opt, T0) -> + {Target,T} = get_option("MT", Opt, T0), + {[{makedep_target,Target}],T}; +parse_dep_option(Opt, _T) -> + io:format(?STDERR, "Unknown option: -M~s\n", [Opt]), + usage(). + +usage() -> + H = [{"-b type","type of output file (e.g. beam)"}, + {"-d","turn on debugging of erlc itself"}, + {"-Dname","define name"}, + {"-Dname=value","define name to have value"}, + {"-help","shows this help text"}, + {"-I path","where to search for include files"}, + {"-M","generate a rule for make(1) describing the dependencies"}, + {"-MF file","write the dependencies to 'file'"}, + {"-MT target","change the target of the rule emitted by dependency " + "generation"}, + {"-MQ target","same as -MT but quote characters special to make(1)"}, + {"-MG","consider missing headers as generated files and add them to " + "the dependencies"}, + {"-MP","add a phony target for each dependency"}, + {"-MD","same as -M -MT file (with default 'file')"}, + {"-o name","name output directory or file"}, + {"-pa path","add path to the front of Erlang's code path"}, + {"-pz path","add path to the end of Erlang's code path"}, + {"-smp","compile using SMP emulator"}, + {"-v","verbose compiler output"}, + {"-Werror","make all warnings into errors"}, + {"-W0","disable warnings"}, + {"-Wnumber","set warning level to number"}, + {"-Wall","enable all warnings"}, + {"-W","enable warnings (default; same as -W1)"}, + {"-E","generate listing of expanded code (Erlang compiler)"}, + {"-S","generate assembly listing (Erlang compiler)"}, + {"-P","generate listing of preprocessed code (Erlang compiler)"}, + {"+term","pass the Erlang term unchanged to the compiler"}], + io:put_chars(?STDERR, + ["Usage: erlc [Options] file.ext ...\n", + "Options:\n", + [io_lib:format("~-14s ~s\n", [K,D]) || {K,D} <- H]]), + error. + +get_option(_Name, [], [[C|_]=Option|T]) when C =/= $- -> + {Option,T}; +get_option(_Name, [_|_]=Option, T) -> + {Option,T}; +get_option(Name, _, _) -> + exit({compiler_error,"No value given to -"++Name++" option"}). + +split_at_equals([$=|T], Acc) -> + {lists:reverse(Acc),T}; +split_at_equals([H|T], Acc) -> + split_at_equals(T, [H|Acc]); +split_at_equals([], Acc) -> + {lists:reverse(Acc),[]}. + +compile2(Files, #options{cwd=Cwd,includes=Incl,outfile=Outfile}=Opts0) -> + Opts = Opts0#options{includes=lists:reverse(Incl)}, + case {Outfile,length(Files)} of {"", _} -> compile3(Files, Cwd, Opts); {[_|_], 1} -> compile3(Files, Cwd, Opts); {[_|_], _N} -> - io:format("Output file name given, but more than one input file.~n"), + io:put_chars(?STDERR, + "Output file name given, " + "but more than one input file.\n"), error end. @@ -170,23 +289,25 @@ compile3([], _Cwd, _Options) -> ok. %% Invokes the appropriate compiler, depending on the file extension. compile_file("", Input, _Output, _Options) -> - io:format("File has no extension: ~ts~n", [Input]), + io:format(?STDERR, "File has no extension: ~ts~n", [Input]), error; compile_file(Ext, Input, Output, Options) -> case compiler(Ext) of no -> - io:format("Unknown extension: '~ts'\n", [Ext]), + io:format(?STDERR, "Unknown extension: '~ts'\n", [Ext]), error; {M, F} -> case catch M:F(Input, Output, Options) of ok -> ok; error -> error; {'EXIT',Reason} -> - io:format("Compiler function ~w:~w/3 failed:\n~p~n", + io:format(?STDERR, + "Compiler function ~w:~w/3 failed:\n~p~n", [M,F,Reason]), error; Other -> - io:format("Compiler function ~w:~w/3 returned:\n~p~n", + io:format(?STDERR, + "Compiler function ~w:~w/3 returned:\n~p~n", [M,F,Other]), error end @@ -215,10 +336,10 @@ make_term(Str) -> case erl_parse:parse_term(Tokens ++ [{dot, 1}]) of {ok, Term} -> Term; {error, {_,_,Reason}} -> - io:format("~ts: ~ts~n", [Reason, Str]), + io:format(?STDERR, "~ts: ~ts~n", [Reason, Str]), throw(error) end; {error, {_,_,Reason}, _} -> - io:format("~ts: ~ts~n", [Reason, Str]), + io:format(?STDERR, "~ts: ~ts~n", [Reason, Str]), throw(error) end. diff --git a/lib/stdlib/src/erl_eval.erl b/lib/stdlib/src/erl_eval.erl index 73b8da335a..ca6a4b5c58 100644 --- a/lib/stdlib/src/erl_eval.erl +++ b/lib/stdlib/src/erl_eval.erl @@ -912,7 +912,7 @@ type_test(binary) -> is_binary; type_test(record) -> is_record; type_test(Test) -> Test. - + %% match(Pattern, Term, Bindings) -> %% {match,NewBindings} | nomatch %% or erlang:error({illegal_pattern, Pattern}). @@ -1051,7 +1051,7 @@ match_list([], [], Bs, _BBs) -> {match,Bs}; match_list(_, _, _Bs, _BBs) -> nomatch. - + %% new_bindings() %% bindings(Bindings) %% binding(Name, Bindings) diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index b6ab39251a..bcf3ccef3b 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -1955,12 +1955,10 @@ expr({string,_Line,_S}, _Vt, St) -> {[],St}; expr({nil,_Line}, _Vt, St) -> {[],St}; expr({cons,_Line,H,T}, Vt, St) -> expr_list([H,T], Vt, St); -expr({lc,_Line,E,Qs}, Vt0, St0) -> - {Vt,St} = handle_comprehension(E, Qs, Vt0, St0), - {vtold(Vt, Vt0),St}; %Don't export local variables -expr({bc,_Line,E,Qs}, Vt0, St0) -> - {Vt,St} = handle_comprehension(E, Qs, Vt0, St0), - {vtold(Vt,Vt0),St}; %Don't export local variables +expr({lc,_Line,E,Qs}, Vt, St) -> + handle_comprehension(E, Qs, Vt, St); +expr({bc,_Line,E,Qs}, Vt, St) -> + handle_comprehension(E, Qs, Vt, St); expr({tuple,_Line,Es}, Vt, St) -> expr_list(Es, Vt, St); expr({record_index,Line,Name,Field}, _Vt, St) -> @@ -2014,8 +2012,7 @@ expr({'fun',Line,Body}, Vt, St) -> %%No one can think funs export! case Body of {clauses,Cs} -> - {Bvt, St1} = fun_clauses(Cs, Vt, St), - {vtupdate(Bvt, Vt), St1}; + fun_clauses(Cs, Vt, St); {function,F,A} -> %% BifClash - Fun expression %% N.B. Only allows BIFs here as well, NO IMPORTS!! @@ -2113,12 +2110,12 @@ expr({'try',Line,Es,Scs,Ccs,As}, Vt, St0) -> {Evt0,St1} = exprs(Es, Vt, St0), TryLine = {'try',Line}, Uvt = vtunsafe(vtnames(vtnew(Evt0, Vt)), TryLine, []), - Evt1 = vtupdate(Uvt, vtupdate(Evt0, Vt)), - {Sccs,St2} = icrt_clauses(Scs++Ccs, TryLine, Evt1, St1), + Evt1 = vtupdate(Uvt, vtsubtract(Evt0, Uvt)), + {Sccs,St2} = icrt_clauses(Scs++Ccs, TryLine, vtupdate(Evt1, Vt), St1), Rvt0 = Sccs, Rvt1 = vtupdate(vtunsafe(vtnames(vtnew(Rvt0, Vt)), TryLine, []), Rvt0), Evt2 = vtmerge(Evt1, Rvt1), - {Avt0,St} = exprs(As, Evt2, St2), + {Avt0,St} = exprs(As, vtupdate(Evt2, Vt), St2), Avt1 = vtupdate(vtunsafe(vtnames(vtnew(Avt0, Vt)), TryLine, []), Avt0), Avt = vtmerge(Evt2, Avt1), {Avt,St}; @@ -2152,10 +2149,11 @@ expr({remote,Line,_M,_F}, _Vt, St) -> %% {UsedVarTable,State} expr_list(Es, Vt, St) -> - foldl(fun (E, {Esvt,St0}) -> - {Evt,St1} = expr(E, Vt, St0), - {vtmerge(Evt, Esvt),St1} - end, {[],St}, Es). + {Vt1,St1} = foldl(fun (E, {Esvt,St0}) -> + {Evt,St1} = expr(E, Vt, St0), + {vtmerge_pat(Evt, Esvt),St1} + end, {[],St}, Es), + {vtmerge(vtnew(Vt1, Vt), vtold(Vt1, Vt)),St1}. record_expr(Line, Rec, Vt, St0) -> St1 = warn_invalid_record(Line, Rec, St0), @@ -2312,7 +2310,7 @@ check_fields(Fs, Name, Fields, Vt, St0, CheckFun) -> check_field({record_field,Lf,{atom,La,F},Val}, Name, Fields, Vt, St, Sfs, CheckFun) -> case member(F, Sfs) of - true -> {Sfs,{Vt,add_error(Lf, {redefine_field,Name,F}, St)}}; + true -> {Sfs,{[],add_error(Lf, {redefine_field,Name,F}, St)}}; false -> {[F|Sfs], case find_field(F, Fields) of @@ -2845,7 +2843,9 @@ icrt_export(Csvt, Vt, In, St) -> Uvt = vtmerge(Evt, Unused), %% Make exported and unsafe unused variables unused in subsequent code: Vt2 = vtmerge(Uvt, vtsubtract(Vt1, Uvt)), - {Vt2,St}. + %% Forget about old variables which were not used: + Vt3 = vtmerge(vtnew(Vt2, Vt), vt_no_unused(vtold(Vt2, Vt))), + {Vt3,St}. handle_comprehension(E, Qs, Vt0, St0) -> {Vt1, Uvt, St1} = lc_quals(Qs, Vt0, St0), @@ -2858,7 +2858,11 @@ handle_comprehension(E, Qs, Vt0, St0) -> %% Local variables that have not been shadowed. {_,St} = check_unused_vars(Vt2, Vt0, St4), Vt3 = vtmerge(vtsubtract(Vt2, Uvt), Uvt), - {Vt3,St}. + %% Don't export local variables. + Vt4 = vtold(Vt3, Vt0), + %% Forget about old variables which were not used. + Vt5 = vt_no_unused(Vt4), + {Vt5,St}. %% lc_quals(Qualifiers, ImportVarTable, State) -> %% {VarTable,ShadowedVarTable,State} @@ -2939,7 +2943,7 @@ fun_clauses(Cs, Vt, St) -> {Cvt,St1} = fun_clause(C, Vt, St0), {vtmerge(Cvt, Bvt0),St1} end, {[],St#lint{recdef_top = false}}, Cs), - {Bvt,St2#lint{recdef_top = OldRecDef}}. + {vt_no_unused(vtold(Bvt, Vt)),St2#lint{recdef_top = OldRecDef}}. fun_clause({clause,_Line,H,G,B}, Vt0, St0) -> {Hvt,Binvt,St1} = head(H, Vt0, [], St0), % No imported pattern variables @@ -3200,6 +3204,8 @@ vt_no_unsafe(Vt) -> [V || {_,{S,_U,_L}}=V <- Vt, _ -> true end]. +vt_no_unused(Vt) -> [V || {_,{_,U,_L}}=V <- Vt, U =/= unused]. + %% vunion(VarTable1, VarTable2) -> [VarName]. %% vunion([VarTable]) -> [VarName]. %% vintersection(VarTable1, VarTable2) -> [VarName]. diff --git a/lib/stdlib/src/erl_tar.erl b/lib/stdlib/src/erl_tar.erl index f49c2a64f4..40b48d7999 100644 --- a/lib/stdlib/src/erl_tar.erl +++ b/lib/stdlib/src/erl_tar.erl @@ -219,7 +219,7 @@ format_error(Atom) when is_atom(Atom) -> format_error(Term) -> lists:flatten(io_lib:format("~tp", [Term])). - + %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%% %%% Useful definitions (also start of implementation). @@ -409,7 +409,7 @@ split_filename([Comp|Rest], Prefix, Suffix, Len) -> split_filename([], Prefix, Suffix, _) -> {filename:join(Prefix),filename:join(Suffix)}. - + %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%% %%% Retrieving files from a tape archive. diff --git a/lib/stdlib/src/filelib.erl b/lib/stdlib/src/filelib.erl index 5b7bc0ab21..a266daa084 100644 --- a/lib/stdlib/src/filelib.erl +++ b/lib/stdlib/src/filelib.erl @@ -248,7 +248,7 @@ ensure_dir(F) -> end end. - + %%% %%% Pattern matching using a compiled wildcard. %%% @@ -360,7 +360,7 @@ do_alt([], _File) -> do_list_dir(Dir, Mod) -> eval_list_dir(Dir, Mod). - + %%% Compiling a wildcard. %% Only for debugging. diff --git a/lib/stdlib/src/gen_server.erl b/lib/stdlib/src/gen_server.erl index 6776f3deaa..5f14e48b0a 100644 --- a/lib/stdlib/src/gen_server.erl +++ b/lib/stdlib/src/gen_server.erl @@ -393,7 +393,7 @@ decode_msg(Msg, Parent, Name, State, Mod, Time, Debug, Hib) -> end. %%% --------------------------------------------------- -%%% Send/recive functions +%%% Send/receive functions %%% --------------------------------------------------- do_send(Dest, Msg) -> case catch erlang:send(Dest, Msg, [noconnect]) of diff --git a/lib/stdlib/src/io_lib.erl b/lib/stdlib/src/io_lib.erl index 53781e97f1..375d05f359 100644 --- a/lib/stdlib/src/io_lib.erl +++ b/lib/stdlib/src/io_lib.erl @@ -582,7 +582,7 @@ printable_unicode_list(_) -> false. %Everything else is false nl() -> "\n". - + %% %% Utilities for collecting characters in input files %% diff --git a/lib/stdlib/src/lists.erl b/lib/stdlib/src/lists.erl index b5577165f4..d6a9f4645d 100644 --- a/lib/stdlib/src/lists.erl +++ b/lib/stdlib/src/lists.erl @@ -630,7 +630,7 @@ flatlength([H|T], L) when is_list(H) -> flatlength([_|T], L) -> flatlength(T, L + 1); flatlength([], L) -> L. - + %% keymember(Key, Index, [Tuple]) Now a BIF! %% keyfind(Key, Index, [Tuple]) A BIF! %% keysearch(Key, Index, [Tuple]) Now a BIF! @@ -1163,7 +1163,7 @@ rumerge(T1, []) -> T1; rumerge(T1, [H2 | T2]) -> lists:reverse(rumerge2_1(T1, T2, [], H2), []). - + %% all(Predicate, List) %% any(Predicate, List) %% map(Function, List) diff --git a/lib/stdlib/src/string.erl b/lib/stdlib/src/string.erl index 0675afb877..f9b083a56d 100644 --- a/lib/stdlib/src/string.erl +++ b/lib/stdlib/src/string.erl @@ -256,7 +256,7 @@ chars(C, N, Tail) when N > 0 -> chars(C, N-1, [C|Tail]); chars(C, 0, Tail) when is_integer(C) -> Tail. - + %% Torbjörn's bit. %%% COPIES %%% @@ -460,7 +460,7 @@ sub_string(String, Start) -> substr(String, Start). Stop :: pos_integer(). sub_string(String, Start, Stop) -> substr(String, Start, Stop - Start + 1). - + %% ISO/IEC 8859-1 (latin1) letters are converted, others are ignored %% |