Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:26
erlang
2731-edoc-Add-doclet-to-convert-to-EEP-59-Markd...
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 2731-edoc-Add-doclet-to-convert-to-EEP-59-Markdown.patch of Package erlang
From eaef24f127d1eb1dcdc737fdcebfe6cd0ec7d359 Mon Sep 17 00:00:00 2001 From: Lukas Larsson <lukas@erlang.org> Date: Tue, 26 Mar 2024 13:38:14 +0100 Subject: [PATCH 1/2] edoc: Add doclet to convert to EEP-59 Markdown --- lib/edoc/src/edoc.app.src | 1 + lib/edoc/src/edoc.erl | 2 +- lib/edoc/src/edoc_doclet_markdown.erl | 437 +++++++++++++++++++++++++ lib/edoc/src/edoc_html_to_markdown.erl | 4 + lib/edoc/src/edoc_layout.erl | 6 + lib/edoc/src/edoc_layout_chunks.erl | 27 +- lib/edoc/src/files.mk | 2 +- 7 files changed, 474 insertions(+), 5 deletions(-) create mode 100644 lib/edoc/src/edoc_doclet_markdown.erl diff --git a/lib/edoc/src/edoc.app.src b/lib/edoc/src/edoc.app.src index 567b5b2ebb..fe97b69c37 100644 --- a/lib/edoc/src/edoc.app.src +++ b/lib/edoc/src/edoc.app.src @@ -9,6 +9,7 @@ edoc_data, edoc_doclet, edoc_doclet_chunks, + edoc_doclet_markdown, edoc_extract, edoc_html_to_markdown, edoc_layout, diff --git a/lib/edoc/src/edoc.erl b/lib/edoc/src/edoc.erl index 1a43c70a80..8e25399f74 100644 --- a/lib/edoc/src/edoc.erl +++ b/lib/edoc/src/edoc.erl @@ -545,7 +545,7 @@ layout(Doc) -> %% INHERIT-OPTIONS: edoc_lib:run_layout/2 --spec layout(Doc, Opts) -> string() when +-spec layout(Doc, Opts) -> term() when Doc :: edoc_module(), Opts :: proplist(). layout(Doc, Opts) -> diff --git a/lib/edoc/src/edoc_doclet_markdown.erl b/lib/edoc/src/edoc_doclet_markdown.erl new file mode 100644 index 0000000000..0abf3dc8cf --- /dev/null +++ b/lib/edoc/src/edoc_doclet_markdown.erl @@ -0,0 +1,437 @@ +%% +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 2024. 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% +%% + +%% @doc Doclet converting an edoc application to use EEP-59 and markdown. +%% +%% This doclet has to be used together with {@link edoc_layout_chunks}. +%% +%% Example: +%% +%% ``` +%%1> edoc:application(example, [{preprocess, true}, {doclet, edoc_doclet_markdown}, +%% {layout, edoc_layout_chunks}]). +%% ''' +%% +%% It will convert the overview to markdown and any module documentation to use +%% `-doc' attributes and markdown. Any XHTML tags in the edoc documentation that are +%% not part of the tags supported by <a href="doc_storage.html#erlang-documentation-format"> +%% Erlang Documentation Format</a> will be added as HTML tags in the Markdown. +%% +%% It does not delete the old edoc documentation. +%% +%% @see edoc_layout_chunks +%% @end + +%% Note that this is written so that it is *not* depending on edoc.hrl! + +-module(edoc_doclet_markdown). + +-export([run/2]). + +%% @headerfile "../include/edoc_doclet.hrl" +-include("../include/edoc_doclet.hrl"). + +-include_lib("xmerl/include/xmerl.hrl"). +-include_lib("kernel/include/eep48.hrl"). + +-define(debug(Format, Args), ok). +%-define(debug(Format, Args), io:format(Format, Args)). + +%% @doc Main doclet entry point. +%% +%% This doclet is tightly coupled with {@link edoc_layout_chunks} +%% and should be used together with it. +-spec run(edoc_doclet:command(), edoc_doclet:context()) -> ok. +run(#doclet_gen{} = Cmd, Ctxt) -> + try + gen(Cmd#doclet_gen.sources, + Cmd#doclet_gen.app, + Cmd#doclet_gen.modules, + Ctxt) + catch E:R:St -> + ?debug("error: ~p\n" + "stacktrace:\n~p\n\n", [R, St]), + erlang:raise(E,R,St) + end; +run(#doclet_toc{} = _Cmd, _Ctxt) -> + erlang:error(not_implemented). + +gen(Sources, App, Modules, Ctxt) -> + Dir = Ctxt#doclet_context.dir, + Env = Ctxt#doclet_context.env, + Options = Ctxt#doclet_context.opts, + overview(Dir, App, Env, Options), + case sources(Sources, App, Modules, Env, Options) of + {_, true = _Error} -> exit(error); + {_, false} -> ok + end. + +-define(OVERVIEW_FILE, "overview.edoc"). +-define(OVERVIEW_MD, "overview.md"). +overview(Dir, App, Env, Opts0) -> + File = proplists:get_value(overview, Opts0, + filename:join(Dir, ?OVERVIEW_FILE)), + Opts = [{source, File} | Opts0], + Title = title(App, Opts), + Encoding = edoc_lib:read_encoding(File, [{in_comment_only, false}]), + Tags = read_file(File, overview, Env, Opts), + Data0 = edoc_data:overview(Title, Tags, Env, Opts), + EncodingAttribute = #xmlAttribute{name = encoding, + value = atom_to_list(Encoding)}, + #xmlElement{attributes = As} = Data0, + Data = Data0#xmlElement{attributes = [EncodingAttribute | As]}, + F = fun (M) -> + M:overview(Data, Opts) + end, + ErlangHtml = edoc_lib:run_layout(F, Opts), + Text = edoc_html_to_markdown:convert_html(App, ErlangHtml), + EncOpts = [{encoding,Encoding}], + edoc_lib:write_file(Text, filename:dirname(File), ?OVERVIEW_MD, EncOpts). + +read_file(File, Context, Env, Opts) -> + case edoc_extract:file(File, Context, Env, Opts) of + {ok, Tags} -> + Tags; + {error, _} -> + [] + end. + +title(App, Options) -> + proplists:get_value(title, Options, + if App == no_app -> + "Overview"; + true -> + io_lib:fwrite("Application: ~ts", [App]) + end). + +%% @doc Process the individual source files. + +%% NEW-OPTIONS: file_suffix, private, hidden +%% INHERIT-OPTIONS: edoc:layout/2 +%% INHERIT-OPTIONS: edoc:get_doc/3 +%% DEFER-OPTIONS: run/2 + +sources(Sources, App, Modules, Env, Options) -> + {Ms, E} = lists:foldl(fun (Src, {Set, Error}) -> + source(Src, App, Env, Set, Error, Options) + end, + {sets:new(), false}, Sources), + {[M || M <- Modules, sets:is_element(M, Ms)], E}. + + +%% @doc Write a chunk file for a source file. +%% +%% Add its name to the set if it was successful. +%% Errors are just flagged at this stage, +%% allowing all source files to be processed even if some of them fail. +source({Module, Name, Path}, App, Env, OkSet, ErrorFlag, Options0) -> + File = filename:join(Path, Name), + try + %% Without these opts the entries returned by EDoc core (`edoc_extract:source1/5') won't have + %% all the necessary data to generate chunks. + RequiredChunkOpts = [return_entries, private, hidden], + %% But we also want to have the real user-defined `private' accessible. + Options = ([{show_private, proplists:get_bool(private, Options0)}] + ++ RequiredChunkOpts + ++ Options0), + {_Module, Doc, Entries} = edoc:get_doc(File, Env, Options), + #docs_v1{ module_doc = ModuleDoc, metadata = ModuleMeta, docs = Docs} = DocsV1 = + binary_to_term(edoc:layout(Doc, [{entries, Entries}, {source, Name} | Options])), + + {ok, Cwd} = file:get_cwd(), + Meta = [{cwd, Cwd}], + AST = edoc:read_source(File, Options), + NewFiles = convert(filter_and_fix_anno(expand_anno(AST), Docs, ModuleDoc), + #{ meta => Meta, ast => AST, docs => DocsV1, + application => App, module => Module }), + {_, ModuleAttrFile, ModuleAttrAnno} = + lists:foldl( + fun({attribute, [{generated,true}|_], file, {MAFile, Line}}, {false, _, _}) -> + {true, MAFile, Line}; + (_, FileAnno) when is_tuple(FileAnno) -> + FileAnno; + ({attribute, _, file, {MAFile,_}}, _) -> + MAFile; + ({attribute, Anno, module, _}, MAFile) -> + {false, MAFile, Anno} + end, undefined, AST), + ModuleAttrFilename = filename:join(proplists:get_value(cwd, Meta, ""), ModuleAttrFile), + + {BeforeModule, AfterModule} = + lists:split( + erl_anno:line(ModuleAttrAnno), + case maps:get(ModuleAttrFilename, NewFiles, undefined) of + undefined -> + {ok, Bin} = file:read_file(ModuleAttrFilename), + string:split(Bin, "\n", all); + F -> F + end), + + NewFilesWithModuleDoc = + NewFiles#{ ModuleAttrFilename => + BeforeModule ++ + convert_moduledoc(ModuleDoc, ModuleMeta, App, Module) ++ + AfterModule + }, + + _ = [ begin + io:format("Updated ~ts~n",[Key]), + ok = file:write_file(Key, format(lists:flatten(lists:join($\n,Value)))) + end || Key := Value <- NewFilesWithModuleDoc, not is_atom(Key)], + {sets:add_element(Name, OkSet), ErrorFlag} + catch _:_R:_St -> + ?debug("error: ~p\n" + "stacktrace:\n~p\n\n", [_R, _St]), + {OkSet, true} + end. + +format(Text) -> + unicode:characters_to_binary( + lists:map(fun({doc, Doc}) -> + doc(Doc); + ({moduledoc, Doc}) -> + moduledoc(Doc); + (Else) -> + Else + end, Text)). + +doc(String) -> + doc("doc", String). +moduledoc(String) -> + doc("moduledoc", String). +doc(Tag,String) -> + TrimmedString = string:trim(String), + case {string:find(TrimmedString,"\n"), + string:find(TrimmedString,"\\"), + string:find(TrimmedString,"\"")} of + {nomatch, nomatch, nomatch} -> + ["-",Tag," \"", TrimmedString, "\"."]; + _ -> + ["-",Tag," \"\"\"\n", TrimmedString, "\n\"\"\"."] + end. + +convert_moduledoc(#{ <<"en">> := ModuleHeader }, Meta, Application, Module) -> + String = edoc_html_to_markdown:convert_html( + Application, Module, + shell_docs:normalize(ModuleHeader)), + [{moduledoc,String} | modulemeta(Meta)]; +convert_moduledoc(#{}, Meta, _, _) -> + [{moduledoc,""} | modulemeta(Meta)]; +convert_moduledoc(hidden, Meta, _, _) -> + ["-moduledoc false." | modulemeta(Meta)]. + +convert(Docs, Files) -> + SortedDocs = + lists:sort( + fun(MFA1, MFA2) -> + Anno1 = element(2, MFA1), + Anno2 = element(2, MFA2), + case erl_anno:file(Anno1) =:= erl_anno:file(Anno2) of + true -> + erl_anno:line(Anno1) >= erl_anno:line(Anno2); + false -> + erl_anno:file(Anno1) >= erl_anno:file(Anno2) + end + end, Docs), + {Prev, Acc} = + case SortedDocs of + [] -> {[],[]}; + SortedDocs -> + lists:foldl( + fun(MFA,{[H|_] = Prev,Acc}) -> + MFAAnno = element(2, MFA), + HAnno = element(2, H), + case erl_anno:file(MFAAnno) =:= erl_anno:file(HAnno) andalso + erl_anno:line(MFAAnno) =:= erl_anno:line(HAnno) of + true -> + {[MFA|Prev],Acc}; + false -> + {[MFA],lists:reverse(Prev) ++ Acc} + end + end, {[hd(SortedDocs)],[]}, tl(SortedDocs)) + end, + %% io:format("~p",[SortedDocs]), + convert([], [], lists:reverse(Prev ++ Acc), Files). +convert([], [], [], Files) -> + %% When there are no documented functions in module + Cwd = proplists:get_value(cwd, maps:get(meta, Files), ""), + {attribute, _, file, {Filename, _}} = lists:keyfind(file, 3, maps:get(ast, Files)), + {ok, Bin} = file:read_file(filename:join(Cwd, Filename)), + Files#{ filename:join(Cwd, Filename) => string:split(Bin,"\n",all) }; +convert(Lines, Acc, [], Files) -> + Files#{ maps:get(filename, Files) => Lines ++ Acc}; +convert(Lines, Acc, [{{K,F,A}, 0, _, _, _} = E | T], Files) -> + io:format("Skipping ~p ~p/~p~n",[K,F,A]), + convert(Lines, Acc, T, Files#{ skipped => [E | maps:get(skipped, Files, [])] }); +convert(Lines, Acc, [{{function = K,behaviour_info = F,1 = A}, _, _, hidden, _} = E | T], Files) -> + io:format("Skipping ~p ~p/~p~n",[K,F,A]), + convert(Lines, Acc, T, Files#{ skipped => [E | maps:get(skipped, Files, [])] }); +convert(Lines, Acc, [{Kind, Anno, _Slogan, D, Meta} = E | T] = Docs, Files) -> + case erl_anno:file(Anno) =:= maps:get(current, Files, undefined) of + true -> + {Before, After} = lists:split(erl_anno:line(Anno)-1, Lines), + DocString = generate_doc_attributes(D, Meta, + Files#{ current => E }), + SpecString = + case lists:search( + fun(Elem) -> + {_, F, A} = Kind, + element(1, Kind) =:= function andalso + tuple_size(Elem) =:= 4 andalso + element(3, Elem) =:= spec andalso + (element(1, element(4, Elem)) =:= {F,A} orelse + element(1, element(4, Elem)) =:= {erlang,F,A}) + end, maps:get(ast, Files)) of + {value,_} -> %% Found a spec + ""; + _ when D =:= #{}, not is_map_key(equiv, Meta) -> + %% Undocumented function + ""; + _ when D =:= false; D =:= hidden -> + %% Undocumented function + ""; + false -> + [] + end, + convert(Before, DocString ++ SpecString ++ After ++ Acc, T, Files); + false -> + Cwd = proplists:get_value(cwd, maps:get(meta, Files), ""), + Filename = filename:join(Cwd, erl_anno:file(Anno)), + {ok, Bin} = file:read_file(Filename), + + NewFiles = + case maps:get(current, Files, undefined) of + undefined -> Files; + _ -> Files#{ maps:get(filename, Files) => Lines ++ Acc } + end, + convert(string:split(Bin,"\n",all), [], Docs, + NewFiles#{ current => erl_anno:file(Anno), filename => Filename }) + end. + +generate_doc_attributes(D, Meta, Files) -> + DocString = + case D of + #{ <<"en">> := ErlangHtml } when not is_map_key(equiv, Meta) -> + [{doc,edoc_html_to_markdown:convert_html( + maps:get(application, Files), + maps:get(module, Files), + shell_docs:normalize(ErlangHtml))}]; + D when D =:= #{}, is_map_key(equiv, Meta) -> + []; + D when D =:= #{} -> + []; + hidden -> + ["-doc false."] + end, + DocString ++ meta(Meta). + +meta(#{ edit_url := _} = Meta) -> + meta(maps:remove(edit_url, Meta)); +meta(#{ signature := _} = Meta) -> + meta(maps:remove(signature, Meta)); +meta(#{ equiv := {function,F,A} } = Meta) -> + [io_lib:format("-doc(#{equiv => ~p/~p}).",[F,A]) | meta(maps:remove(equiv, Meta))]; +meta(Meta) when Meta =:= #{} -> + ""; +meta(Meta) -> + [io_lib:format("-doc(~p).",[Meta])]. + +modulemeta(Meta) -> + case maps:without([name,otp_doc_vsn,source,types],Meta) of + M when map_size(M) =:= 0 -> + []; + M -> + [io_lib:format("-moduledoc(~p).",[M])] + end. + +%% Expand all top level anno in the AST to also include which file the anno refers to +expand_anno(AST) -> + {NewAST, _} = + lists:mapfoldl(fun F({attribute, _, file, {NewFile, _}} = E, File) when NewFile =/= File -> + F(E, NewFile); + F(E, File) -> + {setelement(2, E, erl_anno:set_file(File, element(2, E))), File} + end, undefined, AST), + NewAST. + +%% We fix all the anno tags in the doc entries to point towards the place where the +%% documentation should be inserted. +filter_and_fix_anno(AST, [{{function, behaviour_info, 1}, _Anno, _S, hidden, _M} | T], ModuleDoc) -> + filter_and_fix_anno(AST, T, ModuleDoc); +filter_and_fix_anno(AST, [{{What, F, A}, _Anno, S, D, M} | T], ModuleDoc) + when is_map(D); D =:= hidden andalso ModuleDoc =/= hidden; is_map_key(equiv, M) -> + NewAnno = + case What of + function -> + case lists:search(fun({attribute, _SpecAnno, spec, {FA, _}}) when is_tuple(FA) -> + {F, A} =:= FA orelse {erlang, F, A} =:= FA; + (_) -> + false + end, AST) of + {value, {attribute, SpecAnno, _, _}} -> + SpecAnno; + false -> + case lists:search(fun({function, _FuncAnno, FF, FA, _}) -> + {F, A} =:= {FF, FA}; + (_) -> + false + end, AST) of + {value, {function, FuncAnno, _, _, _}} -> + FuncAnno; + false -> + io:format("~p~n",[AST]), + io:format("Could not find func: ~p/~p~n",[F,A]), + error(badarg) + end + end; + type -> + case lists:search(fun({attribute, _TypeAnno, TO, {FA, _}}) when + is_tuple(FA), TO =:= type orelse TO =:= opaque -> + {F, A} =:= FA; + ({attribute, _TypeAnno, TO, {Type, _, Args}}) when + is_atom(Type), TO =:= type orelse TO =:= opaque -> + {F, A} =:= {Type, length(Args)}; + (_) -> + false + end, AST) of + {value, {attribute, TypeAnno, _, _}} -> + TypeAnno; + false -> + io:format("Could not find type: ~p/~p~n",[F,A]), + error(badarg) + end; + callback -> + case lists:search(fun({attribute, _CBAnno, callback, {FA, _}}) -> + {F, A} =:= FA; + (_) -> + false + end, AST) of + {value, {attribute, CBAnno, _, _}} -> + CBAnno; + false -> + io:format("Could not find callback: ~p/~p~n",[F,A]), + erl_anno:new(0) + end + end, + [{{What, F, A}, NewAnno, S, D, M} | filter_and_fix_anno(AST, T, ModuleDoc)]; +filter_and_fix_anno(AST, [_ | T], ModuleDoc) -> + filter_and_fix_anno(AST, T, ModuleDoc); +filter_and_fix_anno(_, [], _ModuleDoc) -> + []. diff --git a/lib/edoc/src/edoc_html_to_markdown.erl b/lib/edoc/src/edoc_html_to_markdown.erl index de8602837e..15ddd5d3e0 100644 --- a/lib/edoc/src/edoc_html_to_markdown.erl +++ b/lib/edoc/src/edoc_html_to_markdown.erl @@ -503,6 +503,10 @@ render_element({li, [], Content}, [ul | _] = State, Pos, Ind, D) -> render_element({li, [], Content}, [ol | _] = State, Pos, Ind, D) -> {Docs, _NewPos} = render_docs(Content, [li | State], Pos + 2, Ind + 2, D), trimnl(["1. ", Docs]); +render_element({dl, [], [{dt,DTAttr,DTContent}, {dd,_,_} = DD1, {dd, _, _} = DD2 | Content]}, State, Pos, Ind, D) -> + {DD, T} = lists:splitwith(fun(E) -> element(1,E) =:= dd end, Content), + DDs = [{p, [], C} || {_, _, C} <- [DD1, DD2 | DD]], + render_element({dl, [], [{dt,DTAttr,DTContent}, {dd,[],DDs} | T]}, State, Pos, Ind, D); render_element({dl, [], [{dt,DTAttr,DTContent}, {dd,[],DDContent} | Content]}, State, Pos, Ind, D) -> Since = proplists:get_value(since, DTAttr), {DTDocs, _DTNewPos} = diff --git a/lib/edoc/src/edoc_layout.erl b/lib/edoc/src/edoc_layout.erl index 6580ce47d9..b24150c5b6 100644 --- a/lib/edoc/src/edoc_layout.erl +++ b/lib/edoc/src/edoc_layout.erl @@ -34,6 +34,8 @@ -export([module/2, overview/2, type/1]). +-export([copyright/1, version/1, since/1, authors/1, references/1, sees/1, todos/1]). + -callback module(edoc:edoc_module(), _) -> binary(). %% Layout entrypoint. @@ -699,6 +701,7 @@ equiv(Es, P) -> end end. +%% @doc hidden copyright(Es) -> case get_content(copyright, Es) of [] -> []; @@ -706,6 +709,7 @@ copyright(Es) -> [{p, ["Copyright \251 " | Es1]}, ?NL] end. +%% @doc hidden version(Es) -> case get_content(version, Es) of [] -> []; @@ -713,6 +717,7 @@ version(Es) -> [{p, [{b, ["Version:"]}, " " | Es1]}, ?NL] end. +%% @doc hidden since(Es) -> case get_content(since, Es) of [] -> []; @@ -720,6 +725,7 @@ since(Es) -> [{p, [{b, ["Introduced in:"]}, " " | Es1]}, ?NL] end. +%% @doc hidden deprecated(Es, S) -> Es1 = get_content(description, get_content(deprecated, Es)), case get_content(fullDescription, Es1) of diff --git a/lib/edoc/src/edoc_layout_chunks.erl b/lib/edoc/src/edoc_layout_chunks.erl index d4a673113e..044571a26b 100644 --- a/lib/edoc/src/edoc_layout_chunks.erl +++ b/lib/edoc/src/edoc_layout_chunks.erl @@ -40,8 +40,8 @@ %% @end -module(edoc_layout_chunks). -%-behaviour(edoc_layout). --export([module/2]). +% -behaviour(edoc_layout). +-export([module/2, overview/2]). -include("edoc.hrl"). @@ -111,6 +111,18 @@ module(Doc, Options) -> Chunk = edoc_to_chunk(Doc, Options), term_to_binary(Chunk). +-spec overview(Element :: term(), proplists:proplist()) -> term(). +overview(E=#xmlElement{name = overview, content = Es}, Options) -> + xpath_to_chunk("./title", E, Options) + ++ xmerl_to_chunk(edoc_layout:copyright(Es), Options) + ++ xmerl_to_chunk(edoc_layout:version(Es), Options) + ++ xmerl_to_chunk(edoc_layout:since(Es), Options) + ++ xmerl_to_chunk(edoc_layout:authors(Es), Options) + ++ xmerl_to_chunk(edoc_layout:references(Es), Options) + ++ xmerl_to_chunk(edoc_layout:sees(Es), Options) + ++ xmerl_to_chunk(edoc_layout:todos(Es), Options) + ++ xpath_to_chunk("./description/fullDescription", E, Options). + %%. %%' Chunk construction %% @@ -538,8 +550,14 @@ format_content_(#xmlElement{name = equiv} = E, Opts) -> format_element(rewrite_equiv_tag(E), Opts); format_content_(#xmlElement{name = a} = E, Opts) -> format_element(rewrite_a_tag(E), Opts); +format_content_(#xmlElement{name = title} = E, Opts) -> + format_element(rewrite_title_tag(E), Opts); format_content_(#xmlElement{} = E, Opts) -> - format_element(E, Opts). + format_element(E, Opts); +format_content_({Tag, Content}, Opts) -> + format_content_(xmerl_lib:normalize_element({Tag, [], Content}), Opts); +format_content_(List, Opts) when is_list(List) -> + format_content_(#xmlText{ value = List }, Opts). format_element(#xmlElement{} = E, Opts) -> #xmlElement{name = Name, content = Content, attributes = Attributes} = E, @@ -583,6 +601,9 @@ rewrite_a_tag(#xmlElement{name = a} = E) -> SimpleE = xmerl_lib:simplify_element(E), xmerl_lib:normalize_element(rewrite_docgen_link(SimpleE)). +rewrite_title_tag(#xmlElement{name = title} = E) -> + E#xmlElement{ name = h1 }. + rewrite_see_tags([], _Opts) -> []; rewrite_see_tags([#xmlElement{name = see} | _] = SeeTags, Opts) -> Grouped = [ rewrite_see_tag(T) || T <- SeeTags ], diff --git a/lib/edoc/src/Makefile b/lib/edoc/src/Makefile index 8975f61780..4483ed459d 100644 --- a/lib/edoc/src/Makefile +++ b/lib/edoc/src/Makefile @@ -30,7 +30,7 @@ SOURCES= \ edoc_extract.erl edoc_layout.erl edoc_layout_chunks.erl \ edoc_lib.erl edoc_macros.erl edoc_parser.erl edoc_refs.erl edoc_report.erl \ edoc_run.erl edoc_scanner.erl edoc_specs.erl edoc_tags.erl edoc_types.erl edoc_wiki.erl \ - edoc_html_to_markdown.erl + edoc_html_to_markdown.erl edoc_doclet_markdown.erl OBJECTS=$(SOURCES:%.erl=$(EBIN)/%.$(EMULATOR)) $(APP_TARGET) $(APPUP_TARGET) -- 2.35.3
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor