Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:24
erlang
2251-Remove-undocumented-value-Value-Ann-in-erl...
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 2251-Remove-undocumented-value-Value-Ann-in-erl_eval.patch of Package erlang
From 223913f95592cb72f090b892107b8e5e7e4a8f97 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= <jose.valim@dashbit.co> Date: Tue, 7 Dec 2021 12:34:30 +0100 Subject: [PATCH] Remove undocumented {value, Value, Ann} in erl_eval The shell relies on an implicit contract with erl_eval where value triplet is allowed. Unfortunately, to support this, evaluating anonymous functions would require a look-ahead traversal to hide any value triplet from erl_lint and this affected performance negatively. This patch removes this undocumented contract and removes the lookahead. To address this, we took different approaches: 1. v(N) was expanded to a value before evaluated. Now, we process and validate the arguments, but communicate with the shell process to get the value, similar to how history() works 2. References, Ports, and PIDs were converted to variables and then replaced to values. Now, we expand `#PID<0.13.0>` into an expression such as `erlang:list_to_pid("#PID<0.13.0>").` 3. Finally, the prompt evaluation would use values, but it only had to pass `[{history,integer()}]`, which can be manually converted to AST With this change, evaluating anonymous functions in a loop gets considerably faster, up to 10% in a macro benchmark. --- lib/debugger/src/dbg_icmd.erl | 32 ++---- lib/stdlib/src/erl_eval.erl | 200 ++++++++++++++-------------------- lib/stdlib/src/qlc.erl | 21 ++-- lib/stdlib/src/shell.erl | 23 ++-- lib/stdlib/test/qlc_SUITE.erl | 40 +++---- 5 files changed, 129 insertions(+), 187 deletions(-) diff --git a/lib/debugger/src/dbg_icmd.erl b/lib/debugger/src/dbg_icmd.erl index 0eb258567f..8d10fdb2c7 100644 --- a/lib/debugger/src/dbg_icmd.erl +++ b/lib/debugger/src/dbg_icmd.erl @@ -382,19 +382,14 @@ eval_restricted({From,_Mod,Cmd,SP}, Bs) -> case catch parse_cmd(Cmd, 1) of {'EXIT', _Reason} -> From ! {self(), {eval_rsp, 'Parse error'}}; - {[{var,_,Var}], XBs} -> + [{var,_,Var}] -> Bs2 = bindings(Bs, SP), Res = case get_binding(Var, Bs2) of {value, Value} -> Value; - unbound -> - case get_binding(Var, XBs) of - {value, _} -> - 'Only possible to inspect variables'; - unbound -> unbound - end + unbound -> unbound end, From ! {self(), {eval_rsp, Res}}; - {_Forms, _XBs} -> + _Forms -> Rsp = 'Only possible to inspect variables', From ! {self(), {eval_rsp, Rsp}} end. @@ -409,18 +404,17 @@ eval_nonrestricted({From, _Mod, Cmd, _SP}, Bs, {'EXIT', _Reason} -> From ! {self(), {eval_rsp, 'Parse error'}}, Bs; - {Forms, XBs} -> + Forms -> mark_running(Line, Le), - Bs1 = merge_bindings(Bs, XBs), - {Res, Bs2} = + {Res, Bs1} = lists:foldl(fun(Expr, {_Res, Bs0}) -> eval_nonrestricted_1(Expr,Bs0,Ieval) end, - {null, Bs1}, + {null, Bs}, Forms), mark_break(M, Line, Le), From ! {self(), {eval_rsp, Res}}, - remove_binding_structs(Bs2, XBs) + Bs1 end. eval_nonrestricted_1({match,_,{var,_,Var},Expr}, Bs, Ieval) -> @@ -445,14 +439,6 @@ eval_expr(Expr, Bs, Ieval) -> dbg_ieval:eval_expr(Expr, Bs, Ieval#ieval{top=false}), {Res,Bs2}. -%% XBs have unique keys. -merge_bindings(Bs1, XBs) -> - Bs1 ++ erl_eval:bindings(XBs). - -remove_binding_structs(Bs1, XBs) -> - lists:foldl(fun({N, _V}, Bs) -> lists:keydelete(N, 1, Bs) - end, Bs1, erl_eval:bindings(XBs)). - mark_running(LineNo, Le) -> put(next_break, running), put(user_eval, [{LineNo, Le} | get(user_eval)]), @@ -467,8 +453,8 @@ mark_break(Cm, LineNo, Le) -> parse_cmd(Cmd, LineNo) -> {ok,Tokens,_} = erl_scan:string(Cmd, LineNo, [text]), - {ok,Forms,Bs} = erl_eval:extended_parse_exprs(Tokens), - {Forms, Bs}. + {ok,Forms} = erl_eval:extended_parse_exprs(Tokens), + Forms. %%==================================================================== %% Library functions for attached process handling diff --git a/lib/stdlib/src/erl_eval.erl b/lib/stdlib/src/erl_eval.erl index dcd5e61fbd..bcb271b1b5 100644 --- a/lib/stdlib/src/erl_eval.erl +++ b/lib/stdlib/src/erl_eval.erl @@ -24,8 +24,7 @@ -export([exprs/2,exprs/3,exprs/4,expr/2,expr/3,expr/4,expr/5, expr_list/2,expr_list/3,expr_list/4]). -export([new_bindings/0,bindings/1,binding/2,add_binding/3,del_binding/2]). --export([extended_parse_exprs/1, extended_parse_term/1, - subst_values_for_vars/2]). +-export([extended_parse_exprs/1, extended_parse_term/1]). -export([is_constant_expr/1, partial_eval/1, eval_str/1]). %% Is used by standalone Erlang (escript). @@ -284,10 +283,7 @@ expr({'fun',_Anno,{function,Name,Arity}}, _Bs0, _Lf, _Ef, _RBs) -> % R8 %% Don't know what to do... erlang:raise(error, undef, [{?MODULE,Name,Arity}|?STACKTRACE]); expr({'fun',Anno,{clauses,Cs}} = Ex, Bs, Lf, Ef, RBs) -> - %% Save only used variables in the function environment. - %% {value,L,V} are hidden while lint finds used variables. - {Ex1, _} = hide_calls(Ex, 0), - {ok,Used} = erl_lint:used_vars([Ex1], bindings(Bs)), + {ok,Used} = erl_lint:used_vars([Ex], bindings(Bs)), En = filter_bindings(fun(K,_V) -> member(K,Used) end, Bs), Info = {En,Lf,Ef,Cs}, %% This is a really ugly hack! @@ -332,10 +328,7 @@ expr({'fun',Anno,{clauses,Cs}} = Ex, Bs, Lf, Ef, RBs) -> end, ret_expr(F, Bs, RBs); expr({named_fun,Anno,Name,Cs} = Ex, Bs, Lf, Ef, RBs) -> - %% Save only used variables in the function environment. - %% {value,L,V} are hidden while lint finds used variables. - {Ex1, _} = hide_calls(Ex, 0), - {ok,Used} = erl_lint:used_vars([Ex1], bindings(Bs)), + {ok,Used} = erl_lint:used_vars([Ex], bindings(Bs)), En = filter_bindings(fun(K,_V) -> member(K,Used) end, Bs), Info = {En,Lf,Ef,Cs,Name}, %% This is a really ugly hack! @@ -508,10 +501,7 @@ hide_calls(LC, MaxLine) -> {NLC, _, D} = hide(LC, LineId0, maps:new()), {NLC, D}. -%% v/1 and local calls are hidden. -hide({value,L,V}, Id, D) -> - A = erl_anno:new(Id), - {{atom,A,ok}, Id+1, maps:put(Id, {value,L,V}, D)}; +%% Local calls are hidden from qlc so they are not expanded. hide({call,A,{atom,_,N}=Atom,Args}, Id0, D0) -> {NArgs, Id, D} = hide(Args, Id0, D0), C = case erl_internal:bif(N, length(Args)) of @@ -532,14 +522,6 @@ hide([E0 | Es0], Id0, D0) -> hide(E, Id, D) -> {E, Id, D}. -unhide_calls({atom,A,ok}=E, MaxLine, D) -> - L = erl_anno:line(A), - if - L > MaxLine -> - map_get(L, D); - true -> - E - end; unhide_calls({call,Anno,{remote,A,{atom,A,m},{atom,A,f}}=F,Args}, MaxLine, D) -> Line = erl_anno:line(Anno), @@ -1323,28 +1305,6 @@ to_terms(Abstrs) -> to_term(Abstr) -> erl_parse:anno_to_term(Abstr). -%% Substitute {value, A, Item} for {var, A, Var}, preserving A. -%% {value, A, Item} is a shell/erl_eval convention, and for example -%% the linter cannot handle it. - --spec subst_values_for_vars(ExprList, Bindings) -> [term()] when - ExprList :: [erl_parse:abstract_expr()], - Bindings :: binding_struct(). - -subst_values_for_vars({var, A, V}=Var, Bs) -> - case erl_eval:binding(V, Bs) of - {value, Value} -> - {value, A, Value}; - unbound -> - Var - end; -subst_values_for_vars(L, Bs) when is_list(L) -> - [subst_values_for_vars(E, Bs) || E <- L]; -subst_values_for_vars(T, Bs) when is_tuple(T) -> - list_to_tuple(subst_values_for_vars(tuple_to_list(T), Bs)); -subst_values_for_vars(T, _Bs) -> - T. - %% `Tokens' is assumed to have been scanned with the 'text' option. %% The annotations of the returned expressions are locations. %% @@ -1353,18 +1313,17 @@ subst_values_for_vars(T, _Bs) -> %% the items themselves are stored in the returned bindings. -spec extended_parse_exprs(Tokens) -> - {'ok', ExprList, Bindings} | {'error', ErrorInfo} when + {'ok', ExprList} | {'error', ErrorInfo} when Tokens :: [erl_scan:token()], ExprList :: [erl_parse:abstract_expr()], - Bindings :: erl_eval:binding_struct(), ErrorInfo :: erl_parse:error_info(). extended_parse_exprs(Tokens) -> Ts = tokens_fixup(Tokens), case erl_parse:parse_exprs(Ts) of {ok, Exprs0} -> - {Exprs, Bs} = expr_fixup(Exprs0), - {ok, reset_expr_anno(Exprs), Bs}; + Exprs = expr_fixup(Exprs0), + {ok, reset_expr_anno(Exprs)}; _ErrorInfo -> erl_parse:parse_exprs(reset_token_anno(Ts)) end. @@ -1382,7 +1341,7 @@ tokens_fixup([T|Ts]=Ts0) -> token_fixup(Ts) -> {AnnoL, NewTs, FixupTag} = unscannable(Ts), String = lists:append([erl_anno:text(A) || A <- AnnoL]), - _ = (fixup_fun(FixupTag))(String), + _ = validate_tag(FixupTag, String), NewAnno = erl_anno:set_text(fixup_text(FixupTag), hd(AnnoL)), {{string, NewAnno, String}, NewTs}. @@ -1403,37 +1362,26 @@ unscannable([{'#', A1}, {var, A2, 'Ref'}, {'<', A3}, {float, A4, _}, {'.', A5}, {float, A6, _}, {'>', A7}|Ts]) -> {[A1, A2, A3, A4, A5, A6, A7], Ts, reference}. -expr_fixup(Expr0) -> - {Expr, Bs, _} = expr_fixup(Expr0, erl_eval:new_bindings(), 1), - {Expr, Bs}. - -expr_fixup({string,A,S}=T, Bs0, I) -> - try string_fixup(A, S) of - Value -> - Var = new_var(I), - Bs = erl_eval:add_binding(Var, Value, Bs0), - {{var, A, Var}, Bs, I+1} +expr_fixup({string,A,S}=T) -> + try string_fixup(A, S, T) of + Expr -> Expr catch - _:_ -> - {T, Bs0, I} + _:_ -> T end; -expr_fixup(Tuple, Bs0, I0) when is_tuple(Tuple) -> - {L, Bs, I} = expr_fixup(tuple_to_list(Tuple), Bs0, I0), - {list_to_tuple(L), Bs, I}; -expr_fixup([E0|Es0], Bs0, I0) -> - {E, Bs1, I1} = expr_fixup(E0, Bs0, I0), - {Es, Bs, I} = expr_fixup(Es0, Bs1, I1), - {[E|Es], Bs, I}; -expr_fixup(T, Bs, I) -> - {T, Bs, I}. - -string_fixup(A, S) -> - Text = erl_anno:text(A), - FixupTag = fixup_tag(Text, S), - (fixup_fun(FixupTag))(S). - -new_var(I) -> - list_to_atom(lists:concat(['__ExtendedParseExprs_', I, '__'])). +expr_fixup(Tuple) when is_tuple(Tuple) -> + L = expr_fixup(tuple_to_list(Tuple)), + list_to_tuple(L); +expr_fixup([E0|Es0]) -> + E = expr_fixup(E0), + Es = expr_fixup(Es0), + [E|Es]; +expr_fixup(T) -> + T. + +string_fixup(Ann, String, Token) -> + Text = erl_anno:text(Ann), + FixupTag = fixup_tag(Text, String), + fixup_ast(FixupTag, Ann, String, Token). reset_token_anno(Tokens) -> [setelement(2, T, (reset_anno())(element(2, T))) || T <- Tokens]. @@ -1444,18 +1392,15 @@ reset_expr_anno(Exprs) -> reset_anno() -> fun(A) -> erl_anno:new(erl_anno:location(A)) end. -fixup_fun(function) -> fun function/1; -fixup_fun(pid) -> fun erlang:list_to_pid/1; -fixup_fun(port) -> fun erlang:list_to_port/1; -fixup_fun(reference) -> fun erlang:list_to_ref/1. - -function(S) -> - %% External function. - {ok, [_, _, _, - {atom, _, Module}, _, - {atom, _, Function}, _, - {integer, _, Arity}|_], _} = erl_scan:string(S), - erlang:make_fun(Module, Function, Arity). +fixup_ast(pid, A, _S, T) -> + {call,A,{remote,A,{atom,A,erlang},{atom,A,list_to_pid}},[T]}; +fixup_ast(port, A, _S, T) -> + {call,A,{remote,A,{atom,A,erlang},{atom,A,list_to_port}},[T]}; +fixup_ast(reference, A, _S, T) -> + {call,A,{remote,A,{atom,A,erlang},{atom,A,list_to_ref}},[T]}; +fixup_ast(function, A, S, _T) -> + {Module, Function, Arity} = fixup_mfa(S), + {'fun',A,{function,{atom,A,Module},{atom,A,Function},{integer,A,Arity}}}. fixup_text(function) -> "function"; fixup_text(pid) -> "pid"; @@ -1467,6 +1412,20 @@ fixup_tag("pid", "<"++_) -> pid; fixup_tag("port", "#"++_) -> port; fixup_tag("reference", "#"++_) -> reference. +fixup_mfa(S) -> + {ok, [_, _, _, + {atom, _, Module}, _, + {atom, _, Function}, _, + {integer, _, Arity}|_], _} = erl_scan:string(S), + {Module, Function, Arity}. + +validate_tag(pid, String) -> erlang:list_to_pid(String); +validate_tag(port, String) -> erlang:list_to_port(String); +validate_tag(reference, String) -> erlang:list_to_ref(String); +validate_tag(function, String) -> + {Module, Function, Arity} = fixup_mfa(String), + erlang:make_fun(Module, Function, Arity). + %%% End of extended_parse_exprs. %% `Tokens' is assumed to have been scanned with the 'text' option. @@ -1481,8 +1440,8 @@ fixup_tag("reference", "#"++_) -> reference. extended_parse_term(Tokens) -> case extended_parse_exprs(Tokens) of - {ok, [Expr], Bindings} -> - try normalise(Expr, Bindings) of + {ok, [Expr]} -> + try normalise(Expr) of Term -> {ok, Term} catch @@ -1490,7 +1449,7 @@ extended_parse_term(Tokens) -> Loc = erl_anno:location(element(2, Expr)), {error,{Loc,?MODULE,"bad term"}} end; - {ok, [_,Expr|_], _Bindings} -> + {ok, [_,Expr|_]} -> Loc = erl_anno:location(element(2, Expr)), {error,{Loc,?MODULE,"bad term"}}; {error, _} = Error -> @@ -1498,46 +1457,47 @@ extended_parse_term(Tokens) -> end. %% From erl_parse. -normalise({var, _, V}, Bs) -> - {value, Value} = erl_eval:binding(V, Bs), - Value; -normalise({char,_,C}, _Bs) -> C; -normalise({integer,_,I}, _Bs) -> I; -normalise({float,_,F}, _Bs) -> F; -normalise({atom,_,A}, _Bs) -> A; -normalise({string,_,S}, _Bs) -> S; -normalise({nil,_}, _Bs) -> []; -normalise({bin,_,Fs}, Bs) -> +normalise({char,_,C}) -> C; +normalise({integer,_,I}) -> I; +normalise({float,_,F}) -> F; +normalise({atom,_,A}) -> A; +normalise({string,_,S}) -> S; +normalise({nil,_}) -> []; +normalise({bin,_,Fs}) -> {value, B, _} = eval_bits:expr_grp(Fs, [], fun(E, _) -> - {value, normalise(E, Bs), []} + {value, normalise(E), []} end, [], true), B; -normalise({cons,_,Head,Tail}, Bs) -> - [normalise(Head, Bs)|normalise(Tail, Bs)]; -normalise({tuple,_,Args}, Bs) -> - list_to_tuple(normalise_list(Args, Bs)); -normalise({map,_,Pairs}, Bs) -> +normalise({cons,_,Head,Tail}) -> + [normalise(Head)|normalise(Tail)]; +normalise({tuple,_,Args}) -> + list_to_tuple(normalise_list(Args)); +normalise({map,_,Pairs}) -> maps:from_list(lists:map(fun %% only allow '=>' ({map_field_assoc,_,K,V}) -> - {normalise(K, Bs),normalise(V, Bs)} + {normalise(K),normalise(V)} end, Pairs)); %% Special case for unary +/-. -normalise({op,_,'+',{char,_,I}}, _Bs) -> I; -normalise({op,_,'+',{integer,_,I}}, _Bs) -> I; -normalise({op,_,'+',{float,_,F}}, _Bs) -> F; -normalise({op,_,'-',{char,_,I}}, _Bs) -> -I; %Weird, but compatible! -normalise({op,_,'-',{integer,_,I}}, _Bs) -> -I; -normalise({op,_,'-',{float,_,F}}, _Bs) -> -F; -normalise({'fun',_,{function,{atom,_,M},{atom,_,F},{integer,_,A}}}, _Bs) -> +normalise({op,_,'+',{char,_,I}}) -> I; +normalise({op,_,'+',{integer,_,I}}) -> I; +normalise({op,_,'+',{float,_,F}}) -> F; +normalise({op,_,'-',{char,_,I}}) -> -I; %Weird, but compatible! +normalise({op,_,'-',{integer,_,I}}) -> -I; +normalise({op,_,'-',{float,_,F}}) -> -F; +%% Special case for #...<> +normalise({call,_,{remote,_,{atom,_,erlang},{atom,_,Fun}},[{string,_,S}]}) when + Fun =:= list_to_ref; Fun =:= list_to_port; Fun =:= list_to_pid -> + erlang:Fun(S); +normalise({'fun',_,{function,{atom,_,M},{atom,_,F},{integer,_,A}}}) -> %% Since "#Fun<M.F.A>" is recognized, "fun M:F/A" should be too. fun M:F/A. -normalise_list([H|T], Bs) -> - [normalise(H, Bs)|normalise_list(T, Bs)]; -normalise_list([], _Bs) -> +normalise_list([H|T]) -> + [normalise(H)|normalise_list(T)]; +normalise_list([]) -> []. %%---------------------------------------------------------------------------- diff --git a/lib/stdlib/src/qlc.erl b/lib/stdlib/src/qlc.erl index d0e416805f..e9d9c01b7d 100644 --- a/lib/stdlib/src/qlc.erl +++ b/lib/stdlib/src/qlc.erl @@ -652,21 +652,20 @@ string_to_handle(Str, Options, Bindings) when is_list(Str) -> {ok, Tokens, _} -> ScanRes = case erl_eval:extended_parse_exprs(Tokens) of - {ok, [Expr0], SBs} -> - {ok, Expr0, SBs}; - {ok, _ExprList, _SBs} -> + {ok, [Expr0]} -> + {ok, Expr0}; + {ok, _ExprList} -> erlang:error(badarg, [Str, Options, Bindings]); E -> E end, case ScanRes of - {ok, Expr, XBs} -> - Bs1 = merge_binding_structs(Bindings, XBs), - case qlc_pt:transform_expression(Expr, Bs1) of + {ok, Expr} -> + case qlc_pt:transform_expression(Expr, Bindings) of {ok, {call, _, _QlcQ, Handle}} -> {value, QLC_lc, _} = - erl_eval:exprs(Handle, Bs1), + erl_eval:exprs(Handle, Bindings), O = #qlc_opt{unique = Unique, cache = Cache, max_lookup = MaxLookup, @@ -792,10 +791,6 @@ all_selections([{I,Cs} | ICs]) -> %%% Local functions %%% -merge_binding_structs(Bs1, Bs2) -> - lists:foldl(fun({N, V}, Bs) -> erl_eval:add_binding(N, V, Bs) - end, Bs1, erl_eval:bindings(Bs2)). - aux_name1(Name, N, AllNames) -> SN = name_suffix(Name, N), case gb_sets:is_member(SN, AllNames) of @@ -1208,9 +1203,7 @@ abstract1({table, TableDesc}, _NElements, _Depth, _A) -> true -> {ok, Tokens, _} = erl_scan:string(lists:flatten(TableDesc++"."), 1, [text]), - {ok, Es, Bs} = - erl_eval:extended_parse_exprs(Tokens), - [Expr] = erl_eval:subst_values_for_vars(Es, Bs), + {ok, [Expr]} = erl_eval:extended_parse_exprs(Tokens), special(Expr); false -> % abstract expression TableDesc diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl index ac6c185860..2764de616e 100644 --- a/lib/stdlib/src/shell.erl +++ b/lib/stdlib/src/shell.erl @@ -228,10 +228,10 @@ server_loop(N0, Eval_0, Bs00, RT, Ds00, History0, Results0) -> N = N0 + 1, {Eval_1,Bs0,Ds0,Prompt} = prompt(N, Eval_0, Bs00, RT, Ds00), {Res,Eval0} = get_command(Prompt, Eval_1, Bs0, RT, Ds0), + case Res of - {ok,Es0,XBs} -> - Es1 = erl_eval:subst_values_for_vars(Es0, XBs), - case expand_hist(Es1, N) of + {ok,Es0} -> + case expand_hist(Es0, N) of {ok,Es} -> {V,Eval,Bs,Ds} = shell_cmd(Es, Eval0, Bs0, RT, Ds0, cmd), {History,Results} = check_and_get_history_and_results(), @@ -315,9 +315,9 @@ get_command1(Pid, Eval, Bs, RT, Ds) -> prompt(N, Eval0, Bs0, RT, Ds0) -> case get_prompt_func() of {M,F} -> - L = [{history,N}], A = erl_anno:new(1), - C = {call,A,{remote,A,{atom,A,M},{atom,A,F}},[{value,A,L}]}, + L = {cons,A,{tuple,A,[{atom,A,history},{integer,A,N}]},{nil,A}}, + C = {call,A,{remote,A,{atom,A,M},{atom,A,F}},[L]}, {V,Eval,Bs,Ds} = shell_cmd([C], Eval0, Bs0, RT, Ds0, pmt), {Eval,Bs,Ds,case V of {pmt,Val} -> @@ -414,12 +414,12 @@ expand_expr({call,A,{atom,_,e},[N]}, C) -> {Ces,_V,_CommandN} when is_list(Ces) -> {block,A,Ces} end; -expand_expr({call,_A,{atom,_,v},[N]}, C) -> +expand_expr({call,CA,{atom,VA,v},[N]}, C) -> case get_cmd(N, C) of {_,undefined,_} -> no_command(N); - {Ces,V,CommandN} when is_list(Ces) -> - {value,erl_anno:new(CommandN),V} + {Ces,_V,CommandN} when is_list(Ces) -> + {call,CA,{atom,VA,v},[{integer,VA,CommandN}]} end; expand_expr({call,A,F,Args}, C) -> {call,A,expand_expr(F, C),expand_exprs(Args, C)}; @@ -539,6 +539,9 @@ shell_rep(Ev, Bs0, RT, Ds0) -> fwrite_severity(benign, <<"~s: ~ts">>, [pos(Location), M:format_error(Error)]), {{'EXIT',Error},Ev,Bs0,Ds0}; + {shell_req,Ev,{get_cmd,N}} -> + Ev ! {shell_rep,self(),getc(N)}, + shell_rep(Ev, Bs0, RT, Ds0); {shell_req,Ev,get_cmd} -> Ev ! {shell_rep,self(),get()}, shell_rep(Ev, Bs0, RT, Ds0); @@ -956,6 +959,10 @@ init_dict([]) -> true. %% handled in this module (i.e. those that are not eventually handled by %% non_builtin_local_func/3 (user_default/shell_default). +local_func(v, [{integer,_,V}], Bs, Shell, _RT, _Lf, _Ef) -> + %% This command is validated and expanded prior. + {_Ces,Value,_N} = shell_req(Shell, {get_cmd, V}), + {value,Value,Bs}; local_func(h, [], Bs, Shell, RT, _Lf, _Ef) -> Cs = shell_req(Shell, get_cmd), Cs1 = lists:filter(fun({{command, _},_}) -> true; diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl index 3ab1c50332..416a12c211 100644 --- a/lib/stdlib/test/qlc_SUITE.erl +++ b/lib/stdlib/test/qlc_SUITE.erl @@ -7466,10 +7466,10 @@ etsc(F, Opts, Objs) -> V. join_info(H) -> - {{qlc, S, Options}, Bs} = strip_qlc_call2(H), + {qlc, S, Options} = strip_qlc_call(H), %% "Hide" the call to qlc_pt from the test in run_test(). LoadedPT = code:is_loaded(qlc_pt), - QH = qlc:string_to_handle(S, Options, Bs), + QH = qlc:string_to_handle(S, Options, []), _ = [unload_pt() || false <- [LoadedPT]], % doesn't take long... case {join_info_count(H), join_info_count(QH)} of {N, N} -> @@ -7479,26 +7479,22 @@ join_info(H) -> end. strip_qlc_call(H) -> - {Expr, _Bs} = strip_qlc_call2(H), - Expr. - -strip_qlc_call2(H) -> S = qlc:info(H, {flat, false}), {ok, Tokens, _EndLine} = erl_scan:string(S++".", 1, [text]), - {ok, [Expr], Bs} = erl_eval:extended_parse_exprs(Tokens), - {case Expr of - {call,_,{remote,_,{atom,_,qlc},{atom,_,q}},[LC]} -> - {qlc, lists:flatten([erl_pp:expr(LC), "."]), []}; - {call,_,{remote,_,{atom,_,qlc},{atom,_,q}},[LC, Opts]} -> - {qlc, lists:flatten([erl_pp:expr(LC), "."]), - erl_parse:normalise(Opts)}; - {call,_,{remote,_,{atom,_,ets},{atom,_,match_spec_run}},_} -> - {match_spec, Expr}; - {call,_,{remote,_,{atom,_,M},{atom,_,table}},_} -> - {table, M, Expr}; - _ -> - [] - end, Bs}. + {ok, [Expr]} = erl_eval:extended_parse_exprs(Tokens), + case Expr of + {call,_,{remote,_,{atom,_,qlc},{atom,_,q}},[LC]} -> + {qlc, lists:flatten([erl_pp:expr(LC), "."]), []}; + {call,_,{remote,_,{atom,_,qlc},{atom,_,q}},[LC, Opts]} -> + {qlc, lists:flatten([erl_pp:expr(LC), "."]), + erl_parse:normalise(Opts)}; + {call,_,{remote,_,{atom,_,ets},{atom,_,match_spec_run}},_} -> + {match_spec, Expr}; + {call,_,{remote,_,{atom,_,M},{atom,_,table}},_} -> + {table, M, Expr}; + _ -> + [] + end. -record(ji, {nmerge = 0, nlookup = 0, nnested_loop = 0, nkeysort = 0}). @@ -7506,7 +7502,7 @@ strip_qlc_call2(H) -> join_info_count(H) -> S = qlc:info(H, {flat, false}), {ok, Tokens, _EndLine} = erl_scan:string(S++".", 1, [text]), - {ok, [Expr], _Bs} = erl_eval:extended_parse_exprs(Tokens), + {ok, [Expr]} = erl_eval:extended_parse_exprs(Tokens), #ji{nmerge = Nmerge, nlookup = Nlookup, nkeysort = NKeysort, nnested_loop = Nnested_loop} = ji(Expr, #ji{}), @@ -7550,7 +7546,7 @@ lookup_keys({generate,_,Q}, L) -> lookup_keys(Q, L); lookup_keys({table,Chars}, L) when is_list(Chars) -> {ok, Tokens, _} = erl_scan:string(lists:flatten(Chars++"."), 1, [text]), - {ok, [Expr], _Bs} = erl_eval:extended_parse_exprs(Tokens), + {ok, [Expr]} = erl_eval:extended_parse_exprs(Tokens), case Expr of {call,_,_,[_fun,AKs]} -> case erl_parse:normalise(AKs) of -- 2.31.1
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor