Skip to content

Commit

Permalink
stdlib: Include specs in docs_v1 for testing purposes
Browse files Browse the repository at this point in the history
We do this so that when a module in the test set it updated
this testcase does not also need to be updated.
  • Loading branch information
garazdawi committed Oct 21, 2024
1 parent 8ae206c commit ac65ad0
Show file tree
Hide file tree
Showing 7 changed files with 71 additions and 50 deletions.
52 changes: 19 additions & 33 deletions lib/stdlib/src/shell_docs.erl
Original file line number Diff line number Diff line change
Expand Up @@ -857,41 +857,27 @@ render_function(FDocs, #docs_v1{ docs = Docs } = D, Config) ->
end, Grouping).

%% Render the signature of either function, type, or anything else really.
render_signature({{Type,F,A},_Anno,_Sigs,_Docs,Meta}=AST, Specs) ->
MetaSpec = render_meta(Meta),
maybe
M = maps:get(Type, Specs, undefined),
true ?= is_map(M),
{_, _, _, _}=Spec0 ?= maps:get({F, A}, M, undefined),
render_ast(Spec0, MetaSpec)
else
_ ->
{AltSpecs,AltFun} = meta_and_renderer(AST, MetaSpec),
lists:flatmap(AltFun, AltSpecs)
render_signature({{_Type,_F,_A},_Anno,_Sigs,_Docs,#{ signature := Specs } = Meta}, _ASTSpecs) ->
lists:map( fun render_ast/1,Specs) ++ [render_meta(Meta)];
render_signature({{Type,F,A},_Anno,Sigs,_Docs,Meta}, Specs) ->
case maps:find({F, A}, maps:get(Type, Specs, #{})) of
{ok, Spec} ->
[render_ast(Spec) | render_meta(Meta)];
error ->
lists:map(fun(Sig) -> {h2,[],[<<"  "/utf8,Sig/binary>>]} end, Sigs) ++ [render_meta(Meta)]
end.

meta_and_renderer({{_Type,_F,_A},_Anno,Sigs,_Docs, Meta}, MetaSpec) ->
case Meta of
#{ signature := Specs} ->
{Specs, fun(AST0) -> render_ast(AST0, MetaSpec) end};
_ ->
{Sigs, fun (Sig) ->
[{h2,[],[<<"  "/utf8,Sig/binary>>]}|MetaSpec]
end}
end.


render_ast(AST, Meta) ->
PPSpec = erl_pp:attribute(AST,[{encoding,unicode}]),
Spec = case AST of
{_Attribute, _Line, opaque, _} ->
%% We do not want show the internals of the opaque type
hd(string:split(PPSpec,"::"));
_ ->
PPSpec
end,
BinSpec = unicode:characters_to_binary(string:trim(Spec, trailing, "\n")),
[{pre,[],[{strong,[],BinSpec}]} | Meta].
render_ast(AST) ->
PPSpec = erl_pp:attribute(AST,[{encoding,unicode}]),
Spec = case AST of
{_Attribute, _Line, opaque, _} ->
%% We do not want show the internals of the opaque type
hd(string:split(PPSpec,"::"));
_ ->
PPSpec
end,
BinSpec = unicode:characters_to_binary(string:trim(Spec, trailing, "\n")),
{pre,[],[{strong,[],BinSpec}]}.

render_meta(M) ->
case render_meta_(M) of
Expand Down
59 changes: 47 additions & 12 deletions lib/stdlib/test/shell_docs_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -90,7 +90,6 @@ render(Config) ->

lists:foreach(
fun(Module) ->
{ok, [D]} = file:consult(filename:join(DataDir, atom_to_list(Module) ++ ".docs_v1")),
maps:map(
fun(FName, Current) ->
case file:read_file(filename:join(DataDir,FName)) of
Expand All @@ -106,7 +105,7 @@ render(Config) ->
%% available on windows.
ok
end
end, render_module(Module, D))
end, render_module(Module, DataDir))
end, ?RENDER_MODULES).

update_render() ->
Expand All @@ -117,19 +116,52 @@ update_render(DataDir) ->
lists:foreach(
fun(Module) ->
case code:get_doc(Module) of
{ok, D} ->
{ok, Docs} ->
NewEntries =
case beam_lib:chunks(find_path(Module),[abstract_code]) of
{ok,{Module,[{abstract_code,{raw_abstract_v1,AST}}]}} ->
lists:map(fun({{Type, F, A}, Anno, Sig, #{} = Doc, Meta} = E) ->

case lists:search(
fun({attribute, _, spec, {FA, _}}) when Type =:= function ->
FA =:= {F,A};
({attribute, _, What, {Name, _, Args}}) when What =:= Type; What =:= opaque andalso Type =:= type ->
{Name,length(Args)} =:= {F,A};
(_) ->
false
end, AST) of
{value, Signature} ->
{{Type, F, A}, Anno, Sig, Doc, Meta#{ specification => [Signature] }};
_ -> throw({did_not_find, E})
end;
(E) -> E

end, Docs#docs_v1.docs);
{ok,{shell_docs_SUITE,[{abstract_code,no_abstract_code}]}} ->
Docs#docs_v1.docs
end,

ok = file:write_file(
filename:join(DataDir, atom_to_list(Module) ++ ".docs_v1"),
io_lib:format("~w.",[D])),
maps:map(
fun(FName, Output) ->
ok = file:write_file(filename:join(DataDir, FName), Output)
end, render_module(Module, D));
E ->
io:format("Error processing: ~p ~p",[Module, E])
end
io_lib:format("~w.",[Docs#docs_v1{ docs = NewEntries }]));
{error, _} ->
ok
end,
maps:map(
fun(FName, Output) ->
ok = file:write_file(filename:join(DataDir, FName), Output)
end, render_module(Module, DataDir))
end, ?RENDER_MODULES).

find_path(Module) ->
maybe
preloaded ?= code:which(Module),
PreloadedPath = filename:join(code:lib_dir(erts),"ebin"),
filename:join(PreloadedPath, atom_to_list(Module) ++ ".beam")
else
Other -> Other
end.

handle_error({error,_}) ->
ok;
handle_error(Doc) ->
Expand Down Expand Up @@ -461,7 +493,10 @@ render_module(Mod, #docs_v1{ docs = Docs } = D) ->
FName = SMod ++ "_"++atom_to_list(Name)++"_"++integer_to_list(Arity)++"_cb.txt",
Acc#{ sanitize(FName) =>
unicode:characters_to_binary(shell_docs:render_callback(Mod, Name, Arity, D, Opts))}
end, Files, Docs).
end, Files, Docs);
render_module(Mod, Datadir) ->
{ok, [Docs]} = file:consult(filename:join(Datadir, atom_to_list(Mod) ++ ".docs_v1")),
render_module(Mod, Docs).

sanitize(FName) ->
lists:foldl(
Expand Down
2 changes: 1 addition & 1 deletion lib/stdlib/test/shell_docs_SUITE_data/erlang.docs_v1

Large diffs are not rendered by default.

2 changes: 1 addition & 1 deletion lib/stdlib/test/shell_docs_SUITE_data/file.docs_v1

Large diffs are not rendered by default.

2 changes: 1 addition & 1 deletion lib/stdlib/test/shell_docs_SUITE_data/re.docs_v1

Large diffs are not rendered by default.

Original file line number Diff line number Diff line change
@@ -1 +1 @@
{docs_v1,{22,2},erlang,<<116,101,120,116,47,109,97,114,107,100,111,119,110>>,hidden,#{otp_doc_vsn => {1,0,0}},[{{function,execute,3},{494,1},[<<101,120,101,99,117,116,101,40,73,116,101,109,44,32,70,44,32,80,105,100,41>>],none,#{}},{{function,render_all,1},{404,1},[<<114,101,110,100,101,114,95,97,108,108,40,68,105,114,41>>],none,#{}},{{function,render_non_native,1},{385,1},[<<114,101,110,100,101,114,95,110,111,110,95,110,97,116,105,118,101,40,67,111,110,102,105,103,41>>],none,#{}},{{function,normalize,1},{366,1},[<<110,111,114,109,97,108,105,122,101,40,67,111,110,102,105,103,41>>],none,#{}},{{function,links,1},{310,1},[<<108,105,110,107,115,40,67,111,110,102,105,103,41>>],none,#{}},{{function,render_prop,1},{305,1},[<<114,101,110,100,101,114,95,112,114,111,112,40,67,111,110,102,105,103,41>>],none,#{}},{{function,render_callback,1},{210,1},[<<114,101,110,100,101,114,95,99,97,108,108,98,97,99,107,40,67,111,110,102,105,103,41>>],none,#{}},{{function,render_type,1},{187,1},[<<114,101,110,100,101,114,95,116,121,112,101,40,67,111,110,102,105,103,41>>],none,#{}},{{function,render_function,1},{158,1},[<<114,101,110,100,101,114,95,102,117,110,99,116,105,111,110,40,67,111,110,102,105,103,41>>],none,#{}},{{function,update_render,1},{116,1},[<<117,112,100,97,116,101,95,114,101,110,100,101,114,40,68,97,116,97,68,105,114,41>>],none,#{}},{{function,update_render,0},{112,1},[<<117,112,100,97,116,101,95,114,101,110,100,101,114,40,41>>],none,#{}},{{function,render,1},{87,1},[<<114,101,110,100,101,114,40,67,111,110,102,105,103,41>>],none,#{}},{{function,end_per_group,2},{69,1},[<<101,110,100,95,112,101,114,95,103,114,111,117,112,40,71,114,111,117,112,78,97,109,101,44,32,67,111,110,102,105,103,41>>],none,#{}},{{function,init_per_group,2},{64,1},[<<105,110,105,116,95,112,101,114,95,103,114,111,117,112,47,50>>],none,#{}},{{function,end_per_suite,1},{61,1},[<<101,110,100,95,112,101,114,95,115,117,105,116,101,40,67,111,110,102,105,103,41>>],none,#{}},{{function,init_per_suite,1},{57,1},[<<105,110,105,116,95,112,101,114,95,115,117,105,116,101,40,67,111,110,102,105,103,49,41>>],none,#{}},{{function,groups,0},{46,1},[<<103,114,111,117,112,115,40,41>>],none,#{}},{{function,all,0},{40,1},[<<97,108,108,40,41>>],none,#{}},{{function,suite,0},{37,1},[<<115,117,105,116,101,40,41>>],none,#{}}]}.
{docs_v1,{22,2},erlang,<<116,101,120,116,47,109,97,114,107,100,111,119,110>>,hidden,#{otp_doc_vsn => {1,0,0}},[{{function,execute,3},{529,1},[<<101,120,101,99,117,116,101,40,73,116,101,109,44,32,70,44,32,80,105,100,41>>],none,#{}},{{function,render_all,1},{436,1},[<<114,101,110,100,101,114,95,97,108,108,40,68,105,114,41>>],none,#{}},{{function,render_non_native,1},{417,1},[<<114,101,110,100,101,114,95,110,111,110,95,110,97,116,105,118,101,40,67,111,110,102,105,103,41>>],none,#{}},{{function,normalize,1},{398,1},[<<110,111,114,109,97,108,105,122,101,40,67,111,110,102,105,103,41>>],none,#{}},{{function,links,1},{342,1},[<<108,105,110,107,115,40,67,111,110,102,105,103,41>>],none,#{}},{{function,render_prop,1},{337,1},[<<114,101,110,100,101,114,95,112,114,111,112,40,67,111,110,102,105,103,41>>],none,#{}},{{function,render_callback,1},{242,1},[<<114,101,110,100,101,114,95,99,97,108,108,98,97,99,107,40,67,111,110,102,105,103,41>>],none,#{}},{{function,render_type,1},{219,1},[<<114,101,110,100,101,114,95,116,121,112,101,40,67,111,110,102,105,103,41>>],none,#{}},{{function,render_function,1},{190,1},[<<114,101,110,100,101,114,95,102,117,110,99,116,105,111,110,40,67,111,110,102,105,103,41>>],none,#{}},{{function,update_render,1},{115,1},[<<117,112,100,97,116,101,95,114,101,110,100,101,114,40,68,97,116,97,68,105,114,41>>],none,#{}},{{function,update_render,0},{111,1},[<<117,112,100,97,116,101,95,114,101,110,100,101,114,40,41>>],none,#{}},{{function,render,1},{87,1},[<<114,101,110,100,101,114,40,67,111,110,102,105,103,41>>],none,#{}},{{function,end_per_group,2},{69,1},[<<101,110,100,95,112,101,114,95,103,114,111,117,112,40,71,114,111,117,112,78,97,109,101,44,32,67,111,110,102,105,103,41>>],none,#{}},{{function,init_per_group,2},{64,1},[<<105,110,105,116,95,112,101,114,95,103,114,111,117,112,47,50>>],none,#{}},{{function,end_per_suite,1},{61,1},[<<101,110,100,95,112,101,114,95,115,117,105,116,101,40,67,111,110,102,105,103,41>>],none,#{}},{{function,init_per_suite,1},{57,1},[<<105,110,105,116,95,112,101,114,95,115,117,105,116,101,40,67,111,110,102,105,103,49,41>>],none,#{}},{{function,groups,0},{46,1},[<<103,114,111,117,112,115,40,41>>],none,#{}},{{function,all,0},{40,1},[<<97,108,108,40,41>>],none,#{}},{{function,suite,0},{37,1},[<<115,117,105,116,101,40,41>>],none,#{}}]}.
2 changes: 1 addition & 1 deletion lib/stdlib/test/shell_docs_SUITE_data/sofs.docs_v1

Large diffs are not rendered by default.

0 comments on commit ac65ad0

Please sign in to comment.