diff options
author | Hans Bolinder <[email protected]> | 2017-04-28 09:26:52 +0200 |
---|---|---|
committer | Hans Bolinder <[email protected]> | 2017-04-28 09:26:52 +0200 |
commit | e984e201381e1c70679b628022a1218d5090ce55 (patch) | |
tree | 231a3bf46f34981f4dd44951169a6ac95c83ab53 /lib/stdlib/test | |
parent | b674f7b827dec8fd220b858fba1a7d093594cc0b (diff) | |
parent | ee2dde4f7f8508d58a9e1b16da66e26f99cf1cc0 (diff) | |
download | otp-e984e201381e1c70679b628022a1218d5090ce55.tar.gz otp-e984e201381e1c70679b628022a1218d5090ce55.tar.bz2 otp-e984e201381e1c70679b628022a1218d5090ce55.zip |
Merge branch 'hasse/stdlib/fix_qlc_bug/OTP-14296'
* hasse/stdlib/fix_qlc_bug/OTP-14296:
stdlib: Fix a test in sofs_SUITE
debugger: Improve handling of pids, ports, and refs
stdlib: Improve handling of pids, ports, and refs in qlc
stdlib: Improve the Erlang shell's handling of references
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r-- | lib/stdlib/test/qlc_SUITE.erl | 85 | ||||
-rw-r--r-- | lib/stdlib/test/shell_SUITE.erl | 93 | ||||
-rw-r--r-- | lib/stdlib/test/sofs_SUITE.erl | 4 |
3 files changed, 150 insertions, 32 deletions
diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl index 2b5d52287e..5e9e03e410 100644 --- a/lib/stdlib/test/qlc_SUITE.erl +++ b/lib/stdlib/test/qlc_SUITE.erl @@ -1240,6 +1240,17 @@ string_to_handle(Config) when is_list(Config) -> {'EXIT', {no_lookup_to_carry_out, _}} = (catch qlc:e(qlc:string_to_handle(Q, {lookup,true}, Bs2))), ets:delete(Ets), + + %% References can be scanned and parsed. + E2 = ets:new(test, [bag]), + Ref = make_ref(), + true = ets:insert(E2, [{Ref,Ref}]), + S2 = "[{Val1} || {Ref1, Val1} <- ets:table("++io_lib:write(E2)++")," + "Ref1 =:= Ref].", + Bs = erl_eval:add_binding('Ref', Ref, erl_eval:new_bindings()), + [{Ref}] = qlc:e(qlc:string_to_handle(S2, [], Bs)), + ets:delete(E2), + ok. %% table @@ -4321,7 +4332,18 @@ ets(Config) when is_list(Config) -> R = qlc:e(Q), ets:delete(E), [] = R">>] - end + end, + + <<"E2 = ets:new(test, [bag]), + Ref = make_ref(), + true = ets:insert(E2, [{Ref,Ref}]), + Q2 = qlc:q([{Val1} || + {Ref1, Val1} <- ets:table(E2), + Ref1 =:= Ref]), + S = qlc:info(Q2), + true = is_list(S), + [{Ref}] = qlc:e(Q2), + ets:delete(E2)">> ], @@ -7071,7 +7093,7 @@ otp_12946(Config) when is_list(Config) -> %% Examples from qlc(3). manpage(Config) when is_list(Config) -> - + dets:start(), ok = compile_gb_table(Config), Ts = [ @@ -7138,11 +7160,14 @@ manpage(Config) when is_list(Config) -> \" [{X,Z}|{W,Y}] <- V2\n\" \" ])\n\" \"end\", - Info = + Info1 = re:replace(qlc:info(Q), - \"table\\\\(-*[0-9]*\", + \"table\\\\(#Ref<[\\.0-9]*>\", \"table(_\", [{return,list},global]), - L = Info, + F = fun(C) -> C =/= $\n andalso C =/= $\s end, + Info = lists:filter(F, Info1), + L1 = lists:filter(F, L), + L1 = Info, ets:delete(E1), ets:delete(E2)">>, @@ -7445,10 +7470,10 @@ etsc(F, Opts, Objs) -> V. join_info(H) -> - {qlc, S, Options} = strip_qlc_call(H), + {{qlc, S, Options}, Bs} = strip_qlc_call2(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), + QH = qlc:string_to_handle(S, Options, Bs), _ = [unload_pt() || false <- [LoadedPT]], % doesn't take long... case {join_info_count(H), join_info_count(QH)} of {N, N} -> @@ -7458,30 +7483,34 @@ 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++"."), - {ok, [Expr]} = erl_parse: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. + {ok, Tokens, _EndLine} = erl_scan:string(S++".", 1, [text]), + {ok, [Expr], Bs} = lib: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}. -record(ji, {nmerge = 0, nlookup = 0, nnested_loop = 0, nkeysort = 0}). %% Counts join options and (all) calls to qlc:keysort(). join_info_count(H) -> S = qlc:info(H, {flat, false}), - {ok, Tokens, _EndLine} = erl_scan:string(S++"."), - {ok, [Expr]} = erl_parse:parse_exprs(Tokens), + {ok, Tokens, _EndLine} = erl_scan:string(S++".", 1, [text]), + {ok, [Expr], _Bs} = lib:extended_parse_exprs(Tokens), #ji{nmerge = Nmerge, nlookup = Nlookup, nkeysort = NKeysort, nnested_loop = Nnested_loop} = ji(Expr, #ji{}), @@ -7524,8 +7553,8 @@ lookup_keys({list,Q,_}, L) -> 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++".")), - {ok, [Expr]} = erl_parse:parse_exprs(Tokens), + {ok, Tokens, _} = erl_scan:string(lists:flatten(Chars++"."), 1, [text]), + {ok, [Expr], _Bs} = lib:extended_parse_exprs(Tokens), case Expr of {call,_,_,[_fun,AKs]} -> case erl_parse:normalise(AKs) of @@ -7842,7 +7871,7 @@ run_test(Config, Extra, {cres, Body, Opts, ExpectedCompileReturn}) -> {module, _} = code:load_abs(AbsFile, Mod), Ms0 = erlang:process_info(self(),messages), - Before = {{get(), ets:all(), Ms0}, pps()}, + Before = {{get(), lists:sort(ets:all()), Ms0}, pps()}, %% Prepare the check that the qlc module does not call qlc_pt. _ = [unload_pt() || {file, Name} <- [code:is_loaded(qlc_pt)], @@ -7874,7 +7903,7 @@ run_test(Config, Extra, Body) -> wait_for_expected(R, {Strict0,PPS0}=Before, SourceFile, Wait) -> Ms = erlang:process_info(self(),messages), - After = {_,PPS1} = {{get(), ets:all(), Ms}, pps()}, + After = {_,PPS1} = {{get(), lists:sort(ets:all()), Ms}, pps()}, case {R, After} of {ok, Before} -> ok; diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl index 56002dda25..99411bc8fd 100644 --- a/lib/stdlib/test/shell_SUITE.erl +++ b/lib/stdlib/test/shell_SUITE.erl @@ -31,7 +31,7 @@ progex_lc/1, progex_funs/1, otp_5990/1, otp_6166/1, otp_6554/1, otp_7184/1, otp_7232/1, otp_8393/1, otp_10302/1, otp_13719/1, - otp_14285/1]). + otp_14285/1, otp_14296/1]). -export([ start_restricted_from_shell/1, start_restricted_on_command_line/1,restricted_local/1]). @@ -92,7 +92,7 @@ groups() -> progex_funs]}, {tickets, [], [otp_5990, otp_6166, otp_6554, otp_7184, - otp_7232, otp_8393, otp_10302, otp_13719, otp_14285]}]. + otp_7232, otp_8393, otp_10302, otp_13719, otp_14285, otp_14296]}]. init_per_suite(Config) -> Config. @@ -2841,6 +2841,95 @@ otp_14285(Config) -> test_server:stop_node(Node), ok. +otp_14296(Config) when is_list(Config) -> + fun() -> + F = fun() -> a end, + LocalFun = term_to_string(F), + S = LocalFun ++ ".", + "1: syntax error before: Fun" = comm_err(S) + end(), + + fun() -> + F = fun mod:func/1, + ExternalFun = term_to_string(F), + S = ExternalFun ++ ".", + R = ExternalFun ++ ".\n", + R = t(S) + end(), + + fun() -> + UnknownPid = "<100000.0.0>", + S = UnknownPid ++ ".", + "1: syntax error before: '<'" = comm_err(S) + end(), + + fun() -> + KnownPid = term_to_string(self()), + S = KnownPid ++ ".", + R = KnownPid ++ ".\n", + R = t(S) + end(), + + fun() -> + Port = open_port({spawn, "ls"}, [line]), + KnownPort = erlang:port_to_list(Port), + S = KnownPort ++ ".", + R = KnownPort ++ ".\n", + R = t(S) + end(), + + fun() -> + UnknownPort = "#Port<100000.0>", + S = UnknownPort ++ ".", + "1: syntax error before: Port" = comm_err(S) + end(), + + fun() -> + UnknownRef = "#Ref<100000.0.0.0>", + S = UnknownRef ++ ".", + "1: syntax error before: Ref" = comm_err(S) + end(), + + fun() -> + KnownRef = term_to_string(make_ref()), + S = KnownRef ++ ".", + R = KnownRef ++ ".\n", + R = t(S) + end(), + + %% Test lib:extended_parse_term/1 + TF = fun(S) -> + {ok, Ts, _} = erl_scan:string(S++".", 1, [text]), + case lib:extended_parse_term(Ts) of + {ok, Term} -> Term; + {error, _}=Error -> Error + end + end, + Fun = fun m:f/1, + Fun = TF(term_to_string(Fun)), + Fun = TF("fun m:f/1"), + Pid = self(), + Pid = TF(term_to_string(Pid)), + Ref = make_ref(), + Ref = TF(term_to_string(Ref)), + Term = {[10, a], {"foo", []}, #{x => <<"bar">>}}, + Term = TF(lists:flatten(io_lib:format("~p", [Term]))), + {$a, F1, "foo"} = TF("{$a, 1.0, \"foo\"}"), + true = is_float(F1), + 3 = TF("+3"), + $a = TF("+$a"), + true = is_float(TF("+1.0")), + true = -3 =:= TF("-3"), + true = -$a =:= TF("-$a"), + true = is_float(TF("-1.0")), + {error, {_, _, ["syntax error"++_|_]}} = TF("{1"), + {error, {_,_,"bad term"}} = TF("fun() -> foo end"), + {error, {_,_,"bad term"}} = TF("1, 2"), + ok. + +term_to_string(T) -> + lists:flatten(io_lib:format("~w", [T])). + scan(B) -> F = fun(Ts) -> case erl_parse:parse_term(Ts) of diff --git a/lib/stdlib/test/sofs_SUITE.erl b/lib/stdlib/test/sofs_SUITE.erl index f67bf16f0f..39e56c6df6 100644 --- a/lib/stdlib/test/sofs_SUITE.erl +++ b/lib/stdlib/test/sofs_SUITE.erl @@ -1783,7 +1783,7 @@ multiple_relative_product(Conf) when is_list(Conf) -> ok. digraph(Conf) when is_list(Conf) -> - T0 = ets:all(), + T0 = lists:sort(ets:all()), E = empty_set(), R = relation([{a,b},{b,c},{c,d},{d,a}]), F = relation_to_family(R), @@ -1833,7 +1833,7 @@ digraph(Conf) when is_list(Conf) -> true -> ok end, - true = T0 == ets:all(), + true = T0 == lists:sort(ets:all()), ok. digraph_fail(ExitReason, Fail) -> |