Skip to content

Commit

Permalink
Merge pull request #8375 from garazdawi/lukas/stdlib/edlin-fixes/OTP-…
Browse files Browse the repository at this point in the history
…19073

Various edlin expand fixes
  • Loading branch information
garazdawi authored Apr 19, 2024
2 parents 75d5435 + fb4e417 commit fbbff8a
Show file tree
Hide file tree
Showing 4 changed files with 30 additions and 10 deletions.
7 changes: 6 additions & 1 deletion lib/stdlib/src/edlin_expand.erl
Original file line number Diff line number Diff line change
Expand Up @@ -480,7 +480,12 @@ expand_function_parameter_type(Mod, MFA, FunType, Args, Unfinished, Nestings, FT
end,
case match_arguments(TypeTree, Args) of
false -> {no, [], []};
true when Parameters == [] -> {yes, ")", [#{title=>MFA, elems=>[")"], options=>[]}]};
true when Parameters == [] ->
if Nestings == [] ->
{yes, ")", [#{title=>MFA, elems=>[{")",[]}], options=>[]}]};
true ->
{no, [], []}
end;
true ->
Parameter = lists:nth(length(Args)+1, Parameters),
{T, _Name} = case Parameter of
Expand Down
11 changes: 8 additions & 3 deletions lib/stdlib/src/edlin_type_suggestion.erl
Original file line number Diff line number Diff line change
Expand Up @@ -295,7 +295,9 @@ get_arity1({map, Types}, _Constraints, [{'map', _Keys, [], _, _}]) ->
get_arity1({map, Types}, _Constraints, [{'map', _Keys, _Key, _, _}]) ->
length(Types);
get_arity1({map, Types}, Constraints, [{'map', Keys, [], _, _}|Nestings]) ->
lists:flatten([get_arity1(T, Constraints, Nestings) || {_, Key, _}=T <- Types, not lists:member(atom_to_list(Key), Keys)]);
lists:flatten([get_arity1(T, Constraints, Nestings) ||
{_, Key, _}=T <- Types,
not lists:member(catch atom_to_list(Key), Keys)]);
get_arity1({map, Types}, Constraints, [{'map', _Keys, Key, _, _}|Nestings]) ->
case [V || {_, K, V} <- Types, K =:= list_to_atom(Key)] of
[] -> none;
Expand Down Expand Up @@ -334,7 +336,9 @@ get_atoms1({tuple, LT}, Constraints, [{'tuple', Args, _}|Nestings]) when length(
false -> []
end;
get_atoms1({map, Types}, Constraints, [{'map', Keys, [], _, _}|Nestings]) ->
lists:flatten([get_atoms1(T, Constraints, Nestings) || {_, Key, _}=T <- Types, not lists:member(atom_to_list(Key), Keys)]);
lists:flatten([get_atoms1(T, Constraints, Nestings) ||
{_, Key, _}=T <- Types,
not lists:member(catch atom_to_list(Key), Keys)]);
get_atoms1({map, Types}, Constraints, [{'map', _Keys, Key, _, _}|Nestings]) ->
case [V || {_, K, V} <- Types, K =:= list_to_atom(Key)] of
[] -> [];
Expand Down Expand Up @@ -379,7 +383,8 @@ get_types1({tuple, LT}, Cs, [{tuple, Args, _}|Nestings], MaxUserTypeExpansions,
false -> []
end;
get_types1({'map', Types}, Cs, [{'map', Keys, [], _Args, _}|Nestings], MaxUserTypeExpansions, Options) ->
lists:flatten([get_types1(T, Cs, Nestings, MaxUserTypeExpansions, Options) || {_, Key, _}=T <- Types, not lists:member(atom_to_list(Key), Keys)]);
lists:flatten([get_types1(T, Cs, Nestings, MaxUserTypeExpansions, Options) ||
{_, Key, _}=T <- Types, not lists:member(catch atom_to_list(Key), Keys)]);
get_types1({'map', Types}, Cs, [{'map', _, Key, _Args, _}|Nestings], MaxUserTypeExpansions, Options) ->
case [V || {_, K, V} <- Types, K =:= list_to_atom(Key)] of
[] -> [];
Expand Down
15 changes: 10 additions & 5 deletions lib/stdlib/test/edlin_expand_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -259,6 +259,10 @@ function_parameter_completion(Config) ->
{no, [], [#{elems:=[#{elems:=[#{elems:=[{"any()",[]},{"[any() | [Deeplist]]",[]}]}]}]}]} = do_expand("complete_function_parameter:a_deeplist_fun("),
{no,[],[#{title:="typespecs",
elems:=[#{title:=
"complete_function_parameter:multi_arity_fun()",
options:=[],
elems:=[{")",[]}]},
#{title:=
"complete_function_parameter:multi_arity_fun(T1)",
elems:=[#{title:="types",
elems:=[{"integer()",[]}],
Expand All @@ -269,13 +273,10 @@ function_parameter_completion(Config) ->
elems:=[#{title:="types",
elems:=[{"integer()",[]}],
options:=[{hide,title}]}],
options:=[{highlight_param,1}]},
#{title:=
"complete_function_parameter:multi_arity_fun()",
options:=[],
elems:=[")"]}],
options:=[{highlight_param,1}]}],
options:=[highlight_all]}]} = do_expand("complete_function_parameter:multi_arity_fun("),
{no, [], [#{elems:=[#{elems:=[#{elems:=[{"true",[]},{"false",[]}]}]}]}]} = do_expand("complete_function_parameter:multi_arity_fun(1,"),
{no, [], []} = do_expand("complete_function_parameter:multi_arity_fun(["),
{no,[],
[#{elems :=
[#{elems :=
Expand Down Expand Up @@ -362,6 +363,10 @@ get_coverage(Config) ->
do_expand("complete_function_parameter:map_parameter_function(#{}, "),
do_expand("complete_function_parameter:map_parameter_function(#{V=>1}, "),
do_expand("complete_function_parameter:map_parameter_function(#{a=>V}, "),
do_expand("complete_function_parameter:map_variable_parameter_function(#{"),
do_expand("complete_function_parameter:map_variable_parameter_function(#{a"),
do_expand("complete_function_parameter:map_variable_parameter_function(#{a => "),
do_expand("complete_function_parameter:map_variable_parameter_function(#{a => a"),
do_expand("complete_function_parameter:tuple_parameter_function({a,b}, "),
do_expand("complete_function_parameter:tuple_parameter_function({a,V}, "),
do_expand("complete_function_parameter:list_parameter_function([], "),
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,7 @@
'emoji_function🤯'/1,
map_parameter_function/1,
map_parameter_function/2,
map_variable_parameter_function/2,
tuple_parameter_function/2,
list_parameter_function/2,
non_empty_list_parameter_function/2,
Expand Down Expand Up @@ -108,11 +109,15 @@ test_year(_Y) -> 0.
'emoji_function🤯'(_) -> 0.

-spec map_parameter_function(Map) -> boolean() when
Map :: #{a => 1, b => 2, c => 3, d => error}.
Map :: #{ integer() := a, a => 1, b => 2, c => 3, d => error}.
map_parameter_function(_) -> false.
-spec map_parameter_function(Map, any()) -> boolean() when
Map :: #{a => 1, b => 2, c => 3, d => error}.
map_parameter_function(_,_) -> false.
-spec map_variable_parameter_function(Key, Map) -> Value when
Map :: #{ Key => Value, _ => _}.
map_variable_parameter_function(_, _) ->
false.

-spec binary_parameter_function(binary(), any()) -> boolean().
binary_parameter_function(_,_) -> false.
Expand Down

0 comments on commit fbbff8a

Please sign in to comment.