Skip to content

Commit

Permalink
stdlib: enhances the shell completion
Browse files Browse the repository at this point in the history
Adds completion support for bindings, atoms, records, maps and filepaths
including map keys and record fields and function parameters.
Support for attribute expressions -type, -spec and -record in the shell.
  • Loading branch information
frazze-jobb committed Jul 5, 2022
1 parent 33deeff commit 3ac4520
Show file tree
Hide file tree
Showing 16 changed files with 2,832 additions and 761 deletions.
57 changes: 50 additions & 7 deletions lib/kernel/src/code.erl
Expand Up @@ -71,6 +71,7 @@
start_link/0,
which/1,
get_doc/1,
get_doc/2,
where_is_file/1,
where_is_file/2,
set_primary_archive/4,
Expand Down Expand Up @@ -860,15 +861,47 @@ where_is_file(Tail, File, Path, Files) ->
Res :: #docs_v1{},
Reason :: non_existing | missing | file:posix().
get_doc(Mod) when is_atom(Mod) ->
get_doc(Mod, #{sources => [eep48, debug_info]}).
% get_doc_maybe(Mod, #{sources:=[Source|Sources]}=Options) ->
% maybe
% {ok, Filename} ?= case which(Mod) of
% preloaded ->
% {ok, filename:join([code:lib_dir(erts),"preloaded/ebin",atom_to_list(Mod) ++ ".beam"])};
% Error when is_atom(Error) -> {error,Error};
% Fn -> {ok, Fn}
% end,
% {error, missing} ?= case Source of
% debug_info -> get_doc_chunk_from_ast(Filename);
% eep48 -> get_doc_chunk(Filename, Mod)
% end,
% get_doc(Mod, Options#{sources=>Sources})
% end.
get_doc(Mod, #{sources:=[Source|Sources]}=Options) ->
case which(Mod) of
preloaded ->
Fn = filename:join([code:lib_dir(erts),"ebin",atom_to_list(Mod) ++ ".beam"]),
get_doc_chunk(Fn, Mod);
Fn = filename:join([code:lib_dir(erts),"preloaded/ebin",atom_to_list(Mod) ++ ".beam"]),
R = case Source of
debug_info -> get_doc_chunk_from_ast(Fn);
eep48 -> get_doc_chunk(Fn, Mod)
end,
case R of
{error, missing} -> get_doc(Mod, Options#{sources=>Sources});
_ -> R
end;
Error when is_atom(Error) ->
{error, Error};
Fn ->
get_doc_chunk(Fn, Mod)
end.
R = case Source of
debug_info -> get_doc_chunk_from_ast(Fn);
eep48 -> get_doc_chunk(Fn, Mod)
end,
case R of
{error, missing} -> get_doc(Mod, Options#{sources=>Sources});
_ -> R
end
end;
get_doc(_, #{sources:=[]}) ->
{error, missing}.

get_doc_chunk(Filename, Mod) when is_atom(Mod) ->
case beam_lib:chunks(Filename, ["Docs"]) of
Expand Down Expand Up @@ -907,21 +940,31 @@ get_doc_chunk_from_ast(Filename) ->
{ok, {_Mod, [{abstract_code,
{raw_abstract_v1, AST}}]}} ->
Docs = get_function_docs_from_ast(AST),
Types = get_type_docs_from_ast(AST),
{ok, #docs_v1{ anno = 0, beam_language = erlang,
module_doc = none,
metadata = #{ generated => true, otp_doc_vsn => ?CURR_DOC_VERSION },
docs = Docs }};
metadata = #{ generated => true, otp_doc_vsn => ?CURR_DOC_VERSION},
docs = Docs++Types }};
{ok, {_Mod, [{abstract_code,no_abstract_code}]}} ->
{error,missing};
Error ->
Error
end.

get_type_docs_from_ast(AST) ->
lists:flatmap(fun(E) -> get_type_docs_from_ast(E, AST) end, AST).
get_type_docs_from_ast({attribute, Anno, type, {TypeName, _, Ps}}=Meta, _) ->
Arity = length(Ps),
Signature = io_lib:format("~p/~p",[TypeName,Arity]),
[{{type, TypeName, Arity},Anno,[unicode:characters_to_binary(Signature)],none,#{signature => [Meta]}}];
get_type_docs_from_ast(_, _) ->
[].

get_function_docs_from_ast(AST) ->
lists:flatmap(fun(E) -> get_function_docs_from_ast(E, AST) end, AST).
get_function_docs_from_ast({function,Anno,Name,Arity,_Code}, AST) ->
Signature = io_lib:format("~p/~p",[Name,Arity]),
Specs = lists:filter(
Specs = lists:filter(
fun({attribute,_Ln,spec,{FA,_}}) ->
case FA of
{F,A} ->
Expand Down

0 comments on commit 3ac4520

Please sign in to comment.