2020% % %CopyrightEnd%
2121% %
2222-module (man_docs ).
23+ -moduledoc false .
24+
2325-include_lib (" kernel/include/eep48.hrl" ).
2426
25- -export ([module_to_manpage /2 , module_to_manpage /3 , markdown_to_manpage /2 ]).
27+ -export ([module_to_manpage /3 , module_to_manpage /4 , markdown_to_manpage /3 ]).
2628
2729% % Formats a module documentation as a roff man page.
2830% % Fetches the documentation for a module with `code:get_doc/1`
29- -spec module_to_manpage (Module , Path ) -> unicode :chardata () when
31+ -spec module_to_manpage (Module , Path , Section ) -> unicode :chardata () when
3032 Module :: module (),
31- Path :: string ().
32- module_to_manpage (Module , Path ) when is_atom (Module ) ->
33+ Path :: string (),
34+ Section :: string ().
35+ module_to_manpage (Module , Path , Section ) when is_atom (Module ) ->
3336 case code :get_doc (Module ) of
3437 {ok , Docs } ->
35- module_to_manpage (Module , Path , Docs );
38+ module_to_manpage (Module , Path , Docs , Section );
3639 _Error ->
3740 ~ " "
3841 end .
39- -spec module_to_manpage (Module , Path , Docs ) -> unicode :chardata () when
42+ -spec module_to_manpage (Module , Path , Docs , Section ) -> unicode :chardata () when
4043 Module :: module (),
4144 Path :: string (),
42- Docs :: # docs_v1 {}.
43- module_to_manpage (_Module , _Path , # docs_v1 {module_doc = None }) when None =:= none ; None =:= hidden ->
45+ Docs :: # docs_v1 {},
46+ Section :: string ().
47+ module_to_manpage (_Module , _Path , # docs_v1 {module_doc = None }, _Section ) when None =:= none ; None =:= hidden ->
4448 ~ " " ;
45- module_to_manpage (Module , Path , # docs_v1 {module_doc = #{~ " en" := ModuleDoc }, docs = AllDocs })
49+ module_to_manpage (Module , Path , # docs_v1 {module_doc = #{~ " en" := ModuleDoc }, docs = AllDocs }, Section )
4650 when is_atom (Module ) ->
47- PreludeNDescription = markdown_to_manpage (ModuleDoc , Path ),
51+ PreludeNDescription = if is_binary (ModuleDoc ) -> markdown_to_manpage (ModuleDoc , Path , Section );
52+ true -> markdown_to_manpage1 (ModuleDoc , Path , Section )
53+ end ,
4854
4955 Types = [Doc || {{type ,_ ,_ },_ ,_ ,_ ,_ }= Doc <- AllDocs ],
5056 TypesSection = format_section (" DATA TYPES" , Types , Module , AllDocs ),
@@ -56,10 +62,10 @@ module_to_manpage(Module, Path, #docs_v1{module_doc = #{~"en" := ModuleDoc}, doc
5662 iolist_to_binary ([PreludeNDescription , TypesSection , FunctionsSection , CallbacksSection ]).
5763
5864% % Formats markdown as a roff man page.
59- -spec markdown_to_manpage (binary () | shell_docs : chunk_elements (), file : filename ()) -> binary ().
60- markdown_to_manpage (Markdown , Path ) when is_binary ( Markdown ) ->
61- markdown_to_manpage (shell_docs_markdown :parse_md (Markdown ), Path );
62- markdown_to_manpage (MarkdownChunks , Path ) ->
65+ -spec markdown_to_manpage (binary (), file : filename (), string ()) -> binary ().
66+ markdown_to_manpage (Markdown , Path , Section ) ->
67+ markdown_to_manpage1 (shell_docs_markdown :parse_md (Markdown ), Path , Section ).
68+ markdown_to_manpage1 (MarkdownChunks , Path , Section ) ->
6369 Path1 = filename :absname (Path ),
6470 App = case filename :split (string :prefix (Path1 , os :getenv (" ERL_TOP" ))) of
6571 [" /" , " lib" , AppStr | _ ] ->
@@ -80,8 +86,8 @@ markdown_to_manpage(MarkdownChunks, Path) ->
8086 Extension = filename :extension (Path ),
8187 FileName = list_to_binary (filename :rootname (filename :basename (Path ), Extension )),
8288 Name = get_name (MarkdownChunks , FileName ),
83- Prelude = io_lib :format (" .TH ~s 3 \" ~s ~s \" \" Ericsson AB\" \" Erlang Module Definition\"\n " ,
84- [Name , atom_to_binary (App ), Version ]),
89+ Prelude = io_lib :format (" .TH ~s ~s \" ~s ~s \" \" Ericsson AB\" \" Erlang Module Definition\"\n " ,
90+ [Name , Section , atom_to_binary (App ), Version ]),
8591 I = conv (MarkdownChunks , Name ),
8692 iolist_to_binary ([Prelude |I ]).
8793
@@ -113,10 +119,11 @@ conv([{h1,_,[Head]}|T],_) ->
113119 Name = ~ " .SH NAME\n " ,
114120 Desc = ~ " .SH DESCRIPTION\n " ,
115121 [Name ,Head ,$\n ,Desc |format (T )];
116- conv ([H |T ], Head ) ->
122+ conv ([{ p , _ , _ } = ShortDesc0 |T ], Head ) ->
117123 Name = ~ " .SH NAME\n " ,
118124 Desc = ~ " .SH DESCRIPTION\n " ,
119- [Name ,Head ,~ " - " ,format_one (H ),$\n ,Desc |format (T )].
125+ [~ " .PP\n " |ShortDesc ] = format_one (ShortDesc0 ),
126+ [Name ,Head ,~B " \- " ,ShortDesc ,$\n ,Desc |format (T )].
120127
121128escape (Text ) when is_list (Text ) ->
122129 escape (iolist_to_binary (Text ));
@@ -136,10 +143,12 @@ format_one({h1,_,Hs}) ->
136143 [~ ' .SH "' ,Hs ,~ ' "\n ' ];
137144format_one ({h2 ,_ ,Hs }) ->
138145 [~ ' .SS "' ,Hs ,~ ' "\n ' ];
146+ format_one ({h3 ,item ,H }) ->
147+ [~ " \\ fB" ,format_p_item (H )," \\ fR" ];
139148format_one ({h3 ,_ ,[Hs ]}) when is_binary (Hs ) ->
140149 [~ ' .PP\n\\ fB' ,Hs ,~ ' \\ fR\n ' ];
141- format_one ({h3 ,_ ,Hs }) ->
142- [~ ' .PP\n\\ fB ' , format_p ( Hs ), ~ ' \\ fR \n ' ];
150+ format_one ({h3 ,_ ,Hs }) when is_list ( Hs ) ->
151+ [~ ' .PP\n ' ,[ format_one ({ h3 , item , Hi })|| Hi <- Hs ], ~ " \n " ];
143152format_one ({h4 ,_ ,Hs }) ->
144153 format_one ({h3 ,[],Hs });
145154format_one ({h5 ,_ ,Hs }) ->
@@ -152,16 +161,18 @@ format_one({ol,_,Ol}) ->
152161 format_ol (Ol );
153162format_one ({ul ,_ ,Ul }) ->
154163 format_ul (Ul );
164+ format_one ({a ,_ ,[{code ,_ ,Text }]}) ->
165+ [~B " \fI" ,format_p_item (Text ),~B " \fR" ];
155166format_one ({a ,_ ,Text }) ->
156- [~B " \fI" ,format (Text ),~B " \fR" ];
167+ [~B " \fI" ,format_p_item (Text ),~B " \fR" ];
157168format_one ({code ,_ ,Text }) ->
158- [~B " \fI" ,format (Text ),~B " \fR" ];
169+ [~B " \fI" ,format_p_item (Text ),~B " \fR" ];
159170format_one ({strong ,_ ,Text }) ->
160- [" \\ fB" , Text , " \ \ fR" ];
171+ [~B " \ fB" , format_p_item ( Text ), ~B " \fR" ];
161172format_one ({em ,_ ,Text }) ->
162- [~B " \fB" ,format_one (Text ),~B " \fR" ];
173+ [~B " \fB" ,format_p_item (Text ),~B " \fR" ];
163174format_one ({i ,_ ,Text }) ->
164- [~B " \fI" ,format_one (Text ),~B " \fR" ];
175+ [~B " \fI" ,format_p_item (Text ),~B " \fR" ];
165176format_one ({dl ,_ ,Content }) ->
166177 format_dl (Content );
167178format_one ([Text ]) when is_binary (Text ) ->
@@ -172,27 +183,27 @@ format_one(Text) when is_binary(Text) ->
172183format_dl (Is ) ->
173184 [~ " .RS 4\n " , [format_dl_item (I ) || I <- Is ], ~ " .RE\n " ].
174185format_dl_item ({dt ,_ ,Content }) ->
175- [~ " .TP\n " , " \\ fB" , format (Content ), " \\ fR" , $\n ];
186+ [~ " .TP\n " , " \\ fB" , format_p_item (Content ), " \\ fR" , $\n ];
176187format_dl_item ({dd ,_ ,Content }) ->
177- format (Content ).
178-
188+ [format_dd_item (Content ), $\n ].
189+ format_dd_item ([{ul ,_ ,_ }= UL |Rest ]) ->
190+ [format ([UL ]), format_dd_item (Rest )];
191+ format_dd_item ([{p ,_ ,Content }|Rest ]) ->
192+ [format_p (Content )|format_dd_item (Rest )];
193+ format_dd_item ([TextItem |Rest ]) ->
194+ [format_p_item (TextItem ),format_dd_item (Rest )];
195+ format_dd_item ([]) -> [].
179196format_p (Text ) when is_binary (Text ) ->
180197 format_p ([Text ]);
181198format_p (Is0 ) ->
182199 Text0 = iolist_to_binary ([format_p_item (I ) || I <- Is0 ]),
183200 Text = string :trim (Text0 , leading ),
184201 [~ " .PP\n " ,Text ,$\n ].
185202
186- format_p_item ({code ,_ ,Text }) ->
203+ format_p_item ({Fi ,_ ,Text }) when Fi =:= code ; Fi =:= i ; Fi =:= a ->
187204 [~B " \fI" ,format_p_item (Text ),~B " \fR" ];
188- format_p_item ({em ,_ ,Text }) ->
205+ format_p_item ({Fb ,_ ,Text }) when Fb =:= em ; Fb =:= strong ->
189206 [~B " \fB" ,format_p_item (Text ),~B " \fR" ];
190- format_p_item ({i ,_ ,Text }) ->
191- [~B " \fI" ,format_p_item (Text ),~B " \fR" ];
192- format_p_item ({a ,_ ,Text }) ->
193- [~B " \fI" ,format_p_item (Text ),~B " \fR" ];
194- format_p_item ({strong ,_ ,Text }) ->
195- [" \\ fB" , format_p_item (Text ), " \\ fR" ];
196207format_p_item ([H |T ]) ->
197208 [format_p_item (H )|format_p_item (T )];
198209format_p_item ([]) ->
@@ -205,8 +216,7 @@ format_pre(Ps0) ->
205216 [~ " .IP\n .nf\n " ,Ps ,$\n ,~ " .fi\n " ].
206217
207218format_pre_item ({code ,[{class ,<<" table" >>}],Text }) ->
208- Text2 = to_tbl (parse (extract (iolist_to_binary (Text )))),
209- escape_backslashes (Text2 );
219+ to_tbl (parse (extract (iolist_to_binary (Text ))));
210220format_pre_item ({code ,_ ,Text }) ->
211221 escape_backslashes (Text );
212222format_pre_item (Text ) ->
@@ -257,7 +267,13 @@ format_ul_item({li,_,Ps0}) ->
257267 .IP \(bu 2.3
258268 .\}
259269 """ ,
260- [B ,format (Ps0 ),~ " .RE\n " ]
270+ case Ps0 of
271+ [Text |_ ] when is_binary (Text );
272+ element (1 ,Text ) =:= code ;
273+ element (1 ,Text ) =:= a ->
274+ [B ,format_p (Ps0 ),~ " .RE\n " ];
275+ _ -> [B ,format (Ps0 ),~ " .RE\n " ]
276+ end
261277 end .
262278
263279strip_formatting ({_ ,_ ,[_ |_ ]= L }) ->
@@ -341,7 +357,10 @@ parse_row(Line) ->
341357 Cells = binary :split (NoOuterPipes , <<" |" >>, [global ]),
342358
343359 % % 4. Trim whitespace from each individual cell.
344- [string :trim (Cell ) || Cell <- Cells ].
360+ [format_cell (string :trim (Cell )) || Cell <- Cells ].
361+
362+ format_cell (B ) ->
363+ re :replace (B ," `(.+)`" ,<<" \\\\ fI\\ g{1}\\\\ fR" >>, [{return , binary },global ]).
345364
346365% % Helper to safely remove the first and last characters if they are pipes.
347366strip_outer_pipes (Bin ) ->
@@ -415,9 +434,10 @@ format_ast(AST) ->
415434 BinSpec = unicode :characters_to_binary (string :trim (Spec , trailing , " \n " )),
416435
417436 BinSpec2 = re :replace (BinSpec , " -((type)|(spec)|(callback)) " , " " ),
418-
419- [" \\ fB" , escape ( BinSpec2 ) , " \\ fR" , " \n " ].
437+ BinSpec3 = string : replace ( escape ( BinSpec2 ), " \n " , " \\ fR \n\\ fB " , all ),
438+ [" \\ fB" , BinSpec3 , " \\ fR" , " \n " ].
420439
421440format_meta (#{ deprecated := Depr } = M ) ->
422- [" \n .br\n Deprecated: " , unicode :characters_to_binary (Depr ) | format_meta (maps :remove (deprecated , M ))];
441+ [~ " \n .RS\n .LP\n Deprecated: " ,
442+ unicode :characters_to_binary (Depr ), ~ " \n .RE\n " | format_meta (maps :remove (deprecated , M ))];
423443format_meta (_ ) -> [].
0 commit comments