Skip to content

Commit

Permalink
Merge pull request #8932 from madlep/stdlib/argparse-handle-binaries/…
Browse files Browse the repository at this point in the history
…OTP-19303

Stdlib/argparse handle binary arguments and binary command help
  • Loading branch information
garazdawi authored Oct 17, 2024
2 parents fb51687 + 693b9cf commit 99ce260
Show file tree
Hide file tree
Showing 2 changed files with 67 additions and 9 deletions.
21 changes: 15 additions & 6 deletions lib/stdlib/src/argparse.erl
Original file line number Diff line number Diff line change
Expand Up @@ -498,6 +498,11 @@ corresponding key is not present in the resulting map.
-type arg_map() :: #{argument_name() => term()}.
%% Arguments map: argument name to a term, produced by parser. Supplied to the command handler

-doc """
List of command line arguments to be parsed.
""".
-type args() :: [string() | unicode:chardata()].

-doc """
Command handler specification. Called by [`run/3` ](`run/3`)upon successful
parser return.
Expand Down Expand Up @@ -599,7 +604,7 @@ elements are nested command names.
%% Command path, for nested commands

-export_type([arg_type/0, argument_help/0, argument/0,
command/0, handler/0, cmd_path/0, arg_map/0]).
command/0, handler/0, cmd_path/0, arg_map/0, args/0]).

-doc """
Returned from [`parse/2,3`](`parse/3`) when the user input cannot be parsed
Expand Down Expand Up @@ -703,7 +708,7 @@ validate(Command, Options) ->
%% @equiv parse(Args, Command, #{})
-doc(#{equiv => parse/3}).
-doc(#{since => <<"OTP 26.0">>}).
-spec parse(Args :: [string()], command()) -> parse_result().
-spec parse(args(), command()) -> parse_result().
parse(Args, Command) ->
parse(Args, Command, #{}).

Expand All @@ -722,13 +727,14 @@ makes `parse/2,3` to return a tuple
This function does not call command handler.
""".
-doc(#{since => <<"OTP 26.0">>}).
-spec parse(Args :: [string()], command(), Options :: parser_options()) -> parse_result().
-spec parse(args(), command(), Options :: parser_options()) -> parse_result().
parse(Args, Command, Options) ->
Prog = validate(Command, Options),
%% use maps and not sets v2, because sets:is_element/2 cannot be used in guards (unlike is_map_key)
Prefixes = maps:from_list([{P, true} || P <- maps:get(prefixes, Options, [$-])]),
Args2 = [unicode:characters_to_list(Arg) || Arg <- Args],
try
parse_impl(Args, merge_arguments(Prog, Command, init_parser(Prefixes, Command, Options)))
parse_impl(Args2, merge_arguments(Prog, Command, init_parser(Prefixes, Command, Options)))
catch
%% Parser error may happen at any depth, and bubbling the error is really
%% cumbersome. Use exceptions and catch it before returning from `parse/2,3' instead.
Expand Down Expand Up @@ -772,7 +778,7 @@ specification or user-provided command line input.
> may result in an unexpected shutdown of a remote node.
""".
-doc(#{since => <<"OTP 26.0">>}).
-spec run(Args :: [string()], command(), parser_options()) -> term().
-spec run(args(), command(), parser_options()) -> term().
run(Args, Command, Options) ->
try parse(Args, Command, Options) of
{ok, ArgMap, Path, SubCmd} ->
Expand Down Expand Up @@ -1661,7 +1667,10 @@ collect_options(CmdName, Command, [Cmd|Tail], Args) ->

%% gets help for sub-command
get_help(Command, []) ->
maps:get(help, Command, "");
case maps:get(help, Command, "") of
Help when is_binary(Help) -> unicode:characters_to_list(Help);
Help -> Help
end;
get_help(Command, [Cmd|Tail]) ->
Sub = maps:get(commands, Command),
SubCmd = maps:get(Cmd, Sub),
Expand Down
55 changes: 52 additions & 3 deletions lib/stdlib/test/argparse_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,7 @@
-export([
readme/0, readme/1,
basic/0, basic/1,
binary_args/0, binary_args/1,
long_form_eq/0, long_form_eq/1,
built_in_types/0, built_in_types/1,
type_validators/0, type_validators/1,
Expand All @@ -43,6 +44,7 @@
proxy_arguments/0, proxy_arguments/1,

usage/0, usage/1,
usage_help_binary/0, usage_help_binary/1,
usage_required_args/0, usage_required_args/1,
usage_template/0, usage_template/1,
usage_args_ordering/0, usage_args_ordering/1,
Expand All @@ -54,6 +56,7 @@
validator_exception_format/0, validator_exception_format/1,

run_handle/0, run_handle/1,
run_handle_binary_args/0, run_handle_binary_args/1,
run_args_ordering/0, run_args_ordering/1
]).

Expand All @@ -65,21 +68,21 @@ suite() ->
groups() ->
[
{parser, [parallel], [
readme, basic, long_form_eq, built_in_types, type_validators,
readme, basic, binary_args, long_form_eq, built_in_types, type_validators,
invalid_arguments, complex_command, unicode, parser_error,
nargs, argparse, negative, nodigits, pos_mixed_with_opt,
default_for_not_required, global_default, subcommand,
very_short, multi_short, proxy_arguments
]},
{usage, [parallel], [
usage, usage_required_args, usage_template, usage_args_ordering,
usage, usage_help_binary, usage_required_args, usage_template, usage_args_ordering,
parser_error_usage, command_usage, usage_width
]},
{validator, [parallel], [
validator_exception, validator_exception_format
]},
{run, [parallel], [
run_handle, run_args_ordering
run_handle, run_handle_binary_args, run_args_ordering
]}
].

Expand Down Expand Up @@ -227,6 +230,15 @@ basic(Config) when is_list(Config) ->
?assertEqual({ok, #{arg => [true, false]}, [Prog], ArgListCmd},
parse(["true false"], ArgListCmd)).

binary_args() ->
[{doc, "Args are provided as binarys"}].

binary_args(Config) when is_list(Config) ->
%% no command, just argument list
KernelCmd = #{arguments => [#{name => kernel, long => "kernel", type => atom, nargs => 2}]},
?assertEqual({ok, #{kernel => [port, dist]}, [prog()], KernelCmd},
argparse:parse([<<"-kernel">>, <<"port">>, <<"dist">>], KernelCmd)).

long_form_eq() ->
[{doc, "Tests that long form supports --arg=value"}].

Expand Down Expand Up @@ -815,6 +827,33 @@ usage(Config) when is_list(Config) ->
#{progname => "erl", command => ["status", "crawler"]}))),
ok.

usage_help_binary() ->
[{doc, "Test binary command help string"}].

usage_help_binary(Config) when is_list(Config) ->
Cmd2 = #{arguments => [#{
name => shard,
type => integer,
default => 0,
help => <<"help binary for shard">>}],
commands => #{"somecommand" => #{ help => <<"help binary for somecommand">> }},
help => "help binary for command"
},

Expected = "Usage:\n"
" erl {somecommand} <shard>\n"
"\n"
"help binary for command\n"
"\n"
"Subcommands:\n"
" somecommand help binary for somecommand\n"
"\n"
"Arguments:\n"
" shard help binary for shard (int), default: 0\n",

?assertEqual(Expected,
unicode:characters_to_list(argparse:help(Cmd2, #{}))).

usage_required_args() ->
[{doc, "Verify that required args are printed as required in usage"}].

Expand Down Expand Up @@ -1100,6 +1139,16 @@ run_handle(Config) when is_list(Config) ->
arguments => [#{name => arg}]}}},
#{})).

run_handle_binary_args() ->
[{doc, "Verify that argparse:run/3, accepts binary args"}].

run_handle_binary_args(Config) when is_list(Config) ->
%% no subcommand, positional module-based function
?assertEqual(6,
argparse:run([<<"2">>, <<"3">>], #{handler => {erlang, '*', undefined},
arguments => [#{name => l, type => integer}, #{name => r, type => integer}]},
#{})).

run_args_ordering() ->
[{doc, "Test that positional arguments are parsed in the correct order"}].

Expand Down

0 comments on commit 99ce260

Please sign in to comment.