diff options
Diffstat (limited to 'lib')
-rw-r--r-- | lib/compiler/src/beam_dict.erl | 18 | ||||
-rw-r--r-- | lib/compiler/src/sys_core_fold.erl | 37 | ||||
-rw-r--r-- | lib/compiler/src/v3_kernel.erl | 31 | ||||
-rw-r--r-- | lib/compiler/test/bs_match_SUITE.erl | 48 | ||||
-rw-r--r-- | lib/dialyzer/src/dialyzer_contracts.erl | 27 | ||||
-rw-r--r-- | lib/dialyzer/test/small_SUITE_data/results/empty_list_infimum | 2 | ||||
-rw-r--r-- | lib/dialyzer/test/small_SUITE_data/src/empty_list_infimum.erl | 57 | ||||
-rw-r--r-- | lib/dialyzer/test/small_SUITE_data/src/unknown_arity_function_spec.erl | 10 | ||||
-rw-r--r-- | lib/hipe/cerl/erl_types.erl | 4 | ||||
-rw-r--r-- | lib/kernel/src/group.erl | 140 | ||||
-rw-r--r-- | lib/kernel/test/file_SUITE.erl | 57 | ||||
-rw-r--r-- | lib/kernel/test/gen_tcp_misc_SUITE.erl | 72 | ||||
-rw-r--r-- | lib/megaco/src/flex/megaco_flex_scanner_drv.flex.src | 10 | ||||
-rw-r--r-- | lib/public_key/vsn.mk | 2 | ||||
-rw-r--r-- | lib/ssh/src/ssh.appup.src | 2 | ||||
-rw-r--r-- | lib/ssh/src/ssh.erl | 44 | ||||
-rw-r--r-- | lib/ssh/src/ssh_client_key_api.erl | 2 | ||||
-rw-r--r-- | lib/ssh/vsn.mk | 2 | ||||
-rw-r--r-- | lib/stdlib/src/edlin.erl | 109 | ||||
-rw-r--r-- | lib/tools/test/cprof_SUITE.erl | 16 |
20 files changed, 570 insertions, 120 deletions
diff --git a/lib/compiler/src/beam_dict.erl b/lib/compiler/src/beam_dict.erl index ff6c7c11dc..531968b3c8 100644 --- a/lib/compiler/src/beam_dict.erl +++ b/lib/compiler/src/beam_dict.erl @@ -138,17 +138,7 @@ string(Str, Dict) when is_list(Str) -> -spec lambda(label(), non_neg_integer(), bdict()) -> {non_neg_integer(), bdict()}. -lambda(Lbl, 0, #asm{lambdas=Lambdas0}=Dict) -> - case lists:keyfind(Lbl, 1, Lambdas0) of - {Lbl,{OldIndex,_,_,_,_}} -> - {OldIndex,Dict}; - false -> - new_lambda(Lbl, 0, Dict) - end; -lambda(Lbl, NumFree, Dict) -> - new_lambda(Lbl, NumFree, Dict). - -new_lambda(Lbl, NumFree, #asm{lambdas=Lambdas0}=Dict) -> +lambda(Lbl, NumFree, #asm{lambdas=Lambdas0}=Dict) -> OldIndex = length(Lambdas0), %% Set Index the same as OldIndex. Index = OldIndex, @@ -245,12 +235,10 @@ string_table(#asm{strings=Strings,string_offset=Size}) -> -spec lambda_table(bdict()) -> {non_neg_integer(), [<<_:192>>]}. -lambda_table(#asm{exports=Ext0,locals=Loc0,lambdas=Lambdas0}) -> +lambda_table(#asm{locals=Loc0,lambdas=Lambdas0}) -> Lambdas1 = sofs:relation(Lambdas0), Loc = sofs:relation([{Lbl,{F,A}} || {F,A,Lbl} <- Loc0]), - Ext = sofs:relation([{Lbl,{F,A}} || {F,A,Lbl} <- Ext0]), - All = sofs:union(Loc, Ext), - Lambdas2 = sofs:relative_product1(Lambdas1, All), + Lambdas2 = sofs:relative_product1(Lambdas1, Loc), Lambdas = [<<F:32,A:32,Lbl:32,Index:32,NumFree:32,OldUniq:32>> || {{_,Lbl,Index,NumFree,OldUniq},{F,A}} <- sofs:to_external(Lambdas2)], {length(Lambdas),Lambdas}. diff --git a/lib/compiler/src/sys_core_fold.erl b/lib/compiler/src/sys_core_fold.erl index f17b0bd130..fbd7452301 100644 --- a/lib/compiler/src/sys_core_fold.erl +++ b/lib/compiler/src/sys_core_fold.erl @@ -2672,16 +2672,19 @@ bsm_nonempty([#c_clause{pats=Ps}|Cs], Pos) -> bsm_nonempty([], _ ) -> false. %% bsm_ensure_no_partition(Cs, Pos) -> ok (exception if problem) -%% We must make sure that binary matching is not partitioned between +%% We must make sure that matching is not partitioned between %% variables like this: %% foo(<<...>>) -> ... -%% foo(Var) when ... -> ... -%% foo(<<...>>) -> +%% foo(<Variable>) when ... -> ... +%% foo(<Any non-variable pattern>) -> %% If there is such partition, we are not allowed to reuse the binary variable -%% for the match context. Also, arguments to the left of the argument that -%% is matched against a binary, are only allowed to be simple variables, not -%% used in guards. The reason is that we must know that the binary is only -%% matched in one place. +%% for the match context. +%% +%% Also, arguments to the left of the argument that is matched +%% against a binary, are only allowed to be simple variables, not +%% used in guards. The reason is that we must know that the binary is +%% only matched in one place (i.e. there must be only one bs_start_match2 +%% instruction emitted). bsm_ensure_no_partition(Cs, Pos) -> bsm_ensure_no_partition_1(Cs, Pos, before). @@ -2689,6 +2692,12 @@ bsm_ensure_no_partition(Cs, Pos) -> %% Loop through each clause. bsm_ensure_no_partition_1([#c_clause{pats=Ps,guard=G}|Cs], Pos, State0) -> State = bsm_ensure_no_partition_2(Ps, Pos, G, simple_vars, State0), + case State of + 'after' -> + bsm_ensure_no_partition_after(Cs, Pos); + _ -> + ok + end, bsm_ensure_no_partition_1(Cs, Pos, State); bsm_ensure_no_partition_1([], _, _) -> ok. @@ -2698,8 +2707,7 @@ bsm_ensure_no_partition_2([#c_binary{}=Where|_], 1, _, Vstate, State) -> before when Vstate =:= simple_vars -> within; before -> bsm_problem(Where, Vstate); within when Vstate =:= simple_vars -> within; - within -> bsm_problem(Where, Vstate); - 'after' -> bsm_problem(Where, bin_partition) + within -> bsm_problem(Where, Vstate) end; bsm_ensure_no_partition_2([#c_alias{}=Alias|_], 1, N, Vstate, State) -> %% Retrieve the real pattern that the alias refers to and check that. @@ -2748,6 +2756,15 @@ bsm_ensure_no_partition_2([#c_var{name=V}|Ps], N, G, Vstate, S) -> bsm_ensure_no_partition_2([_|Ps], N, G, _, S) -> bsm_ensure_no_partition_2(Ps, N-1, G, bin_argument_order, S). +bsm_ensure_no_partition_after([#c_clause{pats=Ps}|Cs], Pos) -> + case nth(Pos, Ps) of + #c_var{} -> + bsm_ensure_no_partition_after(Cs, Pos); + P -> + bsm_problem(P, bin_partition) + end; +bsm_ensure_no_partition_after([], _) -> ok. + bsm_could_match_binary(#c_alias{pat=P}) -> bsm_could_match_binary(P); bsm_could_match_binary(#c_cons{}) -> false; bsm_could_match_binary(#c_tuple{}) -> false; @@ -2872,7 +2889,7 @@ format_error(useless_building) -> format_error(bin_opt_alias) -> "INFO: the '=' operator will prevent delayed sub binary optimization"; format_error(bin_partition) -> - "INFO: non-consecutive clauses that match binaries " + "INFO: matching non-variables after a previous clause matching a variable " "will prevent delayed sub binary optimization"; format_error(bin_left_var_used_in_guard) -> "INFO: a variable to the left of the binary pattern is used in a guard; " diff --git a/lib/compiler/src/v3_kernel.erl b/lib/compiler/src/v3_kernel.erl index b1bff47f69..8ef71e1346 100644 --- a/lib/compiler/src/v3_kernel.erl +++ b/lib/compiler/src/v3_kernel.erl @@ -235,8 +235,16 @@ gexpr_test_add(Ke, St0) -> %% expr(Cexpr, Sub, State) -> {Kexpr,[PreKexpr],State}. %% Convert a Core expression, flattening it at the same time. -expr(#c_var{anno=A,name={Name,Arity}}, Sub, St) -> - {#k_local{anno=A,name=get_fsub(Name, Arity, Sub),arity=Arity},[],St}; +expr(#c_var{anno=A,name={_Name,Arity}}=Fname, Sub, St) -> + %% A local in an expression. + %% For now, these are wrapped into a fun by reverse + %% etha-conversion, but really, there should be exactly one + %% such "lambda function" for each escaping local name, + %% instead of one for each occurrence as done now. + Vs = [#c_var{name=list_to_atom("V" ++ integer_to_list(V))} || + V <- integers(1, Arity)], + Fun = #c_fun{anno=A,vars=Vs,body=#c_apply{anno=A,op=Fname,args=Vs}}, + expr(Fun, Sub, St); expr(#c_var{anno=A,name=V}, Sub, St) -> {#k_var{anno=A,name=get_vsub(V, Sub)},[],St}; expr(#c_literal{anno=A,val=V}, _Sub, St) -> @@ -1655,19 +1663,6 @@ uexpr(#ifun{anno=A,vars=Vs,body=B0}, {break,Rs}, St0) -> #k_int{val=Index},#k_int{val=Uniq}|Fvs], ret=Rs}, Free,add_local_function(Fun, St)}; -uexpr(#k_local{anno=A,name=Name,arity=Arity}, {break,Rs}, St) -> - Fs = get_free(Name, Arity, St), - FsCount = length(Fs), - Free = lit_list_vars(Fs), - %% Set dummy values for Index and Uniq -- the real values will - %% be assigned by beam_asm. - Index = Uniq = 0, - Bif = #k_bif{anno=#k{us=Free,ns=lit_list_vars(Rs),a=A}, - op=#k_internal{name=make_fun,arity=FsCount+3}, - args=[#k_atom{val=Name},#k_int{val=FsCount+Arity}, - #k_int{val=Index},#k_int{val=Uniq}|Fs], - ret=Rs}, - {Bif,Free,St}; uexpr(Lit, {break,Rs0}, St0) -> %% Transform literals to puts here. %%ok = io:fwrite("uexpr ~w:~p~n", [?LINE,Lit]), @@ -1848,6 +1843,12 @@ make_list(Es) -> #c_cons{hd=E,tl=Acc} end, #c_literal{val=[]}, Es). +%% List of integers in interval [N,M]. Empty list if N > M. + +integers(N, M) when N =< M -> + [N|integers(N + 1, M)]; +integers(_, _) -> []. + %% is_in_guard(State) -> true|false. is_in_guard(#kern{guard_refc=Refc}) -> diff --git a/lib/compiler/test/bs_match_SUITE.erl b/lib/compiler/test/bs_match_SUITE.erl index d63d2235d7..e8a92c509e 100644 --- a/lib/compiler/test/bs_match_SUITE.erl +++ b/lib/compiler/test/bs_match_SUITE.erl @@ -33,7 +33,8 @@ matching_meets_construction/1,simon/1,matching_and_andalso/1, otp_7188/1,otp_7233/1,otp_7240/1,otp_7498/1, match_string/1,zero_width/1,bad_size/1,haystack/1, - cover_beam_bool/1,matched_out_size/1,follow_fail_branch/1]). + cover_beam_bool/1,matched_out_size/1,follow_fail_branch/1, + no_partition/1]). -export([coverage_id/1,coverage_external_ignore/2]). @@ -57,7 +58,8 @@ groups() -> matching_meets_construction,simon, matching_and_andalso,otp_7188,otp_7233,otp_7240, otp_7498,match_string,zero_width,bad_size,haystack, - cover_beam_bool,matched_out_size,follow_fail_branch]}]. + cover_beam_bool,matched_out_size,follow_fail_branch, + no_partition]}]. init_per_suite(Config) -> @@ -1133,6 +1135,48 @@ ffb_2(<<_,T/bitstring>>, List, A) -> [_|_] -> bit_size(T) end. +no_partition(_) -> + one = no_partition_1(<<"string">>, a1), + {two,<<"string">>} = no_partition_1(<<"string">>, a2), + {two,<<>>} = no_partition_1(<<>>, a2), + {two,a} = no_partition_1(a, a2), + three = no_partition_1(undefined, a3), + {four,a,[]} = no_partition_1([a], a4), + {five,a,b} = no_partition_1({a,b}, a5), + + one = no_partition_2(<<"string">>, a1), + two = no_partition_2(<<"string">>, a2), + two = no_partition_2(<<>>, a2), + two = no_partition_2(a, a2), + three = no_partition_2(undefined, a3), + four = no_partition_2(42, a4), + five = no_partition_2([], a5), + six = no_partition_2(42.0, a6), + ok. + +no_partition_1(<<"string">>, a1) -> + one; +no_partition_1(V, a2) -> + {two,V}; +no_partition_1(undefined, a3) -> + three; +no_partition_1([H|T], a4) -> + {four,H,T}; +no_partition_1({A,B}, a5) -> + {five,A,B}. + +no_partition_2(<<"string">>, a1) -> + one; +no_partition_2(_, a2) -> + two; +no_partition_2(undefined, a3) -> + three; +no_partition_2(42, a4) -> + four; +no_partition_2([], a5) -> + five; +no_partition_2(42.0, a6) -> + six. check(F, R) -> R = F(). diff --git a/lib/dialyzer/src/dialyzer_contracts.erl b/lib/dialyzer/src/dialyzer_contracts.erl index 0b932d5a1f..157c951f77 100644 --- a/lib/dialyzer/src/dialyzer_contracts.erl +++ b/lib/dialyzer/src/dialyzer_contracts.erl @@ -254,14 +254,35 @@ check_extraneous([C|Cs], SuccType) -> end. check_extraneous_1(Contract, SuccType) -> - CRngs = erl_types:t_elements(erl_types:t_fun_range(Contract)), + CRng = erl_types:t_fun_range(Contract), + CRngs = erl_types:t_elements(CRng), STRng = erl_types:t_fun_range(SuccType), ?debug("CR = ~p\nSR = ~p\n", [CRngs, STRng]), - case [CR || CR <- CRngs, erl_types:t_is_none(erl_types:t_inf(CR, STRng, opaque))] of - [] -> ok; + case [CR || CR <- CRngs, + erl_types:t_is_none(erl_types:t_inf(CR, STRng, opaque))] of + [] -> + CRngList = list_part(CRng), + STRngList = list_part(STRng), + case is_not_nil_list(CRngList) andalso is_not_nil_list(STRngList) of + false -> ok; + true -> + CRngElements = erl_types:t_list_elements(CRngList), + STRngElements = erl_types:t_list_elements(STRngList), + Inf = erl_types:t_inf(CRngElements, STRngElements, opaque), + case erl_types:t_is_none(Inf) of + true -> {error, invalid_contract}; + false -> ok + end + end; CRs -> {error, {extra_range, erl_types:t_sup(CRs), STRng}} end. +list_part(Type) -> + erl_types:t_inf(erl_types:t_list(), Type, opaque). + +is_not_nil_list(Type) -> + erl_types:t_is_list(Type) andalso not erl_types:t_is_nil(Type). + %% This is the heart of the "range function" -spec process_contracts([contract_pair()], [erl_types:erl_type()]) -> erl_types:erl_type(). diff --git a/lib/dialyzer/test/small_SUITE_data/results/empty_list_infimum b/lib/dialyzer/test/small_SUITE_data/results/empty_list_infimum new file mode 100644 index 0000000000..6eaf60b91d --- /dev/null +++ b/lib/dialyzer/test/small_SUITE_data/results/empty_list_infimum @@ -0,0 +1,2 @@ + +empty_list_infimum.erl:38: Invalid type specification for function empty_list_infimum:list_vhost_permissions/1. The success typing is (_) -> [[{_,_}]]
\ No newline at end of file diff --git a/lib/dialyzer/test/small_SUITE_data/src/empty_list_infimum.erl b/lib/dialyzer/test/small_SUITE_data/src/empty_list_infimum.erl new file mode 100644 index 0000000000..b58fa732cb --- /dev/null +++ b/lib/dialyzer/test/small_SUITE_data/src/empty_list_infimum.erl @@ -0,0 +1,57 @@ +%% +%% The Original Code is RabbitMQ. +%% +%% The Initial Developer of the Original Code is VMware, Inc. +%% + +-module(empty_list_infimum). + +-record(permission, {configure, write, read}). +-record(user_vhost, {username, virtual_host}). +-record(user_permission, {user_vhost, permission}). + +%%---------------------------------------------------------------------------- + +-export([i_delete/1]). + +-type(vhost() :: binary()). + +-type(info_key() :: atom()). +-type(info_keys() :: [info_key()]). + +-type(info() :: {info_key(), any()}). +-type(infos() :: [info()]). + +%%---------------------------------------------------------------------------- + +-spec i_delete(vhost()) -> 'ok'. + +i_delete(VHostPath) -> + [ok || _ <- list_vhost_permissions(VHostPath)], + ok. + +%%---------------------------------------------------------------------------- + +vhost_perms_info_keys() -> + [user, configure, write, read]. + +-spec list_vhost_permissions(vhost()) -> infos(). + +list_vhost_permissions(VHostPath) -> + list_permissions(vhost_perms_info_keys(), rabbit_foo:some_list()). + +filter_props(Keys, Props) -> + [T || T = {K, _} <- Props, lists:member(K, Keys)]. + +list_permissions(Keys, SomeList) -> + [filter_props(Keys, [{user, Username}, + {vhost, VHostPath}, + {configure, ConfigurePerm}, + {write, WritePerm}, + {read, ReadPerm}]) || + #user_permission{user_vhost = #user_vhost{username = Username, + virtual_host = VHostPath}, + permission = #permission{configure = ConfigurePerm, + write = WritePerm, + read = ReadPerm}} <- + SomeList]. diff --git a/lib/dialyzer/test/small_SUITE_data/src/unknown_arity_function_spec.erl b/lib/dialyzer/test/small_SUITE_data/src/unknown_arity_function_spec.erl new file mode 100644 index 0000000000..c7d7459614 --- /dev/null +++ b/lib/dialyzer/test/small_SUITE_data/src/unknown_arity_function_spec.erl @@ -0,0 +1,10 @@ +-module(unknown_arity_function_spec). + +-export([test/2]). + +%-type t() :: 42 | fun((...) -> t()). +%-type f() :: fun((...) -> 42). + +-spec test(fun((...) -> 42), list()) -> 42. +test(F, L) -> + 42 = apply(F, L). diff --git a/lib/hipe/cerl/erl_types.erl b/lib/hipe/cerl/erl_types.erl index f5be8fb08f..ea1e7b1292 100644 --- a/lib/hipe/cerl/erl_types.erl +++ b/lib/hipe/cerl/erl_types.erl @@ -3566,7 +3566,7 @@ t_from_form({type, _L, function, []}, _TypeNames, _InOpaque, _RecDict, t_from_form({type, _L, 'fun', []}, _TypeNames, _InOpaque, _RecDict, _VarDict) -> {t_fun(), []}; -t_from_form({type, _L, 'fun', [{type, _, any, []}, Range]}, TypeNames, +t_from_form({type, _L, 'fun', [{type, _, any}, Range]}, TypeNames, InOpaque, RecDict, VarDict) -> {T, R} = t_from_form(Range, TypeNames, InOpaque, RecDict, VarDict), {t_fun(T), R}; @@ -3909,7 +3909,7 @@ t_form_to_string({type, _L, binary, [Base, Unit]} = Type) -> _ -> io_lib:format("Badly formed bitstr type ~w", [Type]) end; t_form_to_string({type, _L, 'fun', []}) -> "fun()"; -t_form_to_string({type, _L, 'fun', [{type, _, any, []}, Range]}) -> +t_form_to_string({type, _L, 'fun', [{type, _, any}, Range]}) -> "fun(...) -> " ++ t_form_to_string(Range); t_form_to_string({type, _L, 'fun', [{type, _, product, Domain}, Range]}) -> "fun((" ++ string:join(t_form_to_string_list(Domain), ",") ++ ") -> " diff --git a/lib/kernel/src/group.erl b/lib/kernel/src/group.erl index 4d2e31a429..c66e823a04 100644 --- a/lib/kernel/src/group.erl +++ b/lib/kernel/src/group.erl @@ -515,6 +515,27 @@ get_line1({undefined,{_A,Mode,Char},Cs,Cont,Rs}, Drv, Ls0, Encoding) Drv, Ls, Encoding) end; +%% ^R = backward search, ^S = forward search. +%% Search is tricky to implement and does a lot of back-and-forth +%% work with edlin.erl (from stdlib). Edlin takes care of writing +%% and handling lines and escape characters to get out of search, +%% whereas this module does the actual searching and appending to lines. +%% Erlang's shell wasn't exactly meant to traverse the wall between +%% line and line stack, so we at least restrict it by introducing +%% new modes: search, search_quit, search_found. These are added to +%% the regular ones (none, meta_left_sq_bracket) and handle special +%% cases of history search. +get_line1({undefined,{_A,Mode,Char},Cs,Cont,Rs}, Drv, Ls, Encoding) + when ((Mode =:= none) and (Char =:= $\^R)) -> + send_drv_reqs(Drv, Rs), + %% drop current line, move to search mode. We store the current + %% prompt ('N>') and substitute it with the search prompt. + send_drv_reqs(Drv, edlin:erase_line(Cont)), + put(search_quit_prompt, edlin:prompt(Cont)), + Pbs = prompt_bytes("(search)`': ", Encoding), + {more_chars,Ncont,Nrs} = edlin:start(Pbs, search), + send_drv_reqs(Drv, Nrs), + get_line1(edlin:edit_line1(Cs, Ncont), Drv, Ls, Encoding); get_line1({expand, Before, Cs0, Cont,Rs}, Drv, Ls0, Encoding) -> send_drv_reqs(Drv, Rs), ExpandFun = get(expand_fun), @@ -535,8 +556,59 @@ get_line1({undefined,_Char,Cs,Cont,Rs}, Drv, Ls, Encoding) -> send_drv_reqs(Drv, Rs), send_drv(Drv, beep), get_line1(edlin:edit_line(Cs, Cont), Drv, Ls, Encoding); +%% The search item was found and accepted (new line entered on the exact +%% result found) +get_line1({_What,Cont={line,_Prompt,_Chars,search_found},Rs}, Drv, Ls0, Encoding) -> + Line = edlin:current_line(Cont), + %% this may create duplicate entries. + Ls = save_line(new_stack(get_lines(Ls0)), Line), + get_line1({done, Line, "", Rs}, Drv, Ls, Encoding); +%% The search mode has been exited, but the user wants to remain in line +%% editing mode wherever that was, but editing the search result. +get_line1({What,Cont={line,_Prompt,_Chars,search_quit},Rs}, Drv, Ls, Encoding) -> + Line = edlin:current_chars(Cont), + %% Load back the old prompt with the correct line number. + case get(search_quit_prompt) of + undefined -> % should not happen. Fallback. + LsFallback = save_line(new_stack(get_lines(Ls)), Line), + get_line1({done, "\n", Line, Rs}, Drv, LsFallback, Encoding); + Prompt -> % redraw the line and keep going with the same stack position + NCont = {line,Prompt,{lists:reverse(Line),[]},none}, + send_drv_reqs(Drv, Rs), + send_drv_reqs(Drv, edlin:erase_line(Cont)), + send_drv_reqs(Drv, edlin:redraw_line(NCont)), + get_line1({What, NCont ,[]}, Drv, pad_stack(Ls), Encoding) + end; +%% Search mode is entered. +get_line1({What,{line,Prompt,{RevCmd0,_Aft},search},Rs}, + Drv, Ls0, Encoding) -> + send_drv_reqs(Drv, Rs), + %% Figure out search direction. ^S and ^R are returned through edlin + %% whenever we received a search while being already in search mode. + {Search, Ls1, RevCmd} = case RevCmd0 of + [$\^S|RevCmd1] -> + {fun search_down_stack/2, Ls0, RevCmd1}; + [$\^R|RevCmd1] -> + {fun search_up_stack/2, Ls0, RevCmd1}; + _ -> % new search, rewind stack for a proper search. + {fun search_up_stack/2, new_stack(get_lines(Ls0)), RevCmd0} + end, + Cmd = lists:reverse(RevCmd), + {Ls, NewStack} = case Search(Ls1, Cmd) of + {none, Ls2} -> + send_drv(Drv, beep), + {Ls2, {RevCmd, "': "}}; + {Line, Ls2} -> % found. Complete the output edlin couldn't have done. + send_drv_reqs(Drv, [{put_chars, Encoding, Line}]), + {Ls2, {RevCmd, "': "++Line}} + end, + Cont = {line,Prompt,NewStack,search}, + more_data(What, Cont, Drv, Ls, Encoding); get_line1({What,Cont0,Rs}, Drv, Ls, Encoding) -> send_drv_reqs(Drv, Rs), + more_data(What, Cont0, Drv, Ls, Encoding). + +more_data(What, Cont0, Drv, Ls, Encoding) -> receive {Drv,{data,Cs}} -> get_line1(edlin:edit_line(Cs, Cont0), Drv, Ls, Encoding); @@ -557,7 +629,6 @@ get_line1({What,Cont0,Rs}, Drv, Ls, Encoding) -> get_line1(edlin:edit_line([], Cont0), Drv, Ls, Encoding) end. - get_line_echo_off(Chars, Pbs, Drv) -> send_drv_reqs(Drv, [{put_chars, unicode,Pbs}]), get_line_echo_off1(edit_line(Chars,[]), Drv). @@ -632,12 +703,46 @@ save_line({stack, U, {}, []}, Line) -> save_line({stack, U, _L, D}, Line) -> {stack, U, Line, D}. -get_lines({stack, U, {}, []}) -> +get_lines(Ls) -> get_all_lines(Ls). +%get_lines({stack, U, {}, []}) -> +% U; +%get_lines({stack, U, {}, D}) -> +% tl(lists:reverse(D, U)); +%get_lines({stack, U, L, D}) -> +% get_lines({stack, U, {}, [L|D]}). + +%% There's a funny behaviour whenever the line stack doesn't have a "\n" +%% at its end -- get_lines() seemed to work on the assumption it *will* be +%% there, but the manipulations done with search history do not require it. +%% +%% It is an assumption because the function was built with either the full +%% stack being on the 'Up' side (we're on the new line) where it isn't +%% stripped. The only other case when it isn't on the 'Up' side is when +%% someone has used the up/down arrows (or ^P and ^N) to navigate lines, +%% in which case, a line with only a \n is stored at the end of the stack +%% (the \n is returned by edlin:current_line/1). +%% +%% get_all_lines works the same as get_lines, but only strips the trailing +%% character if it's a linebreak. Otherwise it's kept the same. This is +%% because traversing the stack due to search history will *not* insert +%% said empty line in the stack at the same time as other commands do, +%% and thus it should not always be stripped unless we know a new line +%% is the last entry. +get_all_lines({stack, U, {}, []}) -> U; -get_lines({stack, U, {}, D}) -> - tl(lists:reverse(D, U)); -get_lines({stack, U, L, D}) -> - get_lines({stack, U, {}, [L|D]}). +get_all_lines({stack, U, {}, D}) -> + case lists:reverse(D, U) of + ["\n"|Lines] -> Lines; + Lines -> Lines + end; +get_all_lines({stack, U, L, D}) -> + get_all_lines({stack, U, {}, [L|D]}). + +%% For the same reason as above, though, we need to expand the stack +%% in some cases to make sure we play nice with up/down arrows. We need +%% to insert newlines, but not always. +pad_stack({stack, U, L, D}) -> + {stack, U, L, D++["\n"]}. save_line_buffer("\n", Lines) -> save_line_buffer(Lines); @@ -649,6 +754,27 @@ save_line_buffer(Line, Lines) -> save_line_buffer(Lines) -> put(line_buffer, Lines). +search_up_stack(Stack, Substr) -> + case up_stack(Stack) of + {none,NewStack} -> {none,NewStack}; + {L, NewStack} -> + case string:str(L, Substr) of + 0 -> search_up_stack(NewStack, Substr); + _ -> {string:strip(L,right,$\n), NewStack} + end + end. + +search_down_stack(Stack, Substr) -> + case down_stack(Stack) of + {none,NewStack} -> {none,NewStack}; + {L, NewStack} -> + case string:str(L, Substr) of + 0 -> search_down_stack(NewStack, Substr); + _ -> {string:strip(L,right,$\n), NewStack} + end + end. + + %% This is get_line without line editing (except for backspace) and %% without echo. get_password_line(Chars, Drv) -> @@ -687,7 +813,7 @@ edit_password([$\177|Cs],[_|Chars]) ->%% is backspace enough? edit_password([Char|Cs],Chars) -> edit_password(Cs,[Char|Chars]). -%% prompt_bytes(Prompt) +%% prompt_bytes(Prompt, Encoding) %% Return a flat list of characters for the Prompt. prompt_bytes(Prompt, Encoding) -> lists:flatten(io_lib:format_prompt(Prompt, Encoding)). diff --git a/lib/kernel/test/file_SUITE.erl b/lib/kernel/test/file_SUITE.erl index 914f0d6127..f34341f561 100644 --- a/lib/kernel/test/file_SUITE.erl +++ b/lib/kernel/test/file_SUITE.erl @@ -60,7 +60,8 @@ -export([ read_not_really_compressed/1, read_compressed_cooked/1, read_compressed_cooked_binary/1, read_cooked_tar_problem/1, - write_compressed/1, compress_errors/1, catenated_gzips/1]). + write_compressed/1, compress_errors/1, catenated_gzips/1, + compress_async_crash/1]). -export([ make_link/1, read_link_info_for_non_link/1, symlinks/1]). @@ -135,7 +136,8 @@ groups() -> {compression, [], [read_compressed_cooked, read_compressed_cooked_binary, read_cooked_tar_problem, read_not_really_compressed, - write_compressed, compress_errors, catenated_gzips]}, + write_compressed, compress_errors, catenated_gzips, + compress_async_crash]}, {links, [], [make_link, read_link_info_for_non_link, symlinks]}]. @@ -2312,6 +2314,57 @@ compress_errors(Config) when is_list(Config) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +compress_async_crash(suite) -> []; +compress_async_crash(doc) -> []; +compress_async_crash(Config) when is_list(Config) -> + ?line DataDir = ?config(data_dir, Config), + ?line Path = filename:join(DataDir, "test.gz"), + ExpectedData = <<"qwerty">>, + + ?line _ = ?FILE_MODULE:delete(Path), + ?line {ok, Fd} = ?FILE_MODULE:open(Path, [write, binary, compressed]), + ?line ok = ?FILE_MODULE:write(Fd, ExpectedData), + ?line ok = ?FILE_MODULE:close(Fd), + + % Test that when using async thread pool, the emulator doesn't crash + % when the efile port driver is stopped while a compressed file operation + % is in progress (being carried by an async thread). + ?line ok = compress_async_crash_loop(10000, Path, ExpectedData), + ?line ok = ?FILE_MODULE:delete(Path), + ok. + +compress_async_crash_loop(0, _Path, _ExpectedData) -> + ok; +compress_async_crash_loop(N, Path, ExpectedData) -> + Parent = self(), + {Pid, Ref} = spawn_monitor( + fun() -> + ?line {ok, Fd} = ?FILE_MODULE:open( + Path, [read, compressed, raw, binary]), + Len = byte_size(ExpectedData), + Parent ! {self(), continue}, + ?line {ok, ExpectedData} = ?FILE_MODULE:read(Fd, Len), + ?line ok = ?FILE_MODULE:close(Fd), + receive foobar -> ok end + end), + receive + {Pid, continue} -> + exit(Pid, shutdown), + receive + {'DOWN', Ref, _, _, Reason} -> + ?line shutdown = Reason + end; + {'DOWN', Ref, _, _, Reason2} -> + test_server:fail({worker_exited, Reason2}) + after 60000 -> + exit(Pid, shutdown), + erlang:demonitor(Ref, [flush]), + test_server:fail(worker_timeout) + end, + compress_async_crash_loop(N - 1, Path, ExpectedData). + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + altname(doc) -> "Test the file:altname/1 function"; altname(suite) -> diff --git a/lib/kernel/test/gen_tcp_misc_SUITE.erl b/lib/kernel/test/gen_tcp_misc_SUITE.erl index 93dc2a69d1..a72e76f813 100644 --- a/lib/kernel/test/gen_tcp_misc_SUITE.erl +++ b/lib/kernel/test/gen_tcp_misc_SUITE.erl @@ -42,11 +42,12 @@ killing_acceptor/1,killing_multi_acceptors/1,killing_multi_acceptors2/1, several_accepts_in_one_go/1, accept_system_limit/1, active_once_closed/1, send_timeout/1, send_timeout_active/1, - otp_7731/1, zombie_sockets/1, otp_7816/1, otp_8102/1, + otp_7731/1, zombie_sockets/1, otp_7816/1, otp_8102/1, wrapping_oct/1, otp_9389/1]). %% Internal exports. -export([sender/3, not_owner/1, passive_sockets_server/2, priority_server/1, + oct_acceptor/1, otp_7731_server/1, zombie_server/2, do_iter_max_socks/2]). init_per_testcase(_Func, Config) when is_list(Config) -> @@ -75,6 +76,7 @@ all() -> killing_acceptor, killing_multi_acceptors, killing_multi_acceptors2, several_accepts_in_one_go, accept_system_limit, active_once_closed, send_timeout, send_timeout_active, otp_7731, + wrapping_oct, zombie_sockets, otp_7816, otp_8102, otp_9389]. groups() -> @@ -2581,3 +2583,71 @@ otp_9389_loop(S, OrigLinkHdr, State) -> 3000 -> ?line error({timeout,header}) end. + +wrapping_oct(doc) -> + "Check that 64bit octet counters work."; +wrapping_oct(suite) -> + []; +wrapping_oct(Config) when is_list(Config) -> + Dog = test_server:timetrap(test_server:seconds(600)), + {ok,Sock} = gen_tcp:listen(0,[{active,false},{mode,binary}]), + {ok,Port} = inet:port(Sock), + spawn_link(?MODULE,oct_acceptor,[Sock]), + Res = oct_datapump(Port,16#1FFFFFFFF), + gen_tcp:close(Sock), + test_server:timetrap_cancel(Dog), + ok = Res, + ok. + +oct_datapump(Port,N) -> + {ok,Sock} = gen_tcp:connect("localhost",Port, + [{active,false},{mode,binary}]), + oct_pump(Sock,N,binary:copy(<<$a:8>>,100000),0). + +oct_pump(S,N,_,_) when N =< 0 -> + gen_tcp:close(S), + ok; +oct_pump(S,N,Bin,Last) -> + case gen_tcp:send(S,Bin) of + ok -> + {ok,Stat}=inet:getstat(S), + {_,R}=lists:keyfind(send_oct,1,Stat), + case (R < Last) of + true -> + io:format("ERROR (output) ~p < ~p~n",[R,Last]), + output_counter_error; + false -> + oct_pump(S,N-byte_size(Bin),Bin,R) + end; + _ -> + input_counter_error + end. + + +oct_acceptor(Sock) -> + {ok,Data} = gen_tcp:accept(Sock), + oct_aloop(Data,0,0). + +oct_aloop(S,X,Times) -> + case gen_tcp:recv(S,0) of + {ok,_} -> + {ok,Stat}=inet:getstat(S), + {_,R}=lists:keyfind(recv_oct,1,Stat), + case (R < X) of + true -> + io:format("ERROR ~p < ~p~n",[R,X]), + gen_tcp:close(S), + input_counter_error; + false -> + case Times rem 16#FFFFF of + 0 -> + io:format("Read: ~p~n",[R]); + _ -> + ok + end, + oct_aloop(S,R,Times+1) + end; + _ -> + gen_tcp:close(S), + closed + end. diff --git a/lib/megaco/src/flex/megaco_flex_scanner_drv.flex.src b/lib/megaco/src/flex/megaco_flex_scanner_drv.flex.src index b8146c345d..5faddb08c5 100644 --- a/lib/megaco/src/flex/megaco_flex_scanner_drv.flex.src +++ b/lib/megaco/src/flex/megaco_flex_scanner_drv.flex.src @@ -76,6 +76,7 @@ typedef struct { ErlDrvPort port; + ErlDrvTermData port_id; char* digit_map_name_ptr; int digit_map_name_len; char* digit_map_value_ptr; @@ -1497,6 +1498,7 @@ static ErlDrvData mfs_start(ErlDrvPort port, char *buf) DBG( ("mfs_start -> entry\n") ); dataP->port = port; + dataP->port_id = driver_mk_port(port); dataP->digit_map_name_ptr = NULL; dataP->digit_map_name_len = 0; dataP->digit_map_value_ptr = NULL; @@ -1841,10 +1843,10 @@ static ErlDrvSSizeT mfs_control(ErlDrvData handle, "\n term_spec_size: %d\n", dataP->term_spec_index, dataP->term_spec_size) ); - driver_send_term(dataP->port, - driver_caller(dataP->port), - dataP->term_spec, - dataP->term_spec_index); + erl_drv_send_term(dataP->port_id, + driver_caller(dataP->port), + dataP->term_spec, + dataP->term_spec_index); if (dataP->text_buf != NULL) FREE(dataP->text_buf); if (dataP->term_spec != NULL) FREE(dataP->term_spec); diff --git a/lib/public_key/vsn.mk b/lib/public_key/vsn.mk index b8af89d040..bd20a5546b 100644 --- a/lib/public_key/vsn.mk +++ b/lib/public_key/vsn.mk @@ -1 +1 @@ -PUBLIC_KEY_VSN = 0.17 +PUBLIC_KEY_VSN = 0.18 diff --git a/lib/ssh/src/ssh.appup.src b/lib/ssh/src/ssh.appup.src index 826a11f1f4..cbd8166bb9 100644 --- a/lib/ssh/src/ssh.appup.src +++ b/lib/ssh/src/ssh.appup.src @@ -19,12 +19,14 @@ {"%VSN%", [ + {<<"2.1.2">>, [{restart_application, ssh}]}, {<<"2.1.1">>, [{restart_application, ssh}]}, {<<"2.1">>, [{restart_application, ssh}]}, {<<"2.0\\.*">>, [{restart_application, ssh}]}, {<<"1\\.*">>, [{restart_application, ssh}]} ], [ + {<<"2.1.2">>, [{restart_application, ssh}]}, {<<"2.1.1">>, [{restart_application, ssh}]}, {<<"2.1">>,[{restart_application, ssh}]}, {<<"2.0\\.*">>, [{restart_application, ssh}]}, diff --git a/lib/ssh/src/ssh.erl b/lib/ssh/src/ssh.erl index b5a0aa2e05..193f877b98 100644 --- a/lib/ssh/src/ssh.erl +++ b/lib/ssh/src/ssh.erl @@ -31,11 +31,6 @@ stop_listener/1, stop_listener/2, stop_daemon/1, stop_daemon/2, shell/1, shell/2, shell/3]). --deprecated({sign_data, 2, next_major_release}). --deprecated({verify_data, 3, next_major_release}). - --export([sign_data/2, verify_data/3]). - %%-------------------------------------------------------------------- %% Function: start([, Type]) -> ok %% @@ -394,8 +389,8 @@ handle_ssh_option({public_key_alg, Value} = Opt) when Value == 'ssh-rsa'; Value Opt; handle_ssh_option({pref_public_key_algs, Value} = Opt) when is_list(Value), length(Value) >= 1 -> case handle_pref_algs(Value, []) of - true -> - Opt; + {true, NewOpts} -> + NewOpts; _ -> throw({error, {eoptions, Opt}}) end; @@ -503,38 +498,3 @@ inetopt(false) -> %%% %% Deprecated %%% - -%%-------------------------------------------------------------------- -%% Function: sign_data(Data, Algorithm) -> binary() | -%% {error, Reason} -%% -%% Data = binary() -%% Algorithm = "ssh-rsa" -%% -%% Description: Use SSH key to sign data. -%%-------------------------------------------------------------------- -sign_data(Data, Algorithm) when is_binary(Data) -> - case ssh_file:user_key(Algorithm,[]) of - {ok, Key} when Algorithm == "ssh-rsa" -> - public_key:sign(Data, sha, Key); - Error -> - Error - end. - -%%-------------------------------------------------------------------- -%% Function: verify_data(Data, Signature, Algorithm) -> ok | -%% {error, Reason} -%% -%% Data = binary() -%% Signature = binary() -%% Algorithm = "ssh-rsa" -%% -%% Description: Use SSH signature to verify data. -%%-------------------------------------------------------------------- -verify_data(Data, Signature, Algorithm) when is_binary(Data), is_binary(Signature) -> - case ssh_file:user_key(Algorithm, []) of - {ok, #'RSAPrivateKey'{publicExponent = E, modulus = N}} when Algorithm == "ssh-rsa" -> - public_key:verify(Data, sha, Signature, #'RSAPublicKey'{publicExponent = E, modulus = N}); - Error -> - Error - end. diff --git a/lib/ssh/src/ssh_client_key_api.erl b/lib/ssh/src/ssh_client_key_api.erl index eed0b85f47..58054a9fc5 100644 --- a/lib/ssh/src/ssh_client_key_api.erl +++ b/lib/ssh/src/ssh_client_key_api.erl @@ -26,7 +26,7 @@ Algorithm :: 'ssh-rsa'| 'ssh-dss'| atom(), ConnectOptions :: proplists:proplist()) -> boolean(). --callback user_key(Algorithm :: 'ssh-rsa'| 'ssh-dss'| atom(), ConnectOptions :: proplists:proplists()) -> +-callback user_key(Algorithm :: 'ssh-rsa'| 'ssh-dss'| atom(), ConnectOptions :: proplists:proplist()) -> {ok, PrivateKey :: #'RSAPrivateKey'{}| #'DSAPrivateKey'{} | term()} | {error, string()}. diff --git a/lib/ssh/vsn.mk b/lib/ssh/vsn.mk index 921ec2206a..71666a3179 100644 --- a/lib/ssh/vsn.mk +++ b/lib/ssh/vsn.mk @@ -1,5 +1,5 @@ #-*-makefile-*- ; force emacs to enter makefile-mode -SSH_VSN = 2.1.2 +SSH_VSN = 2.1.3 APP_VSN = "ssh-$(SSH_VSN)" diff --git a/lib/stdlib/src/edlin.erl b/lib/stdlib/src/edlin.erl index 1164ee49eb..3192879f09 100644 --- a/lib/stdlib/src/edlin.erl +++ b/lib/stdlib/src/edlin.erl @@ -22,10 +22,10 @@ %% A simple Emacs-like line editor. %% About Latin-1 characters: see the beginning of erl_scan.erl. --export([init/0,start/1,edit_line/2,prefix_arg/1]). +-export([init/0,start/1,start/2,edit_line/2,prefix_arg/1]). -export([erase_line/1,erase_inp/1,redraw_line/1]). -export([length_before/1,length_after/1,prompt/1]). --export([current_line/1]). +-export([current_line/1, current_chars/1]). %%-export([expand/1]). -export([edit_line1/2]). @@ -54,7 +54,12 @@ init() -> %% {undefined,Char,Rest,Cont,Requests} start(Pbs) -> - {more_chars,{line,Pbs,{[],[]},none},[{put_chars,unicode,Pbs}]}. + start(Pbs, none). + +%% Only two modes used: 'none' and 'search'. Other modes can be +%% handled inline through specific character handling. +start(Pbs, Mode) -> + {more_chars,{line,Pbs,{[],[]},Mode},[{put_chars,unicode,Pbs}]}. edit_line(Cs, {line,P,L,{blink,N}}) -> edit(Cs, P, L, none, [{move_rel,N}]); @@ -76,6 +81,10 @@ edit([C|Cs], P, {Bef,Aft}, Prefix, Rs0) -> edit(Cs, P, {Bef,Aft}, meta, Rs0); meta_left_sq_bracket -> edit(Cs, P, {Bef,Aft}, meta_left_sq_bracket, Rs0); + search_meta -> + edit(Cs, P, {Bef,Aft}, search_meta, Rs0); + search_meta_left_sq_bracket -> + edit(Cs, P, {Bef,Aft}, search_meta_left_sq_bracket, Rs0); ctlx -> edit(Cs, P, {Bef,Aft}, ctlx, Rs0); new_line -> @@ -115,6 +124,8 @@ edit([C|Cs], P, {Bef,Aft}, Prefix, Rs0) -> case do_op(Op, Bef, Aft, Rs0) of {blink,N,Line,Rs} -> edit(Cs, P, Line, {blink,N}, Rs); + {Line, Rs, Mode} -> % allow custom modes from do_op + edit(Cs, P, Line, Mode, Rs); {Line,Rs} -> edit(Cs, P, Line, none, Rs) end @@ -168,9 +179,15 @@ key_map($\^], none) -> auto_blink; key_map($\^X, none) -> ctlx; key_map($\^Y, none) -> yank; key_map($\e, none) -> meta; -key_map($), Prefix) when Prefix =/= meta -> {blink,$),$(}; -key_map($}, Prefix) when Prefix =/= meta -> {blink,$},${}; -key_map($], Prefix) when Prefix =/= meta -> {blink,$],$[}; +key_map($), Prefix) when Prefix =/= meta, + Prefix =/= search, + Prefix =/= search_meta -> {blink,$),$(}; +key_map($}, Prefix) when Prefix =/= meta, + Prefix =/= search, + Prefix =/= search_meta -> {blink,$},${}; +key_map($], Prefix) when Prefix =/= meta, + Prefix =/= search, + Prefix =/= search_meta -> {blink,$],$[}; key_map($B, meta) -> backward_word; key_map($D, meta) -> kill_word; key_map($F, meta) -> forward_word; @@ -188,6 +205,32 @@ key_map($D, meta_left_sq_bracket) -> backward_char; key_map($C, meta_left_sq_bracket) -> forward_char; key_map(C, none) when C >= $\s -> {insert,C}; +%% for search, we need smarter line handling and so +%% we cheat a bit on the dispatching, and allow to +%% return a mode. +key_map($\^H, search) -> {search, backward_delete_char}; +key_map($\177, search) -> {search, backward_delete_char}; +key_map($\^R, search) -> {search, skip_up}; +key_map($\^S, search) -> {search, skip_down}; +key_map($\n, search) -> {search, search_found}; +key_map($\r, search) -> {search, search_found}; +key_map($\^A, search) -> {search, search_quit}; +key_map($\^B, search) -> {search, search_quit}; +key_map($\^D, search) -> {search, search_quit}; +key_map($\^E, search) -> {search, search_quit}; +key_map($\^F, search) -> {search, search_quit}; +key_map($\t, search) -> {search, search_quit}; +key_map($\^L, search) -> {search, search_quit}; +key_map($\^T, search) -> {search, search_quit}; +key_map($\^U, search) -> {search, search_quit}; +key_map($\^], search) -> {search, search_quit}; +key_map($\^X, search) -> {search, search_quit}; +key_map($\^Y, search) -> {search, search_quit}; +key_map($\e, search) -> search_meta; +key_map($[, search_meta) -> search_meta_left_sq_bracket; +key_map(_, search_meta) -> {search, search_quit}; +key_map(_C, search_meta_left_sq_bracket) -> {search, search_quit}; +key_map(C, search) -> {insert_search,C}; key_map(C, _) -> {undefined,C}. %% do_op(Action, Before, After, Requests) @@ -196,6 +239,57 @@ do_op({insert,C}, Bef, [], Rs) -> {{[C|Bef],[]},[{put_chars, unicode,[C]}|Rs]}; do_op({insert,C}, Bef, Aft, Rs) -> {{[C|Bef],Aft},[{insert_chars, unicode, [C]}|Rs]}; +%% Search mode prompt always looks like (search)`$TERMS': $RESULT. +%% the {insert_search, _} handlings allow to share this implementation +%% correctly with group.erl. This module provides $TERMS, and group.erl +%% is in charge of providing $RESULT. +%% This require a bit of trickery. Because search disables moving around +%% on the line (left/right arrow keys and other shortcuts that just exit +%% search mode), we can use the Bef and Aft variables to hold each +%% part of the line. Bef takes charge of "(search)`$TERMS" and Aft +%% takes charge of "': $RESULT". +do_op({insert_search, C}, Bef, [], Rs) -> + Aft="': ", + {{[C|Bef],Aft}, + [{insert_chars, unicode, [C]++Aft}, {delete_chars,-3} | Rs], + search}; +do_op({insert_search, C}, Bef, Aft, Rs) -> + Offset= length(Aft), + NAft = "': ", + {{[C|Bef],NAft}, + [{insert_chars, unicode, [C]++NAft}, {delete_chars,-Offset} | Rs], + search}; +do_op({search, backward_delete_char}, [_|Bef], Aft, Rs) -> + Offset= length(Aft)+1, + NAft = "': ", + {{Bef,NAft}, + [{insert_chars, unicode, NAft}, {delete_chars,-Offset}|Rs], + search}; +do_op({search, backward_delete_char}, [], _Aft, Rs) -> + Aft="': ", + {{[],Aft}, Rs, search}; +do_op({search, skip_up}, Bef, Aft, Rs) -> + Offset= length(Aft), + NAft = "': ", + {{[$\^R|Bef],NAft}, % we insert ^R as a flag to whoever called us + [{insert_chars, unicode, NAft}, {delete_chars,-Offset}|Rs], + search}; +do_op({search, skip_down}, Bef, Aft, Rs) -> + Offset= length(Aft), + NAft = "': ", + {{[$\^S|Bef],NAft}, % we insert ^S as a flag to whoever called us + [{insert_chars, unicode, NAft}, {delete_chars,-Offset}|Rs], + search}; +do_op({search, search_found}, _Bef, Aft, Rs) -> + "': "++NAft = Aft, + {{[],NAft}, + [{put_chars, unicode, "\n"}, {move_rel,-length(Aft)} | Rs], + search_found}; +do_op({search, search_quit}, _Bef, Aft, Rs) -> + "': "++NAft = Aft, + {{[],NAft}, + [{put_chars, unicode, "\n"}, {move_rel,-length(Aft)} | Rs], + search_quit}; %% do blink after $$ do_op({blink,C,M}, Bef=[$$,$$|_], Aft, Rs) -> N = over_paren(Bef, C, M), @@ -453,6 +547,9 @@ prompt({line,Pbs,_,_}) -> current_line({line,_,{Bef, Aft},_}) -> reverse(Bef, Aft ++ "\n"). +current_chars({line,_,{Bef,Aft},_}) -> + reverse(Bef, Aft). + %% %% expand(CurrentBefore) -> %% %% {yes,Expansion} | no %% %% Try to expand the word before as either a module name or a function diff --git a/lib/tools/test/cprof_SUITE.erl b/lib/tools/test/cprof_SUITE.erl index 93caee0c8f..ce5cf66a14 100644 --- a/lib/tools/test/cprof_SUITE.erl +++ b/lib/tools/test/cprof_SUITE.erl @@ -230,10 +230,10 @@ on_load_test(Config) -> %% ?line N4 = cprof:restart(), ?line {ok,Module} = c:c(File, [{outdir,Priv}]), - ?line L = Module:seq(1, M, fun (I) -> succ(I) end), - ?line Lr = Module:seq_r(1, M, fun (I) -> succ(I) end), - ?line L = seq(1, M, fun (I) -> succ(I) end), - ?line Lr = seq_r(1, M, fun (I) -> succ(I) end), + ?line L = Module:seq(1, M, fun succ/1), + ?line Lr = Module:seq_r(1, M, fun succ/1), + ?line L = seq(1, M, fun succ/1), + ?line Lr = seq_r(1, M, fun succ/1), ?line N2 = cprof:pause(), ?line {Module,0,[]} = cprof:analyse(Module), ?line M_1 = M - 1, @@ -265,10 +265,10 @@ modules_test(Config) -> ?line M2__1 = M2 + 1, ?line erlang:yield(), ?line N = cprof:start(), - ?line L = Module:seq(1, M, fun (I) -> succ(I) end), - ?line Lr = Module:seq_r(1, M, fun (I) -> succ(I) end), - ?line L = seq(1, M, fun (I) -> succ(I) end), - ?line Lr = seq_r(1, M, fun (I) -> succ(I) end), + ?line L = Module:seq(1, M, fun succ/1), + ?line Lr = Module:seq_r(1, M, fun succ/1), + ?line L = seq(1, M, fun succ/1), + ?line Lr = seq_r(1, M, fun succ/1), ?line N = cprof:pause(), ?line Lr = lists:reverse(L), ?line M_1 = M - 1, |