File 1161-docs-add-support-for-ref-man-man-pages.patch of Package erlang
From e3bda07a7379d8ced640fff56343e704ca3c60b7 Mon Sep 17 00:00:00 2001
From: Fredrik Frantzen <frazze@erlang.org>
Date: Tue, 23 Sep 2025 11:36:50 +0200
Subject: [PATCH 1/2] docs: add support for ref-man man-pages
---
.gitignore | 1 +
lib/stdlib/src/Makefile | 1 +
lib/stdlib/src/beam_lib.erl | 11 +-
lib/stdlib/src/gen_statem.erl | 7 -
lib/stdlib/src/man_docs.erl | 423 +++++++++++++++++++++++++++
lib/stdlib/src/shell_docs.erl | 3 +-
lib/stdlib/src/stdlib.app.src | 1 +
lib/stdlib/test/shell_docs_SUITE.erl | 21 +-
make/doc.mk | 30 +-
make/markdown_to_man.escript | 173 +++--------
make/otp.mk.in | 1 +
11 files changed, 514 insertions(+), 158 deletions(-)
create mode 100644 lib/stdlib/src/man_docs.erl
diff --git a/lib/stdlib/src/Makefile b/lib/stdlib/src/Makefile
index b52b3d1fde..ddecd63245 100644
--- a/lib/stdlib/src/Makefile
+++ b/lib/stdlib/src/Makefile
@@ -103,6 +103,7 @@ MODULES= \
json \
lists \
log_mf_h \
+ man_docs \
maps \
math \
ms_transform \
diff --git a/lib/stdlib/src/beam_lib.erl b/lib/stdlib/src/beam_lib.erl
index ebf9ed561b..884ece0b48 100644
--- a/lib/stdlib/src/beam_lib.erl
+++ b/lib/stdlib/src/beam_lib.erl
@@ -99,14 +99,11 @@ The key can be provided in the following two ways:
[`compile`](`m:compile#debug_info_key`) and function `crypto_key_fun/1` to
register a fun that returns the key whenever `beam_lib` must decrypt the
debug information.
-
-If no such fun is registered, `beam_lib` instead searches for an `.erlang.crypt`
-file, see the next section.
-
+ If no such fun is registered, `beam_lib` instead searches for an `.erlang.crypt`
+ file, see the next section.
1. Store the key in a text file named `.erlang.crypt`.
-
-In this case, Compiler option `encrypt_debug_info` can be used, see
-[`compile`](`m:compile#encrypt_debug_info`).
+ In this case, Compiler option `encrypt_debug_info` can be used, see
+ [`compile`](`m:compile#encrypt_debug_info`).
## .erlang.crypt
diff --git a/lib/stdlib/src/gen_statem.erl b/lib/stdlib/src/gen_statem.erl
index b800102916..93d9388a9b 100644
--- a/lib/stdlib/src/gen_statem.erl
+++ b/lib/stdlib/src/gen_statem.erl
@@ -779,7 +779,6 @@ and returns. Here are the sequence of steps for a _state transition_:
in order of appearance. In this step all replies generated
by any `t:reply_action/0` are sent. Other actions set
`t:transition_option/0`s that come into play in subsequent steps.
-
2. If [_state enter calls_](`t:state_enter/0`) are used,
it is either the initial state or one of the callback results
[`repeat_state`](`t:state_callback_result/2`) or
@@ -797,15 +796,11 @@ and returns. Here are the sequence of steps for a _state transition_:
[`(enter, OldState, State, Data)`](`t:state_enter/0`) (depending on
[_callback mode_](`t:callback_mode/0`)) and when it returns
starts again from the top of this sequence.
-
3. If `t:postpone/0` is `true`, the current event is postponed.
-
4. If this is a _state change_, the queue of incoming events is reset
to start with the oldest postponed.
-
5. All events stored with `t:action/0` `next_event` are inserted
to be processed before previously queued events.
-
6. Time-out timers `t:event_timeout/0`, `t:generic_timeout/0` and
`t:state_timeout/0` are handled. Time-outs with zero time
are guaranteed to be delivered to the state machine
@@ -820,12 +815,10 @@ and returns. Here are the sequence of steps for a _state transition_:
A _state change_ cancels a `t:state_timeout/0` and any new transition
option of this type belongs to the new state, that is;
a `t:state_timeout/0` applies to the state the state machine enters.
-
7. If there are enqueued events the
[_state callback_](#state-callback) for the possibly
new state is called with the oldest enqueued event, and we start again
from the top of this sequence.
-
8. Otherwise the `gen_statem` goes into `receive` or hibernation
(if `t:hibernate/0` is `true`) to wait for the next message.
In hibernation the next non-system event awakens the `gen_statem`,
diff --git a/lib/stdlib/src/man_docs.erl b/lib/stdlib/src/man_docs.erl
new file mode 100644
index 0000000000..83bf8b3c4e
--- /dev/null
+++ b/lib/stdlib/src/man_docs.erl
@@ -0,0 +1,423 @@
+%%
+%% %CopyrightBegin%
+%%
+%% SPDX-License-Identifier: Apache-2.0
+%%
+%% Copyright Ericsson AB 2024-2025. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%% http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+-module(man_docs).
+-include_lib("kernel/include/eep48.hrl").
+
+-export([module_to_manpage/2, module_to_manpage/3, markdown_to_manpage/2]).
+
+%% Formats a module documentation as a roff man page.
+%% Fetches the documentation for a module with `code:get_doc/1`
+-spec module_to_manpage(Module, Path) -> unicode:chardata() when
+ Module :: module(),
+ Path :: string().
+module_to_manpage(Module, Path) when is_atom(Module) ->
+ case code:get_doc(Module) of
+ {ok, Docs} ->
+ module_to_manpage(Module, Path, Docs);
+ _Error ->
+ ~""
+ end.
+-spec module_to_manpage(Module, Path, Docs) -> unicode:chardata() when
+ Module :: module(),
+ Path :: string(),
+ Docs :: #docs_v1{}.
+module_to_manpage(_Module, _Path, #docs_v1{module_doc = None}) when None =:= none; None =:= hidden ->
+ ~"";
+module_to_manpage(Module, Path, #docs_v1{module_doc = #{~"en" := ModuleDoc}, docs = AllDocs})
+ when is_atom(Module) ->
+ PreludeNDescription = markdown_to_manpage(ModuleDoc, Path),
+
+ Types = [Doc || {{type,_,_},_,_,_,_}=Doc <- AllDocs],
+ TypesSection = format_section("DATA TYPES", Types, Module, AllDocs),
+ Callbacks = [Doc || {{callback,_,_},_,_,_,_}=Doc <- AllDocs],
+ CallbacksSection = format_section("CALLBACKS", Callbacks, Module, AllDocs),
+ Functions = [Doc || {{function,_,_},_,_,_,_}=Doc <- AllDocs],
+ FunctionsSection = format_section("FUNCTIONS", Functions, Module, AllDocs),
+
+ iolist_to_binary([PreludeNDescription, TypesSection, FunctionsSection, CallbacksSection]).
+
+%% Formats markdown as a roff man page.
+-spec markdown_to_manpage(binary() | shell_docs:chunk_elements(), file:filename()) -> binary().
+markdown_to_manpage(Markdown, Path) when is_binary(Markdown) ->
+ markdown_to_manpage(shell_docs_markdown:parse_md(Markdown), Path);
+markdown_to_manpage(MarkdownChunks, Path) ->
+ Path1 = filename:absname(Path),
+ App = case filename:split(string:prefix(Path1, os:getenv("ERL_TOP"))) of
+ ["/", "lib", AppStr | _] ->
+ list_to_atom(AppStr);
+ ["lib", AppStr | _] ->
+ list_to_atom(AppStr);
+ ["/", "erts" | _] ->
+ list_to_atom("erts");
+ ["nomatch"] ->
+ error("ERL_TOP environment variable doesn't match the PATH " ++ Path)
+ end,
+ Version = case application:load(App) of
+ ok -> {ok,Vsn} = application:get_key(App, vsn), Vsn;
+ {error, {"no such file or directory","erts.app"}} -> erlang:system_info(version);
+ {error, {already_loaded, App}} -> {ok,Vsn} = application:get_key(App, vsn), Vsn
+ end,
+
+ Extension = filename:extension(Path),
+ FileName = list_to_binary(filename:rootname(filename:basename(Path), Extension)),
+ Name = get_name(MarkdownChunks, FileName),
+ Prelude = io_lib:format(".TH ~s 3 \"~s ~s\" \"Ericsson AB\" \"Erlang Module Definition\"\n",
+ [Name, atom_to_binary(App), Version]),
+ I = conv(MarkdownChunks, Name),
+ iolist_to_binary([Prelude|I]).
+
+get_name([{h1,_,[Name]}|_], _) when is_binary(Name) ->
+ Name;
+get_name(_, Default) when is_binary(Default) ->
+ Default.
+
+conv([{h1,_,[Name]},
+ {p,_,[ShortDesc0]},
+ {h2,_,[~"Synopsis"]},
+ Synopsis0,
+ {h2,_,[~"Description"]}|T],_) when is_binary(ShortDesc0) ->
+ ShortDesc = string:trim(ShortDesc0, trailing, [$., $\s]),
+ Synopsis = strip_formatting(Synopsis0),
+ [~".SH NAME\n",
+ Name,~B" \- ",ShortDesc,$\n,
+ ~".SH SYNOPSIS\n",
+ Synopsis,$\n,
+ ~".SH DESCRIPTION\n"|format(T)];
+conv([{h1,_,[Name]},
+ {p,_,[ShortDesc0]},
+ {h2,_,[~"Description"]}|T],_) when is_binary(ShortDesc0) ->
+ ShortDesc = string:trim(ShortDesc0, trailing, [$., $\s]),
+ [~".SH NAME\n",
+ Name,~B" \- ",ShortDesc,$\n,
+ ~".SH DESCRIPTION\n"|format(T)];
+conv([{h1,_,[Head]}|T],_) ->
+ Name = ~".SH NAME\n",
+ Desc = ~".SH DESCRIPTION\n",
+ [Name,Head,$\n,Desc|format(T)];
+conv([H|T], Head) ->
+ Name = ~".SH NAME\n",
+ Desc = ~".SH DESCRIPTION\n",
+ [Name,Head,~" - ",format_one(H),$\n,Desc|format(T)].
+
+escape(Text) when is_list(Text) ->
+ escape(iolist_to_binary(Text));
+escape(Text) when is_binary(Text) ->
+ binary:replace(Text, <<$\\>>, ~"\\\\", [global]).
+
+format(Is) ->
+ [[format_one(I),$\n] || I <- Is].
+
+format_one({blockquote,_,[{h4,_,Head0},{p,_,Text}|Ps]}) ->
+ Head = string:uppercase(<<(string:trim(Head0))/binary,": ">>),
+ L = [{p,[],[{em,[],Head}|Text]}|Ps],
+ format(L);
+format_one({blockquote,_,Qs0}) ->
+ [".RS 4\n", format(Qs0), ".RE\n"];
+format_one({h1,_,Hs}) ->
+ [~'.SH "',Hs,~'"\n'];
+format_one({h2,_,Hs}) ->
+ [~'.SS "',Hs,~'"\n'];
+format_one({h3,_,[Hs]}) when is_binary(Hs) ->
+ [~'.PP\n\\fB',Hs,~'\\fR\n'];
+format_one({h3,_,Hs}) ->
+ [~'.PP\n\\fB',format_p(Hs),~'\\fR\n'];
+format_one({h4,_,Hs}) ->
+ format_one({h3,[],Hs});
+format_one({h5,_,Hs}) ->
+ format_one({h3,[],Hs});
+format_one({p,_,Ps}) ->
+ format_p(Ps);
+format_one({pre,_,Ps}) ->
+ format_pre(Ps);
+format_one({ol,_,Ol}) ->
+ format_ol(Ol);
+format_one({ul,_,Ul}) ->
+ format_ul(Ul);
+format_one({a,_,Text}) ->
+ [~B"\fI",format(Text),~B"\fR"];
+format_one({code,_,Text}) ->
+ [~B"\fI",format(Text),~B"\fR"];
+format_one({strong,_,Text}) ->
+ ["\\fB", Text, "\\fR"];
+format_one({em,_,Text}) ->
+ [~B"\fB",format_one(Text),~B"\fR"];
+format_one({i,_,Text}) ->
+ [~B"\fI",format_one(Text),~B"\fR"];
+format_one({dl,_,Content}) ->
+ format_dl(Content);
+format_one([Text]) when is_binary(Text) ->
+ format_one({p,[],[Text]});
+format_one(Text) when is_binary(Text) ->
+ format_one({p,[],Text}).
+
+format_dl(Is) ->
+ [~".RS 4\n", [format_dl_item(I) || I <- Is], ~".RE\n"].
+format_dl_item({dt,_,Content}) ->
+ [~".TP\n", "\\fB", format(Content), "\\fR", $\n];
+format_dl_item({dd,_,Content}) ->
+ format(Content).
+
+format_p(Text) when is_binary(Text) ->
+ format_p([Text]);
+format_p(Is0) ->
+ Text0 = iolist_to_binary([format_p_item(I) || I <- Is0]),
+ Text = string:trim(Text0, leading),
+ [~".PP\n",Text,$\n].
+
+format_p_item({code,_,Text}) ->
+ [~B"\fI",format_p_item(Text),~B"\fR"];
+format_p_item({em,_,Text}) ->
+ [~B"\fB",format_p_item(Text),~B"\fR"];
+format_p_item({i,_,Text}) ->
+ [~B"\fI",format_p_item(Text),~B"\fR"];
+format_p_item({a,_,Text}) ->
+ [~B"\fI",format_p_item(Text),~B"\fR"];
+format_p_item({strong,_,Text}) ->
+ ["\\fB", format_p_item(Text), "\\fR"];
+format_p_item([H|T]) ->
+ [format_p_item(H)|format_p_item(T)];
+format_p_item([]) ->
+ [];
+format_p_item(Text) when is_binary(Text) ->
+ escape_backslashes(Text).
+
+format_pre(Ps0) ->
+ Ps = [format_pre_item(P) || P <- Ps0],
+ [~".IP\n.nf\n",Ps,$\n,~".fi\n"].
+
+format_pre_item({code,[{class,<<"table">>}],Text}) ->
+ Text2 = to_tbl(parse(extract(iolist_to_binary(Text)))),
+ escape_backslashes(Text2);
+format_pre_item({code,_,Text}) ->
+ escape_backslashes(Text);
+format_pre_item(Text) ->
+ escape_backslashes(Text).
+
+format_ol(OL) ->
+ [".nr li 0 1\n"|[format_ol_item(LI) || LI <- OL]].
+
+format_ol_item({li,_,Ps0}) ->
+ B = ~"""
+ .sp
+ .RS 4
+ .ie n \{\
+ \h'-04'\n+[li].\h'+03'\c
+ .\}
+ .el \{\
+ .sp -1
+ .IP "\n+[li]." 4
+ .\}
+ """,
+ [B,format(Ps0),~".RE\n"].
+
+format_ul(UL) ->
+ [format_ul_item(I) || I <- UL].
+
+format_ul_item({li,_,Ps0}) ->
+ case Ps0 of
+ [{p,_,[Head,<<" - ",Text0/binary>>|Items]}|T] ->
+ Text = string:trim(Text0, leading),
+ [strip_formatting(Head),$\n,
+ ~".RS 2\n",
+ Text,$\n,
+ [format_p_item(I) || I <- Items],
+ $\n,
+ format(T),$\n,
+ ~".RE\n"
+ ];
+ _ ->
+ B = ~"""
+
+ .sp
+ .RS 4
+ .ie n \{\
+ \h'-04'\(bu\h'+03'\c
+ .\}
+ .el \{\
+ .sp -1
+ .IP \(bu 2.3
+ .\}
+ """,
+ [B,format(Ps0),~".RE\n"]
+ end.
+
+strip_formatting({_,_,[_|_]=L}) ->
+ strip_formatting(L);
+strip_formatting([H|T]) ->
+ [strip_formatting(H),strip_formatting(T)];
+strip_formatting([]) ->
+ [];
+strip_formatting(<<".",_/binary>> = Bin) ->
+ [~B"\&",Bin];
+strip_formatting(Bin) when is_binary(Bin) ->
+ Bin.
+
+escape_backslashes(Text) when is_list(Text) ->
+ escape_backslashes(iolist_to_binary(Text));
+escape_backslashes(Text) when is_binary(Text) ->
+ binary:replace(Text, ~B"\", ~B"\\", [global]).
+
+%% Extracts all Markdown tables from a binary text.
+%% Returns a list of binaries, where each binary is a complete table.
+extract(Text) ->
+ %% This regex finds the header, the separator line, and all data rows.
+ Regex = "^\\s*\\|.+\\|\\s*\\n\\s*\\|[-:|\\s]+\\|\\s*\\n(?:\\s*\\|.+\\|\\s*\\n?)+",
+
+ %% Scan for all occurrences and extract the matched strings.
+ case re:run(Text, Regex, [{capture, all, binary}, global, multiline]) of
+ {match, [[Captured]|_]} -> Captured;
+ nomatch -> []
+ end.
+
+%% Parses a single Markdown table string into a list of rows (list of cells).
+%% It automatically discodes the separator line.
+parse([]) -> [];
+parse(TableString) ->
+ Lines = binary:split(TableString, <<"\n">>, [global, trim]),
+
+ %% Map over each line, parsing it into a list of cells.
+ ParsedRows = [parse_row(Line) || Line <- Lines],
+
+ %% The second line is the separator (|---|-|); we remove it.
+ [Header | DataRows] = ParsedRows,
+ [Header | tl(DataRows)].
+
+%% Converts a parsed table (list of lists of binaries) into tbl format.
+to_tbl([]) -> <<>>;
+to_tbl([[] | _]) -> <<>>;
+to_tbl([Header | _] = ParsedData) ->
+ NumCols = length(Header),
+
+ % 1. Define global options for the table.
+ Options = <<"allbox;">>,
+
+ % 2. Generate format lines. We'll default to a centered (c) header
+ % and left-aligned (l) data columns.
+ HeaderFmt = iolist_to_binary(lists:join(<<" ">>, lists:duplicate(NumCols, <<"c">>))),
+ DataFmt = iolist_to_binary([lists:join(<<" ">>, lists:duplicate(NumCols, <<"l">>)), <<".">>]),
+
+ % 3. Convert each row of cells into a single tab-separated binary.
+ FormattedRows = [iolist_to_binary(lists:join(<<"\t">>, Row)) || Row <- ParsedData],
+
+ % 4. Assemble all parts into the final tbl block.
+ Parts = [
+ <<".TS\n">>,
+ Options, <<"\n">>,
+ HeaderFmt, <<"\n">>,
+ DataFmt, <<"\n">>,
+ iolist_to_binary(lists:join(<<"\n">>, FormattedRows)),
+ <<"\n.TE">>
+ ],
+ iolist_to_binary(Parts).
+
+%% Parses a single row string into a list of binary cells.
+parse_row(Line) ->
+ %% 1. Remove surrounding whitespace from the line.
+ TrimmedLine = string:trim(Line),
+
+ %% 2. Remove the leading and trailing pipes.
+ NoOuterPipes = strip_outer_pipes(TrimmedLine),
+
+ %% 3. Split the row by the pipe delimiter.
+ Cells = binary:split(NoOuterPipes, <<"|">>, [global]),
+
+ %% 4. Trim whitespace from each individual cell.
+ [string:trim(Cell) || Cell <- Cells].
+
+%% Helper to safely remove the first and last characters if they are pipes.
+strip_outer_pipes(Bin) ->
+ string:trim(Bin, both, "|").
+
+
+format_section(Title, Docs, Module, AllDocs) ->
+ case Docs of
+ [] -> [];
+ _ ->
+ SortedDocs = lists:sort(fun({MFA1,_,_,_,_}, {MFA2,_,_,_,_}) -> MFA1 =< MFA2 end, Docs),
+ [".SH ", Title, "\n.LP\n" |
+ lists:flatmap(fun(Doc) ->
+ format_function([Doc], Module, AllDocs)
+ end, SortedDocs)]
+ end.
+
+format_function(FDocs, Module, AllDocs) ->
+ GlobalSpecs = shell_docs:extract_type_specs(Module),
+ Grouping = %% Groups functions using the 'equiv' meta attribute
+ lists:foldr(
+ fun({_Group,_Anno,_Sig,_Doc,#{ equiv := Group }} = Func, Acc) ->
+ case lists:keytake(Group, 1, Acc) of
+ false -> [{Group, [Func], format_signature(Func, GlobalSpecs)} | Acc];
+ {value, {Group, Members, Sigs}, NewAcc} ->
+ [{Group, [Func | Members], format_signature(Func, GlobalSpecs) ++ Sigs} | NewAcc]
+ end;
+ ({Group, _Anno, _Sig, _Doc, _Meta} = Func, Acc) ->
+ [{Group, [Func], format_signature(Func, GlobalSpecs)} | Acc]
+ end, [],
+ lists:sort(fun(A, B) -> element(1, A) =< element(1, B) end, FDocs)),
+ lists:map(
+ fun({Group, [{{Type,_,_},_,_,_,_}|_]=Members, Signatures}) ->
+ DocContents = case lists:search(fun({_,_,_,Doc,_}) -> Doc =/= #{} end, Members) of
+ {value, {_,_,_,Doc,_Meta}} -> Doc;
+ false ->
+ case lists:keyfind(Group, 1, AllDocs) of
+ false -> none;
+ {_,_,_,Doc,_} -> Doc
+ end
+ end,
+
+ case DocContents of
+ #{}=M when map_size(M) =:= 0 -> ~"";
+ ~"" when Type =/= type -> ~"";
+ none when Type =/= type -> ~"";
+ hidden -> ~"";
+ _ -> FormattedDocs = case DocContents of
+ #{~"en" := MarkdownText} when is_binary(MarkdownText) -> format(shell_docs_markdown:parse_md(MarkdownText));
+ #{~"en" := MarkdownContent1} -> format(MarkdownContent1);
+ none -> ~""
+ end,
+ [".B\n", Signatures, "\n.br\n.RS\n",FormattedDocs,"\n.RE\n"]
+ end
+ end, Grouping).
+
+format_signature({{Type,F,A},_Anno,Sigs,_Docs,Meta}, Specs) ->
+ case maps:find({F, A}, maps:get(Type, Specs, #{})) of
+ {ok, Spec} ->
+ [format_ast(Spec) |format_meta(Meta)];
+ _Error ->
+ lists:map(fun(Sig) -> ["\\fB", escape(Sig), "\\fR", "\n"] end, Sigs) ++ [format_meta(Meta)]
+ end.
+
+format_ast(AST) ->
+ PPSpec = erl_pp:attribute(AST,[{encoding,unicode}]),
+ Spec = case AST of
+ {_Attribute, _Line, opaque, _} -> hd(string:split(PPSpec,"::"));
+ _ -> PPSpec
+ end,
+ BinSpec = unicode:characters_to_binary(string:trim(Spec, trailing, "\n")),
+
+ BinSpec2 = re:replace(BinSpec, "-((type)|(spec)|(callback)) ", ""),
+
+ ["\\fB", escape(BinSpec2), "\\fR", "\n"].
+
+format_meta(#{ deprecated := Depr } = M) ->
+ ["\n.br\nDeprecated: ", unicode:characters_to_binary(Depr) | format_meta(maps:remove(deprecated, M))];
+format_meta(_) -> [].
diff --git a/lib/stdlib/src/shell_docs.erl b/lib/stdlib/src/shell_docs.erl
index 9eda7d7b9e..45ae2019ff 100644
--- a/lib/stdlib/src/shell_docs.erl
+++ b/lib/stdlib/src/shell_docs.erl
@@ -75,7 +75,7 @@ be rendered as is.
%% Convenience functions
-export([get_doc/1, get_doc/3, get_type_doc/3, get_callback_doc/3]).
-
+-export([extract_type_specs/1]).
-export_type([chunk_elements/0, chunk_element_attr/0]).
-record(config, { docs,
@@ -618,6 +618,7 @@ render_type(Module, D) ->
render_type(Module, D, #{}).
%% extract AST raw type specifications.
+-spec extract_type_specs(module()) -> map().
extract_type_specs(Module) ->
maybe
Path = find_path(Module),
diff --git a/lib/stdlib/src/stdlib.app.src b/lib/stdlib/src/stdlib.app.src
index f146370803..7f42f85737 100644
--- a/lib/stdlib/src/stdlib.app.src
+++ b/lib/stdlib/src/stdlib.app.src
@@ -83,6 +83,7 @@
json,
lists,
log_mf_h,
+ man_docs,
maps,
math,
ms_transform,
diff --git a/lib/stdlib/test/shell_docs_SUITE.erl b/lib/stdlib/test/shell_docs_SUITE.erl
index 4e6f17e1eb..ccdda82e4e 100644
--- a/lib/stdlib/test/shell_docs_SUITE.erl
+++ b/lib/stdlib/test/shell_docs_SUITE.erl
@@ -26,7 +26,7 @@
-export([all/0, suite/0, groups/0, init_per_suite/1, end_per_suite/1,
init_per_group/2, end_per_group/2, init_per_testcase/2, end_per_testcase/2]).
--export([render/1, links/1, normalize/1, render_prop/1,render_non_native/1, ansi/1, columns/1]).
+-export([render/1, links/1, normalize/1, render_prop/1,render_non_native/1, ansi/1, columns/1, render_man/1]).
-export([render_function/1, render_type/1, render_callback/1, doctests/1]).
-export([render_all/1, update_render/0, update_render/1]).
@@ -50,7 +50,7 @@ all() ->
groups() ->
[ {prop,[],[render_prop]},
- {render, [], [render, render_non_native, links, normalize]},
+ {render, [], [render, render_non_native, links, normalize, render_man]},
{render_smoke, [], [render_function, render_type, render_callback]}
].
@@ -318,6 +318,23 @@ render_callback(_Config) ->
end),
ok.
+render_man(_Config) ->
+ docsmap(
+ fun(Mod, #docs_v1{metadata = Metadata} = D) ->
+ try
+ Path1 = case Metadata of
+ #{source_path := Path} -> Path;
+ #{} -> proplists:get_value(source, proplists:get_value(compile, Mod:module_info()))
+ end,
+ man_docs:module_to_manpage(Mod, Path1, D)
+ catch _E:R:ST ->
+ io:format("Failed to render man page for ~p~n~p:~p~n~p~n",
+ [Mod,R,ST,D]),
+ exit(R)
+ end
+ end),
+ ok.
+
docsmap(Fun) ->
F = fun F({Mod,_,_}) ->
F(Mod);
diff --git a/make/doc.mk b/make/doc.mk
index 73f57fdc81..5ef7fac458 100644
--- a/make/doc.mk
+++ b/make/doc.mk
@@ -50,9 +50,19 @@ endif
# ----------------------------------------------------
# Man dependencies
# ----------------------------------------------------
+ERL_FILES := $(wildcard $(APP_SRC_DIR)/*.erl)
+ERL_FILES_WITH_DOC := $(shell grep -L '-moduledoc false.' $(ERL_FILES))
MAN1_DEPS?=$(wildcard */*_cmd.md)
+MAN3_DEPS?=$(wildcard */references/*.md) $(wildcard references/*.md) \
+ $(wildcard */src/*.md) $(wildcard src/*.md) \
+ $(ERL_FILES_WITH_DOC)
+MAN3_DEPS_FILTERED=$(filter-out $(wildcard */references/*_cmd.md) $(wildcard references/*_cmd.md),$(MAN3_DEPS))
MAN1_PAGES=$(MAN1_DEPS:references/%_cmd.md=$(MAN1DIR)/%.1)
+MAN3_PAGES=$(MAN3_DEPS_FILTERED:$(APP_SRC_DIR)/%.erl=$(MAN3DIR)/%.3)
+MAN3_PAGES+=$(MAN3_DEPS_FILTERED:references/%.md=$(MAN3DIR)/%.3)
+MAN3_PAGES+=$(MAN3_DEPS_FILTERED:src/%.md=$(MAN3DIR)/%.3)
+
# ----------------------------------------------------
# Targets
@@ -64,6 +74,9 @@ endif
ifneq ($(MAN1_DEPS),)
DEFAULT_DOC_TARGETS+=man
endif
+ifneq ($(MAN3_DEPS_FILTERED),)
+DEFAULT_DOC_TARGETS+=man
+endif
DOC_TARGETS?=$(DEFAULT_DOC_TARGETS)
EX_DOC_WARNINGS_AS_ERRORS?=default
@@ -80,13 +93,24 @@ $(HTMLDIR)/index.html: $(HTML_DEPS) docs.exs $(ERL_TOP)/make/ex_doc.exs
html: $(HTMLDIR)/index.html
-man: $(MAN1_PAGES)
+man: $(MAN1_PAGES) $(MAN3_PAGES)
MARKDOWN_TO_MAN=$(ERL_TOP)/make/markdown_to_man.escript
man1/%.1: references/%_cmd.md $(MARKDOWN_TO_MAN)
escript$(EXEEXT) $(MARKDOWN_TO_MAN) -o $(MAN1DIR) $<
+man3/%.3: src/%.md $(MARKDOWN_TO_MAN)
+ escript$(EXEEXT) $(MARKDOWN_TO_MAN) -o $(MAN3DIR) $<
+
+man3/%.3: references/%.md $(MARKDOWN_TO_MAN)
+ escript$(EXEEXT) $(MARKDOWN_TO_MAN) -o $(MAN3DIR) $<
+
+man3/%.3: ../src/%.erl $(MARKDOWN_TO_MAN)
+ escript$(EXEEXT) $(MARKDOWN_TO_MAN) -o $(MAN3DIR) $<
+
+# ----------------------------------------------------
+
$(TYPES):
clean clean_docs: clean_html
@@ -113,6 +137,10 @@ ifneq ($(MAN1_DEPS),)
$(INSTALL_DIR) "$(RELSYS_MANDIR)/man1"
$(INSTALL_DIR_DATA) "$(MAN1DIR)" "$(RELSYS_MANDIR)/man1"
endif
+ifneq ($(MAN3_DEPS_FILTERED),)
+ $(INSTALL_DIR) "$(RELSYS_MANDIR)/man3"
+ $(INSTALL_DIR_DATA) "$(MAN3DIR)" "$(RELSYS_MANDIR)/man3"
+endif
release_docs_spec: $(DOC_TARGETS:%=release_%_spec)
ifneq ($(STANDARDS),)
diff --git a/make/markdown_to_man.escript b/make/markdown_to_man.escript
index 90b801e0d4..d92f1d2de8 100755
--- a/make/markdown_to_man.escript
+++ b/make/markdown_to_man.escript
@@ -21,6 +21,8 @@
%% %CopyrightEnd%
%%
-module(markdown_to_man).
+-include_lib("kernel/include/eep48.hrl").
+
-export([main/1]).
main(Args) ->
@@ -50,19 +52,39 @@ convert_files([], _) ->
ok.
convert_file(Name, OutDir) ->
- Base0 = filename:rootname(filename:basename(Name), ".md"),
- Base = case lists:reverse(Base0) of
- "dmc_" ++ Base1 ->
- lists:reverse(Base1);
- _ ->
- fail(~'~p: file name does not end in "_cmd.md"',
- [Name])
- end,
- OutFile = filename:join(OutDir, Base ++ ".1"),
+ case filename:extension(Name) of
+ ".md" ->
+ Base0 = filename:rootname(filename:basename(Name), ".md"),
+ case lists:reverse(Base0) of
+ "dmc_" ++ Base1 ->
+ Base2 = lists:reverse(Base1),
+ convert_markdown_to_man(Base2, OutDir, Name, ".1");
+ _ ->
+ convert_markdown_to_man(Base0, OutDir, Name, ".3")
+ end;
+ ".erl" ->
+ Base0 = filename:rootname(filename:basename(Name), ".erl"),
+ Output = man_docs:module_to_manpage(list_to_atom(Base0), Name),
+ Outfile = filename:join(OutDir, Base0 ++ ".3"),
+ _ = filelib:ensure_dir(Outfile),
+ case Output =/= <<>> andalso file:write_file(Outfile, Output) of
+ ok ->
+ ok;
+ false ->
+ ok; %% No documentation to write
+ {error,Reason0} ->
+ Reason = file:format_error(Reason0),
+ fail(io_lib:format("~ts: write failed: ~ts",
+ [Outfile,Reason]))
+ end
+ end.
+
+convert_markdown_to_man(Base, OutDir, Name, Section) ->
+ OutFile = filename:join(OutDir, Base ++ Section),
_ = filelib:ensure_dir(OutFile),
case file:read_file(Name) of
- {ok,Markdown} ->
- Man = convert(Markdown),
+ {ok,Markdown} ->
+ Man = man_docs:markdown_to_manpage(Markdown, Name),
case file:write_file(OutFile, Man) of
ok ->
ok;
@@ -76,135 +98,6 @@ convert_file(Name, OutDir) ->
fail(io_lib:format("~ts: ~ts", [Name,Reason]))
end.
-fail(Format, Args) ->
- fail(io_lib:format(Format, Args)).
-
fail(String) ->
E = io_lib:format("~p: ~ts\n", [?MODULE,String]),
throw({error,E}).
-
-convert(Markdown) when is_binary(Markdown) ->
- Items = shell_docs_markdown:parse_md(Markdown),
- Name = get_name(Items),
- Prelude = [~'.TH ', Name, ~' 1 "erts ',
- erlang:system_info(version),
- ~'" "Ericsson AB" "User Commands"\n'],
- iolist_to_binary([Prelude|conv(Items)]).
-
-get_name([{h1,_,[Name]}|_]) when is_binary(Name) ->
- Name.
-
-conv([{h1,_,[Name]},
- {p,_,[ShortDesc0]},
- {h2,_,[~"Synopsis"]},
- Synopsis0,
- {h2,_,[~"Description"]}|T]) when is_binary(ShortDesc0) ->
- ShortDesc = string:trim(ShortDesc0, trailing, [$., $\s]),
- Synopsis = strip_formatting(Synopsis0),
- [~".SH NAME\n",
- Name,~B" \- ",ShortDesc,$\n,
- ~".SH SYNOPSIS\n",
- Synopsis,$\n,
- ~".SH DESCRIPTION\n"|format(T)];
-conv([{h1,_,[Name]},
- {p,_,[ShortDesc0]},
- {h2,_,[~"Description"]}|T]) when is_binary(ShortDesc0) ->
- ShortDesc = string:trim(ShortDesc0, trailing, [$., $\s]),
- [~".SH NAME\n",
- Name,~B" \- ",ShortDesc,$\n,
- ~".SH DESCRIPTION\n"|format(T)];
-conv([{h1,_,[Head]}|T]) ->
- Name = ~".SH NAME\n",
- Desc = ~".SH DESCRIPTION\n",
- [Name,Head,$\n,Desc|format(T)].
-
-format(Is) ->
- [[format_one(I),$\n] || I <- Is].
-
-format_one({blockquote,_,Qs0}) ->
- [{h4,_,Head0},{p,_,Text}|Ps] = Qs0,
- Head = string:uppercase(<<(string:trim(Head0))/binary,": ">>),
- L = [{p,[],[{em,[],Head}|Text]}|Ps],
- format(L);
-format_one({h1,_,Hs}) ->
- [~'.SH "',Hs,~'"\n'];
-format_one({h2,_,Hs}) ->
- [~'.SS "',Hs,~'"\n'];
-format_one({p,_,Ps}) ->
- format_p(Ps);
-format_one({pre,_,Ps}) ->
- format_pre(Ps);
-format_one({ul,_,Ul}) ->
- format_ul(Ul).
-
-format_p(Is0) ->
- Text0 = iolist_to_binary([format_p_item(I) || I <- Is0]),
- Text = string:trim(Text0, leading),
- [~".PP\n",Text,$\n].
-
-format_p_item({code,_,Text}) ->
- [~B"\fI",format_p_item(Text),~B"\fR"];
-format_p_item({em,_,Text}) ->
- [~B"\fB",format_p_item(Text),~B"\fR"];
-format_p_item({i,_,Text}) ->
- [~B"\fI",format_p_item(Text),~B"\fR"];
-format_p_item([H|T]) ->
- [format_p_item(H)|format_p_item(T)];
-format_p_item([]) ->
- [];
-format_p_item(Text) when is_binary(Text) ->
- escape_backslashes(Text).
-
-format_pre(Ps0) ->
- Ps = [format_pre_item(P) || P <- Ps0],
- [~".IP\n.nf\n",Ps,$\n,~".fi\n"].
-
-format_pre_item({code,_,Text}) ->
- escape_backslashes(Text).
-
-format_ul(UL) ->
- [format_ul_item(I) || I <- UL].
-
-format_ul_item({li,_,Ps0}) ->
- case Ps0 of
- [{p,_,[Head,<<" - ",Text0/binary>>|Items]}|T] ->
- Text = string:trim(Text0, leading),
- [strip_formatting(Head),$\n,
- ~".RS 2\n",
- Text,$\n,
- [format_p_item(I) || I <- Items],
- $\n,
- format(T),$\n,
- ~".RE\n"
- ];
- _ ->
- B = ~"""
-
- .sp
- .RS 4
- .ie n \{\
- \h'-04'\(bu\h'+03'\c
- .\}
- .el \{\
- .sp -1
- .IP \(bu 2.3
- .\}
- """,
- [B,format(Ps0),~".RE\n"]
- end.
-
-strip_formatting({_,_,[_|_]=L}) ->
- strip_formatting(L);
-strip_formatting([H|T]) ->
- [strip_formatting(H),strip_formatting(T)];
-strip_formatting([]) ->
- [];
-strip_formatting(<<".",_/binary>> = Bin) ->
- [~B"\&",Bin];
-strip_formatting(Bin) when is_binary(Bin) ->
- Bin.
-
-escape_backslashes(Text) when is_list(Text) ->
- escape_backslashes(iolist_to_binary(Text));
-escape_backslashes(Text) when is_binary(Text) ->
- binary:replace(Text, ~B"\", ~B"\\", [global]).
diff --git a/make/otp.mk.in b/make/otp.mk.in
index 39d0acd305..09c920c2f7 100644
--- a/make/otp.mk.in
+++ b/make/otp.mk.in
@@ -217,6 +217,7 @@ EX_DOC = @EX_DOC@
DOCDIR=.
HTMLDIR = $(DOCDIR)/html
MAN1DIR = $(DOCDIR)/man1
+MAN3DIR = $(DOCDIR)/man3
CHUNKSDIR = $(DOCDIR)/chunks
ifeq ($(HTMLLOGO),)
--
2.51.0