diff --git a/lib/eunit/doc/guides/chapter.md b/lib/eunit/doc/guides/chapter.md index 3315b6dfd8d1..3b9e77971d23 100644 --- a/lib/eunit/doc/guides/chapter.md +++ b/lib/eunit/doc/guides/chapter.md @@ -1009,11 +1009,16 @@ The following representations specify fixture handling for test sets: - **`{node, Node::atom(), Tests | Instantiator}`** -- **`{node, Node::atom(), Args::string(), Tests | Instantiator}`** - `node` is - like `setup`, but with a built-in behaviour: it starts a slave node for the +- **`{node, Node::atom(), Args::[string()] | string(), Tests | Instantiator}`** - `node` is + like `setup`, but with a built-in behaviour: it starts a peer node for the duration of the tests. The atom `Node` should have the format `nodename@full.machine.name`, and `Args` are the optional arguments to the new - node; see `slave:start_link/3` for details. + node; see `peer:start_link/1` for details. To remain compatible + with pre-existing user tests, `Args` accepts both a list of strings and a string. + If a string is passed, it is parsed into a list of arguments, treating + single- and double-quoted text as single arguments and removing the quotes. + If you wish a quote character to remain a part of the parsed argument list, + escape it with a backslash "\". Unbalanced quotes also become a part of the output. - **`{foreach, Where, Setup, Cleanup, [Tests | Instantiator]}`** diff --git a/lib/eunit/doc/overview.edoc b/lib/eunit/doc/overview.edoc index 17f738640ccc..c5f8402dacd6 100644 --- a/lib/eunit/doc/overview.edoc +++ b/lib/eunit/doc/overview.edoc @@ -1,6 +1,28 @@ -*- html -*- + + EUnit overview page @title EUnit - a Lightweight Unit Testing Framework for Erlang @@ -963,11 +985,16 @@ tests, with optional teardown afterwards. The arguments are described in detail below.
`{node, Node::atom(), Tests | Instantiator}'
-
`{node, Node::atom(), Args::string(), Tests | Instantiator}'
+
`{node, Node::atom(), Args::[string()] | string(), Tests | Instantiator}'
`node' is like `setup', but with a built-in behaviour: it starts a -slave node for the duration of the tests. The atom `Node' should have +peer node for the duration of the tests. The atom `Node' should have the format `nodename@full.machine.name', and `Args' are the optional -arguments to the new node; see `slave:start_link/3' for details. +arguments to the new node; see `peer:start_link/1' for details. To remain compatible +with pre-existing user tests, `Args' accepts both a list of strings and a string +If a string is passed, it is parsed into a list of arguments, treating +single- and double-quoted text as single arguments and removing the quotes. +If you wish a quote character to remain a part of the parsed argument list, +escape it with a backslash "\". Unbalanced quotes also become a part of the output.
`{foreach, Where, Setup, Cleanup, [Tests | Instantiator]}'
`{foreach, Setup, Cleanup, [Tests | Instantiator]}'
diff --git a/lib/eunit/src/eunit.app.src b/lib/eunit/src/eunit.app.src index b6c1f27b5807..1b4e079737b5 100644 --- a/lib/eunit/src/eunit.app.src +++ b/lib/eunit/src/eunit.app.src @@ -25,4 +25,4 @@ {registered,[]}, {applications, [kernel,stdlib]}, {env, []}, - {runtime_dependencies, ["stdlib-3.4","kernel-5.3","erts-9.0"]}]}. + {runtime_dependencies, ["stdlib-6.0","kernel-5.3","erts-9.0"]}]}. diff --git a/lib/eunit/src/eunit_data.erl b/lib/eunit/src/eunit_data.erl index c8962bb178d4..72be36166f65 100644 --- a/lib/eunit/src/eunit_data.erl +++ b/lib/eunit/src/eunit_data.erl @@ -45,6 +45,7 @@ -export([iter_init/3, iter_next/1, iter_prev/1, iter_id/1, enter_context/3, get_module_tests/2]). +-export([parse_command_line/2]). % for unit testing -define(TICKS_PER_SECOND, 1000). @@ -193,8 +194,69 @@ next(Tests, Options) -> none end. -%% Temporary suppression --compile([{nowarn_deprecated_function,[{slave,start_link,3},{slave,stop,1}]}]). +%% Read a word till whitespace or end of input +-spec cmd_parse_read_unquoted(string(), Acc :: string()) + -> #{token => string(), tail => string()}. +cmd_parse_read_unquoted([], Acc) -> + #{token => lists:reverse(Acc), tail => []}; +cmd_parse_read_unquoted([C | Tail], Acc) -> + case unicode_util:is_whitespace(C) of + true -> #{token => lists:reverse(Acc), tail => Tail}; + false -> cmd_parse_read_unquoted(Tail, [C | Acc]) + end. + +%% Balanced: "value with spaces" becomes "value with spaces" without quotes. +%% Unbalanced: "value with spaces (no closing) - parsed word starts with the quote. +cmd_parse_read_quoted(Quote, [], Acc) -> + %% No closing quote: return token with dangling opening quote, as-is + %% (include the opening quote, keep content unchanged) + #{token => [Quote | lists:reverse(Acc)], tail => []}; +cmd_parse_read_quoted(Quote, [Quote | Rest], Acc) -> + #{token => lists:reverse(Acc), tail => Rest}; +cmd_parse_read_quoted(Quote, [$\\, C | Rest], Acc) -> + %% Backslash escapes the next character inside quotes + cmd_parse_read_quoted(Quote, Rest, [C | Acc]); +cmd_parse_read_quoted(Quote, [C | Rest], Acc) -> + cmd_parse_read_quoted(Quote, Rest, [C | Acc]). + +%% Parses an old style command line (a single string) into a list of strings. +%% - Splits on whitespace. +%% - If the next non-whitespace character is ' or ", consumes until the matching +%% closing quote; the quotes are removed for balanced quotes. +%% - Inside quotes, backslash escapes the following character. +%% - If the closing quote is missing, returns the parameter as-is with a dangling quote +parse_command_line(Input, Acc) when is_list(Input) -> + case string:trim(Input) of + [] -> + lists:reverse(Acc); + [$" | Rest] -> + #{token := Token1, tail := Rest1} + = cmd_parse_read_quoted($", Rest, []), + parse_command_line(Rest1, [Token1 | Acc]); + [$' | Rest] -> + #{token := Token2, tail := Rest2} + = cmd_parse_read_quoted($', Rest, []), + parse_command_line(Rest2, [Token2 | Acc]); + Other -> + #{token := Token3, tail := Rest3} + = cmd_parse_read_unquoted(Other, []), + parse_command_line(Rest3, [Token3 | Acc]) + end. + +%% Adapter for a string command line passed to old deprecated option. Coalesces any command line +%% format (string or list of strings) into list of strings. +-spec parse_peer_args(string() | [string()]) -> [string()]. +parse_peer_args([]) -> []; +parse_peer_args(Args) when is_list(Args) -> % can be string or list of strings + case io_lib:printable_unicode_list(Args) of + true -> + parse_command_line(Args, []); + false -> + case lists:all(fun io_lib:printable_unicode_list/1, Args) of % each element of Args is a string + true -> Args; % no modification, it is already a list + false -> erlang:throw({badarg, Args}) + end + end. %% this returns either a #test{} or #group{} record, or {data, T} to %% signal that T has been substituted for the given representation @@ -336,12 +398,18 @@ parse({node, N, A, T1}=T, Options) when is_atom(N) -> %% end, %% ?debugVal({started, StartedNet}), {Name, Host} = eunit_lib:split_node(N), - {ok, Node} = slave:start_link(Host, Name, A), + {ok, Node} = case peer:start_link(#{ + host => atom_to_list(Host), + name => Name, args => parse_peer_args(A)}) of + {ok, Pid} -> {ok, Pid}; + {ok, Pid, _Node} -> {ok, Pid}; + {error, Rsn} -> throw({peer_start, Rsn}) + end, {Node, StartedNet} end, fun ({Node, StopNet}) -> %% ?debugVal({stop, StopNet}), - slave:stop(Node), + peer:stop(Node), case StopNet of true -> net_kernel:stop(); false -> ok diff --git a/lib/eunit/test/eunit_SUITE.erl b/lib/eunit/test/eunit_SUITE.erl index 38b0267533d4..93c3be91dd70 100644 --- a/lib/eunit/test/eunit_SUITE.erl +++ b/lib/eunit/test/eunit_SUITE.erl @@ -27,7 +27,7 @@ fixture_test/1, primitive_test/1, surefire_utf8_test/1, surefire_latin_test/1, surefire_c0_test/1, surefire_ensure_dir_test/1, stacktrace_at_timeout_test/1, scale_timeouts_test/1, - report_failed_setup_inparallel_test/1]). + report_failed_setup_inparallel_test/1, parse_commandline_test/1]). %% Two eunit tests: -export([times_out_test_/0, times_out_default_test/0]). @@ -44,7 +44,8 @@ all() -> [app_test, appup_test, eunit_test, eunit_exact_test, primitive_test, fixture_test, surefire_utf8_test, surefire_latin_test, surefire_c0_test, surefire_ensure_dir_test, stacktrace_at_timeout_test, - scale_timeouts_test, report_failed_setup_inparallel_test]. + scale_timeouts_test, report_failed_setup_inparallel_test, + parse_commandline_test]. groups() -> []. @@ -274,3 +275,51 @@ report_failed_setup_inparallel_test(_Config) -> eunit:test(Test,[verbose, {report, {eunit_test_listener, [self()]}}]), check_test_results(Test, #{skip => 0,cancel => 1,fail => 0,pass => 1}), ok. + +%% Eunit: Checks that eunit_data:parse_command_line correctly handles various command lines +parse_commandline_test(_Config) -> + lists:foreach( + fun({Input, Expect}) -> + Output = eunit_data:parse_command_line(Input, []), + ?assertEqual(Expect, Output, lists:flatten(io_lib:format( + "Input=~0p expected=~0p output=~0p", [Input, Expect, Output]))) + end, + [ + %% Basic splitting and whitespace handling + {"", []}, + {"ab", ["ab"]}, + {"a", ["a"]}, + {"a b c", ["a", "b", "c"]}, + {" a b c ", ["a", "b", "c"]}, + {"a\tb\nc", ["a", "b", "c"]}, + + %% Double-quoted sections (quotes removed) + {"a \"b c\" d", ["a", "b c", "d"]}, + {"a \"b\tc\" d", ["a", "b\tc", "d"]}, + {"a \"b\nc\" d", ["a", "b\nc", "d"]}, + {"\"a b\" \"c d\"", ["a b", "c d"]}, + {"\"\"", [""]}, % empty string in double quotes + + %% Escapes inside double quotes + {"a \"b\\\"c\" d", ["a", "b\"c", "d"]}, + {"a \"b\\\\c\" d", ["a", "b\\c", "d"]}, + + %% Single-quoted sections (quotes removed) + {"a 'b c' d", ["a", "b c", "d"]}, + {"''", [""]}, + + %% Escapes inside single quotes (backslash escapes next char) + {"'it\\'s' ok", ["it's", "ok"]}, + {"a 'b\\\\c' d", ["a", "b\\c", "d"]}, + + %% Unbalanced quotes: returned token keeps the dangling opening quote + {"a \"b c", ["a", "\"b c"]}, + {"'b c", ["'b c"]}, + + %% Backslash outside quotes is literal + single quote test: parser + %% should return the following words separately + {"a\\ b", ["a\\", "b"]}, + {"a ' b", ["a", "' b"]}, + {"a ' b c", ["a", "' b c"]} + ]), + ok.