File 1162-doc-create-man-pages-for-apps-with-source-files-spli.patch of Package erlang
From 27a5ef85b5fc8e5281838b525eaecc0870076252 Mon Sep 17 00:00:00 2001
From: Fredrik Frantzen <frazze@erlang.org>
Date: Fri, 26 Sep 2025 13:43:32 +0200
Subject: [PATCH 2/2] doc: create man pages for apps with source files split up
in sub dirs
---
.gitignore | 3 +
lib/stdlib/src/man_docs.erl | 106 ++++++++++++++++-----------
lib/stdlib/src/shell_docs.erl | 1 +
lib/stdlib/test/shell_docs_SUITE.erl | 2 +-
make/doc.mk | 97 +++++++++++++++++++-----
make/markdown_to_man.escript | 48 +++++++-----
make/otp.mk.in | 3 +
7 files changed, 178 insertions(+), 82 deletions(-)
diff --git a/lib/stdlib/src/man_docs.erl b/lib/stdlib/src/man_docs.erl
index 83bf8b3c4e..2bcac70f1e 100644
--- a/lib/stdlib/src/man_docs.erl
+++ b/lib/stdlib/src/man_docs.erl
@@ -20,31 +20,37 @@
%% %CopyrightEnd%
%%
-module(man_docs).
+-moduledoc false.
+
-include_lib("kernel/include/eep48.hrl").
--export([module_to_manpage/2, module_to_manpage/3, markdown_to_manpage/2]).
+-export([module_to_manpage/3, module_to_manpage/4, markdown_to_manpage/3]).
%% 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
+-spec module_to_manpage(Module, Path, Section) -> unicode:chardata() when
Module :: module(),
- Path :: string().
-module_to_manpage(Module, Path) when is_atom(Module) ->
+ Path :: string(),
+ Section :: string().
+module_to_manpage(Module, Path, Section) when is_atom(Module) ->
case code:get_doc(Module) of
{ok, Docs} ->
- module_to_manpage(Module, Path, Docs);
+ module_to_manpage(Module, Path, Docs, Section);
_Error ->
~""
end.
--spec module_to_manpage(Module, Path, Docs) -> unicode:chardata() when
+-spec module_to_manpage(Module, Path, Docs, Section) -> 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 ->
+ Docs :: #docs_v1{},
+ Section :: string().
+module_to_manpage(_Module, _Path, #docs_v1{module_doc = None}, _Section) when None =:= none; None =:= hidden ->
~"";
-module_to_manpage(Module, Path, #docs_v1{module_doc = #{~"en" := ModuleDoc}, docs = AllDocs})
+module_to_manpage(Module, Path, #docs_v1{module_doc = #{~"en" := ModuleDoc}, docs = AllDocs}, Section)
when is_atom(Module) ->
- PreludeNDescription = markdown_to_manpage(ModuleDoc, Path),
+ PreludeNDescription = if is_binary(ModuleDoc) -> markdown_to_manpage(ModuleDoc, Path, Section);
+ true -> markdown_to_manpage1(ModuleDoc, Path, Section)
+ end,
Types = [Doc || {{type,_,_},_,_,_,_}=Doc <- AllDocs],
TypesSection = format_section("DATA TYPES", Types, Module, AllDocs),
@@ -56,10 +62,10 @@ module_to_manpage(Module, Path, #docs_v1{module_doc = #{~"en" := ModuleDoc}, doc
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) ->
+-spec markdown_to_manpage(binary(), file:filename(), string()) -> binary().
+markdown_to_manpage(Markdown, Path, Section) ->
+ markdown_to_manpage1(shell_docs_markdown:parse_md(Markdown), Path, Section).
+markdown_to_manpage1(MarkdownChunks, Path, Section) ->
Path1 = filename:absname(Path),
App = case filename:split(string:prefix(Path1, os:getenv("ERL_TOP"))) of
["/", "lib", AppStr | _] ->
@@ -80,8 +86,8 @@ markdown_to_manpage(MarkdownChunks, Path) ->
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]),
+ Prelude = io_lib:format(".TH ~s ~s \"~s ~s\" \"Ericsson AB\" \"Erlang Module Definition\"\n",
+ [Name, Section, atom_to_binary(App), Version]),
I = conv(MarkdownChunks, Name),
iolist_to_binary([Prelude|I]).
@@ -113,10 +119,11 @@ conv([{h1,_,[Head]}|T],_) ->
Name = ~".SH NAME\n",
Desc = ~".SH DESCRIPTION\n",
[Name,Head,$\n,Desc|format(T)];
-conv([H|T], Head) ->
+conv([{p,_,_}=ShortDesc0|T], Head) ->
Name = ~".SH NAME\n",
Desc = ~".SH DESCRIPTION\n",
- [Name,Head,~" - ",format_one(H),$\n,Desc|format(T)].
+ [~".PP\n"|ShortDesc] = format_one(ShortDesc0),
+ [Name,Head,~B" \- ",ShortDesc,$\n,Desc|format(T)].
escape(Text) when is_list(Text) ->
escape(iolist_to_binary(Text));
@@ -136,10 +143,12 @@ format_one({h1,_,Hs}) ->
[~'.SH "',Hs,~'"\n'];
format_one({h2,_,Hs}) ->
[~'.SS "',Hs,~'"\n'];
+format_one({h3,item,H}) ->
+ [~"\\fB",format_p_item(H),"\\fR"];
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({h3,_,Hs}) when is_list(Hs) ->
+ [~'.PP\n',[format_one({h3,item,Hi})||Hi<-Hs],~"\n"];
format_one({h4,_,Hs}) ->
format_one({h3,[],Hs});
format_one({h5,_,Hs}) ->
@@ -152,16 +161,18 @@ format_one({ol,_,Ol}) ->
format_ol(Ol);
format_one({ul,_,Ul}) ->
format_ul(Ul);
+format_one({a,_,[{code,_,Text}]}) ->
+ [~B"\fI",format_p_item(Text),~B"\fR"];
format_one({a,_,Text}) ->
- [~B"\fI",format(Text),~B"\fR"];
+ [~B"\fI",format_p_item(Text),~B"\fR"];
format_one({code,_,Text}) ->
- [~B"\fI",format(Text),~B"\fR"];
+ [~B"\fI",format_p_item(Text),~B"\fR"];
format_one({strong,_,Text}) ->
- ["\\fB", Text, "\\fR"];
+ [~B"\fB", format_p_item(Text), ~B"\fR"];
format_one({em,_,Text}) ->
- [~B"\fB",format_one(Text),~B"\fR"];
+ [~B"\fB",format_p_item(Text),~B"\fR"];
format_one({i,_,Text}) ->
- [~B"\fI",format_one(Text),~B"\fR"];
+ [~B"\fI",format_p_item(Text),~B"\fR"];
format_one({dl,_,Content}) ->
format_dl(Content);
format_one([Text]) when is_binary(Text) ->
@@ -172,10 +183,16 @@ format_one(Text) when is_binary(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];
+ [~".TP\n", "\\fB", format_p_item(Content), "\\fR", $\n];
format_dl_item({dd,_,Content}) ->
- format(Content).
-
+ [format_dd_item(Content), $\n].
+format_dd_item([{ul,_,_}=UL|Rest]) ->
+ [format([UL]), format_dd_item(Rest)];
+format_dd_item([{p,_,Content}|Rest]) ->
+ [format_p(Content)|format_dd_item(Rest)];
+format_dd_item([TextItem|Rest]) ->
+ [format_p_item(TextItem),format_dd_item(Rest)];
+format_dd_item([]) -> [].
format_p(Text) when is_binary(Text) ->
format_p([Text]);
format_p(Is0) ->
@@ -183,16 +200,10 @@ format_p(Is0) ->
Text = string:trim(Text0, leading),
[~".PP\n",Text,$\n].
-format_p_item({code,_,Text}) ->
+format_p_item({Fi,_,Text}) when Fi =:= code; Fi =:= i; Fi =:= a ->
[~B"\fI",format_p_item(Text),~B"\fR"];
-format_p_item({em,_,Text}) ->
+format_p_item({Fb,_,Text}) when Fb =:= em; Fb =:= strong ->
[~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([]) ->
@@ -205,8 +216,7 @@ format_pre(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);
+ to_tbl(parse(extract(iolist_to_binary(Text))));
format_pre_item({code,_,Text}) ->
escape_backslashes(Text);
format_pre_item(Text) ->
@@ -257,7 +267,13 @@ format_ul_item({li,_,Ps0}) ->
.IP \(bu 2.3
.\}
""",
- [B,format(Ps0),~".RE\n"]
+ case Ps0 of
+ [Text|_] when is_binary(Text);
+ element(1,Text) =:= code;
+ element(1,Text) =:= a ->
+ [B,format_p(Ps0),~".RE\n"];
+ _ -> [B,format(Ps0),~".RE\n"]
+ end
end.
strip_formatting({_,_,[_|_]=L}) ->
@@ -341,7 +357,10 @@ parse_row(Line) ->
Cells = binary:split(NoOuterPipes, <<"|">>, [global]),
%% 4. Trim whitespace from each individual cell.
- [string:trim(Cell) || Cell <- Cells].
+ [format_cell(string:trim(Cell)) || Cell <- Cells].
+
+format_cell(B) ->
+ re:replace(B,"`(.+)`",<<"\\\\fI\\g{1}\\\\fR">>, [{return, binary},global]).
%% Helper to safely remove the first and last characters if they are pipes.
strip_outer_pipes(Bin) ->
@@ -415,9 +434,10 @@ format_ast(AST) ->
BinSpec = unicode:characters_to_binary(string:trim(Spec, trailing, "\n")),
BinSpec2 = re:replace(BinSpec, "-((type)|(spec)|(callback)) ", ""),
-
- ["\\fB", escape(BinSpec2), "\\fR", "\n"].
+ BinSpec3 = string:replace(escape(BinSpec2),"\n","\\fR\n\\fB",all),
+ ["\\fB", BinSpec3, "\\fR", "\n"].
format_meta(#{ deprecated := Depr } = M) ->
- ["\n.br\nDeprecated: ", unicode:characters_to_binary(Depr) | format_meta(maps:remove(deprecated, M))];
+ [~"\n.RS\n.LP\nDeprecated: ",
+ unicode:characters_to_binary(Depr), ~"\n.RE\n" | 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 45ae2019ff..2f169ea2c1 100644
--- a/lib/stdlib/src/shell_docs.erl
+++ b/lib/stdlib/src/shell_docs.erl
@@ -618,6 +618,7 @@ render_type(Module, D) ->
render_type(Module, D, #{}).
%% extract AST raw type specifications.
+-doc false.
-spec extract_type_specs(module()) -> map().
extract_type_specs(Module) ->
maybe
diff --git a/lib/stdlib/test/shell_docs_SUITE.erl b/lib/stdlib/test/shell_docs_SUITE.erl
index ccdda82e4e..bb6a8780ca 100644
--- a/lib/stdlib/test/shell_docs_SUITE.erl
+++ b/lib/stdlib/test/shell_docs_SUITE.erl
@@ -326,7 +326,7 @@ render_man(_Config) ->
#{source_path := Path} -> Path;
#{} -> proplists:get_value(source, proplists:get_value(compile, Mod:module_info()))
end,
- man_docs:module_to_manpage(Mod, Path1, D)
+ man_docs:module_to_manpage(Mod, Path1, D, "3")
catch _E:R:ST ->
io:format("Failed to render man page for ~p~n~p:~p~n~p~n",
[Mod,R,ST,D]),
diff --git a/make/doc.mk b/make/doc.mk
index 5ef7fac458..2fd5a86c69 100644
--- a/make/doc.mk
+++ b/make/doc.mk
@@ -50,19 +50,39 @@ endif
# ----------------------------------------------------
# Man dependencies
# ----------------------------------------------------
-ERL_FILES := $(wildcard $(APP_SRC_DIR)/*.erl)
-ERL_FILES_WITH_DOC := $(shell grep -L '-moduledoc false.' $(ERL_FILES))
+ERL_FILES := $(wildcard $(APP_SRC_DIR)/*.erl) $(wildcard $(APP_SRC_DIR)/*/*.erl) $(wildcard $(APP_DIR)/preloaded/src/*.erl)
+ERL_STRIP := $(strip $(ERL_FILES))
+ifneq ($(ERL_STRIP),)
+ ERL_FILES_WITH_DOC := $(shell grep -L "moduledoc false." $(ERL_FILES))
+else
+ ERL_FILES_WITH_DOC :=
+endif
+ERL_FILENAMES_ONLY := $(notdir $(ERL_FILES_WITH_DOC))
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))
-
+MAN3_DEPS_UNFILTERED?=$(wildcard */src/*.md) $(wildcard src/*.md) \
+ $(wildcard */references/*.md) $(wildcard references/*.md) \
+ $(ERL_FILENAMES_ONLY)
+MAN4_DEPS=$(wildcard references/app.md references/config.md references/appup.md references/rel.md \
+ references/relup.md references/script.md references/diameter_dict.md references/erlang.el.md)
+MAN3_DEPS=$(filter-out $(wildcard */references/*_cmd.md) $(wildcard references/*_cmd.md) $(MAN4_DEPS),$(MAN3_DEPS_UNFILTERED))
+MAN6_DEPS=$(wildcard *_app.md)
+MAN7_DEPS=$(wildcard $(APP_DIR)/mibs/*.mib)
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)
-
+MAN3_PAGES=$(MAN3_DEPS:%.erl=$(MAN3DIR)/%.3)
+MAN3_PAGES+=$(MAN3_DEPS:src/%.md=$(MAN3DIR)/%.3)
+MAN3_PAGES+=$(MAN3_DEPS:references/%.md=$(MAN3DIR)/%.3)
+MAN4_PAGES=$(MAN4_DEPS:references/%.md=$(MAN4DIR)/%.4)
+MAN6_PAGES=$(MAN6_DEPS:%_app.md=$(MAN6DIR)/%.6)
+MAN7_PAGES=$(MAN7_DEPS:$(APP_DIR)/mibs/%.mib=$(MAN7DIR)/%.7)
+
+# 1. Find all possible source directories recursively
+ifneq ($(wildcard $(APP_SRC_DIR)),)
+ERL_SRC_DIRS := $(shell find $(APP_SRC_DIR) -type d)
+else
+ERL_SRC_DIRS :=
+endif
+# 2. Tell make to search for .erl files in all those directories
+vpath %.erl $(ERL_SRC_DIRS) $(APP_DIR)/preloaded/src
# ----------------------------------------------------
# Targets
@@ -74,9 +94,19 @@ endif
ifneq ($(MAN1_DEPS),)
DEFAULT_DOC_TARGETS+=man
endif
-ifneq ($(MAN3_DEPS_FILTERED),)
+ifneq ($(MAN3_DEPS),)
DEFAULT_DOC_TARGETS+=man
endif
+ifneq ($(MAN4_DEPS),)
+DEFAULT_DOC_TARGETS+=man
+endif
+ifneq ($(MAN6_DEPS),)
+DEFAULT_DOC_TARGETS+=man
+endif
+ifneq ($(MAN7_DEPS),)
+DEFAULT_DOC_TARGETS+=man
+endif
+
DOC_TARGETS?=$(DEFAULT_DOC_TARGETS)
EX_DOC_WARNINGS_AS_ERRORS?=default
@@ -93,21 +123,36 @@ $(HTMLDIR)/index.html: $(HTML_DEPS) docs.exs $(ERL_TOP)/make/ex_doc.exs
html: $(HTMLDIR)/index.html
-man: $(MAN1_PAGES) $(MAN3_PAGES)
+man: $(MAN1_PAGES) $(MAN3_PAGES) $(MAN4_PAGES) $(MAN6_PAGES) $(MAN7_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) $<
+ @escript$(EXEEXT) $(MARKDOWN_TO_MAN) -o $(MAN1DIR) $<
man3/%.3: src/%.md $(MARKDOWN_TO_MAN)
- escript$(EXEEXT) $(MARKDOWN_TO_MAN) -o $(MAN3DIR) $<
+ @escript$(EXEEXT) $(MARKDOWN_TO_MAN) -o $(MAN3DIR) $<
man3/%.3: references/%.md $(MARKDOWN_TO_MAN)
- escript$(EXEEXT) $(MARKDOWN_TO_MAN) -o $(MAN3DIR) $<
+ @escript$(EXEEXT) $(MARKDOWN_TO_MAN) -o $(MAN3DIR) $<
+
+man3/%.3: %.erl $(MARKDOWN_TO_MAN)
+ @escript$(EXEEXT) $(MARKDOWN_TO_MAN) -o $(MAN3DIR) $<
+
+man4/%.4: references/%.md $(MARKDOWN_TO_MAN)
+ @escript$(EXEEXT) $(MARKDOWN_TO_MAN) -o $(MAN4DIR) -s 4 $<
+
+man6/%.6: %_app.md $(MARKDOWN_TO_MAN)
+ @escript$(EXEEXT) $(MARKDOWN_TO_MAN) -o $(MAN6DIR) $<
-man3/%.3: ../src/%.erl $(MARKDOWN_TO_MAN)
- escript$(EXEEXT) $(MARKDOWN_TO_MAN) -o $(MAN3DIR) $<
+man7/%.7: $(APP_DIR)/mibs/%.mib
+ @mkdir -p man7
+ $(eval REL_PATH := $(patsubst $(ERL_TOP)/lib/%,%,$(abspath $<)))
+ $(eval APP_NAME := $(shell echo $(firstword $(subst /, ,$(REL_PATH))) | tr '[:lower:]' '[:upper:]'))
+ $(eval MIB_NAME := $(basename $(notdir $<)))
+ @echo .TH $(MIB_NAME) 7 \"$(APP_NAME)\" \"Erlang/OTP\" \"MIB\" > $@
+ @echo .nf >> $@
+ @grep -v '^--' $< >> $@
# ----------------------------------------------------
@@ -137,10 +182,24 @@ ifneq ($(MAN1_DEPS),)
$(INSTALL_DIR) "$(RELSYS_MANDIR)/man1"
$(INSTALL_DIR_DATA) "$(MAN1DIR)" "$(RELSYS_MANDIR)/man1"
endif
-ifneq ($(MAN3_DEPS_FILTERED),)
+ifneq ($(MAN3_DEPS),)
$(INSTALL_DIR) "$(RELSYS_MANDIR)/man3"
$(INSTALL_DIR_DATA) "$(MAN3DIR)" "$(RELSYS_MANDIR)/man3"
endif
+ifneq ($(MAN4_DEPS),)
+ $(INSTALL_DIR) "$(RELSYS_MANDIR)/man4"
+ $(INSTALL_DIR_DATA) "$(MAN4DIR)" "$(RELSYS_MANDIR)/man4"
+endif
+ifneq ($(MAN6_DEPS),)
+ $(INSTALL_DIR) "$(RELSYS_MANDIR)/man6"
+ $(INSTALL_DIR_DATA) "$(MAN6DIR)" "$(RELSYS_MANDIR)/man6"
+endif
+ifneq ($(MAN7_DEPS),)
+ $(INSTALL_DIR) "$(RELSYS_MANDIR)/man7"
+ $(INSTALL_DIR_DATA) "$(MAN7DIR)" "$(RELSYS_MANDIR)/man7"
+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 d92f1d2de8..d841914e05 100755
--- a/make/markdown_to_man.escript
+++ b/make/markdown_to_man.escript
@@ -27,44 +27,54 @@
main(Args) ->
try
- case parse_args(Args, ".", []) of
+ case parse_args(Args, "3", ".", []) of
{_,[]} ->
ok;
- {OutDir,[_|_]=Files} ->
- convert_files(Files, OutDir)
+ {OutDir,Section,[_|_]=Files} ->
+ convert_files(Files, OutDir, Section)
end
catch
throw:{error,Error} ->
io:put_chars(standard_error, Error)
end.
-parse_args(["-o",OutDir|As], _OutDir, FilesAcc) ->
- parse_args(As, OutDir, FilesAcc);
-parse_args([F|Fs], OutDir, FilesAcc) ->
- parse_args(Fs, OutDir, [F|FilesAcc]);
-parse_args([], OutDir, FilesAcc) ->
- {OutDir,lists:reverse(FilesAcc)}.
+parse_args(["-s", Num|As], _Section, OutDir, FilesAcc) ->
+ case lists:member(Num, ["1","3","4","6"]) of
+ true ->
+ parse_args(As, Num, OutDir, FilesAcc);
+ false ->
+ fail(io_lib:format("Invalid section number: ~s", [Num]))
+ end;
+parse_args(["-o",OutDir|As], Section, _OutDir, FilesAcc) ->
+ parse_args(As, Section, OutDir, FilesAcc);
+parse_args([F|Fs], Section, OutDir, FilesAcc) ->
+ parse_args(Fs, Section, OutDir, [F|FilesAcc]);
+parse_args([], Section, OutDir, FilesAcc) ->
+ {OutDir, Section, lists:reverse(FilesAcc)}.
-convert_files([F|Fs], OutDir) ->
- convert_file(F, OutDir),
- convert_files(Fs, OutDir);
-convert_files([], _) ->
+convert_files([F|Fs], OutDir, Section) ->
+ convert_file(F, OutDir, Section),
+ convert_files(Fs, OutDir, Section);
+convert_files([], _, _) ->
ok.
-convert_file(Name, OutDir) ->
+convert_file(Name, OutDir, Section) ->
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(Base2, OutDir, Name, "1");
+ "ppa_" ++ Base1 ->
+ Base2 = lists:reverse(Base1),
+ convert_markdown_to_man(Base2, OutDir, Name, "6");
_ ->
- convert_markdown_to_man(Base0, OutDir, Name, ".3")
+ convert_markdown_to_man(Base0, OutDir, Name, Section)
end;
".erl" ->
Base0 = filename:rootname(filename:basename(Name), ".erl"),
- Output = man_docs:module_to_manpage(list_to_atom(Base0), Name),
+ Output = man_docs:module_to_manpage(list_to_atom(Base0), Name, "3"),
Outfile = filename:join(OutDir, Base0 ++ ".3"),
_ = filelib:ensure_dir(Outfile),
case Output =/= <<>> andalso file:write_file(Outfile, Output) of
@@ -80,11 +90,11 @@ convert_file(Name, OutDir) ->
end.
convert_markdown_to_man(Base, OutDir, Name, Section) ->
- OutFile = filename:join(OutDir, Base ++ Section),
+ OutFile = filename:join(OutDir, Base ++ "." ++ Section),
_ = filelib:ensure_dir(OutFile),
case file:read_file(Name) of
{ok,Markdown} ->
- Man = man_docs:markdown_to_manpage(Markdown, Name),
+ Man = man_docs:markdown_to_manpage(Markdown, Name, Section),
case file:write_file(OutFile, Man) of
ok ->
ok;
diff --git a/make/otp.mk.in b/make/otp.mk.in
index 09c920c2f7..b2d9149677 100644
--- a/make/otp.mk.in
+++ b/make/otp.mk.in
@@ -218,6 +218,9 @@ DOCDIR=.
HTMLDIR = $(DOCDIR)/html
MAN1DIR = $(DOCDIR)/man1
MAN3DIR = $(DOCDIR)/man3
+MAN4DIR = $(DOCDIR)/man4
+MAN6DIR = $(DOCDIR)/man6
+MAN7DIR = $(DOCDIR)/man7
CHUNKSDIR = $(DOCDIR)/chunks
ifeq ($(HTMLLOGO),)
--
2.51.0