1
0
mirror of https://github.com/erlang/rebar3.git synced 2025-04-19 02:04:00 +03:00

completion provider

This commit is contained in:
Marko Mindek 2024-01-16 22:25:26 +01:00
parent 8207d82465
commit 570889843d
6 changed files with 384 additions and 0 deletions

1
THANKS
View File

@ -146,3 +146,4 @@ Justin Wood
Guilherme Andrade
Manas Chaudhari
Luís Rascão
Marko Minđek

View File

@ -52,6 +52,7 @@
rebar_prv_clean,
rebar_prv_common_test,
rebar_prv_compile,
rebar_prv_completion,
rebar_prv_cover,
rebar_prv_deps,
rebar_prv_deps_tree,

View File

@ -0,0 +1,36 @@
-module(rebar_completion).
-export([generate/2]).
-type arg_type() :: atom | binary | boolean | float | interger | string.
-type cmpl_arg() :: #{short => char() | undefined,
long => string() | undefined,
type => arg_type(),
help => string()}.
-type cmpl_cmd() :: #{name := string(),
help := string() | undefined,
args := [cmpl_arg()],
cmds => [cmpl_cmd()]}.
-type cmpl_opts() :: #{aliases => [string()],
file => file:filename(),
hints => boolean(),
%% TODO support fish and maybe some more shells
shell => bash | zsh,
type_hints => boolean()}.
-export([prelude/1]).
-export_type([cmpl_opts/0, cmpl_cmd/0, cmpl_arg/0]).
-callback generate([cmpl_cmd()], cmpl_opts()) -> iolist().
-spec generate([cmpl_cmd()], cmpl_opts()) -> string().
generate(Commands, #{shell:=bash}=CmplOpts) ->
rebar_completion_bash:generate(Commands,CmplOpts);
generate(Commands, #{shell:=zsh}=CmplOpts) ->
rebar_completion_zsh:generate(Commands,CmplOpts).
prelude(#{shell:=Shell}) ->
"# "++atom_to_list(Shell)++" completion file for rebar3 (autogenerated by rebar3).\n".

View File

@ -0,0 +1,113 @@
%% @doc Completion file generator for bash
%% @end
-module(rebar_completion_bash).
-behavior(rebar_completion).
-export([generate/2]).
-define(str(N), integer_to_list(N)).
-spec generate([rebar_completion:cmpl_cmd()], rebar_completion:cmpl_opts()) -> iolist().
generate(Commands, #{shell:=bash}=CmplOpts) ->
[rebar_completion:prelude(CmplOpts),
io_lib:nl(),
main(Commands, CmplOpts),
complete(CmplOpts),
io_lib:nl()].
cmd_clause(Cmd) ->
nested_cmd_clause(Cmd, [], 1).
-spec nested_cmd_clause(rebar_completion:cmpl_cmd(), [string()], pos_integer()) -> iolist().
nested_cmd_clause(#{name:=Name,arguments:=Args,commands:=Cmds},Prevs,Depth) ->
Opts = [{S,L} || #{short:=S, long:=L} <- Args],
{Shorts0,Longs0} = lists:unzip(Opts),
Defined = fun(Opt) -> Opt =/= undefined end,
Shorts = lists:filter(Defined, Shorts0),
Longs = lists:filter(Defined, Longs0),
SOpts = lists:join(" ",
[[$-,S] || S <- Shorts]),
LOpts = lists:join(" ",
["--"++L || L <- Longs]),
Cmdsnvars = lists:join(" ",
[N || #{name:=N} <- Cmds]),
IfBody = match_prev_if_body([Name | Prevs]),
ClauseHead = ["elif [[ ",IfBody," ]] ; then\n"],
ClauseBody = [" sopts=\"",SOpts,"\"\n",
" lopts=\"",LOpts,"\"\n",
" cmdsnvars=\"",Cmdsnvars,"\"\n"],
Nested = [nested_cmd_clause(C, [Name | Prevs], Depth+1) || C <- Cmds],
[ClauseHead,ClauseBody,Nested].
match_prev_if_body([P | Rest]) ->
lists:join(" && ",
do_match_prev_if_body([P | Rest],1)).
do_match_prev_if_body([],_) ->
[];
do_match_prev_if_body([P | Rest],Cnt) ->
[["${prev",?str(Cnt),"} == ",P] | do_match_prev_if_body(Rest,Cnt+1)].
main(Commands, #{shell:=bash, aliases:=Aliases}) ->
MaxDepth=cmd_depth(Commands,1,0),
CmdNames = [Name || #{name:=Name} <- Commands],
Triggers = ["rebar3" | Aliases],
TriggerConds = [["${prev1} == \"",T,"\""] || T <- Triggers],
Trigger = lists:join(" || ", TriggerConds),
IfTriggerThen = ["if [[ ",Trigger," ]] ; then\n"],
["_rebar3_ref_idx() {\n",
" startc=$1\n",
" # is at least one of the two previous words a flag?\n",
" prev=${COMP_CWORD}-${startc}+1\n",
" if [[ ${COMP_WORDS[${prev}]} == -* || ${COMP_WORDS[${prev}-1]} == -* ]] ; then\n",
" startc=$((startc+1))\n",
" _rebar3_ref_idx $startc\n",
" fi\n",
" return $startc\n",
"}\n",
"\n",
"_rebar3(){\n",
" local cur sopts lopts cmdsnvars refidx \n",
" local ",lists:join(" ", ["prev"++?str(I) || I <- lists:seq(1, MaxDepth)]),"\n",
" COMPREPLY=()\n",
" _rebar3_ref_idx ",?str(MaxDepth),"\n",
" refidx=$?\n",
" cur=\"${COMP_WORDS[COMP_CWORD]}\"\n",
prev_definitions(MaxDepth,1),
" ",IfTriggerThen,
" sopts=\"-h -v\"\n"
" lopts=\"--help --version\"\n",
" cmdsnvars=\"",lists:join(" \\\n", CmdNames),"\"\n",
" ",[cmd_clause(Cmd) || Cmd <- Commands],
" fi\n",
" COMPREPLY=( $(compgen -W \"${sopts} ${lopts} ${cmdsnvars} \" -- ${cur}) )\n",
" if [ -n \"$COMPREPLY\" ] ; then\n",
" # append space if matched\n",
" COMPREPLY=\"${COMPREPLY} \"\n",
" # remove trailing space after equal sign\n",
" COMPREPLY=${COMPREPLY/%= /=}\n",
" fi\n",
" return 0\n",
"}\n"].
prev_definitions(MaxDepth, Cnt) when (Cnt-1)=:=MaxDepth ->
[];
prev_definitions(MaxDepth, Cnt) ->
P = [" prev",?str(Cnt),"=\"${COMP_WORDS[COMP_CWORD-${refidx}+",?str((MaxDepth-Cnt)),"]}\"\n"],
[P | prev_definitions(MaxDepth,Cnt+1)].
cmd_depth([], _, Max) ->
Max;
cmd_depth([#{commands:=[]} | Rest],Depth,Max) ->
cmd_depth(Rest,Depth,max(Depth,Max));
cmd_depth([#{commands:=Cmds} | Rest],Depth, Max) ->
D = cmd_depth(Cmds, Depth+1, Max),
cmd_depth(Rest, Depth, max(D,Max));
cmd_depth([_ | Rest],Depth,Max) ->
cmd_depth(Rest,Depth,max(Depth,Max)).
complete(#{shell:=bash, aliases:=Aliases}) ->
Triggers = ["rebar3" | Aliases],
[["complete -o nospace -F _rebar3 ", Trigger, "\n"] || Trigger <- Triggers].

View File

@ -0,0 +1,165 @@
%% @doc Generates shell completion files based on available providers and their opts.
%% @end
-module(rebar_prv_completion).
-behaviour(provider).
-export([init/1,
do/1,
format_error/1]).
-include_lib("providers/include/providers.hrl").
-include("rebar.hrl").
-define(PROVIDER, completion).
-define(DEPS, [app_discovery]).
-define(DEF_SHELL, bash).
%% ===================================================================
%% Public API
%% ===================================================================
-spec init(rebar_state:t()) -> {ok, rebar_state:t()}.
init(State) ->
AliasesHelp = "Comma separated list of OS level aliases on which rebar3 completion will be triggered (e.g. \"rebar\" or \"r3\").",
AliasesOpt = {aliases, $a, "aliases", string, AliasesHelp},
FileHelp = "Completion file name. Relative to \"_build/\".",
FileOpt = {file, $f, "file", string, FileHelp},
ShellHelp = "Shell type, 'bash' or 'zsh'.",
ShellOpt = {shell, $s, "shell", atom, ShellHelp},
Provider = providers:create([{name, ?PROVIDER},
{module, ?MODULE},
{bare, true},
{deps, ?DEPS},
{example, "rebar3 completion"},
{short_desc, "Generate completion file for your shell."},
{desc, "Generate completion file for your shell."},
{opts, [AliasesOpt, FileOpt, ShellOpt]}]),
State1 = rebar_state:add_provider(State,Provider),
{ok, State1}.
-spec do(rebar_state:t()) -> {ok, rebar_state:t()} | {error, string()}.
do(State) ->
DefaultOpts = #{aliases => [],
file => "_rebar3",
shell => detect_shell()},
{CliOptsList, _} = rebar_state:command_parsed_args(State),
CliOpts = maps:from_list(CliOptsList),
Conf = maps:from_list(rebar_state:get(State, completion, [])),
%% Opts passed in CLI override config
CmplOpts0 = maps:merge(DefaultOpts, Conf),
CmplOpts = maps:merge(CmplOpts0, CliOpts),
Providers0 = rebar_state:providers(State),
BareProviders = lists:filter(fun(P) -> provider_get(P, bare) end, Providers0),
ByNamespace = maps:groups_from_list(fun(P) -> provider_get(P, namespace) end, BareProviders),
Cmds0 = maps:fold(
fun(NS,Ps,CmdAcc) -> namespace_to_cmpl_cmds(NS, Ps)++CmdAcc end,
[],
ByNamespace),
Cmds = [oracle(Cmd, CmplOpts, State) || Cmd <- Cmds0],
Compl = rebar_completion:generate(Cmds, CmplOpts),
write_completion(Compl,State,CmplOpts),
{ok, State}.
detect_shell() ->
case os:getenv("SHELL") of
false ->
?DIAGNOSTIC("SHELL variable not set, default shell will be used.",
[]),
?DEF_SHELL;
Path ->
to_shell(filename:basename(Path))
end.
to_shell("bash") -> bash;
to_shell("zsh") -> zsh;
to_shell(Unsupp) ->
?WARN("Unsupported shell found: ~p, default shell will be used.",
[Unsupp]),
?DEF_SHELL.
-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);
namespace_to_cmpl_cmds(Namespace,Providers) ->
Name = atom_to_list(Namespace),
[#{name=>Name,
commands=>lists:map(fun(P)->provider_to_cmpl_cmd(P) end, Providers),
arguments=>[],
help=>Name++" namespace"}].
-spec provider_to_cmpl_cmd(providers:t()) -> rebar_completion:cmpl_cmd().
provider_to_cmpl_cmd(Provider) ->
Opts = providers:opts(Provider),
Name = providers:impl(Provider),
Cmd = getopt_to_cmpl_cmd(atom_to_list(Name),Opts),
Help = provider_get(Provider, short_desc),
Cmd#{help=>Help}.
-spec getopt_to_cmpl_cmd(string(), [tuple()]) -> rebar_completion:cmpl_cmd().
getopt_to_cmpl_cmd(Name, Opts) ->
Args = [#{short=>S,
long=>L,
type=>cmpl_arg_type(Spec),
help=>H} || {_,S,L,Spec,H} <- Opts],
#{name => Name,
arguments => Args,
commands => [],
help => undefined}.
cmpl_arg_type({Type,_Default}) ->
Type;
cmpl_arg_type(Type) ->
Type.
%% ad-hoc injection of data for some known providers!
-spec oracle(rebar_completion:cmpl_cmd(),
rebar_completion:cmpl_opts(),
rebar_state:t()) -> rebar_completion:cmpl_cmd().
oracle(#{name:="as"}=Cmd, _CmplOpts, State) ->
%% profile completion
ConfigProfiles = rebar_opts:get(rebar_state:opts(State), profiles, []),
Args = [#{short=>undefined,
long=>atom_to_list(ProfileName),
help=>undefined,
type=>string} || {ProfileName,_} <- ConfigProfiles],
Cmd#{arguments=>Args};
oracle(Cmd,_,_) ->
Cmd.
-spec write_completion(iolist(), rebar_state:t(), rebar_completion:cmpl_opts()) -> ok.
write_completion(CompletionStr, State, #{shell:=Shell, file:=Filename}) ->
BaseDir = rebar_dir:base_dir(State),
Dest = filename:join(BaseDir, Filename),
case filelib:ensure_dir(Dest) of
ok ->
?DIAGNOSTIC("Writing completion file for ~p shell to: ~p~n",
[Shell, Dest]),
case file:write_file(Dest, CompletionStr, [write, raw]) of
ok ->
ok;
{error,Err} ->
throw(?PRV_ERROR({error_writing_file,Dest,Err}))
end;
{error,Err} ->
throw(?PRV_ERROR({error_creating_dir,filename:dirname(Dest),Err}))
end.
%% for some reason providers don't expose some of their attributes via API
provider_get(P, bare) ->
element(5, P);
provider_get(P, short_desc) ->
element(8, P);
provider_get(P, namespace) ->
element(12, P).
-spec format_error(any()) -> iolist().
format_error({error_writing_file,File,Err}) ->
io_lib:format("Error occurred when trying to write into ~p file.~nReason: ~p~n", [File,Err]);
format_error({error_creating_dir,Dir,Err}) ->
io_lib:format("Error occurred when trying to create dir: ~p.~nReason: ~p~n", [Dir,Err]).

View File

@ -0,0 +1,68 @@
-module(rebar_completion_SUITE).
-compile([export_all, nowarn_export_all]).
-include_lib("common_test/include/ct.hrl").
suite() ->
[].
all() ->
[test_competion_gen, check_bash].
groups() ->
[].
init_per_suite(Config) ->
Shells = [bash],
ComplFile = compl_file(Config),
ok = filelib:ensure_dir(ComplFile),
[{compl_file, ComplFile}, {shells, Shells} | Config].
end_per_suite(_Config) ->
ok.
init_per_testcase(_, Config) ->
rebar_test_utils:init_rebar_state(Config, "completion_").
end_per_testcase(_, _Config) ->
ok.
%% test cases
test_competion_gen(Config) ->
Shells = ?config(shells, Config),
ComplFile = ?config(compl_file, Config),
lists:foreach(fun(Shell) ->
file:delete(ComplFile),
completion_gen(Config, #{shell=>Shell, file=>ComplFile}),
{Shell, true} = {Shell,filelib:is_file(ComplFile)}
end,
Shells).
check_bash(Config) ->
ComplFile = ?config(compl_file, Config),
Aliases = ["rebar", "r3"],
Opts = #{shell => bash,
file => ComplFile,
aliases => Aliases},
completion_gen(Config, Opts),
{ok, Completion} = file:read_file(ComplFile),
%% function definition
{match, _} = re:run(Completion, "_rebar3\\(\\)\\{"),
%% aliases
CompleteCmd = "complete -o nospace -F _rebar3 ",
lists:foreach(fun(Alias) ->
{Alias, {match, _}} = {Alias, re:run(Completion, CompleteCmd++Alias++"\n")}
end,
["rebar3" | Aliases]).
%% helpers
completion_gen(Config, CmplOpts) ->
CmplConf = maps:to_list(CmplOpts),
Res = rebar_test_utils:run_and_check(Config, [{completion,CmplConf}], ["completion"], return),
{ok, _} = Res.
compl_file(Config) ->
filename:absname(filename:join(?config(priv_dir,Config), "_rebar3")).