diff --git a/bin/ex_doc b/bin/ex_doc index 4655e163f..a2d1e9e6e 100755 --- a/bin/ex_doc +++ b/bin/ex_doc @@ -6,6 +6,10 @@ Code.prepend_path Path.expand("../_build/#{mix_env}/lib/makeup_elixir/ebin", __D Code.prepend_path Path.expand("../_build/#{mix_env}/lib/makeup_erlang/ebin", __DIR__) Code.prepend_path Path.expand("../_build/#{mix_env}/lib/makeup_html/ebin", __DIR__) Code.prepend_path Path.expand("../_build/#{mix_env}/lib/earmark_parser/ebin", __DIR__) +Code.prepend_path Path.expand("../_build/#{mix_env}/lib/rustler_precompiled/ebin", __DIR__) +Code.prepend_path Path.expand("../_build/#{mix_env}/lib/castore/ebin", __DIR__) +Code.prepend_path Path.expand("../_build/#{mix_env}/lib/jason/ebin", __DIR__) +Code.prepend_path Path.expand("../_build/#{mix_env}/lib/mdex/ebin", __DIR__) Code.prepend_path Path.expand("../_build/#{mix_env}/lib/ex_doc/ebin", __DIR__) if Code.ensure_loaded?(ExDoc.CLI) do diff --git a/lib/ex_doc.ex b/lib/ex_doc.ex index c108c3560..f797133e1 100644 --- a/lib/ex_doc.ex +++ b/lib/ex_doc.ex @@ -35,11 +35,16 @@ defmodule ExDoc do end defp find_formatter(name) do - [ExDoc.Formatter, String.upcase(name)] + [ExDoc.Formatter, modname(name)] |> Module.concat() |> check_formatter_module(name) end + defp modname("epub"), do: EPUB + defp modname("html"), do: HTML + defp modname("markdown"), do: Markdown + defp modname(_), do: nil + defp check_formatter_module(modname, argname) do if Code.ensure_loaded?(modname) do modname diff --git a/lib/ex_doc/cli.ex b/lib/ex_doc/cli.ex index 5a13e5d67..a0cabd0c6 100644 --- a/lib/ex_doc/cli.ex +++ b/lib/ex_doc/cli.ex @@ -192,7 +192,7 @@ defmodule ExDoc.CLI do See "Custom config" section below for more information. --favicon Path to a favicon image for the project. Must be PNG, JPEG or SVG. The image will be placed in the output "assets" directory. - -f, --formatter Docs formatter to use (html or epub), default: html and epub + -f, --formatter Docs formatter to use (html, epub or markdown), default: html and epub --homepage-url URL to link to for the site name --language Identify the primary language of the documents, its value must be a valid [BCP 47](https://tools.ietf.org/html/bcp47) language tag, default: "en" diff --git a/lib/ex_doc/formatter/markdown.ex b/lib/ex_doc/formatter/markdown.ex new file mode 100644 index 000000000..6a72114ac --- /dev/null +++ b/lib/ex_doc/formatter/markdown.ex @@ -0,0 +1,533 @@ +defmodule ExDoc.Formatter.Markdown do + @moduledoc false + + alias __MODULE__.Assets + alias __MODULE__.Templates + alias ExDoc.GroupMatcher + alias ExDoc.Markdown + alias ExDoc.Utils + + # @main "api-reference" + @assets_dir "assets" + + @doc """ + Generates Markdown documentation for the given modules. + """ + @spec run([ExDoc.ModuleNode.t()], [ExDoc.ModuleNode.t()], ExDoc.Config.t()) :: String.t() + def run(project_nodes, filtered_modules, config) when is_map(config) do + Utils.unset_warned() + + config = %{config | output: Path.expand(config.output)} + build = Path.join(config.output, ".build") + output_setup(build, config) + + project_nodes = render_all(project_nodes, filtered_modules, ".md", config, []) + extras = build_extras(config, ".md") + # Generate search early on without api reference in extras + static_files = generate_assets(".", default_assets(config), config) + + # TODO: Move this categorization to the language + nodes_map = %{ + modules: filter_list(:module, project_nodes), + tasks: filter_list(:task, project_nodes) + } + + extras = + if config.api_reference do + [build_api_reference(nodes_map, config) | extras] + else + extras + end + + all_files = + (static_files ++ + generate_extras(extras, config) ++ + generate_logo(@assets_dir, config) ++ + generate_list(nodes_map.modules, config) ++ + generate_list(nodes_map.tasks, config)) + |> Enum.uniq() + |> Kernel.--([@assets_dir]) + |> Enum.sort() + + generate_build(all_files, build) + + config.output + |> Path.join("index.md") + |> Path.relative_to_cwd() + end + + @doc """ + Autolinks and renders all docs. + """ + def render_all(project_nodes, filtered_modules, ext, config, opts) do + base = [ + apps: config.apps, + deps: config.deps, + ext: ext, + extras: extra_paths(config), + skip_undefined_reference_warnings_on: config.skip_undefined_reference_warnings_on, + skip_code_autolink_to: config.skip_code_autolink_to, + filtered_modules: filtered_modules + ] + + project_nodes + |> Task.async_stream( + fn node -> + language = node.language + + autolink_opts = + [ + current_module: node.module, + file: node.moduledoc_file, + line: node.moduledoc_line, + module_id: node.id, + language: language + ] ++ base + + docs = + for child_node <- node.docs do + id = id(node, child_node) + + autolink_opts = + autolink_opts ++ + [ + id: id, + line: child_node.doc_line, + file: child_node.doc_file, + current_kfa: {child_node.type, child_node.name, child_node.arity} + ] + + specs = Enum.map(child_node.specs, &language.format_spec(&1)) + child_node = %{child_node | specs: specs} + render_doc(child_node, language, autolink_opts, opts, 4) + end + + %{ + render_doc(node, language, [{:id, node.id} | autolink_opts], opts, 2) + | docs: docs + } + end, + timeout: :infinity + ) + |> Enum.map(&elem(&1, 1)) + end + + defp render_doc(%{doc: nil} = node, _language, _autolink_opts, _opts, _base_heading), + do: node + + defp render_doc( + %{doc: _doc, source_doc: source_doc} = node, + _language, + _autolink_opts, + _opts, + base_heading + ) do + # rendered = autolink_and_render(doc, language, autolink_opts, opts) + rendered = rewrite_headings(source_doc["en"], base_heading) + %{node | rendered_doc: rendered} + end + + defp rewrite_headings(markdown, base_heading) + when is_binary(markdown) and is_integer(base_heading) and base_heading >= 1 do + {:ok, document} = MDEx.parse_document(markdown) + + document = + case find_lowest_heading(document) do + lowest_heading when lowest_heading >= base_heading -> + document + + lowest_heading -> + levels_to_bump = base_heading - lowest_heading + + bump_levels(document, levels_to_bump) + end + + MDEx.to_commonmark!(document) + end + + defp find_lowest_heading(document) when is_struct(document, MDEx.Document) do + Enum.reduce_while(document, 6, fn + %MDEx.Heading{level: 1}, _lowest_level -> + {:halt, 1} + + %MDEx.Heading{level: level}, lowest_level when level < lowest_level -> + {:cont, level} + + _, lowest_level -> + {:cont, lowest_level} + end) + end + + defp bump_levels(document, levels_to_bump) when is_struct(document, MDEx.Document) do + update_in( + document, + [:document, Access.key!(:nodes), Access.filter(&is_struct(&1, MDEx.Heading))], + fn %MDEx.Heading{level: level} = heading -> + %{heading | level: increase_level(level, levels_to_bump)} + end + ) + end + + defp increase_level(level, levels_to_bump) do + min(level + levels_to_bump, 6) + end + + defp id(%{id: mod_id}, %{id: "c:" <> id}) do + "c:" <> mod_id <> "." <> id + end + + defp id(%{id: mod_id}, %{id: "t:" <> id}) do + "t:" <> mod_id <> "." <> id + end + + defp id(%{id: mod_id}, %{id: id}) do + mod_id <> "." <> id + end + + defp output_setup(build, config) do + if File.exists?(build) do + build + |> File.read!() + |> String.split("\n", trim: true) + |> Enum.map(&Path.join(config.output, &1)) + |> Enum.each(&File.rm/1) + + File.rm(build) + else + File.rm_rf!(config.output) + File.mkdir_p!(config.output) + end + end + + defp generate_build(files, build) do + entries = Enum.map(files, &[&1, "\n"]) + File.write!(build, entries) + end + + defp generate_extras(extras, config) do + generated_extras = + extras + |> with_prev_next() + |> Enum.map(fn {node, prev, next} -> + filename = "#{node.id}.md" + output = "#{config.output}/#{filename}" + config = set_canonical_url(config, filename) + + refs = %{ + prev: prev && %{path: "#{prev.id}.md", title: prev.title}, + next: next && %{path: "#{next.id}.md", title: next.title} + } + + extension = node.source_path && Path.extname(node.source_path) + markdown = Templates.extra_template(config, node, extra_type(extension), refs) + + if File.regular?(output) do + Utils.warn("file #{Path.relative_to_cwd(output)} already exists", []) + end + + File.write!(output, markdown) + filename + end) + + generated_extras ++ copy_extras(config, extras) + end + + defp extra_type(".cheatmd"), do: :cheatmd + defp extra_type(".livemd"), do: :livemd + defp extra_type(_), do: :extra + + defp copy_extras(config, extras) do + for %{source_path: source_path, id: id} when source_path != nil <- extras, + ext = extension_name(source_path), + ext == ".livemd" do + output = "#{config.output}/#{id}#{ext}" + + File.copy!(source_path, output) + + output + end + end + + defp with_prev_next([]), do: [] + + defp with_prev_next([head | tail]) do + Enum.zip([[head | tail], [nil, head | tail], tail ++ [nil]]) + end + + @doc """ + Generate assets from configs with the given default assets. + """ + def generate_assets(namespace, defaults, %{output: output, assets: assets}) do + namespaced_assets = + if is_map(assets) do + Enum.map(assets, fn {source, target} -> {source, Path.join(namespace, target)} end) + else + IO.warn(""" + giving a binary to :assets is deprecated, please give a map from source to target instead: + + #{inspect(assets: %{assets => "assets"})} + """) + + [{assets, Path.join(namespace, "assets")}] + end + + Enum.flat_map(defaults ++ namespaced_assets, fn {dir_or_files, relative_target_dir} -> + target_dir = Path.join(output, relative_target_dir) + File.mkdir_p!(target_dir) + + cond do + is_list(dir_or_files) -> + Enum.map(dir_or_files, fn {name, content} -> + target = Path.join(target_dir, name) + File.write(target, content) + Path.relative_to(target, output) + end) + + is_binary(dir_or_files) and File.dir?(dir_or_files) -> + dir_or_files + |> File.cp_r!(target_dir, dereference_symlinks: true) + |> Enum.map(&Path.relative_to(&1, output)) + + is_binary(dir_or_files) -> + [] + + true -> + raise ":assets must be a map of source directories to target directories" + end + end) + end + + defp default_assets(config) do + [ + {Assets.dist(config.proglang), "dist"} + ] + end + + defp build_api_reference(nodes_map, config) do + title = "API Reference" + api_reference = Templates.api_reference_template(nodes_map, title) + + %{ + content: api_reference, + group: nil, + id: "api-reference", + source_path: nil, + source_url: config.source_url, + title: title + } + end + + @doc """ + Builds extra nodes by normalizing the config entries. + """ + def build_extras(config, ext) do + groups = config.groups_for_extras + + language = + case config.proglang do + :erlang -> ExDoc.Language.Erlang + _ -> ExDoc.Language.Elixir + end + + source_url_pattern = config.source_url_pattern + + autolink_opts = [ + apps: config.apps, + deps: config.deps, + ext: ext, + extras: extra_paths(config), + language: language, + skip_undefined_reference_warnings_on: config.skip_undefined_reference_warnings_on, + skip_code_autolink_to: config.skip_code_autolink_to + ] + + extras = + config.extras + |> Task.async_stream( + &build_extra(&1, groups, language, autolink_opts, source_url_pattern), + timeout: :infinity + ) + |> Enum.map(&elem(&1, 1)) + + ids_count = Enum.reduce(extras, %{}, &Map.update(&2, &1.id, 1, fn c -> c + 1 end)) + + extras + |> Enum.map_reduce(1, fn extra, idx -> + if ids_count[extra.id] > 1, do: {disambiguate_id(extra, idx), idx + 1}, else: {extra, idx} + end) + |> elem(0) + |> Enum.sort_by(fn extra -> GroupMatcher.index(groups, extra.group) end) + end + + defp disambiguate_id(extra, discriminator) do + Map.put(extra, :id, "#{extra.id}-#{discriminator}") + end + + defp build_extra({input, input_options}, groups, _language, _autolink_opts, source_url_pattern) do + input = to_string(input) + id = input_options[:filename] || input |> filename_to_title() |> Utils.text_to_id() + source_file = input_options[:source] || input + opts = [file: source_file, line: 1] + + {source, ast} = + case extension_name(input) do + extension when extension in ["", ".txt"] -> + source = File.read!(input) + ast = [{:pre, [], "\n" <> source, %{}}] + {source, ast} + + extension when extension in [".md", ".livemd", ".cheatmd"] -> + source = File.read!(input) + + ast = + source + |> Markdown.to_ast(opts) + + # |> sectionize(extension) + + {source, ast} + + _ -> + raise ArgumentError, + "file extension not recognized, allowed extension is either .cheatmd, .livemd, .md, .txt or no extension" + end + + {title_ast, _ast} = + case ExDoc.DocAST.extract_title(ast) do + {:ok, title_ast, ast} -> {title_ast, ast} + :error -> {nil, ast} + end + + title_text = title_ast && ExDoc.DocAST.text_from_ast(title_ast) + title_markdown = title_ast && ExDoc.DocAST.to_string(title_ast) + # content_markdown = autolink_and_render(ast, language, [file: input] ++ autolink_opts, opts) + content_markdown = source + + group = GroupMatcher.match_extra(groups, input) + title = input_options[:title] || title_text || filename_to_title(input) + + source_path = source_file |> Path.relative_to(File.cwd!()) |> String.replace_leading("./", "") + source_url = source_url_pattern.(source_path, 1) + + %{ + source: source, + content: content_markdown, + group: group, + id: id, + source_path: source_path, + source_url: source_url, + title: title, + title_content: title_markdown || title + } + end + + defp build_extra(input, groups, language, autolink_opts, source_url_pattern) do + build_extra({input, []}, groups, language, autolink_opts, source_url_pattern) + end + + defp extension_name(input) do + input + |> Path.extname() + |> String.downcase() + end + + # defp sectionize(ast, ".cheatmd") do + # ExDoc.DocAST.sectionize(ast, fn + # {:h2, _, _, _} -> true + # {:h3, _, _, _} -> true + # _ -> false + # end) + # end + + # defp sectionize(ast, _), do: ast + + defp filename_to_title(input) do + input |> Path.basename() |> Path.rootname() + end + + @doc """ + Generates the logo from config into the given directory. + """ + def generate_logo(_dir, %{logo: nil}) do + [] + end + + def generate_logo(dir, %{output: output, logo: logo}) do + generate_image(output, dir, logo, "logo") + end + + @doc """ + Generates the cover from config into the given directory. + """ + def generate_cover(_dir, %{cover: nil}) do + [] + end + + def generate_cover(dir, %{output: output, cover: cover}) do + generate_image(output, dir, cover, "cover") + end + + defp generate_image(output, dir, image, name) do + extname = + image + |> Path.extname() + |> String.downcase() + + if extname in ~w(.png .jpg .jpeg .svg) do + filename = Path.join(dir, "#{name}#{extname}") + target = Path.join(output, filename) + File.mkdir_p!(Path.dirname(target)) + File.copy!(image, target) + [filename] + else + raise ArgumentError, "image format not recognized, allowed formats are: .png, .jpg, .svg" + end + end + + def filter_list(:module, nodes) do + Enum.filter(nodes, &(&1.type != :task)) + end + + def filter_list(type, nodes) do + Enum.filter(nodes, &(&1.type == type)) + end + + defp generate_list(nodes, config) do + nodes + |> Task.async_stream(&generate_module_page(&1, config), timeout: :infinity) + |> Enum.map(&elem(&1, 1)) + end + + defp generate_module_page(module_node, config) do + filename = "#{module_node.id}.md" + config = set_canonical_url(config, filename) + content = Templates.module_page(module_node, config) + File.write!("#{config.output}/#{filename}", content) + filename + end + + defp set_canonical_url(config, filename) do + if config.canonical do + canonical_url = + config.canonical + |> String.trim_trailing("/") + |> Kernel.<>("/" <> filename) + + Map.put(config, :canonical, canonical_url) + else + config + end + end + + defp extra_paths(config) do + Map.new(config.extras, fn + path when is_binary(path) -> + base = Path.basename(path) + {base, Utils.text_to_id(Path.rootname(base))} + + {path, opts} -> + base = path |> to_string() |> Path.basename() + {base, opts[:filename] || Utils.text_to_id(Path.rootname(base))} + end) + end +end diff --git a/lib/ex_doc/formatter/markdown/templates.ex b/lib/ex_doc/formatter/markdown/templates.ex new file mode 100644 index 000000000..2b64993e6 --- /dev/null +++ b/lib/ex_doc/formatter/markdown/templates.ex @@ -0,0 +1,93 @@ +defmodule ExDoc.Formatter.Markdown.Templates do + @moduledoc false + require EEx + + import ExDoc.Utils, + only: [ + h: 1, + text_to_id: 1 + ] + + @doc """ + Generate content from the module template for a given `node` + """ + def module_page(module_node, config) do + summary = module_summary(module_node) + module_template(config, module_node, summary) + end + + @doc """ + Format the attribute type used to define the spec of the given `node`. + """ + def format_spec_attribute(module, node) do + module.language.format_spec_attribute(node) + end + + @doc """ + Get the pretty name of a function node + """ + def pretty_type(%{type: t}) do + Atom.to_string(t) + end + + @doc """ + Returns the HTML formatted title for the module page. + """ + def module_type(%{type: :task}), do: "" + def module_type(%{type: :module}), do: "" + def module_type(%{type: type}), do: to_string(type) + + @doc """ + Gets the first paragraph of the documentation of a node. It strips + surrounding white-spaces and trailing `:`. + + If `doc` is `nil`, it returns `nil`. + """ + @spec synopsis(String.t()) :: String.t() + @spec synopsis(nil) :: nil + def synopsis(nil), do: nil + + def synopsis(doc) when is_binary(doc) do + case :binary.split(doc, "\n\n") do + [left, _] -> String.trim_trailing(left, ":") <> "\n\n" + [all] -> all + end + end + + defp enc(binary), do: URI.encode(binary) + + def module_summary(module_node) do + # TODO: Maybe it should be moved to retriever and it already returned grouped metadata + ExDoc.GroupMatcher.group_by(module_node.docs_groups, module_node.docs, & &1.group) + end + + def asset_rev(output, pattern) do + output = Path.expand(output) + + output + |> Path.join(pattern) + |> Path.wildcard() + |> relative_asset(output, pattern) + end + + defp relative_asset([], output, pattern), + do: raise("could not find matching #{output}/#{pattern}") + + defp relative_asset([h | _], output, _pattern), do: Path.relative_to(h, output) + + templates = [ + detail_template: [:config, :node, :module], + footer_template: [:config], + head_template: [:config, :page], + module_template: [:config, :module, :summary], + api_reference_entry_template: [:module_node], + api_reference_template: [:nodes_map, :title], + extra_template: [:config, :node, :type, :refs] + ] + + Enum.each(templates, fn {name, args} -> + filename = Path.expand("templates/#{name}.eex", __DIR__) + @doc false + EEx.function_from_file(:def, name, filename, args, trim: true) + end) +end diff --git a/lib/ex_doc/formatter/markdown/templates/api_reference_entry_template.eex b/lib/ex_doc/formatter/markdown/templates/api_reference_entry_template.eex new file mode 100644 index 000000000..763b67548 --- /dev/null +++ b/lib/ex_doc/formatter/markdown/templates/api_reference_entry_template.eex @@ -0,0 +1,3 @@ +**[<%=h module_node.title %>](<%=enc module_node.id %>.md)**<%= if module_node.deprecated do %> *deprecated*<% end %> +<%= if doc = module_node.rendered_doc do %><%= String.trim(synopsis(doc)) %> +<% end %> diff --git a/lib/ex_doc/formatter/markdown/templates/api_reference_template.eex b/lib/ex_doc/formatter/markdown/templates/api_reference_template.eex new file mode 100644 index 000000000..669d03b1f --- /dev/null +++ b/lib/ex_doc/formatter/markdown/templates/api_reference_template.eex @@ -0,0 +1,19 @@ +# <%= title %> + +<%= if nodes_map.modules != [] do %> +## Modules + +<%= for module_node <- Enum.sort_by(nodes_map.modules, & &1.id) do +api_reference_entry_template(module_node) <> "\n" +end %> +<% end %> + +<%= if nodes_map.tasks != [] do %> +## Mix Tasks + +<%= for task_node <- nodes_map.tasks do +api_reference_entry_template(task_node) + +end %> + +<% end %> diff --git a/lib/ex_doc/formatter/markdown/templates/detail_template.eex b/lib/ex_doc/formatter/markdown/templates/detail_template.eex new file mode 100644 index 000000000..d5c84bd1e --- /dev/null +++ b/lib/ex_doc/formatter/markdown/templates/detail_template.eex @@ -0,0 +1,9 @@ +### <%=h node.signature %> + +<%= for annotation <- node.annotations do %>*(<%= annotation %>)* <% end %> +<%= if node.specs != [] do %>```<%= config.proglang %> +<%= for spec <- node.specs do %><%= format_spec_attribute(module, node) %> <%= spec %> +<% end %>```<% end %> +<%= if deprecated = node.deprecated do %>**This <%= node.type %> is deprecated. <%= h(deprecated) %>.** +<% end %> +<%= if doc = node.rendered_doc do %><%= doc %><% end %> diff --git a/lib/ex_doc/formatter/markdown/templates/extra_template.eex b/lib/ex_doc/formatter/markdown/templates/extra_template.eex new file mode 100644 index 000000000..986118a0f --- /dev/null +++ b/lib/ex_doc/formatter/markdown/templates/extra_template.eex @@ -0,0 +1,6 @@ +<%= if type == :livemd do %>![Livebook badge](https://livebook.dev/badge/v1/blue.svg "Run in Livebook") +<% end %><%= node.content %> + +--- +<%= if refs.prev do %>[← Previous Page](<%= refs.prev.path %> "<%= refs.prev.title %>")<% end %><%= if refs.prev && refs.next do %> - <% end %><%= if refs.next do %>[Next Page →](<%= refs.next.path %> "<%= refs.next.title %>")<% end %> +<%= footer_template(config) %> diff --git a/lib/ex_doc/formatter/markdown/templates/footer_template.eex b/lib/ex_doc/formatter/markdown/templates/footer_template.eex new file mode 100644 index 000000000..44ceb497a --- /dev/null +++ b/lib/ex_doc/formatter/markdown/templates/footer_template.eex @@ -0,0 +1,3 @@ + +--- +Built using [ExDoc](https://github.com/elixir-lang/ex_doc "ExDoc") (v<%= ExDoc.version() %>) for the <%= if config.proglang == :erlang do %>[Erlang programming language](href="https://erlang.org" "Erlang")<% else %>[Elixir programming language](href="https://elixir-lang.org" "Elixir")<% end %>. diff --git a/lib/ex_doc/formatter/markdown/templates/head_template.eex b/lib/ex_doc/formatter/markdown/templates/head_template.eex new file mode 100644 index 000000000..6b1dddd9d --- /dev/null +++ b/lib/ex_doc/formatter/markdown/templates/head_template.eex @@ -0,0 +1 @@ +<%= page.title %> — <%= config.project %> v<%= config.version %> diff --git a/lib/ex_doc/formatter/markdown/templates/metadata.eex b/lib/ex_doc/formatter/markdown/templates/metadata.eex new file mode 100644 index 000000000..37f39b976 --- /dev/null +++ b/lib/ex_doc/formatter/markdown/templates/metadata.eex @@ -0,0 +1,6 @@ +- Language: <%= config.language %> +- Generator: ExDoc v<%= ExDoc.version() %> +- Project: <%= config.project %> v<%= config.version%> +<%= if config.authors do %> +- Authors: <%= Enum.join(config.authors, ", ") %> +<% end %> diff --git a/lib/ex_doc/formatter/markdown/templates/module_template.eex b/lib/ex_doc/formatter/markdown/templates/module_template.eex new file mode 100644 index 000000000..c822efcd6 --- /dev/null +++ b/lib/ex_doc/formatter/markdown/templates/module_template.eex @@ -0,0 +1,13 @@ +# <%= module.title %> <%= module_type(module) %> +(<%= config.project %> v<%= config.version %>) + +<%= for annotation <- module.annotations do %>*(<%= annotation %>)* <% end %> +<%= if deprecated = module.deprecated do %>This <%= module.type %> is deprecated. <%= h(deprecated) %>. +<% end %><%= if doc = module.rendered_doc do %><%= doc %> +<% end %> +<%= for {name, nodes} <- summary, _key = text_to_id(name) do %>## <%= name %> +<%= for node <- nodes do %> +<%= detail_template(config, node, module) %> +<% end %> +<% end %> +<%= footer_template(config) %> diff --git a/lib/ex_doc/formatter/markdown/templates/summary_template.eex b/lib/ex_doc/formatter/markdown/templates/summary_template.eex new file mode 100644 index 000000000..74c85d50f --- /dev/null +++ b/lib/ex_doc/formatter/markdown/templates/summary_template.eex @@ -0,0 +1,5 @@ +## <%= name %> + +<%= for node <- nodes do %> +<%=h node.signature %> +<%= if deprecated = node.deprecated do %>(deprecated)<% end %><%= synopsis(doc) %><% end %> diff --git a/lib/ex_doc/language/elixir.ex b/lib/ex_doc/language/elixir.ex index 636cfa1a4..a527c3418 100644 --- a/lib/ex_doc/language/elixir.ex +++ b/lib/ex_doc/language/elixir.ex @@ -380,18 +380,20 @@ defmodule ExDoc.Language.Elixir do def autolink_spec(ast, opts) do config = struct!(Autolink, opts) - string = - ast - |> Macro.to_string() - |> safe_format_string!() - |> ExDoc.Utils.h() - + string = format_spec(ast) name = typespec_name(ast) {name, rest} = split_name(string, name) name <> do_typespec(rest, config) end + def format_spec(ast) do + ast + |> Macro.to_string() + |> safe_format_string!() + |> ExDoc.Utils.h() + end + @impl true def highlight_info() do %{ diff --git a/lib/ex_doc/markdown/assets.ex b/lib/ex_doc/markdown/assets.ex new file mode 100644 index 000000000..42a123e89 --- /dev/null +++ b/lib/ex_doc/markdown/assets.ex @@ -0,0 +1,14 @@ +defmodule ExDoc.Formatter.Markdown.Assets do + @moduledoc false + + defmacrop embed_pattern(pattern) do + ["formatters/markdown", pattern] + |> Path.join() + |> Path.wildcard() + |> Enum.map(&{Path.basename(&1), File.read!(&1)}) + end + + def dist(_proglang), do: dist_license() + + defp dist_license(), do: embed_pattern("dist/*.LICENSE.txt") +end diff --git a/mix.exs b/mix.exs index 825bc3143..45ba8a85c 100644 --- a/mix.exs +++ b/mix.exs @@ -45,9 +45,10 @@ defmodule ExDoc.Mixfile do # Add other makeup lexers as optional for the executable {:makeup_c, ">= 0.1.0", optional: true}, {:makeup_html, ">= 0.1.0", optional: true}, - {:jason, "~> 1.2", only: :test}, + {:jason, "~> 1.4"}, {:floki, "~> 0.0", only: :test}, - {:easyhtml, "~> 0.0", only: :test} + {:easyhtml, "~> 0.0", only: :test}, + {:mdex, "~> 0.3"} ] end diff --git a/mix.lock b/mix.lock index b056eb45f..ac466f31c 100644 --- a/mix.lock +++ b/mix.lock @@ -1,5 +1,6 @@ %{ - "earmark_parser": {:hex, :earmark_parser, "1.4.43", "34b2f401fe473080e39ff2b90feb8ddfeef7639f8ee0bbf71bb41911831d77c5", [:mix], [], "hexpm", "970a3cd19503f5e8e527a190662be2cee5d98eed1ff72ed9b3d1a3d466692de8"}, + "castore": {:hex, :castore, "1.0.12", "053f0e32700cbec356280c0e835df425a3be4bc1e0627b714330ad9d0f05497f", [:mix], [], "hexpm", "3dca286b2186055ba0c9449b4e95b97bf1b57b47c1f2644555879e659960c224"}, + "earmark_parser": {:hex, :earmark_parser, "1.4.44", "f20830dd6b5c77afe2b063777ddbbff09f9759396500cdbe7523efd58d7a339c", [:mix], [], "hexpm", "4778ac752b4701a5599215f7030989c989ffdc4f6df457c5f36938cc2d2a2750"}, "easyhtml": {:hex, :easyhtml, "0.3.2", "050adfc8074f53b261f7dfe83303d864f1fbf5988245b369f8fdff1bf4c4b3e6", [:mix], [{:floki, "~> 0.35", [hex: :floki, repo: "hexpm", optional: false]}], "hexpm", "b6a936f91612a4870aa3e828cd8da5a08d9e3b6221b4d3012b6ec70b87845d06"}, "floki": {:hex, :floki, "0.36.2", "a7da0193538c93f937714a6704369711998a51a6164a222d710ebd54020aa7a3", [:mix], [], "hexpm", "a8766c0bc92f074e5cb36c4f9961982eda84c5d2b8e979ca67f5c268ec8ed580"}, "jason": {:hex, :jason, "1.4.4", "b9226785a9aa77b6857ca22832cffa5d5011a667207eb2a0ad56adb5db443b8a", [:mix], [{:decimal, "~> 1.0 or ~> 2.0", [hex: :decimal, repo: "hexpm", optional: true]}], "hexpm", "c5eb0cab91f094599f94d55bc63409236a8ec69a21a67814529e8d5f6cc90b3b"}, @@ -8,5 +9,9 @@ "makeup_elixir": {:hex, :makeup_elixir, "0.16.2", "627e84b8e8bf22e60a2579dad15067c755531fea049ae26ef1020cad58fe9578", [:mix], [{:makeup, "~> 1.0", [hex: :makeup, repo: "hexpm", optional: false]}, {:nimble_parsec, "~> 1.2.3 or ~> 1.3", [hex: :nimble_parsec, repo: "hexpm", optional: false]}], "hexpm", "41193978704763f6bbe6cc2758b84909e62984c7752b3784bd3c218bb341706b"}, "makeup_erlang": {:hex, :makeup_erlang, "1.0.2", "03e1804074b3aa64d5fad7aa64601ed0fb395337b982d9bcf04029d68d51b6a7", [:mix], [{:makeup, "~> 1.0", [hex: :makeup, repo: "hexpm", optional: false]}], "hexpm", "af33ff7ef368d5893e4a267933e7744e46ce3cf1f61e2dccf53a111ed3aa3727"}, "makeup_html": {:hex, :makeup_html, "0.1.1", "c3d4abd39d5f7e925faca72ada6e9cc5c6f5fa7cd5bc0158315832656cf14d7f", [:mix], [{:makeup, "~> 1.0", [hex: :makeup, repo: "hexpm", optional: false]}], "hexpm", "44f2a61bc5243645dd7fafeaa6cc28793cd22f3c76b861e066168f9a5b2c26a4"}, + "mdex": {:hex, :mdex, "0.4.2", "df88b558a059312b313214afdf311f74f7f6ecf2726ce20ee851ebb9fc068b74", [:mix], [{:rustler, "~> 0.32", [hex: :rustler, repo: "hexpm", optional: false]}, {:rustler_precompiled, "~> 0.7", [hex: :rustler_precompiled, repo: "hexpm", optional: false]}], "hexpm", "4f7c36abb6cf98dbbe6872e170520d8c3fa32e3515ebd988d03c79421248058c"}, "nimble_parsec": {:hex, :nimble_parsec, "1.4.2", "8efba0122db06df95bfaa78f791344a89352ba04baedd3849593bfce4d0dc1c6", [:mix], [], "hexpm", "4b21398942dda052b403bbe1da991ccd03a053668d147d53fb8c4e0efe09c973"}, + "rustler": {:hex, :rustler, "0.36.1", "2d4b1ff57ea2789a44756a40dbb5fbb73c6ee0a13d031dcba96d0a5542598a6a", [:mix], [{:jason, "~> 1.0", [hex: :jason, repo: "hexpm", optional: false]}, {:toml, "~> 0.7", [hex: :toml, repo: "hexpm", optional: false]}], "hexpm", "f3fba4ad272970e0d1bc62972fc4a99809651e54a125c5242de9bad4574b2d02"}, + "rustler_precompiled": {:hex, :rustler_precompiled, "0.8.2", "5f25cbe220a8fac3e7ad62e6f950fcdca5a5a5f8501835d2823e8c74bf4268d5", [:mix], [{:castore, "~> 0.1 or ~> 1.0", [hex: :castore, repo: "hexpm", optional: false]}, {:rustler, "~> 0.23", [hex: :rustler, repo: "hexpm", optional: true]}], "hexpm", "63d1bd5f8e23096d1ff851839923162096364bac8656a4a3c00d1fff8e83ee0a"}, + "toml": {:hex, :toml, "0.7.0", "fbcd773caa937d0c7a02c301a1feea25612720ac3fa1ccb8bfd9d30d822911de", [:mix], [], "hexpm", "0690246a2478c1defd100b0c9b89b4ea280a22be9a7b313a8a058a2408a2fa70"}, }