diff options
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r-- | lib/stdlib/src/Makefile | 1 | ||||
-rw-r--r-- | lib/stdlib/src/erl_eval.erl | 31 | ||||
-rw-r--r-- | lib/stdlib/src/erl_lint.erl | 15 | ||||
-rw-r--r-- | lib/stdlib/src/erl_parse.yrl | 12 | ||||
-rw-r--r-- | lib/stdlib/src/erl_pp.erl | 10 | ||||
-rw-r--r-- | lib/stdlib/src/filename.erl | 46 | ||||
-rw-r--r-- | lib/stdlib/src/gen.erl | 4 | ||||
-rw-r--r-- | lib/stdlib/src/gen_event.erl | 3 | ||||
-rw-r--r-- | lib/stdlib/src/gen_fsm.erl | 16 | ||||
-rw-r--r-- | lib/stdlib/src/gen_server.erl | 8 | ||||
-rw-r--r-- | lib/stdlib/src/otp_internal.erl | 130 | ||||
-rw-r--r-- | lib/stdlib/src/qlc.erl | 5 | ||||
-rw-r--r-- | lib/stdlib/src/re.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/src/regexp.erl | 557 | ||||
-rw-r--r-- | lib/stdlib/src/shell.erl | 7 | ||||
-rw-r--r-- | lib/stdlib/src/stdlib.app.src | 1 | ||||
-rw-r--r-- | lib/stdlib/src/stdlib.appup.src | 28 | ||||
-rw-r--r-- | lib/stdlib/src/supervisor.erl | 8 |
18 files changed, 133 insertions, 751 deletions
diff --git a/lib/stdlib/src/Makefile b/lib/stdlib/src/Makefile index 600303d7e1..9ce1f6f5c8 100644 --- a/lib/stdlib/src/Makefile +++ b/lib/stdlib/src/Makefile @@ -105,7 +105,6 @@ MODULES= \ qlc_pt \ queue \ random \ - regexp \ sets \ shell \ shell_default \ diff --git a/lib/stdlib/src/erl_eval.erl b/lib/stdlib/src/erl_eval.erl index 4f4fa16040..bf3c7b3504 100644 --- a/lib/stdlib/src/erl_eval.erl +++ b/lib/stdlib/src/erl_eval.erl @@ -256,7 +256,8 @@ expr({'receive',_,Cs}, Bs, Lf, Ef, RBs) -> expr({'receive',_, Cs, E, TB}, Bs0, Lf, Ef, RBs) -> {value,T,Bs} = expr(E, Bs0, Lf, Ef, none), receive_clauses(T, Cs, {TB,Bs}, Bs0, Lf, Ef, [], RBs); -expr({'fun',_Line,{function,Mod,Name,Arity}}, Bs, _Lf, _Ef, RBs) -> +expr({'fun',_Line,{function,Mod0,Name0,Arity0}}, Bs0, Lf, Ef, RBs) -> + {[Mod,Name,Arity],Bs} = expr_list([Mod0,Name0,Arity0], Bs0, Lf, Ef), F = erlang:make_fun(Mod, Name, Arity), ret_expr(F, Bs, RBs); expr({'fun',_Line,{function,Name,Arity}}, _Bs0, _Lf, _Ef, _RBs) -> % R8 @@ -340,7 +341,7 @@ expr({call,_,{remote,_,Mod,Func},As0}, Bs0, Lf, Ef, RBs) -> true -> bif(F, As, Bs3, Ef, RBs); false -> - do_apply({M,F}, As, Bs3, Ef, RBs) + do_apply(M, F, As, Bs3, Ef, RBs) end; expr({call,_,{atom,_,Func},As0}, Bs0, Lf, Ef, RBs) -> case erl_internal:bif(Func, length(As0)) of @@ -498,11 +499,11 @@ local_func2({eval,F,As,Bs}, RBs) -> % This reply is not documented. bif(apply, [erlang,apply,As], Bs, Ef, RBs) -> bif(apply, As, Bs, Ef, RBs); bif(apply, [M,F,As], Bs, Ef, RBs) -> - do_apply({M,F}, As, Bs, Ef, RBs); + do_apply(M, F, As, Bs, Ef, RBs); bif(apply, [F,As], Bs, Ef, RBs) -> do_apply(F, As, Bs, Ef, RBs); bif(Name, As, Bs, Ef, RBs) -> - do_apply({erlang,Name}, As, Bs, Ef, RBs). + do_apply(erlang, Name, As, Bs, Ef, RBs). %% do_apply(MF, Arguments, Bindings, ExternalFuncHandler, RBs) -> %% {value,Value,Bindings} | Value when @@ -562,6 +563,19 @@ do_apply(Func, As, Bs0, Ef, RBs) -> ret_expr(F(Func, As), Bs0, RBs) end. +do_apply(Mod, Func, As, Bs0, Ef, RBs) -> + case Ef of + none when RBs =:= value -> + %% Make tail recursive calls when possible. + apply(Mod, Func, As); + none -> + ret_expr(apply(Mod, Func, As), Bs0, RBs); + {value,F} when RBs =:= value -> + F({Mod,Func}, As); + {value,F} -> + ret_expr(F({Mod,Func}, As), Bs0, RBs) + end. + %% eval_lc(Expr, [Qualifier], Bindings, LocalFunctionHandler, %% ExternalFuncHandler, RetBindings) -> %% {value,Value,Bindings} | Value @@ -730,10 +744,10 @@ expr_list([], Vs, _, Bs, _Lf, _Ef) -> {reverse(Vs),Bs}. eval_op(Op, Arg1, Arg2, Bs, Ef, RBs) -> - do_apply({erlang,Op}, [Arg1,Arg2], Bs, Ef, RBs). + do_apply(erlang, Op, [Arg1,Arg2], Bs, Ef, RBs). eval_op(Op, Arg, Bs, Ef, RBs) -> - do_apply({erlang,Op}, [Arg], Bs, Ef, RBs). + do_apply(erlang, Op, [Arg], Bs, Ef, RBs). %% if_clauses(Clauses, Bindings, LocalFuncHandler, ExtFuncHandler, RBs) @@ -919,8 +933,9 @@ guard0([], _Bs, _Lf, _Ef) -> true. guard_test({call,L,{atom,Ln,F},As0}, Bs0, Lf, Ef) -> TT = type_test(F), - guard_test({call,L,{tuple,Ln,[{atom,Ln,erlang},{atom,Ln,TT}]},As0}, - Bs0, Lf, Ef); + G = {call,L,{atom,Ln,TT},As0}, + try {value,true,_} = expr(G, Bs0, Lf, Ef, none) + catch error:_ -> {value,false,Bs0} end; guard_test({call,L,{remote,_Lr,{atom,_Lm,erlang},{atom,_Lf,_F}=T},As0}, Bs0, Lf, Ef) -> guard_test({call,L,T,As0}, Bs0, Lf, Ef); diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index 78b996d94b..e5adb84932 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -2127,8 +2127,13 @@ expr({'fun',Line,Body}, Vt, St) -> true -> {[],St}; false -> {[],call_function(Line, F, A, St)} end; - {function,_M,_F,_A} -> - {[],St} + {function,M,F,A} when is_atom(M), is_atom(F), is_integer(A) -> + %% Compatibility with pre-R15 abstract format. + {[],St}; + {function,M,F,A} -> + %% New in R15. + {Bvt, St1} = expr_list([M,F,A], Vt, St), + {vtupdate(Bvt, Vt),St1} end; expr({call,_Line,{atom,_Lr,is_record},[E,{atom,Ln,Name}]}, Vt, St0) -> {Rvt,St1} = expr(E, Vt, St0), @@ -2762,12 +2767,6 @@ default_types() -> {var, 1}], dict:from_list([{T, -1} || T <- DefTypes]). -%% R12B-5 -is_newly_introduced_builtin_type({module, 0}) -> true; -is_newly_introduced_builtin_type({node, 0}) -> true; -is_newly_introduced_builtin_type({nonempty_string, 0}) -> true; -is_newly_introduced_builtin_type({term, 0}) -> true; -is_newly_introduced_builtin_type({timeout, 0}) -> true; %% R13 is_newly_introduced_builtin_type({arity, 0}) -> true; is_newly_introduced_builtin_type({array, 0}) -> true; % opaque diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl index 709bd83e6f..928c10f7f2 100644 --- a/lib/stdlib/src/erl_parse.yrl +++ b/lib/stdlib/src/erl_parse.yrl @@ -35,7 +35,7 @@ tuple %struct record_expr record_tuple record_field record_fields if_expr if_clause if_clauses case_expr cr_clause cr_clauses receive_expr -fun_expr fun_clause fun_clauses +fun_expr fun_clause fun_clauses atom_or_var integer_or_var try_expr try_catch try_clause try_clauses query_expr function_call argument_list exprs guard @@ -395,11 +395,17 @@ receive_expr -> 'receive' cr_clauses 'after' expr clause_body 'end' : fun_expr -> 'fun' atom '/' integer : {'fun',?line('$1'),{function,element(3, '$2'),element(3, '$4')}}. -fun_expr -> 'fun' atom ':' atom '/' integer : - {'fun',?line('$1'),{function,element(3, '$2'),element(3, '$4'),element(3,'$6')}}. +fun_expr -> 'fun' atom_or_var ':' atom_or_var '/' integer_or_var : + {'fun',?line('$1'),{function,'$2','$4','$6'}}. fun_expr -> 'fun' fun_clauses 'end' : build_fun(?line('$1'), '$2'). +atom_or_var -> atom : '$1'. +atom_or_var -> var : '$1'. + +integer_or_var -> integer : '$1'. +integer_or_var -> var : '$1'. + fun_clauses -> fun_clause : ['$1']. fun_clauses -> fun_clause ';' fun_clauses : ['$1' | '$3']. diff --git a/lib/stdlib/src/erl_pp.erl b/lib/stdlib/src/erl_pp.erl index 7dc19f2e9b..6b5aa951cf 100644 --- a/lib/stdlib/src/erl_pp.erl +++ b/lib/stdlib/src/erl_pp.erl @@ -457,8 +457,16 @@ lexpr({'fun',_,{function,F,A}}, _Prec, _Hook) -> leaf(format("fun ~w/~w", [F,A])); lexpr({'fun',_,{function,F,A},Extra}, _Prec, _Hook) -> {force_nl,fun_info(Extra),leaf(format("fun ~w/~w", [F,A]))}; -lexpr({'fun',_,{function,M,F,A}}, _Prec, _Hook) -> +lexpr({'fun',_,{function,M,F,A}}, _Prec, _Hook) + when is_atom(M), is_atom(F), is_integer(A) -> + %% For backward compatibility with pre-R15 abstract format. leaf(format("fun ~w:~w/~w", [M,F,A])); +lexpr({'fun',_,{function,M,F,A}}, _Prec, Hook) -> + %% New format in R15. + NameItem = lexpr(M, Hook), + CallItem = lexpr(F, Hook), + ArityItem = lexpr(A, Hook), + ["fun ",NameItem,$:,CallItem,$/,ArityItem]; lexpr({'fun',_,{clauses,Cs}}, _Prec, Hook) -> {list,[{first,'fun',fun_clauses(Cs, Hook)},'end']}; lexpr({'fun',_,{clauses,Cs},Extra}, _Prec, Hook) -> diff --git a/lib/stdlib/src/filename.erl b/lib/stdlib/src/filename.erl index 1cb9e4a25e..dbfcbea4f7 100644 --- a/lib/stdlib/src/filename.erl +++ b/lib/stdlib/src/filename.erl @@ -147,9 +147,10 @@ basename(Name) when is_binary(Name) -> end; basename(Name0) -> - Name = flatten(Name0), + Name1 = flatten(Name0), {DirSep2, DrvSep} = separators(), - basename1(skip_prefix(Name, DrvSep), [], DirSep2). + Name = skip_prefix(Name1, DrvSep), + basename1(Name, Name, DirSep2). win_basenameb(<<Letter,$:,Rest/binary>>) when ?IS_DRIVELETTER(Letter) -> basenameb(Rest,[<<"/">>,<<"\\">>]); @@ -167,16 +168,18 @@ basenameb(Bin,Sep) -> -basename1([$/|[]], Tail, DirSep2) -> - basename1([], Tail, DirSep2); +basename1([$/], Tail0, _DirSep2) -> + %% End of filename -- must get rid of trailing directory separator. + [_|Tail] = lists:reverse(Tail0), + lists:reverse(Tail); basename1([$/|Rest], _Tail, DirSep2) -> - basename1(Rest, [], DirSep2); + basename1(Rest, Rest, DirSep2); basename1([DirSep2|Rest], Tail, DirSep2) when is_integer(DirSep2) -> basename1([$/|Rest], Tail, DirSep2); basename1([Char|Rest], Tail, DirSep2) when is_integer(Char) -> - basename1(Rest, [Char|Tail], DirSep2); + basename1(Rest, Tail, DirSep2); basename1([], Tail, _DirSep2) -> - lists:reverse(Tail). + Tail. skip_prefix(Name, false) -> Name; @@ -369,8 +372,8 @@ extension(Name0) -> Name = flatten(Name0), extension(Name, [], major_os_type()). -extension([$.|Rest], _Result, OsType) -> - extension(Rest, [$.], OsType); +extension([$.|Rest]=Result, _Result, OsType) -> + extension(Rest, Result, OsType); extension([Char|Rest], [], OsType) when is_integer(Char) -> extension(Rest, [], OsType); extension([$/|Rest], _Result, OsType) -> @@ -378,9 +381,9 @@ extension([$/|Rest], _Result, OsType) -> extension([$\\|Rest], _Result, win32) -> extension(Rest, [], win32); extension([Char|Rest], Result, OsType) when is_integer(Char) -> - extension(Rest, [Char|Result], OsType); + extension(Rest, Result, OsType); extension([], Result, _OsType) -> - lists:reverse(Result). + Result. %% Joins a list of filenames with directory separators. @@ -833,16 +836,18 @@ try_file(undefined, ObjFilename, Mod, Rules) -> Error -> Error end; try_file(Src, _ObjFilename, Mod, _Rules) -> - List = Mod:module_info(compile), - {options, Options} = lists:keyfind(options, 1, List), + List = case Mod:module_info(compile) of + none -> []; + List0 -> List0 + end, + Options = proplists:get_value(options, List, []), {ok, Cwd} = file:get_cwd(), AbsPath = make_abs_path(Cwd, Src), {AbsPath, filter_options(dirname(AbsPath), Options, [])}. %% Filters the options. %% -%% 1) Remove options that have no effect on the generated code, -%% such as report and verbose. +%% 1) Only keep options that have any effect on code generation. %% %% 2) The paths found in {i, Path} and {outdir, Path} are converted %% to absolute paths. When doing this, it is assumed that relatives @@ -854,14 +859,10 @@ filter_options(Base, [{outdir, Path}|Rest], Result) -> filter_options(Base, Rest, [{outdir, make_abs_path(Base, Path)}|Result]); filter_options(Base, [{i, Path}|Rest], Result) -> filter_options(Base, Rest, [{i, make_abs_path(Base, Path)}|Result]); -filter_options(Base, [Option|Rest], Result) when Option =:= trace -> - filter_options(Base, Rest, [Option|Result]); filter_options(Base, [Option|Rest], Result) when Option =:= export_all -> filter_options(Base, Rest, [Option|Result]); filter_options(Base, [Option|Rest], Result) when Option =:= binary -> filter_options(Base, Rest, [Option|Result]); -filter_options(Base, [Option|Rest], Result) when Option =:= fast -> - filter_options(Base, Rest, [Option|Result]); filter_options(Base, [Tuple|Rest], Result) when element(1, Tuple) =:= d -> filter_options(Base, Rest, [Tuple|Result]); filter_options(Base, [Tuple|Rest], Result) @@ -875,12 +876,7 @@ filter_options(_Base, [], Result) -> %% Gets the source file given path of object code and module name. get_source_file(Obj, Mod, Rules) -> - case catch Mod:module_info(source_file) of - {'EXIT', _Reason} -> - source_by_rules(dirname(Obj), packages:last(Mod), Rules); - File -> - {ok, File} - end. + source_by_rules(dirname(Obj), packages:last(Mod), Rules). source_by_rules(Dir, Base, [{From, To}|Rest]) -> case try_rule(Dir, Base, From, To) of diff --git a/lib/stdlib/src/gen.erl b/lib/stdlib/src/gen.erl index 574146b1cd..5d803091b6 100644 --- a/lib/stdlib/src/gen.erl +++ b/lib/stdlib/src/gen.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2010. All Rights Reserved. +%% Copyright Ericsson AB 1996-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 @@ -273,7 +273,7 @@ reply({To, Tag}, Reply) -> %%%----------------------------------------------------------------- %%% Misc. functions. %%%----------------------------------------------------------------- -where({global, Name}) -> global:safe_whereis_name(Name); +where({global, Name}) -> global:whereis_name(Name); where({local, Name}) -> whereis(Name). name_register({local, Name} = LN) -> diff --git a/lib/stdlib/src/gen_event.erl b/lib/stdlib/src/gen_event.erl index 9879b76391..3317b30e5c 100644 --- a/lib/stdlib/src/gen_event.erl +++ b/lib/stdlib/src/gen_event.erl @@ -70,7 +70,8 @@ -callback init(InitArgs :: term()) -> {ok, State :: term()} | - {ok, State :: term(), hibernate}. + {ok, State :: term(), hibernate} | + {error, Reason :: term()}. -callback handle_event(Event :: term(), State :: term()) -> {ok, NewState :: term()} | {ok, NewState :: term(), hibernate} | diff --git a/lib/stdlib/src/gen_fsm.erl b/lib/stdlib/src/gen_fsm.erl index 3db8c9f4f2..57734a075c 100644 --- a/lib/stdlib/src/gen_fsm.erl +++ b/lib/stdlib/src/gen_fsm.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2010. All Rights Reserved. +%% Copyright Ericsson AB 1996-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 @@ -296,7 +296,7 @@ get_proc_name({local, Name}) -> exit(process_not_registered) end; get_proc_name({global, Name}) -> - case global:safe_whereis_name(Name) of + case global:whereis_name(Name) of undefined -> exit(process_not_registered_globally); Pid when Pid =:= self() -> @@ -318,7 +318,7 @@ get_parent() -> name_to_pid(Name) -> case whereis(Name) of undefined -> - case global:safe_whereis_name(Name) of + case global:whereis_name(Name) of undefined -> exit(could_not_find_registerd_name); Pid -> @@ -348,12 +348,15 @@ init_it(Starter, Parent, Name0, Mod, Args, Options) -> proc_lib:init_ack(Starter, {ok, self()}), loop(Parent, Name, StateName, StateData, Mod, Timeout, Debug); {stop, Reason} -> + unregister_name(Name0), proc_lib:init_ack(Starter, {error, Reason}), exit(Reason); ignore -> + unregister_name(Name0), proc_lib:init_ack(Starter, ignore), exit(normal); {'EXIT', Reason} -> + unregister_name(Name0), proc_lib:init_ack(Starter, {error, Reason}), exit(Reason); Else -> @@ -366,6 +369,13 @@ name({local,Name}) -> Name; name({global,Name}) -> Name; name(Pid) when is_pid(Pid) -> Pid. +unregister_name({local,Name}) -> + _ = (catch unregister(Name)); +unregister_name({global,Name}) -> + _ = global:unregister_name(Name); +unregister_name(Pid) when is_pid(Pid) -> + Pid. + %%----------------------------------------------------------------- %% The MAIN loop %%----------------------------------------------------------------- diff --git a/lib/stdlib/src/gen_server.erl b/lib/stdlib/src/gen_server.erl index dd0ef74f30..af07bc988a 100644 --- a/lib/stdlib/src/gen_server.erl +++ b/lib/stdlib/src/gen_server.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2010. All Rights Reserved. +%% Copyright Ericsson AB 1996-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 @@ -134,7 +134,7 @@ term(). -callback code_change(OldVsn :: (term() | {down, term()}), State :: term(), Extra :: term()) -> - {ok, NewState :: term()}. + {ok, NewState :: term()} | {error, Reason :: term()}. %%% ----------------------------------------------------------------- %%% Starts a generic server. @@ -820,7 +820,7 @@ get_proc_name({local, Name}) -> exit(process_not_registered) end; get_proc_name({global, Name}) -> - case global:safe_whereis_name(Name) of + case global:whereis_name(Name) of undefined -> exit(process_not_registered_globally); Pid when Pid =:= self() -> @@ -842,7 +842,7 @@ get_parent() -> name_to_pid(Name) -> case whereis(Name) of undefined -> - case global:safe_whereis_name(Name) of + case global:whereis_name(Name) of undefined -> exit(could_not_find_registerd_name); Pid -> diff --git a/lib/stdlib/src/otp_internal.erl b/lib/stdlib/src/otp_internal.erl index c1285dab60..ade79e710a 100644 --- a/lib/stdlib/src/otp_internal.erl +++ b/lib/stdlib/src/otp_internal.erl @@ -41,37 +41,12 @@ obsolete(Module, Name, Arity) -> no end. -obsolete_1(init, get_flag, 1) -> - {removed, {init, get_argument, 1}, "R12B"}; -obsolete_1(init, get_flags, 0) -> - {removed, {init, get_arguments, 0}, "R12B"}; -obsolete_1(init, get_args, 0) -> - {removed, {init, get_plain_arguments, 0}, "R12B"}; -obsolete_1(unix, cmd, 1) -> - {removed, {os,cmd,1}, "R9B"}; - obsolete_1(net, _, _) -> {deprecated, "module 'net' obsolete; use 'net_adm'"}; obsolete_1(erl_internal, builtins, 0) -> {deprecated, {erl_internal, bif, 2}}; -obsolete_1(string, re_sh_to_awk, 1) -> - {removed, {regexp, sh_to_awk, 1}, "R12B"}; -obsolete_1(string, re_parse, 1) -> - {removed, {regexp, parse, 1}, "R12B"}; -obsolete_1(string, re_match, 2) -> - {removed, {regexp, match, 2}, "R12B"}; -obsolete_1(string, re_sub, 3) -> - {removed, {regexp, sub, 3}, "R12B"}; -obsolete_1(string, re_gsub, 3) -> - {removed, {regexp, gsub, 3}, "R12B"}; -obsolete_1(string, re_split, 2) -> - {removed, {regexp, split, 2}, "R12B"}; - -obsolete_1(string, index, 2) -> - {removed, {string, str, 2}, "R12B"}; - obsolete_1(erl_eval, seq, 2) -> {deprecated, {erl_eval, exprs, 2}}; obsolete_1(erl_eval, seq, 3) -> @@ -81,99 +56,9 @@ obsolete_1(erl_eval, arg_list, 2) -> obsolete_1(erl_eval, arg_list, 3) -> {deprecated, {erl_eval, expr_list, 3}}; -obsolete_1(erl_pp, seq, 1) -> - {removed, {erl_pp, exprs, 1}, "R12B"}; -obsolete_1(erl_pp, seq, 2) -> - {removed, {erl_pp, exprs, 2}, "R12B"}; - -obsolete_1(io, scan_erl_seq, 1) -> - {removed, {io, scan_erl_exprs, 1}, "R12B"}; -obsolete_1(io, scan_erl_seq, 2) -> - {removed, {io, scan_erl_exprs, 2}, "R12B"}; -obsolete_1(io, scan_erl_seq, 3) -> - {removed, {io, scan_erl_exprs, 3}, "R12B"}; -obsolete_1(io, parse_erl_seq, 1) -> - {removed, {io, parse_erl_exprs, 1}, "R12B"}; -obsolete_1(io, parse_erl_seq, 2) -> - {removed, {io, parse_erl_exprs, 2}, "R12B"}; -obsolete_1(io, parse_erl_seq, 3) -> - {removed, {io, parse_erl_exprs, 3}, "R12B"}; -obsolete_1(io, parse_exprs, 2) -> - {removed, {io, parse_erl_exprs, 2}, "R12B"}; - -obsolete_1(io_lib, scan, 1) -> - {removed, {erl_scan, string, 1}, "R12B"}; -obsolete_1(io_lib, scan, 2) -> - {removed, {erl_scan, string, 2}, "R12B"}; -obsolete_1(io_lib, scan, 3) -> - {removed, {erl_scan, tokens, 3}, "R12B"}; -obsolete_1(io_lib, reserved_word, 1) -> - {removed, {erl_scan, reserved_word, 1}, "R12B"}; - -obsolete_1(lists, keymap, 4) -> - {removed, {lists, keymap, 3}, "R12B"}; -obsolete_1(lists, all, 3) -> - {removed, {lists, all, 2}, "R12B"}; -obsolete_1(lists, any, 3) -> - {removed, {lists, any, 2}, "R12B"}; -obsolete_1(lists, map, 3) -> - {removed, {lists, map, 2}, "R12B"}; -obsolete_1(lists, flatmap, 3) -> - {removed, {lists, flatmap, 2}, "R12B"}; -obsolete_1(lists, foldl, 4) -> - {removed, {lists, foldl, 3}, "R12B"}; -obsolete_1(lists, foldr, 4) -> - {removed, {lists, foldr, 3}, "R12B"}; -obsolete_1(lists, mapfoldl, 4) -> - {removed, {lists, mapfoldl, 3}, "R12B"}; -obsolete_1(lists, mapfoldr, 4) -> - {removed, {lists, mapfoldr, 3}, "R12B"}; -obsolete_1(lists, filter, 3) -> - {removed, {lists, filter, 2}, "R12B"}; -obsolete_1(lists, foreach, 3) -> - {removed, {lists, foreach, 2}, "R12B"}; -obsolete_1(lists, zf, 3) -> - {removed, {lists, zf, 2}, "R12B"}; - -obsolete_1(ets, fixtable, 2) -> - {removed, {ets, safe_fixtable, 2}, "R12B"}; - -obsolete_1(erlang, old_binary_to_term, 1) -> - {removed, {erlang, binary_to_term, 1}, "R12B"}; -obsolete_1(erlang, info, 1) -> - {removed, {erlang, system_info, 1}, "R12B"}; obsolete_1(erlang, hash, 2) -> {deprecated, {erlang, phash2, 2}}; -obsolete_1(file, file_info, 1) -> - {removed, {file, read_file_info, 1}, "R12B"}; - -obsolete_1(dict, dict_to_list, 1) -> - {removed, {dict,to_list,1}, "R12B"}; -obsolete_1(dict, list_to_dict, 1) -> - {removed, {dict,from_list,1}, "R12B"}; -obsolete_1(orddict, dict_to_list, 1) -> - {removed, {orddict,to_list,1}, "R12B"}; -obsolete_1(orddict, list_to_dict, 1) -> - {removed, {orddict,from_list,1}, "R12B"}; - -obsolete_1(sets, new_set, 0) -> - {removed, {sets, new, 0}, "R12B"}; -obsolete_1(sets, set_to_list, 1) -> - {removed, {sets, to_list, 1}, "R12B"}; -obsolete_1(sets, list_to_set, 1) -> - {removed, {sets, from_list, 1}, "R12B"}; -obsolete_1(sets, subset, 2) -> - {removed, {sets, is_subset, 2}, "R12B"}; -obsolete_1(ordsets, new_set, 0) -> - {removed, {ordsets, new, 0}, "R12B"}; -obsolete_1(ordsets, set_to_list, 1) -> - {removed, {ordsets, to_list, 1}, "R12B"}; -obsolete_1(ordsets, list_to_set, 1) -> - {removed, {ordsets, from_list, 1}, "R12B"}; -obsolete_1(ordsets, subset, 2) -> - {removed, {ordsets, is_subset, 2}, "R12B"}; - obsolete_1(calendar, local_time_to_universal_time, 1) -> {deprecated, {calendar, local_time_to_universal_time_dst, 1}}; @@ -302,17 +187,6 @@ obsolete_1(auth, node_cookie, 1) -> obsolete_1(auth, node_cookie, 2) -> {deprecated, "Deprecated; use erlang:set_cookie/2 and net_adm:ping/1 instead"}; -%% Added in R11B-5. -obsolete_1(http_base_64, _, _) -> - {removed, "The http_base_64 module was removed in R12B; use the base64 module instead"}; -obsolete_1(httpd_util, encode_base64, 1) -> - {removed, "Removed in R12B; use one of the encode functions in the base64 module instead"}; -obsolete_1(httpd_util, decode_base64, 1) -> - {removed, "Removed in R12B; use one of the decode functions in the base64 module instead"}; -obsolete_1(httpd_util, to_upper, 1) -> - {removed, {string, to_upper, 1}, "R12B"}; -obsolete_1(httpd_util, to_lower, 1) -> - {removed, {string, to_lower, 1}, "R12B"}; obsolete_1(erlang, is_constant, 1) -> {removed, "Removed in R13B"}; @@ -431,7 +305,7 @@ obsolete_1(ssh_sshd, stop, 1) -> %% Added in R13A. obsolete_1(regexp, _, _) -> - {deprecated, "the regexp module is deprecated (will be removed in R15A); use the re module instead"}; + {removed, "removed in R15; use the re module instead"}; obsolete_1(lists, flat_length, 1) -> {removed,{lists,flatlength,1},"R14"}; @@ -472,6 +346,8 @@ obsolete_1(docb_xml_check, _, _) -> %% Added in R15B 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"}; obsolete_1(_, _, _) -> no. diff --git a/lib/stdlib/src/qlc.erl b/lib/stdlib/src/qlc.erl index f5e180b4bd..2b691e6abf 100644 --- a/lib/stdlib/src/qlc.erl +++ b/lib/stdlib/src/qlc.erl @@ -1272,7 +1272,10 @@ abstr_term(Fun, Line) when is_function(Fun) -> case erlang:fun_info(Fun, type) of {type, external} -> {module, Module} = erlang:fun_info(Fun, module), - {'fun', Line, {function,Module,Name,Arity}}; + {'fun', Line, {function, + {atom,Line,Module}, + {atom,Line,Name}, + {integer,Line,Arity}}}; {type, local} -> {'fun', Line, {function,Name,Arity}} end diff --git a/lib/stdlib/src/re.erl b/lib/stdlib/src/re.erl index 99bcbd722e..246d535943 100644 --- a/lib/stdlib/src/re.erl +++ b/lib/stdlib/src/re.erl @@ -48,7 +48,7 @@ split(Subject,RE) -> Subject :: iodata() | unicode:charlist(), RE :: mp() | iodata() | unicode:charlist(), Options :: [ Option ], - Option :: anchored | global | notbol | noteol | notempty + Option :: anchored | notbol | noteol | notempty | {offset, non_neg_integer()} | {newline, nl_spec()} | bsr_anycrlf | bsr_unicode | {return, ReturnType} | {parts, NumParts} | group | trim | CompileOpt, diff --git a/lib/stdlib/src/regexp.erl b/lib/stdlib/src/regexp.erl deleted file mode 100644 index 65f9ca247d..0000000000 --- a/lib/stdlib/src/regexp.erl +++ /dev/null @@ -1,557 +0,0 @@ -%% -%% %CopyrightBegin% -%% -%% Copyright Ericsson AB 1996-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(regexp). - -%% This entire module is deprecated and will be removed in a future -%% release. Use the 're' module instead. -%% -%% This module provides a basic set of regular expression functions -%% for strings. The functions provided are taken from AWK. -%% -%% Note that we interpret the syntax tree of a regular expression -%% directly instead of converting it to an NFA and then interpreting -%% that. This method seems to go significantly faster. - --export([sh_to_awk/1,parse/1,format_error/1,match/2,first_match/2,matches/2]). --export([sub/3,gsub/3,split/2]). - --deprecated([sh_to_awk/1,parse/1,format_error/1,match/2,first_match/2,matches/2]). --deprecated([sub/3,gsub/3,split/2]). - --import(string, [substr/2,substr/3]). --import(lists, [reverse/1]). - --type errordesc() :: term(). --opaque regexp() :: term(). - -%% -type matchres() = {match,Start,Length} | nomatch | {error,E}. -%% -type subres() = {ok,RepString,RepCount} | {error,E}. -%% -type splitres() = {ok,[SubString]} | {error,E}. - -%%-compile([export_all]). - -%% This is the regular expression grammar used. It is equivalent to the -%% one used in AWK, except that we allow ^ $ to be used anywhere and fail -%% in the matching. -%% -%% reg -> reg1 : '$1'. -%% reg1 -> reg1 "|" reg2 : {'or','$1','$2'}. -%% reg1 -> reg2 : '$1'. -%% reg2 -> reg2 reg3 : {concat,'$1','$2'}. -%% reg2 -> reg3 : '$1'. -%% reg3 -> reg3 "*" : {kclosure,'$1'}. -%% reg3 -> reg3 "+" : {pclosure,'$1'}. -%% reg3 -> reg3 "?" : {optional,'$1'}. -%% reg3 -> reg4 : '$1'. -%% reg4 -> "(" reg ")" : '$2'. -%% reg4 -> "\\" char : '$2'. -%% reg4 -> "^" : bos. -%% reg4 -> "$" : eos. -%% reg4 -> "." : char. -%% reg4 -> "[" class "]" : {char_class,char_class('$2')} -%% reg4 -> "[" "^" class "]" : {comp_class,char_class('$3')} -%% reg4 -> "\"" chars "\"" : char_string('$2') -%% reg4 -> char : '$1'. -%% reg4 -> empty : epsilon. -%% The grammar of the current regular expressions. The actual parser -%% is a recursive descent implementation of the grammar. - -reg(S) -> reg1(S). - -%% reg1 -> reg2 reg1' -%% reg1' -> "|" reg2 -%% reg1' -> empty - -reg1(S0) -> - {L,S1} = reg2(S0), - reg1p(S1, L). - -reg1p([$||S0], L) -> - {R,S1} = reg2(S0), - reg1p(S1, {'or',L,R}); -reg1p(S, L) -> {L,S}. - -%% reg2 -> reg3 reg2' -%% reg2' -> reg3 -%% reg2' -> empty - -reg2(S0) -> - {L,S1} = reg3(S0), - reg2p(S1, L). - -reg2p([C|S0], L) when C =/= $|, C =/= $) -> - {R,S1} = reg3([C|S0]), - reg2p(S1, {concat,L,R}); -reg2p(S, L) -> {L,S}. - -%% reg3 -> reg4 reg3' -%% reg3' -> "*" reg3' -%% reg3' -> "+" reg3' -%% reg3' -> "?" reg3' -%% reg3' -> empty - -reg3(S0) -> - {L,S1} = reg4(S0), - reg3p(S1, L). - -reg3p([$*|S], L) -> reg3p(S, {kclosure,L}); -reg3p([$+|S], L) -> reg3p(S, {pclosure,L}); -reg3p([$?|S], L) -> reg3p(S, {optional,L}); -reg3p(S, L) -> {L,S}. - --define(HEX(C), C >= $0 andalso C =< $9 orelse - C >= $A andalso C =< $F orelse - C >= $a andalso C =< $f). - -reg4([$(|S0]) -> - case reg(S0) of - {R,[$)|S1]} -> {R,S1}; - {_R,_S} -> throw({error,{unterminated,"("}}) - end; -reg4([$\\,O1,O2,O3|S]) when - O1 >= $0, O1 =< $7, O2 >= $0, O2 =< $7, O3 >= $0, O3 =< $7 -> - {(O1*8 + O2)*8 + O3 - 73*$0,S}; -reg4([$\\,$x,H1,H2|S]) when ?HEX(H1), ?HEX(H2) -> - {erlang:list_to_integer([H1,H2], 16),S}; -reg4([$\\,$x,${|S]) -> - hex(S, []); -reg4([$\\,$x|_]) -> - throw({error,{illegal,[$x]}}); -reg4([$\\,C|S]) -> {escape_char(C),S}; -reg4([$\\]) -> throw({error,{unterminated,"\\"}}); -reg4([$^|S]) -> {bos,S}; -reg4([$$|S]) -> {eos,S}; -reg4([$.|S]) -> {{comp_class,"\n"},S}; -reg4("[^" ++ S0) -> - case char_class(S0) of - {Cc,[$]|S1]} -> {{comp_class,Cc},S1}; - {_Cc,_S} -> throw({error,{unterminated,"["}}) - end; -reg4([$[|S0]) -> - case char_class(S0) of - {Cc,[$]|S1]} -> {{char_class,Cc},S1}; - {_Cc,_S1} -> throw({error,{unterminated,"["}}) - end; -%reg4([$"|S0]) -> -% case char_string(S0) of -% {St,[$"|S1]} -> {St,S1}; -% {St,S1} -> throw({error,{unterminated,"\""}}) -% end; -reg4([C|S]) when C =/= $*, C =/= $+, C =/= $?, C =/= $] -> {C,S}; -reg4([C|_S]) -> throw({error,{illegal,[C]}}); -reg4([]) -> {epsilon,[]}. - -hex([C|Cs], L) when ?HEX(C) -> - hex(Cs, [C|L]); -hex([$}|S], L) -> - case catch erlang:list_to_integer(lists:reverse(L), 16) of - V when V =< 16#FF -> - {V,S}; - _ -> - throw({error,{illegal,[$}]}}) - end; -hex(_S, _) -> - throw({error,{unterminated,"\\x{"}}). - -escape_char($n) -> $\n; %\n = LF -escape_char($r) -> $\r; %\r = CR -escape_char($t) -> $\t; %\t = TAB -escape_char($v) -> $\v; %\v = VT -escape_char($b) -> $\b; %\b = BS -escape_char($f) -> $\f; %\f = FF -escape_char($e) -> $\e; %\e = ESC -escape_char($s) -> $\s; %\s = SPACE -escape_char($d) -> $\d; %\d = DEL -escape_char(C) -> C. - -char_class([$]|S]) -> char_class(S, [$]]); -char_class(S) -> char_class(S, []). - -char($\\, [O1,O2,O3|S]) when - O1 >= $0, O1 =< $7, O2 >= $0, O2 =< $7, O3 >= $0, O3 =< $7 -> - {(O1*8 + O2)*8 + O3 - 73*$0,S}; -char($\\, [$x,H1,H2|S]) when ?HEX(H1), ?HEX(H2) -> - {erlang:list_to_integer([H1,H2], 16),S}; -char($\\,[$x,${|S]) -> - hex(S, []); -char($\\,[$x|_]) -> - throw({error,{illegal,[$x]}}); -char($\\, [C|S]) -> {escape_char(C),S}; -char(C, S) -> {C,S}. - -char_class([C1|S0], Cc) when C1 =/= $] -> - case char(C1, S0) of - {Cf,[$-,C2|S1]} when C2 =/= $] -> - case char(C2, S1) of - {Cl,S2} when Cf < Cl -> char_class(S2, [{Cf,Cl}|Cc]); - {Cl,_S2} -> throw({error,{char_class,[Cf,$-,Cl]}}) - end; - {C,S1} -> char_class(S1, [C|Cc]) - end; -char_class(S, Cc) -> {Cc,S}. - -%char_string([C|S]) when C =/= $" -> char_string(S, C); -%char_string(S) -> {epsilon,S}. - -%char_string([C|S0], L) when C =/= $" -> -% char_string(S0, {concat,L,C}); -%char_string(S, L) -> {L,S}. - -%% -deftype re_app_res() = {match,RestPos,Rest} | nomatch. - -%% re_apply(String, StartPos, RegExp) -> re_app_res(). -%% -%% Apply the (parse of the) regular expression RegExp to String. If -%% there is a match return the position of the remaining string and -%% the string if else return 'nomatch'. BestMatch specifies if we want -%% the longest match, or just a match. -%% -%% StartPos should be the real start position as it is used to decide -%% if we ae at the beginning of the string. -%% -%% Pass two functions to re_apply_or so it can decide, on the basis -%% of BestMatch, whether to just any take any match or try both to -%% find the longest. This is slower but saves duplicatng code. - -re_apply(S, St, RE) -> re_apply(RE, [], S, St). - -re_apply(epsilon, More, S, P) -> %This always matches - re_apply_more(More, S, P); -re_apply({'or',RE1,RE2}, More, S, P) -> - re_apply_or(re_apply(RE1, More, S, P), - re_apply(RE2, More, S, P)); -re_apply({concat,RE1,RE2}, More, S0, P) -> - re_apply(RE1, [RE2|More], S0, P); -re_apply({kclosure,CE}, More, S, P) -> - %% Be careful with the recursion, explicitly do one call before - %% looping. - re_apply_or(re_apply_more(More, S, P), - re_apply(CE, [{kclosure,CE}|More], S, P)); -re_apply({pclosure,CE}, More, S, P) -> - re_apply(CE, [{kclosure,CE}|More], S, P); -re_apply({optional,CE}, More, S, P) -> - re_apply_or(re_apply_more(More, S, P), - re_apply(CE, More, S, P)); -re_apply(bos, More, S, 1) -> re_apply_more(More, S, 1); -re_apply(eos, More, [$\n|S], P) -> re_apply_more(More, S, P); -re_apply(eos, More, [], P) -> re_apply_more(More, [], P); -re_apply({char_class,Cc}, More, [C|S], P) -> - case in_char_class(C, Cc) of - true -> re_apply_more(More, S, P+1); - false -> nomatch - end; -re_apply({comp_class,Cc}, More, [C|S], P) -> - case in_char_class(C, Cc) of - true -> nomatch; - false -> re_apply_more(More, S, P+1) - end; -re_apply(C, More, [C|S], P) when is_integer(C) -> - re_apply_more(More, S, P+1); -re_apply(_RE, _More, _S, _P) -> nomatch. - -%% re_apply_more([RegExp], String, Length) -> re_app_res(). - -re_apply_more([RE|More], S, P) -> re_apply(RE, More, S, P); -re_apply_more([], S, P) -> {match,P,S}. - -%% in_char_class(Char, Class) -> bool(). - -in_char_class(C, [{C1,C2}|_Cc]) when C >= C1, C =< C2 -> true; -in_char_class(C, [C|_Cc]) -> true; -in_char_class(C, [_|Cc]) -> in_char_class(C, Cc); -in_char_class(_C, []) -> false. - -%% re_apply_or(Match1, Match2) -> re_app_res(). -%% If we want the best match then choose the longest match, else just -%% choose one by trying sequentially. - -re_apply_or({match,P1,S1}, {match,P2,_S2}) when P1 >= P2 -> {match,P1,S1}; -re_apply_or({match,_P1,_S1}, {match,P2,S2}) -> {match,P2,S2}; -re_apply_or(nomatch, R2) -> R2; -re_apply_or(R1, nomatch) -> R1. - -%% sh_to_awk(ShellRegExp) -%% Convert a sh style regexp into a full AWK one. The main difficulty is -%% getting character sets right as the conventions are different. - --spec sh_to_awk(ShRegExp) -> AwkRegExp when - ShRegExp :: string(), - AwkRegExp :: string(). - -sh_to_awk(Sh) -> "^(" ++ sh_to_awk_1(Sh). %Fix the beginning - -sh_to_awk_1([$*|Sh]) -> %This matches any string - ".*" ++ sh_to_awk_1(Sh); -sh_to_awk_1([$?|Sh]) -> %This matches any character - [$.|sh_to_awk_1(Sh)]; -sh_to_awk_1([$[,$^,$]|Sh]) -> %This takes careful handling - "\\^" ++ sh_to_awk_1(Sh); -sh_to_awk_1("[^" ++ Sh) -> [$[|sh_to_awk_2(Sh, true)]; -sh_to_awk_1("[!" ++ Sh) -> "[^" ++ sh_to_awk_2(Sh, false); -sh_to_awk_1([$[|Sh]) -> [$[|sh_to_awk_2(Sh, false)]; -sh_to_awk_1([C|Sh]) -> - %% Unspecialise everything else which is not an escape character. - case special_char(C) of - true -> [$\\,C|sh_to_awk_1(Sh)]; - false -> [C|sh_to_awk_1(Sh)] - end; -sh_to_awk_1([]) -> ")$". %Fix the end - -sh_to_awk_2([$]|Sh], UpArrow) -> [$]|sh_to_awk_3(Sh, UpArrow)]; -sh_to_awk_2(Sh, UpArrow) -> sh_to_awk_3(Sh, UpArrow). - -sh_to_awk_3([$]|Sh], true) -> "^]" ++ sh_to_awk_1(Sh); -sh_to_awk_3([$]|Sh], false) -> [$]|sh_to_awk_1(Sh)]; -sh_to_awk_3([C|Sh], UpArrow) -> [C|sh_to_awk_3(Sh, UpArrow)]; -sh_to_awk_3([], true) -> [$^|sh_to_awk_1([])]; -sh_to_awk_3([], false) -> sh_to_awk_1([]). - -%% -type special_char(char()) -> bool(). -%% Test if a character is a special character. - -special_char($|) -> true; -special_char($*) -> true; -special_char($+) -> true; -special_char($?) -> true; -special_char($() -> true; -special_char($)) -> true; -special_char($\\) -> true; -special_char($^) -> true; -special_char($$) -> true; -special_char($.) -> true; -special_char($[) -> true; -special_char($]) -> true; -special_char($") -> true; -special_char(_C) -> false. - -%% parse(RegExp) -> {ok,RE} | {error,E}. -%% Parse the regexp described in the string RegExp. - --spec parse(RegExp) -> ParseRes when - RegExp :: string(), - ParseRes :: {ok, RE} | {error, Error}, - RE :: regexp(), - Error :: errordesc(). - -parse(S) -> - case catch reg(S) of - {R,[]} -> {ok,R}; - {_R,[C|_]} -> {error,{illegal,[C]}}; - {error,E} -> {error,E} - end. - -%% format_error(Error) -> String. - --spec format_error(ErrorDescriptor) -> Chars when - ErrorDescriptor :: errordesc(), - Chars :: io_lib:chars(). - -format_error({illegal,What}) -> ["illegal character `",What,"'"]; -format_error({unterminated,What}) -> ["unterminated `",What,"'"]; -format_error({char_class,What}) -> - ["illegal character class ",io_lib:write_string(What)]. - -%% -type match(String, RegExp) -> matchres(). -%% Find the longest match of RegExp in String. - --spec match(String, RegExp) -> MatchRes when - String :: string(), - RegExp :: string() | regexp(), - MatchRes :: {match, Start, Length} | nomatch | {error, Error}, - Start :: pos_integer(), - Length :: pos_integer(), - Error :: errordesc(). - -match(S, RegExp) when is_list(RegExp) -> - case parse(RegExp) of - {ok,RE} -> match(S, RE); - {error,E} -> {error,E} - end; -match(S, RE) -> - case match(RE, S, 1, 0, -1) of - {Start,Len} when Len >= 0 -> - {match,Start,Len}; - {_Start,_Len} -> nomatch - end. - -match(RE, S, St, Pos, L) -> - case first_match(RE, S, St) of - {St1,L1} -> - Nst = St1 + 1, - if L1 > L -> match(RE, lists:nthtail(Nst-St, S), Nst, St1, L1); - true -> match(RE, lists:nthtail(Nst-St, S), Nst, Pos, L) - end; - nomatch -> {Pos,L} - end. - -%% -type first_match(String, RegExp) -> matchres(). -%% Find the first match of RegExp in String. - --spec first_match(String, RegExp) -> MatchRes when - String :: string(), - RegExp :: string() | regexp(), - MatchRes :: {match, Start, Length} | nomatch | {error, Error}, - Start :: pos_integer(), - Length :: pos_integer(), - Error :: errordesc(). - -first_match(S, RegExp) when is_list(RegExp) -> - case parse(RegExp) of - {ok,RE} -> first_match(S, RE); - {error,E} -> {error,E} - end; -first_match(S, RE) -> - case first_match(RE, S, 1) of - {Start,Len} when Len >= 0 -> - {match,Start,Len}; - nomatch -> nomatch - end. - -first_match(RE, S, St) when S =/= [] -> - case re_apply(S, St, RE) of - {match,P,_Rest} -> {St,P-St}; - nomatch -> first_match(RE, tl(S), St+1) - end; -first_match(_RE, [], _St) -> nomatch. - -%% -type matches(String, RegExp) -> {match,[{Start,Length}]} | {error,E}. -%% Return the all the non-overlapping matches of RegExp in String. - --spec matches(String, RegExp) -> MatchRes when - String :: string(), - RegExp :: string() | regexp(), - MatchRes :: {match, Matches} | {error, Error}, - Matches :: [{Start, Length}], - Start :: pos_integer(), - Length :: pos_integer(), - Error :: errordesc(). - -matches(S, RegExp) when is_list(RegExp) -> - case parse(RegExp) of - {ok,RE} -> matches(S, RE); - {error,E} -> {error,E} - end; -matches(S, RE) -> - {match,matches(S, RE, 1)}. - -matches(S, RE, St) -> - case first_match(RE, S, St) of - {St1,0} -> [{St1,0}|matches(substr(S, St1+2-St), RE, St1+1)]; - {St1,L1} -> [{St1,L1}|matches(substr(S, St1+L1+1-St), RE, St1+L1)]; - nomatch -> [] - end. - -%% -type sub(String, RegExp, Replace) -> subsres(). -%% Substitute the first match of the regular expression RegExp with -%% the string Replace in String. Accept pre-parsed regular -%% expressions. - --spec sub(String, RegExp, New) -> SubRes when - String :: string(), - RegExp :: string() | regexp(), - New :: string(), - NewString :: string(), - SubRes :: {ok, NewString, RepCount} | {error, Error}, - RepCount :: 0 | 1, - Error :: errordesc(). - -sub(String, RegExp, Rep) when is_list(RegExp) -> - case parse(RegExp) of - {ok,RE} -> sub(String, RE, Rep); - {error,E} -> {error,E} - end; -sub(String, RE, Rep) -> - Ss = sub_match(String, RE, 1), - {ok,sub_repl(Ss, Rep, String, 1),length(Ss)}. - -sub_match(S, RE, St) -> - case first_match(RE, S, St) of - {St1,L1} -> [{St1,L1}]; - nomatch -> [] - end. - -sub_repl([{St,L}|Ss], Rep, S, Pos) -> - Rs = sub_repl(Ss, Rep, S, St+L), - substr(S, Pos, St-Pos) ++ sub_repl(Rep, substr(S, St, L), Rs); -sub_repl([], _Rep, S, Pos) -> substr(S, Pos). - -sub_repl([$&|Rep], M, Rest) -> M ++ sub_repl(Rep, M, Rest); -sub_repl("\\&" ++ Rep, M, Rest) -> [$&|sub_repl(Rep, M, Rest)]; -sub_repl([C|Rep], M, Rest) -> [C|sub_repl(Rep, M, Rest)]; -sub_repl([], _M, Rest) -> Rest. - -%% -type gsub(String, RegExp, Replace) -> subres(). -%% Substitute every match of the regular expression RegExp with the -%% string New in String. Accept pre-parsed regular expressions. - --spec gsub(String, RegExp, New) -> SubRes when - String :: string(), - RegExp :: string() | regexp(), - New :: string(), - NewString :: string(), - SubRes :: {ok, NewString, RepCount} | {error, Error}, - RepCount :: non_neg_integer(), - Error :: errordesc(). - -gsub(String, RegExp, Rep) when is_list(RegExp) -> - case parse(RegExp) of - {ok,RE} -> gsub(String, RE, Rep); - {error,E} -> {error,E} - end; -gsub(String, RE, Rep) -> - Ss = matches(String, RE, 1), - {ok,sub_repl(Ss, Rep, String, 1),length(Ss)}. - -%% -type split(String, RegExp) -> splitres(). -%% Split a string into substrings where the RegExp describes the -%% field seperator. The RegExp " " is specially treated. - --spec split(String, RegExp) -> SplitRes when - String :: string(), - RegExp :: string() | regexp(), - SplitRes :: {ok, FieldList} | {error, Error}, - FieldList :: [string()], - Error :: errordesc(). - -split(String, " ") -> %This is really special - {ok,RE} = parse("[ \t]+"), - case split_apply(String, RE, true) of - [[]|Ss] -> {ok,Ss}; - Ss -> {ok,Ss} - end; -split(String, RegExp) when is_list(RegExp) -> - case parse(RegExp) of - {ok,RE} -> {ok,split_apply(String, RE, false)}; - {error,E} -> {error,E} - end; -split(String, RE) -> {ok,split_apply(String, RE, false)}. - -split_apply(S, RE, Trim) -> split_apply(S, 1, RE, Trim, []). - -split_apply([], _P, _RE, true, []) -> []; -split_apply([], _P, _RE, _T, Sub) -> [reverse(Sub)]; -split_apply(S, P, RE, T, Sub) -> - case re_apply(S, P, RE) of - {match,P,_Rest} -> - split_apply(tl(S), P+1, RE, T, [hd(S)|Sub]); - {match,P1,Rest} -> - [reverse(Sub)|split_apply(Rest, P1, RE, T, [])]; - nomatch -> - split_apply(tl(S), P+1, RE, T, [hd(S)|Sub]) - end. diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl index 964697cae6..dc450f0ee6 100644 --- a/lib/stdlib/src/shell.erl +++ b/lib/stdlib/src/shell.erl @@ -1065,9 +1065,10 @@ local_func(F, As0, Bs0, _Shell, _RT, Lf, Ef) when is_atom(F) -> non_builtin_local_func(F,As,Bs). non_builtin_local_func(F,As,Bs) -> - case erlang:function_exported(user_default, F, length(As)) of + Arity = length(As), + case erlang:function_exported(user_default, F, Arity) of true -> - {eval,{user_default,F},As,Bs}; + {eval,erlang:make_fun(user_default, F, Arity),As,Bs}; false -> shell_default(F,As,Bs) end. @@ -1079,7 +1080,7 @@ shell_default(F,As,Bs) -> {module, _} -> case erlang:function_exported(M,F,A) of true -> - {eval,{M,F},As,Bs}; + {eval,erlang:make_fun(M, F, A),As,Bs}; false -> shell_undef(F,A) end; diff --git a/lib/stdlib/src/stdlib.app.src b/lib/stdlib/src/stdlib.app.src index 9d15f01683..da65db4b9d 100644 --- a/lib/stdlib/src/stdlib.app.src +++ b/lib/stdlib/src/stdlib.app.src @@ -85,7 +85,6 @@ queue, random, re, - regexp, sets, shell, shell_default, diff --git a/lib/stdlib/src/stdlib.appup.src b/lib/stdlib/src/stdlib.appup.src index 54a63833e6..94e81188b5 100644 --- a/lib/stdlib/src/stdlib.appup.src +++ b/lib/stdlib/src/stdlib.appup.src @@ -1 +1,27 @@ -{"%VSN%",[],[]}. +%% -*- erlang -*- +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 1999-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% +{"%VSN%", + %% Up from - max two major revisions back + [{<<"1\\.18(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R15 + {<<"1\\.17(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R14 + {<<"1\\.16(\\.[0-9]+)*">>,[restart_new_emulator]}],%% R13 + %% Down to - max two major revisions back + [{<<"1\\.18(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R15 + {<<"1\\.17(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R14 + {<<"1\\.16(\\.[0-9]+)*">>,[restart_new_emulator]}] %% R13 +}. diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl index f20ea18fd0..42ea42f42e 100644 --- a/lib/stdlib/src/supervisor.erl +++ b/lib/stdlib/src/supervisor.erl @@ -37,7 +37,7 @@ %%-------------------------------------------------------------------------- --type child() :: pid() | 'undefined'. +-type child() :: 'undefined' | pid() | [pid()]. -type child_id() :: term(). -type mfargs() :: {M :: module(), F :: atom(), A :: [term()] | undefined}. -type modules() :: [module()] | 'dynamic'. @@ -1238,15 +1238,15 @@ report_error(Error, Reason, Child, SupName) -> error_logger:error_report(supervisor_report, ErrorMsg). -extract_child(Child) when is_pid(Child#child.pid) -> - [{pid, Child#child.pid}, +extract_child(Child) when is_list(Child#child.pid) -> + [{nb_children, length(Child#child.pid)}, {name, Child#child.name}, {mfargs, Child#child.mfargs}, {restart_type, Child#child.restart_type}, {shutdown, Child#child.shutdown}, {child_type, Child#child.child_type}]; extract_child(Child) -> - [{nb_children, length(Child#child.pid)}, + [{pid, Child#child.pid}, {name, Child#child.name}, {mfargs, Child#child.mfargs}, {restart_type, Child#child.restart_type}, |