Skip to content

Commit

Permalink
Fix two bugs
Browse files Browse the repository at this point in the history
nested terms, not inside a function
i.e {li
and autocomplete terms of function without type spec
  • Loading branch information
frazze-jobb committed Aug 22, 2022
1 parent 05f0018 commit 10fbf29
Show file tree
Hide file tree
Showing 4 changed files with 17 additions and 4 deletions.
11 changes: 9 additions & 2 deletions lib/stdlib/src/edlin_context.erl
Expand Up @@ -88,10 +88,17 @@ get_context([$?|_], _) ->
{macro};
get_context(Bef0, Word) when is_list(Word) ->
get_context(lists:reverse(Word) ++ Bef0, #context{});
get_context([], #context{arguments = Args, parameter_count = Count} = _CR) ->
get_context([], #context{arguments = Args, parameter_count = Count, nestings = Nestings} = _CR) ->
case Count+1 == length(Args) of
true -> {term, lists:droplast(Args), lists:last(Args)};
_ -> {term, Args, []}
_ ->
%% Nestings will not end up as an argument
case Nestings of
[] -> {term, Args, []};
[{list, Args1, Arg}] -> {term, Args1, Arg};
[{tuple, Args1, Arg}] -> {term, Args1, Arg};
[{map, _, _, Args1, Arg}] -> {term, Args1, Arg}
end
end;
get_context([$(|Bef], CR) ->
%% We have an unclosed opening parenthesis
Expand Down
5 changes: 4 additions & 1 deletion lib/stdlib/src/edlin_expand.erl
Expand Up @@ -528,7 +528,10 @@ expand_function_type(ModStr, FunStr, Args, Unfinished, Nestings, FT) ->
FunTypes = edlin_type_suggestion:get_function_type(Mod, Fun, Arity, FT),
case FunTypes of
[] -> MFA = print_function_head(ModStr, FunStr, Arity),
{no, [], [#section{title=MFA, elems=[]}]};
case Unfinished of
[] -> {no, [], [#section{title=MFA, elems=[]}]};
_ -> {no, [], []}
end;
_ ->
fold_results([begin
MFA = print_function_head(ModStr, FunStr, FunType, FT),
Expand Down
4 changes: 3 additions & 1 deletion lib/stdlib/test/edlin_context_SUITE.erl
Expand Up @@ -60,7 +60,9 @@ get_context(_Config) ->
{function, "file", "open", [{string, "\"\""}], [], [{list, [], []},{tuple, [], {atom, "atom"}}]} = edlin_context:get_context(lists:reverse("file:open(\"\",[{atom")),
{function, "file", "open", [{string, "\"\""}], [], [{list, [], []},{tuple, [{atom, "atom"}], []}]} = edlin_context:get_context(lists:reverse("file:open(\"\",[{atom,")),
{function, "file", "open", [{string, "\"\""}], [], [{map, ["atom"], "atom", [], []}]} = edlin_context:get_context(lists:reverse("file:open(\"\",#{ atom =>")),
{term, [], []} = edlin_context:get_context(lists:reverse("#{")),
{term, [], {atom, "list"}} = edlin_context:get_context(lists:reverse("#{list")),
{term, [], {atom, "list"}} = edlin_context:get_context(lists:reverse("{list")),
{term, [], {atom, "list"}} = edlin_context:get_context(lists:reverse("[list")),
{map, "M", []} = edlin_context:get_context(lists:reverse("M#{")),
{map, "M", []} = edlin_context:get_context(lists:reverse("M#{key")),
{map, "M", ["key"]} = edlin_context:get_context(lists:reverse("M#{key=>")),
Expand Down
1 change: 1 addition & 0 deletions lib/stdlib/test/edlin_expand_SUITE.erl
Expand Up @@ -205,6 +205,7 @@ function_parameter_completion(Config) ->
%% test that getting type of out of bound parameter does not trigger crash
compile_and_load2(Config,complete_function_parameter),
{no, [], [#section{title="complete_function_parameter:an_untyped_fun/2", elems=[]}]} = do_expand("complete_function_parameter:an_untyped_fun("),
{yes, ":", _} = do_expand("complete_function_parameter:an_untyped_fun(lists"),
{no, [], [#section{elems=[#section{title="types",elems=[{"integer()",[]}]}]}]} = do_expand("complete_function_parameter:a_fun_name("),
{no, [], [#section{elems=[#section{elems=[{"integer()",[]}]}]}]} = do_expand("complete_function_parameter:a_fun_name(1,"),
{no, [], [#section{elems=[#section{elems=[{"integer()",[]}]}]}]} = do_expand("complete_function_parameter : a_fun_name ( 1 , "),
Expand Down

0 comments on commit 10fbf29

Please sign in to comment.