Skip to content

Commit

Permalink
Merge branch 'maint'
Browse files Browse the repository at this point in the history
  • Loading branch information
kikofernandez committed May 28, 2024
2 parents 9f778f5 + 2c23ea4 commit 85d8c9c
Show file tree
Hide file tree
Showing 2 changed files with 62 additions and 28 deletions.
40 changes: 22 additions & 18 deletions lib/stdlib/src/shell_docs_markdown.erl
Original file line number Diff line number Diff line change
Expand Up @@ -73,12 +73,12 @@ format_line(Ls) ->
OmissionSet :: sets:set(atom()).
format_line([], _BlockSet0) ->
[];
format_line([{Tag, [], List} | Rest], BlockSet0) ->
format_line([{Tag, Attrs, List} | Rest], BlockSet0) ->
case format_line(List, sets:add_element(Tag, BlockSet0)) of
[] ->
format_line(Rest, BlockSet0);
Ls ->
[{Tag, [], Ls}] ++ format_line(Rest, BlockSet0)
[{Tag, Attrs, Ls}] ++ format_line(Rest, BlockSet0)
end;
format_line([Bin | Rest], BlockSet0) when is_binary(Bin) ->
%% Ignores formatting these elements
Expand Down Expand Up @@ -365,8 +365,8 @@ process_kind_block([<<">", _/binary>>=Line | Rest], Block) ->
%%
%% process block code
%%
process_kind_block([<<"```", _Line/binary>> | Rest], Block) ->
Block ++ process_fence_code(Rest, []);
process_kind_block([<<"```", Line/binary>> | Rest], Block) ->
Block ++ process_fence_code(Rest, [], Line);
%%
%% New line
%%
Expand Down Expand Up @@ -459,8 +459,9 @@ strip_spaces(Rest, Acc, _) ->
ol | li | dl | dt | dd |
h1 | h2 | h3 | h4 | h5 | h6.
-type chunk_element_attrs() :: [].
-type quote() :: {blockquote,[], shell_docs:chunk_elements()}.
-type code() :: {pre, chunk_element_attrs(), [{code,[], shell_docs:chunk_elements()}]}.
-type code_element_attrs() :: [{class,unicode:chardata()}].
-type quote() :: {blockquote, chunk_element_attrs(), shell_docs:chunk_elements()}.
-type code() :: {pre, chunk_element_attrs(), [{code, code_element_attrs(), shell_docs:chunk_elements()}]}.
-type p() :: {p, chunk_element_attrs(), shell_docs:chunk_elements()}.
-type i() :: {i, chunk_element_attrs(), shell_docs:chunk_elements()}.
-type em() :: {em, chunk_element_attrs(), shell_docs:chunk_elements()}.
Expand Down Expand Up @@ -803,27 +804,30 @@ format(Format, Line0) when is_list(Line0)->
PrevLines :: [binary()], %% Represent unprocessed lines.
HtmlErlang :: shell_docs:chunk_elements().
process_code([], Block) ->
[create_code(Block)];
[create_code(Block, [])];
process_code([<<" ", Line/binary>> | Rest], Block) ->
%% process blank line followed by code
process_code(Rest, [Line | Block]);
process_code(Rest, Block) ->
process_code([], Block) ++ parse_md(Rest, []).

process_fence_code([], Block) ->
[create_code(Block)];
process_fence_code([<<"```">> | Rest], Block) ->
process_fence_code([], Block, Leading) ->
case string:trim(hd(binary:split(Leading, [~"\t", ~" "]))) of
<<>> -> [create_code(Block, [])];
Trimmed -> [create_code(Block, [{class, <<"language-", Trimmed/binary>>}])]
end;
process_fence_code([<<"```">> | Rest], Block, Leading) ->
%% close block
process_fence_code([], Block) ++ parse_md(Rest, []);
process_fence_code([Line | Rest], Block) ->
process_fence_code([], Block, Leading) ++ parse_md(Rest, []);
process_fence_code([Line | Rest], Block, Leading) ->
{Stripped, _} = strip_spaces(Line, 0, infinity),
maybe
<<"```", RestLine/binary>> ?= Stripped,
{<<>>, _} ?= strip_spaces(RestLine, 0, infinity),
process_fence_code([<<"```">> | Rest], Block)
process_fence_code([<<"```">> | Rest], Block, Leading)
else
_ ->
process_fence_code(Rest, [Line | Block])
process_fence_code(Rest, [Line | Block], Leading)
end.

-spec process_comment(Line :: [binary()]) -> [binary()].
Expand Down Expand Up @@ -853,14 +857,14 @@ create_paragraph(<<$\s, Line/binary>>) ->
create_paragraph(Line) when is_binary(Line) ->
p(Line).

-spec create_code(Lines :: [binary()]) -> code().
create_code(CodeBlocks) when is_list(CodeBlocks) ->
-spec create_code(Lines :: [binary()], code_element_attrs()) -> code().
create_code(CodeBlocks, CodeAttrs) when is_list(CodeBlocks) ->
%% assumes that the code block is in reverse order
Bin = trim_and_add_new_line(CodeBlocks),
{pre,[], [{code,[], [Bin]}]}.
{pre, [], [{code, CodeAttrs, [Bin]}]}.

create_table(Table) when is_list(Table) ->
{pre,[], [{code,[], Table}]}.
{pre, [], [{code, [{class, ~"table"}], Table}]}.


-spec quote(Quote :: list()) -> quote().
Expand Down
50 changes: 40 additions & 10 deletions lib/stdlib/test/shell_docs_markdown_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -48,8 +48,9 @@

%% fence code
-export([single_line_fence_code_test/1, multiple_line_fence_code_test/1,
single_line_fence_code_no_language_test/1, single_line_fence_code_no_language_spaces_test/1,
paragraph_between_fence_code_test/1, fence_code_ignores_link_format_test/1,
fence_code_with_spaces/1]).
fence_code_with_spaces/1, fence_code_with_tabs/1]).

%% br
-export([start_with_br_test/1, multiple_br_followed_by_paragraph_test/1,
Expand Down Expand Up @@ -188,9 +189,11 @@ code_tests() ->
fence_code_tests() ->
[single_line_fence_code_test,
multiple_line_fence_code_test,
single_line_fence_code_no_language_test,
single_line_fence_code_no_language_spaces_test,
paragraph_between_fence_code_test,
fence_code_ignores_link_format_test,
fence_code_with_spaces
fence_code_with_spaces, fence_code_with_tabs
].

br_tests() ->
Expand Down Expand Up @@ -492,7 +495,7 @@ single_line_fence_code_test(_Conf) ->
```erlang
test() -> ok.
```",
Result = [ code(~"test() -> ok.\n")],
Result = [ code(~"test() -> ok.\n", [{class, ~"language-erlang"}])],
compile_and_compare(Input, Result).

multiple_line_fence_code_test(_Conf) ->
Expand All @@ -501,9 +504,24 @@ multiple_line_fence_code_test(_Conf) ->
test() ->
ok.
```",
Result = [ code(~"test() ->\n ok.\n")],
Result = [ code(~"test() ->\n ok.\n", [{class, ~"language-erlang"}])],
compile_and_compare(Input, Result).

single_line_fence_code_no_language_test(_Conf) ->
Input = ~"
```
test() -> ok.
```",
Result = [ code(~"test() -> ok.\n")],
compile_and_compare(Input, Result).

single_line_fence_code_no_language_spaces_test(_Conf) ->
Input = ~"
```\s\s
test() -> ok.
```",
Result = [ code(~"test() -> ok.\n")],
compile_and_compare(Input, Result).

paragraph_between_fence_code_test(_Conf) ->
Input = ~"This is a test:
Expand All @@ -512,7 +530,7 @@ test() ->
ok.
```",
Result = [p(~"This is a test:"),
code(~"test() ->\n ok.\n")],
code(~"test() ->\n ok.\n", [{class, ~"language-erlang"}])],
compile_and_compare(Input, Result).

fence_code_ignores_link_format_test(_Conf) ->
Expand All @@ -521,15 +539,23 @@ fence_code_ignores_link_format_test(_Conf) ->
[foo](bar)
```",
Result = [p(~"This is a test:"),
code(~"[foo](bar)\n")],
code(~"[foo](bar)\n", [{class, ~"language-erlang"}])],
compile_and_compare(Input, Result).

fence_code_with_spaces(_Config) ->
Input =
~" ```erlang
~" ```erlang\s\s
[foo](bar)
```",
Result = [code(~" [foo](bar)\n", [{class, ~"language-erlang"}])],
compile_and_compare(Input, Result).

fence_code_with_tabs(_Config) ->
Input =
~" ```erlang\ttrailing
[foo](bar)
```",
Result = [code(~" [foo](bar)\n")],
Result = [code(~" [foo](bar)\n", [{class, ~"language-erlang"}])],
compile_and_compare(Input, Result).

start_with_br_test(_Conf) ->
Expand Down Expand Up @@ -1019,10 +1045,14 @@ header(Level, Text) when is_integer(Level) ->
{HeadingLevelAtom, [], [Text]}.

code(X) ->
{pre,[],[inline_code(X)]}.
code(X, []).
code(X, Attrs) when is_list(X) ->
{pre,[],[{code,Attrs,X}]};
code(X, Attrs) ->
{pre,[],[{code,Attrs,[X]}]}.

table(Table) when is_list(Table) ->
{pre,[], [inline_code(Table)]}.
{pre,[], [{code, [{class, ~"table"}], Table}]}.

inline_code(X) when is_list(X) ->
{code,[],X};
Expand Down

0 comments on commit 85d8c9c

Please sign in to comment.