|
45 | 45 |
|
46 | 46 | -export([iter_init/3, iter_next/1, iter_prev/1, iter_id/1, |
47 | 47 | enter_context/3, get_module_tests/2]). |
| 48 | +-export([parse_command_line/2]). % for unit testing |
48 | 49 |
|
49 | 50 | -define(TICKS_PER_SECOND, 1000). |
50 | 51 |
|
@@ -193,8 +194,69 @@ next(Tests, Options) -> |
193 | 194 | none |
194 | 195 | end. |
195 | 196 |
|
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. |
198 | 260 |
|
199 | 261 | %% this returns either a #test{} or #group{} record, or {data, T} to |
200 | 262 | %% 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) -> |
336 | 398 | %% end, |
337 | 399 | %% ?debugVal({started, StartedNet}), |
338 | 400 | {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, |
340 | 408 | {Node, StartedNet} |
341 | 409 | end, |
342 | 410 | fun ({Node, StopNet}) -> |
343 | 411 | %% ?debugVal({stop, StopNet}), |
344 | | - slave:stop(Node), |
| 412 | + peer:stop(Node), |
345 | 413 | case StopNet of |
346 | 414 | true -> net_kernel:stop(); |
347 | 415 | false -> ok |
|
0 commit comments