Skip to content

Commit ab4e569

Browse files
committed
Merge branch 'maint'
2 parents f0c12f1 + d38cf6d commit ab4e569

File tree

5 files changed

+162
-13
lines changed

5 files changed

+162
-13
lines changed

lib/eunit/doc/guides/chapter.md

Lines changed: 8 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1010,11 +1010,16 @@ The following representations specify fixture handling for test sets:
10101010

10111011
- **`{node, Node::atom(), Tests | Instantiator}`**
10121012

1013-
- **`{node, Node::atom(), Args::string(), Tests | Instantiator}`** - `node` is
1014-
like `setup`, but with a built-in behaviour: it starts a slave node for the
1013+
- **`{node, Node::atom(), Args::[string()] | string(), Tests | Instantiator}`** - `node` is
1014+
like `setup`, but with a built-in behaviour: it starts a peer node for the
10151015
duration of the tests. The atom `Node` should have the format
10161016
`[email protected]`, and `Args` are the optional arguments to the new
1017-
node; see `slave:start_link/3` for details.
1017+
node; see `peer:start_link/1` for details. To remain compatible
1018+
with pre-existing user tests, `Args` accepts both a list of strings and a string.
1019+
If a string is passed, it is parsed into a list of arguments, treating
1020+
single- and double-quoted text as single arguments and removing the quotes.
1021+
If you wish a quote character to remain a part of the parsed argument list,
1022+
escape it with a backslash "\". Unbalanced quotes also become a part of the output.
10181023

10191024
- **`{foreach, Where, Setup, Cleanup, [Tests | Instantiator]}`**
10201025

lib/eunit/doc/overview.edoc

Lines changed: 30 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,28 @@
11

22
-*- html -*-
33

4+
<!--
5+
%CopyrightBegin%
6+
7+
SPDX-License-Identifier: Apache-2.0
8+
9+
Copyright Ericsson AB 2000-2025. All Rights Reserved.
10+
11+
Licensed under the Apache License, Version 2.0 (the "License");
12+
you may not use this file except in compliance with the License.
13+
You may obtain a copy of the License at
14+
15+
http://www.apache.org/licenses/LICENSE-2.0
16+
17+
Unless required by applicable law or agreed to in writing, software
18+
distributed under the License is distributed on an "AS IS" BASIS,
19+
WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
20+
See the License for the specific language governing permissions and
21+
limitations under the License.
22+
23+
%CopyrightEnd%
24+
-->
25+
426
EUnit overview page
527

628
@title EUnit - a Lightweight Unit Testing Framework for Erlang
@@ -963,11 +985,16 @@ tests, with optional teardown afterwards. The arguments are described in
963985
detail below.
964986
</dd>
965987
<dt>`{node, Node::atom(), Tests | Instantiator}'</dt>
966-
<dt>`{node, Node::atom(), Args::string(), Tests | Instantiator}'</dt>
988+
<dt>`{node, Node::atom(), Args::[string()] | string(), Tests | Instantiator}'</dt>
967989
<dd>`node' is like `setup', but with a built-in behaviour: it starts a
968-
slave node for the duration of the tests. The atom `Node' should have
990+
peer node for the duration of the tests. The atom `Node' should have
969991
the format `[email protected]', and `Args' are the optional
970-
arguments to the new node; see `slave:start_link/3' for details.
992+
arguments to the new node; see `peer:start_link/1' for details. To remain compatible
993+
with pre-existing user tests, `Args' accepts both a list of strings and a string
994+
If a string is passed, it is parsed into a list of arguments, treating
995+
single- and double-quoted text as single arguments and removing the quotes.
996+
If you wish a quote character to remain a part of the parsed argument list,
997+
escape it with a backslash "\". Unbalanced quotes also become a part of the output.
971998
</dd>
972999
<dt>`{foreach, Where, Setup, Cleanup, [Tests | Instantiator]}'</dt>
9731000
<dt>`{foreach, Setup, Cleanup, [Tests | Instantiator]}'</dt>

lib/eunit/src/eunit.app.src

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -25,4 +25,4 @@
2525
{registered,[]},
2626
{applications, [kernel,stdlib]},
2727
{env, []},
28-
{runtime_dependencies, ["stdlib-3.4","kernel-5.3","erts-9.0"]}]}.
28+
{runtime_dependencies, ["stdlib-6.0","kernel-5.3","erts-9.0"]}]}.

lib/eunit/src/eunit_data.erl

Lines changed: 72 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -45,6 +45,7 @@
4545

4646
-export([iter_init/3, iter_next/1, iter_prev/1, iter_id/1,
4747
enter_context/3, get_module_tests/2]).
48+
-export([parse_command_line/2]). % for unit testing
4849

4950
-define(TICKS_PER_SECOND, 1000).
5051

@@ -193,8 +194,69 @@ next(Tests, Options) ->
193194
none
194195
end.
195196

196-
%% Temporary suppression
197-
-compile([{nowarn_deprecated_function,[{slave,start_link,3},{slave,stop,1}]}]).
197+
%% Read a word till whitespace or end of input
198+
-spec cmd_parse_read_unquoted(string(), Acc :: string())
199+
-> #{token => string(), tail => string()}.
200+
cmd_parse_read_unquoted([], Acc) ->
201+
#{token => lists:reverse(Acc), tail => []};
202+
cmd_parse_read_unquoted([C | Tail], Acc) ->
203+
case unicode_util:is_whitespace(C) of
204+
true -> #{token => lists:reverse(Acc), tail => Tail};
205+
false -> cmd_parse_read_unquoted(Tail, [C | Acc])
206+
end.
207+
208+
%% Balanced: "value with spaces" becomes "value with spaces" without quotes.
209+
%% Unbalanced: "value with spaces (no closing) - parsed word starts with the quote.
210+
cmd_parse_read_quoted(Quote, [], Acc) ->
211+
%% No closing quote: return token with dangling opening quote, as-is
212+
%% (include the opening quote, keep content unchanged)
213+
#{token => [Quote | lists:reverse(Acc)], tail => []};
214+
cmd_parse_read_quoted(Quote, [Quote | Rest], Acc) ->
215+
#{token => lists:reverse(Acc), tail => Rest};
216+
cmd_parse_read_quoted(Quote, [$\\, C | Rest], Acc) ->
217+
%% Backslash escapes the next character inside quotes
218+
cmd_parse_read_quoted(Quote, Rest, [C | Acc]);
219+
cmd_parse_read_quoted(Quote, [C | Rest], Acc) ->
220+
cmd_parse_read_quoted(Quote, Rest, [C | Acc]).
221+
222+
%% Parses an old style command line (a single string) into a list of strings.
223+
%% - Splits on whitespace.
224+
%% - If the next non-whitespace character is ' or ", consumes until the matching
225+
%% closing quote; the quotes are removed for balanced quotes.
226+
%% - Inside quotes, backslash escapes the following character.
227+
%% - If the closing quote is missing, returns the parameter as-is with a dangling quote
228+
parse_command_line(Input, Acc) when is_list(Input) ->
229+
case string:trim(Input) of
230+
[] ->
231+
lists:reverse(Acc);
232+
[$" | Rest] ->
233+
#{token := Token1, tail := Rest1}
234+
= cmd_parse_read_quoted($", Rest, []),
235+
parse_command_line(Rest1, [Token1 | Acc]);
236+
[$' | Rest] ->
237+
#{token := Token2, tail := Rest2}
238+
= cmd_parse_read_quoted($', Rest, []),
239+
parse_command_line(Rest2, [Token2 | Acc]);
240+
Other ->
241+
#{token := Token3, tail := Rest3}
242+
= cmd_parse_read_unquoted(Other, []),
243+
parse_command_line(Rest3, [Token3 | Acc])
244+
end.
245+
246+
%% Adapter for a string command line passed to old deprecated option. Coalesces any command line
247+
%% format (string or list of strings) into list of strings.
248+
-spec parse_peer_args(string() | [string()]) -> [string()].
249+
parse_peer_args([]) -> [];
250+
parse_peer_args(Args) when is_list(Args) -> % can be string or list of strings
251+
case io_lib:printable_unicode_list(Args) of
252+
true ->
253+
parse_command_line(Args, []);
254+
false ->
255+
case lists:all(fun io_lib:printable_unicode_list/1, Args) of % each element of Args is a string
256+
true -> Args; % no modification, it is already a list
257+
false -> erlang:throw({badarg, Args})
258+
end
259+
end.
198260

199261
%% this returns either a #test{} or #group{} record, or {data, T} to
200262
%% 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) ->
336398
%% end,
337399
%% ?debugVal({started, StartedNet}),
338400
{Name, Host} = eunit_lib:split_node(N),
339-
{ok, Node} = slave:start_link(Host, Name, A),
401+
{ok, Node} = case peer:start_link(#{
402+
host => atom_to_list(Host),
403+
name => Name, args => parse_peer_args(A)}) of
404+
{ok, Pid} -> {ok, Pid};
405+
{ok, Pid, _Node} -> {ok, Pid};
406+
{error, Rsn} -> throw({peer_start, Rsn})
407+
end,
340408
{Node, StartedNet}
341409
end,
342410
fun ({Node, StopNet}) ->
343411
%% ?debugVal({stop, StopNet}),
344-
slave:stop(Node),
412+
peer:stop(Node),
345413
case StopNet of
346414
true -> net_kernel:stop();
347415
false -> ok

lib/eunit/test/eunit_SUITE.erl

Lines changed: 51 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,7 @@
2727
fixture_test/1, primitive_test/1, surefire_utf8_test/1,
2828
surefire_latin_test/1, surefire_c0_test/1, surefire_ensure_dir_test/1,
2929
stacktrace_at_timeout_test/1, scale_timeouts_test/1,
30-
report_failed_setup_inparallel_test/1]).
30+
report_failed_setup_inparallel_test/1, parse_commandline_test/1]).
3131

3232
%% Two eunit tests:
3333
-export([times_out_test_/0, times_out_default_test/0]).
@@ -44,7 +44,8 @@ all() ->
4444
[app_test, appup_test, eunit_test, eunit_exact_test, primitive_test,
4545
fixture_test, surefire_utf8_test, surefire_latin_test, surefire_c0_test,
4646
surefire_ensure_dir_test, stacktrace_at_timeout_test,
47-
scale_timeouts_test, report_failed_setup_inparallel_test].
47+
scale_timeouts_test, report_failed_setup_inparallel_test,
48+
parse_commandline_test].
4849

4950
groups() ->
5051
[].
@@ -274,3 +275,51 @@ report_failed_setup_inparallel_test(_Config) ->
274275
eunit:test(Test,[verbose, {report, {eunit_test_listener, [self()]}}]),
275276
check_test_results(Test, #{skip => 0,cancel => 1,fail => 0,pass => 1}),
276277
ok.
278+
279+
%% Eunit: Checks that eunit_data:parse_command_line correctly handles various command lines
280+
parse_commandline_test(_Config) ->
281+
lists:foreach(
282+
fun({Input, Expect}) ->
283+
Output = eunit_data:parse_command_line(Input, []),
284+
?assertEqual(Expect, Output, lists:flatten(io_lib:format(
285+
"Input=~0p expected=~0p output=~0p", [Input, Expect, Output])))
286+
end,
287+
[
288+
%% Basic splitting and whitespace handling
289+
{"", []},
290+
{"ab", ["ab"]},
291+
{"a", ["a"]},
292+
{"a b c", ["a", "b", "c"]},
293+
{" a b c ", ["a", "b", "c"]},
294+
{"a\tb\nc", ["a", "b", "c"]},
295+
296+
%% Double-quoted sections (quotes removed)
297+
{"a \"b c\" d", ["a", "b c", "d"]},
298+
{"a \"b\tc\" d", ["a", "b\tc", "d"]},
299+
{"a \"b\nc\" d", ["a", "b\nc", "d"]},
300+
{"\"a b\" \"c d\"", ["a b", "c d"]},
301+
{"\"\"", [""]}, % empty string in double quotes
302+
303+
%% Escapes inside double quotes
304+
{"a \"b\\\"c\" d", ["a", "b\"c", "d"]},
305+
{"a \"b\\\\c\" d", ["a", "b\\c", "d"]},
306+
307+
%% Single-quoted sections (quotes removed)
308+
{"a 'b c' d", ["a", "b c", "d"]},
309+
{"''", [""]},
310+
311+
%% Escapes inside single quotes (backslash escapes next char)
312+
{"'it\\'s' ok", ["it's", "ok"]},
313+
{"a 'b\\\\c' d", ["a", "b\\c", "d"]},
314+
315+
%% Unbalanced quotes: returned token keeps the dangling opening quote
316+
{"a \"b c", ["a", "\"b c"]},
317+
{"'b c", ["'b c"]},
318+
319+
%% Backslash outside quotes is literal + single quote test: parser
320+
%% should return the following words separately
321+
{"a\\ b", ["a\\", "b"]},
322+
{"a ' b", ["a", "' b"]},
323+
{"a ' b c", ["a", "' b c"]}
324+
]),
325+
ok.

0 commit comments

Comments
 (0)