Skip to content

Commit

Permalink
shell_docs: fix links
Browse files Browse the repository at this point in the history
  • Loading branch information
kikofernandez committed Mar 4, 2024
1 parent 54ebbc9 commit 5ea526c
Show file tree
Hide file tree
Showing 4 changed files with 42 additions and 56 deletions.
2 changes: 1 addition & 1 deletion lib/stdlib/src/doc_html.erl
Original file line number Diff line number Diff line change
Expand Up @@ -310,7 +310,7 @@ format_link(Bin) when is_binary(Bin) ->
remove_square_brackets(Bin) when is_binary(Bin) ->
%% thanks to Elixir folks:
%% https://github.com/elixir-lang/elixir/blob/main/lib/elixir/lib/io/ansi/docs.ex#L626C22-L626C44
R = re:replace(Bin, "\\\[([^\\\]]*?)\\\]\\\((.*?)\\\)", "\\1 (\\2)"),
R = re:replace(Bin, "\\\[([^\\\]]*?)\\\]\\\((.*?)\\\)", "\\1"),
case R of
Text when is_list(Text) ->
list_to_binary(Text);
Expand Down
12 changes: 5 additions & 7 deletions lib/stdlib/src/shell_docs.erl
Original file line number Diff line number Diff line change
Expand Up @@ -528,15 +528,14 @@ render(_Module, Function, Arity, #docs_v1{ } = D) ->
Docs :: docs_v1(),
Config :: config(),
Res :: unicode:chardata() | {error,function_missing}.
render(Module, Function, Arity, #docs_v1{} = D, Config)
render(Module, Function, Arity, #docs_v1{ docs = Docs }=D, Config)
when is_atom(Module), is_atom(Function), is_integer(Arity), is_map(Config) ->
#docs_v1{ docs = Docs }=DocHtml = doc_html:markdown_to_shelldoc(D),
render_function(
lists:filter(fun({{function, F, A},_Anno,_Sig,_Doc,_Meta}) ->
F =:= Function andalso A =:= Arity;
(_) ->
false
end, Docs), DocHtml, Config).
end, Docs), D, Config).

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% API function for dealing with the type documentation
Expand Down Expand Up @@ -739,7 +738,7 @@ render_function([], _D, _Config) ->
{error,function_missing};
render_function(FDocs, D, Config) when is_map(Config) ->
render_function(FDocs, D, init_config(D, Config));
render_function(FDocs, #docs_v1{ docs = Docs } = DocV1, Config) ->
render_function(FDocs, #docs_v1{} = DocV1, Config) ->
#docs_v1{ docs = Docs }=D = doc_html:markdown_to_shelldoc(DocV1),
Grouping =
lists:foldl(
Expand Down Expand Up @@ -898,8 +897,7 @@ init_config(D, Config) ->

render_docs(Elems,State,Pos,Ind,D) when is_list(Elems) ->
lists:mapfoldl(fun(Elem,P) ->
%%% io:format("Elem: ~p (~p) (~p,~p)~n",[Elem,State,P,Ind]),
render_docs(Elem,State,P,Ind,D)
render_docs(Elem,State,P,Ind,D)
end,Pos,Elems);
render_docs(Elem,State,Pos,Ind,D) ->
render_element(Elem,State,Pos,Ind,D).
Expand Down Expand Up @@ -1228,5 +1226,5 @@ ansi(Curr) ->
end.

format_doc(Module) ->
{ok, Doc} = code:get_doc(Module),
{ok, Doc}=_R = code:get_doc(Module),
doc_html:markdown_to_shelldoc(Doc).
74 changes: 29 additions & 45 deletions lib/stdlib/test/doc_html_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -399,7 +399,6 @@ paragraph_after_heading_test(_Conf) ->
Expected = #{<<"en">> =>
[ header(1, <<"Header 1">>),
p(<<"This is text">>),
br(),
p(<<"Body content">>)]},
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
Expand Down Expand Up @@ -446,7 +445,6 @@ paragraph_between_code_test(_Conf) ->
HtmlDocs = compile(Docs),

Expected = expected([ p(<<"This is a paragraph">>),
br(),
code(<<"# Here\nThis is code\n Nested Line">>),
p(<<"Another paragraph">>)]),
Expected = extract_moduledoc(HtmlDocs),
Expand All @@ -459,7 +457,7 @@ single_line_fence_code_test(_Conf) ->
test() -> ok.
```">>),
HtmlDocs = compile(Docs),
Expected = expected([ br(), code(<<"test() -> ok.">>)]),
Expected = expected([ code(<<"test() -> ok.">>)]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.
Expand All @@ -471,7 +469,7 @@ test() ->
ok.
```">>),
HtmlDocs = compile(Docs),
Expected = expected([ br(), code(<<"test() ->\n ok.">>)]),
Expected = expected([ code(<<"test() ->\n ok.">>)]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.
Expand All @@ -494,19 +492,15 @@ test() ->
start_with_br_test(_Conf) ->
Docs = create_eep48_doc(<<"\n\nAnother paragraph">>),
HtmlDocs = compile(Docs),
Expected = expected([ br(),
br(),
p(<<"Another paragraph">>)]),
Expected = expected([ p(<<"Another paragraph">>)]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.

multiple_br_followed_by_paragraph_test(_Conf) ->
Docs = create_eep48_doc(<<"\nAnother paragraph\n\nAnother paragraph">>),
HtmlDocs = compile(Docs),
Expected = expected([ br(),
p(<<"Another paragraph">>),
br(),
Expected = expected([ p(<<"Another paragraph">>),
p(<<"Another paragraph">>)]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
Expand All @@ -532,7 +526,7 @@ by the elements of `List2`.
ending_br_test(_Conf) ->
Docs = create_eep48_doc(<<"Test\n">>),
HtmlDocs = compile(Docs),
Expected = expected([ p(<<"Test">>), br() ]),
Expected = expected([ p(<<"Test">>)]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.
Expand Down Expand Up @@ -651,7 +645,7 @@ unmatched_complex_format_with_inline(_Conf) ->
format_inline_link_with_inline(_Config) ->
Docs = create_eep48_doc(<<"[`splitwith/2`](`splitwith/2`) behaves as if">>),
HtmlDocs = compile(Docs),
Expected = expected([ p([inline_code(<<"splitwith/2">>),<<" (">>,inline_code(<<"splitwith/2">>), <<") behaves as if">>])]),
Expected = expected([ p([inline_code(<<"splitwith/2">>),<<" behaves as if">>])]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.
Expand All @@ -677,31 +671,31 @@ skip_symbols_in_inline(_Config) ->
singleton_bullet_list(_Config) ->
Docs = create_eep48_doc(<<"* One liner">>),
HtmlDocs = compile(Docs),
Expected = expected([ul([li(p(<<"One liner">>))]), br()]),
Expected = expected([ul([li(p(<<"One liner">>))])]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.

singleton_bullet_list_followed_new_paragraph(_Config) ->
Docs = create_eep48_doc(<<"* One liner\n\nThis is a new paragraph">>),
HtmlDocs = compile(Docs),
Expected = expected([ul([li(p(<<"One liner">>))]), br(), br(), p(<<"This is a new paragraph">>)]),
Expected = expected([ul([li(p(<<"One liner">>))]), p(<<"This is a new paragraph">>)]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.

singleton_bullet_list_followed_inner_paragraph(_Config) ->
Docs = create_eep48_doc(<<"* One liner\n This is a new paragraph">>),
HtmlDocs = compile(Docs),
Expected = expected([ul([li([p(<<"One liner">>), p(<<"This is a new paragraph">>)])]), br()]),
Expected = expected([ul([li([p([<<"One liner">>, <<"This is a new paragraph">>])])])]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.

singleton_bullet_list_followed_inner_paragraph2(_Config) ->
Docs = create_eep48_doc(<<"* One liner\nThis is a new paragraph">>),
HtmlDocs = compile(Docs),
Expected = expected([ul([li([p(<<"One liner">>), p(<<"This is a new paragraph">>)])]), br()]),
Expected = expected([ul([li([p([<<"One liner">>, <<"This is a new paragraph">>])])])]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.
Expand All @@ -710,15 +704,15 @@ singleton_bullet_list_followed_inner_paragraph2(_Config) ->
singleton_bullet_list_with_format(_Config) ->
Docs = create_eep48_doc(<<"* *One* __liner__">>),
HtmlDocs = compile(Docs),
Expected = expected([ul([li(p([it(<<"One">>), <<" ">>, em(<<"liner">>)]))]), br()]),
Expected = expected([ul([li(p([it(<<"One">>), <<" ">>, em(<<"liner">>)]))])]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.

multiline_bullet_list(_Config) ->
Docs = create_eep48_doc(<<"* One liner\n* Second line">>),
HtmlDocs = compile(Docs),
Expected = expected([ul([li(p(<<"One liner">>)), li(p(<<"Second line">>))]), br()]),
Expected = expected([ul([li(p(<<"One liner">>)), li(p(<<"Second line">>))])]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.
Expand All @@ -727,7 +721,7 @@ multiline_bullet_indented_list(_Config) ->
Docs = create_eep48_doc(
<<" * One liner\n * Second line">>),
HtmlDocs = compile(Docs),
Expected = expected([ul([li(p(<<"One liner">>)), li(p(<<"Second line">>))]), br()]),
Expected = expected([ul([li(p(<<"One liner">>)), li(p(<<"Second line">>))])]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.
Expand All @@ -737,7 +731,7 @@ multiline_bullet_indented_list2(_Config) ->
<<" * _One liner_\n * _Second_ `line`">>),
HtmlDocs = compile(Docs),
Expected = expected([ul([li(p(it(<<"One liner">>))),
li(p([it(<<"Second">>), <<" ">>, inline_code(<<"line">>)]))]), br()]),
li(p([it(<<"Second">>), <<" ">>, inline_code(<<"line">>)]))])]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.
Expand All @@ -751,8 +745,7 @@ even_nested_bullet_list(_Config) ->
li(p(<<"Second nested line">>))
])
])
]),
br()]),
])]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.
Expand All @@ -767,8 +760,7 @@ odd_nested_bullet_list(_Config) ->
li(p(<<"Third nested line">>))
])
])
]),
br()]),
])]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.
Expand All @@ -781,8 +773,7 @@ complex_nested_bullet_list(_Config) ->
ul([ li(p(<<"First nested line">>)) ])
]),
li([p(<<"Second line">>)])
]),
br()]),
])]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.
Expand All @@ -796,8 +787,7 @@ complex_nested_bullet_list2(_Config) ->
* Another nested line
* Second one liner">>),
HtmlDocs = compile(Docs),
Expected = expected([br(),
ul([
Expected = expected([ul([
li([ p(<<"One liner">>),
ul([ li([
p(<<"First nested line">>),
Expand All @@ -810,16 +800,15 @@ complex_nested_bullet_list2(_Config) ->
])
]),
li([ p(<<"Second one liner">>)])
]),
br()]),
])]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.

singleton_numbered_list(_Config) ->
Docs = create_eep48_doc(<<"1. One liner">>),
HtmlDocs = compile(Docs),
Expected = expected([ol([li(p(<<"One liner">>))]), br()]),
Expected = expected([ol([li(p(<<"One liner">>))])]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.
Expand All @@ -828,23 +817,23 @@ singleton_numbered_list(_Config) ->
singleton_numbered_list_followed_new_paragraph(_Config) ->
Docs = create_eep48_doc(<<"1. One liner\n\nThis is a new paragraph">>),
HtmlDocs = compile(Docs),
Expected = expected([ol([li(p(<<"One liner">>))]), br(), br(), p(<<"This is a new paragraph">>)]),
Expected = expected([ol([li(p(<<"One liner">>))]), p(<<"This is a new paragraph">>)]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.

singleton_numbered_list_followed_inner_paragraph(_Config) ->
Docs = create_eep48_doc(<<"1. One liner\n This is a new paragraph">>),
HtmlDocs = compile(Docs),
Expected = expected([ol([li([p(<<"One liner">>), p(<<"This is a new paragraph">>)])]), br()]),
Expected = expected([ol([li([p([<<"One liner">>, <<"This is a new paragraph">>])])])]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.

singleton_numbered_list_followed_inner_paragraph2(_Config) ->
Docs = create_eep48_doc(<<"1. One liner\nThis is a new paragraph">>),
HtmlDocs = compile(Docs),
Expected = expected([ol([li([p(<<"One liner">>), p(<<"This is a new paragraph">>)])]), br()]),
Expected = expected([ol([li([p([<<"One liner">>, <<"This is a new paragraph">>])])])]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.
Expand All @@ -853,15 +842,15 @@ singleton_numbered_list_followed_inner_paragraph2(_Config) ->
singleton_numbered_list_with_format(_Config) ->
Docs = create_eep48_doc(<<"1. *One* __liner__">>),
HtmlDocs = compile(Docs),
Expected = expected([ol([li(p([it(<<"One">>), <<" ">>, em(<<"liner">>)]))]), br()]),
Expected = expected([ol([li(p([it(<<"One">>), <<" ">>, em(<<"liner">>)]))])]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.

multiline_numbered_indented_list(_Config) ->
Docs = create_eep48_doc(<<" 1. One liner\n 2. Second line">>),
HtmlDocs = compile(Docs),
Expected = expected([ol([li(p(<<"One liner">>)), li(p(<<"Second line">>))]), br()]),
Expected = expected([ol([li(p(<<"One liner">>)), li(p(<<"Second line">>))])]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.
Expand All @@ -871,15 +860,15 @@ multiline_numbered_indented_list2(_Config) ->
<<" 1. _One liner_\n 2. _Second_ `line`">>),
HtmlDocs = compile(Docs),
Expected = expected([ol([li(p(it(<<"One liner">>))),
li(p([it(<<"Second">>), <<" ">>, inline_code(<<"line">>)]))]), br()]),
li(p([it(<<"Second">>), <<" ">>, inline_code(<<"line">>)]))])]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.

multiline_numbered_list(_Config) ->
Docs = create_eep48_doc(<<"1. One liner\n2. Second line">>),
HtmlDocs = compile(Docs),
Expected = expected([ol([li(p(<<"One liner">>)), li(p(<<"Second line">>))]), br()]),
Expected = expected([ol([li(p(<<"One liner">>)), li(p(<<"Second line">>))])]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.
Expand All @@ -893,8 +882,7 @@ even_nested_numbered_list(_Config) ->
li(p(<<"Second nested line">>))
])
])
]),
br()]),
])]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.
Expand All @@ -909,8 +897,7 @@ odd_nested_numbered_list(_Config) ->
li(p(<<"Third nested line">>))
])
])
]),
br()]),
])]),
Expected = extract_moduledoc(HtmlDocs),
[ ?EXPECTED_FUN(Expected) ] = extract_doc(HtmlDocs),
ok.
Expand Down Expand Up @@ -945,9 +932,6 @@ it(X) when is_list(X) ->
it(X) when is_binary(X); is_tuple(X) ->
it([X]).

br() ->
{br, [], []}.

ul(Items) when is_list(Items) ->
{ul, [], Items}.

Expand Down
10 changes: 7 additions & 3 deletions lib/stdlib/test/shell_docs_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -133,26 +133,30 @@ render_smoke(_Config) ->
E(shell_docs:render(Mod, D, Config)),
E(shell_docs:render_type(Mod, D, Config)),
E(shell_docs:render_callback(Mod, D, Config)),

Exports = try Mod:module_info(exports)
catch _:undef -> []
end, %% nif file not available on this platform

DHTML = doc_html:markdown_to_shelldoc(D),
[try
E(shell_docs:render(Mod, F, A, D, Config))
E(shell_docs:render(Mod, F, A, DHTML, Config))
catch _E:R:ST ->
io:format("Failed to render ~p:~p/~p~n~p:~p~n~p~n",
[Mod,F,A,R,ST,shell_docs:get_doc(Mod,F,A)]),
erlang:raise(error,R,ST)
end || {F,A} <- Exports],

[try
E(shell_docs:render_type(Mod, T, A, D, Config))
E(shell_docs:render_type(Mod, T, A, DHTML, Config))
catch _E:R:ST ->
io:format("Failed to render type ~p:~p/~p~n~p:~p~n~p~n",
[Mod,T,A,R,ST,shell_docs:get_type_doc(Mod,T,A)]),
erlang:raise(error,R,ST)
end || {{type,T,A},_,_,_,_} <- Docs],

[try
E(shell_docs:render_callback(Mod, T, A, D, Config))
E(shell_docs:render_callback(Mod, T, A, DHTML, Config))
catch _E:R:ST ->
io:format("Failed to render callback ~p:~p/~p~n~p:~p~n~p~n",
[Mod,T,A,R,ST,shell_docs:get_callback_doc(Mod,T,A)]),
Expand Down

0 comments on commit 5ea526c

Please sign in to comment.