Skip to content

Commit

Permalink
Merge pull request #2868 from MarkoMin/completion
Browse files Browse the repository at this point in the history
`zsh` support for aliases in `completion`
  • Loading branch information
ferd authored Mar 11, 2024
2 parents 59238ca + 62290e8 commit 06aaecd
Show file tree
Hide file tree
Showing 3 changed files with 23 additions and 15 deletions.
11 changes: 7 additions & 4 deletions apps/rebar/src/rebar_completion_zsh.erl
Original file line number Diff line number Diff line change
Expand Up @@ -7,12 +7,15 @@
-export([generate/2]).

-spec generate([rebar_completion:cmpl_cmd()], rebar_completion:cmpl_opts()) -> iolist().
generate(Commands, #{shell:=zsh}=CmplOpts) ->
["#compdef _rebar3 rebar3\n",
rebar_completion:prelude(CmplOpts),
generate(Commands, #{shell:=zsh, aliases:=As}=CmplOpts) ->
[rebar_completion:prelude(CmplOpts),
io_lib:nl(),
main(Commands, CmplOpts),
io_lib:nl()].
io_lib:nl(),
compdefs(["rebar3" | As])].

compdefs(As) ->
[["compdef _rebar3 ", A, io_lib:nl()] || A <- As].

main(Commands, CmplOpts) ->
H = #{short=>$s,
Expand Down
17 changes: 9 additions & 8 deletions apps/rebar/src/rebar_prv_completion.erl
Original file line number Diff line number Diff line change
Expand Up @@ -47,11 +47,12 @@ do(State) ->
file => "_rebar3",
shell => detect_shell()},
{CliOptsList, _} = rebar_state:command_parsed_args(State),
CliOpts = maps:from_list(CliOptsList),
CliOpts0 = maps:from_list(CliOptsList),
CliOpts = process_cli_opts(CliOpts0),
Conf = maps:from_list(rebar_state:get(State, completion, [])),
%% Opts passed in CLI override config
CmplOpts0 = maps:merge(DefaultOpts, Conf),
CmplOpts = check_opts(maps:merge(CmplOpts0, CliOpts)),
CmplOpts = maps:merge(CmplOpts0, CliOpts),

Providers0 = rebar_state:providers(State),
BareProviders = lists:filter(fun(P) -> provider_get(P, bare) end, Providers0),
Expand All @@ -69,12 +70,6 @@ do(State) ->
write_completion(Compl,State,CmplOpts),
{ok, State}.

check_opts(#{shell:=zsh, aliases:=As}=Opts) when As=/=[] ->
?WARN("OS aliases are not supported for `zsh`, they must be added manually.", []),
Opts;
check_opts(Opts) ->
Opts.

detect_shell() ->
case os:getenv("SHELL") of
false ->
Expand All @@ -92,6 +87,12 @@ to_shell(Unsupp) ->
[Unsupp]),
?DEF_SHELL.

process_cli_opts(#{aliases:=AStr}=Cli) ->
As = [string:trim(A) || A <- string:split(AStr, ",", all)],
Cli#{aliases:=As};
process_cli_opts(Cli) ->
Cli.

-spec namespace_to_cmpl_cmds(atom(), [providers:t()]) -> [rebar_completion:cmpl_cmd()].
namespace_to_cmpl_cmds(default,Providers) ->
lists:map(fun(P)->provider_to_cmpl_cmd(P) end,Providers);
Expand Down
10 changes: 7 additions & 3 deletions apps/rebar/test/rebar_completion_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -77,15 +77,19 @@ check_bash(Config) ->

check_zsh(Config) ->
ComplFile = ?config(compl_file, Config),
Aliases = ["rebar", "r3"],
Opts = #{shell => zsh,
file => ComplFile,
aliases => []},
aliases => Aliases},
completion_gen(Config, Opts),
{ok, Completion} = file:read_file(ComplFile),
%% function definition
{match, _} = re:run(Completion, "function _rebar3 {"),
CompleteCmd = "#compdef _rebar3 ",
?assertMatch({match, _}, re:run(Completion, CompleteCmd++"rebar3"++"\n")).
CompleteCmd = "compdef _rebar3 ",
lists:foreach(fun(Alias) ->
?assertMatch({Alias, {match, _}}, {Alias, re:run(Completion, CompleteCmd++Alias++"\n")})
end,
["rebar3" | Aliases]).

%% helpers

Expand Down

0 comments on commit 06aaecd

Please sign in to comment.