From cf8530a12ecf939e67bbbea4fbb9609b11a0c7b0 Mon Sep 17 00:00:00 2001 From: Eksperimental Date: Sun, 24 Apr 2022 10:06:15 +0000 Subject: [PATCH] Optimize html/epub tests by making them asyncronous by using tmp_dir tag (#1557) --- .gitignore | 1 + test/ex_doc/formatter/epub_test.exs | 120 ++++++----- test/ex_doc/formatter/html_test.exs | 300 +++++++++++++++------------- 3 files changed, 213 insertions(+), 208 deletions(-) diff --git a/.gitignore b/.gitignore index 9f8e27862..1a2bf195c 100644 --- a/.gitignore +++ b/.gitignore @@ -25,6 +25,7 @@ ex_doc-*.tar node_modules/ /test/fixtures/umbrella/_build/ /test/tmp/ +/tmp/ /npm-debug.log # Ignore artifacts from non-production builds diff --git a/test/ex_doc/formatter/epub_test.exs b/test/ex_doc/formatter/epub_test.exs index eca1ad1e2..7d38a36c0 100644 --- a/test/ex_doc/formatter/epub_test.exs +++ b/test/ex_doc/formatter/epub_test.exs @@ -1,18 +1,7 @@ defmodule ExDoc.Formatter.EPUBTest do - use ExUnit.Case + use ExUnit.Case, async: true - setup do - File.rm_rf(output_dir()) - File.mkdir_p!(output_dir()) - end - - defp output_dir do - Path.expand("../../tmp/epub", __DIR__) - end - - defp beam_dir do - Path.expand("../../tmp/beam", __DIR__) - end + @moduletag :tmp_dir @before_closing_head_tag_content_epub "UNIQUE:©BEFORE-CLOSING-HEAD-TAG-HTML" @before_closing_body_tag_content_epub "UNIQUE:©BEFORE-CLOSING-BODY-TAG-HTML" @@ -20,95 +9,95 @@ defmodule ExDoc.Formatter.EPUBTest do defp before_closing_head_tag(:epub), do: @before_closing_head_tag_content_epub defp before_closing_body_tag(:epub), do: @before_closing_body_tag_content_epub - defp doc_config do + defp doc_config(%{tmp_dir: tmp_dir} = _context) do [ app: :elixir, project: "Elixir", version: "1.0.1", formatter: "epub", - output: output_dir(), - source_beam: beam_dir(), + output: tmp_dir <> "/epub", + source_beam: "test/tmp/beam", extras: ["test/fixtures/README.md"], skip_undefined_reference_warnings_on: ["Warnings"] ] end - defp doc_config(config) do - Keyword.merge(doc_config(), config) + defp doc_config(context, config) when is_map(context) and is_list(config) do + Keyword.merge(doc_config(context), config) end defp generate_docs(config) do ExDoc.generate_docs(config[:project], config[:version], config) end - defp generate_docs_and_unzip(options) do - generate_docs(options) - unzip_dir = String.to_charlist("#{doc_config()[:output]}") + defp generate_docs_and_unzip(context, config) do + generate_docs(config) + unzip_dir = String.to_charlist("#{doc_config(context)[:output]}") - "#{doc_config()[:output]}/#{doc_config()[:project]}.epub" + "#{doc_config(context)[:output]}/#{doc_config(context)[:project]}.epub" |> String.to_charlist() |> :zip.unzip(cwd: unzip_dir) end - test "generates headers for module pages" do - generate_docs_and_unzip(doc_config(main: "RandomError")) + test "generates headers for module pages", %{tmp_dir: tmp_dir} = context do + generate_docs_and_unzip(context, doc_config(context, main: "RandomError")) - content = File.read!("#{output_dir()}/OEBPS/RandomError.xhtml") + content = File.read!(tmp_dir <> "/epub/OEBPS/RandomError.xhtml") assert content =~ ~r{}ms assert content =~ ~r{}ms assert content =~ ~r{} assert content =~ ~r{RandomError - Elixir v1.0.1} end - test "allows to set the primary language of the document" do - generate_docs_and_unzip(doc_config(main: "RandomError", language: "fr")) + test "allows to set the primary language of the document", %{tmp_dir: tmp_dir} = context do + generate_docs_and_unzip(context, doc_config(context, main: "RandomError", language: "fr")) - content = File.read!("#{output_dir()}/OEBPS/RandomError.xhtml") + content = File.read!(tmp_dir <> "/epub/OEBPS/RandomError.xhtml") assert content =~ ~r{}ms end - test "allows to set the authors of the book" do - generate_docs_and_unzip(doc_config(authors: ["John Doe", "Jane Doe"])) + test "allows to set the authors of the book", %{tmp_dir: tmp_dir} = context do + generate_docs_and_unzip(context, doc_config(context, authors: ["John Doe", "Jane Doe"])) - content = File.read!("#{output_dir()}/OEBPS/content.opf") + content = File.read!(tmp_dir <> "/epub/OEBPS/content.opf") assert content =~ ~r{John Doe} assert content =~ ~r{Jane Doe} end - test "raises when assets are invalid" do + test "raises when assets are invalid", context do File.mkdir_p!("test/tmp/epub_assets/hello") File.touch!("test/tmp/epub_assets/hello/world.pdf") assert_raise( RuntimeError, ~s{asset with extension ".pdf" is not supported by EPUB format}, - fn -> generate_docs(doc_config(assets: "test/tmp/epub_assets")) end + fn -> generate_docs(doc_config(context, assets: "test/tmp/epub_assets")) end ) after File.rm_rf!("test/tmp/epub_assets") end - test "generates an EPUB file in the default directory" do - generate_docs(doc_config()) - assert File.regular?("#{output_dir()}/#{doc_config()[:project]}.epub") + test "generates an EPUB file in the default directory", %{tmp_dir: tmp_dir} = context do + generate_docs(doc_config(context)) + assert File.regular?(tmp_dir <> "/epub/#{doc_config(context)[:project]}.epub") end - test "generates an EPUB file with erlang as proglang" do - generate_docs(Keyword.put(doc_config(), :proglang, :erlang)) - assert File.regular?("#{output_dir()}/#{doc_config()[:project]}.epub") + test "generates an EPUB file with erlang as proglang", %{tmp_dir: tmp_dir} = context do + generate_docs(Keyword.put(doc_config(context), :proglang, :erlang)) + assert File.regular?(tmp_dir <> "/epub/#{doc_config(context)[:project]}.epub") end - test "generates an EPUB file in specified output directory" do - config = doc_config(output: "#{output_dir()}/another_dir", main: "RandomError") + test "generates an EPUB file in specified output directory", %{tmp_dir: tmp_dir} = context do + config = doc_config(context, output: tmp_dir <> "/epub/another_dir", main: "RandomError") generate_docs(config) - assert File.regular?("#{output_dir()}/another_dir/#{doc_config()[:project]}.epub") + assert File.regular?(tmp_dir <> "/epub/another_dir/#{doc_config(context)[:project]}.epub") end - test "generates an EPUB file with a standardized structure" do - generate_docs_and_unzip(doc_config()) + test "generates an EPUB file with a standardized structure", %{tmp_dir: tmp_dir} = context do + generate_docs_and_unzip(context, doc_config(context)) - root_dir = "#{output_dir()}" + root_dir = tmp_dir <> "/epub" meta_dir = "#{root_dir}/META-INF" oebps_dir = "#{root_dir}/OEBPS" dist_dir = "#{oebps_dir}/dist" @@ -126,9 +115,9 @@ defmodule ExDoc.Formatter.EPUBTest do assert [_] = Path.wildcard("#{dist_dir}/elixir*.css") end - test "generates all listing files" do - generate_docs_and_unzip(doc_config()) - content = File.read!("#{output_dir()}/OEBPS/content.opf") + test "generates all listing files", %{tmp_dir: tmp_dir} = context do + generate_docs_and_unzip(context, doc_config(context)) + content = File.read!(tmp_dir <> "/epub/OEBPS/content.opf") assert content =~ ~r{.*"CompiledWithDocs\".*}ms assert content =~ ~r{.*"CompiledWithDocs.Nested\".*}ms @@ -139,11 +128,11 @@ defmodule ExDoc.Formatter.EPUBTest do assert content =~ ~r{.*"Mix\.Tasks\.TaskWithDocs\".*}ms end - test "generates the readme file" do - config = doc_config(main: "README") - generate_docs_and_unzip(config) + test "generates the readme file", %{tmp_dir: tmp_dir} = context do + config = doc_config(context, main: "README") + generate_docs_and_unzip(context, config) - content = File.read!("#{output_dir()}/OEBPS/readme.xhtml") + content = File.read!(tmp_dir <> "/epub/OEBPS/readme.xhtml") assert content =~ ~r{README [^<]*} assert content =~ ~r{RandomError} @@ -153,14 +142,14 @@ defmodule ExDoc.Formatter.EPUBTest do assert content =~ ~r{TypesAndSpecs.Sub} - content = File.read!("#{output_dir()}/OEBPS/nav.xhtml") + content = File.read!(tmp_dir <> "/epub/OEBPS/nav.xhtml") assert content =~ ~r{
  • README
  • } end - test "uses samp as highlight tag for markdown" do - generate_docs_and_unzip(doc_config()) + test "uses samp as highlight tag for markdown", %{tmp_dir: tmp_dir} = context do + generate_docs_and_unzip(context, doc_config(context)) - assert File.read!("#{output_dir()}/OEBPS/CompiledWithDocs.xhtml") =~ + assert File.read!(tmp_dir <> "/epub/OEBPS/CompiledWithDocs.xhtml") =~ "CompiledWithDocs<\/samp>" end @@ -174,15 +163,17 @@ defmodule ExDoc.Formatter.EPUBTest do "CompiledWithDocs.Nested.xhtml" ] - test "before_closing_*_tags required by the user are in the right place" do + test "before_closing_*_tags required by the user are in the right place", + %{tmp_dir: tmp_dir} = context do generate_docs_and_unzip( - doc_config( + context, + doc_config(context, before_closing_head_tag: &before_closing_head_tag/1, before_closing_body_tag: &before_closing_body_tag/1 ) ) - oebps_dir = "#{output_dir()}/OEBPS" + oebps_dir = tmp_dir <> "/epub/OEBPS" for basename <- @example_basenames do content = File.read!(Path.join(oebps_dir, basename)) @@ -191,21 +182,22 @@ defmodule ExDoc.Formatter.EPUBTest do end end - test "assets required by the user end up in the right place" do + test "assets required by the user end up in the right place", %{tmp_dir: tmp_dir} = context do File.mkdir_p!("test/tmp/epub_assets/hello") File.touch!("test/tmp/epub_assets/hello/world.png") generate_docs_and_unzip( - doc_config( + context, + doc_config(context, assets: "test/tmp/epub_assets", logo: "test/fixtures/elixir.png", cover: "test/fixtures/elixir.png" ) ) - assert File.regular?("#{output_dir()}/OEBPS/assets/hello/world.png") - assert File.regular?("#{output_dir()}/OEBPS/assets/logo.png") - assert File.regular?("#{output_dir()}/OEBPS/assets/cover.png") + assert File.regular?(tmp_dir <> "/epub/OEBPS/assets/hello/world.png") + assert File.regular?(tmp_dir <> "/epub/OEBPS/assets/logo.png") + assert File.regular?(tmp_dir <> "/epub/OEBPS/assets/cover.png") after File.rm_rf!("test/tmp/epub_assets") end diff --git a/test/ex_doc/formatter/html_test.exs b/test/ex_doc/formatter/html_test.exs index fd7b891f9..00fc51ad4 100644 --- a/test/ex_doc/formatter/html_test.exs +++ b/test/ex_doc/formatter/html_test.exs @@ -1,21 +1,10 @@ defmodule ExDoc.Formatter.HTMLTest do - use ExUnit.Case + use ExUnit.Case, async: true import ExUnit.CaptureIO alias ExDoc.Formatter.HTML - setup do - File.rm_rf(output_dir()) - File.mkdir_p!(output_dir()) - end - - defp output_dir do - Path.expand("../../tmp/html", __DIR__) - end - - defp beam_dir do - Path.expand("../../tmp/beam", __DIR__) - end + @moduletag :tmp_dir defp read_wildcard!(path) do [file] = Path.wildcard(path) @@ -28,23 +17,23 @@ defmodule ExDoc.Formatter.HTMLTest do defp before_closing_head_tag(:html), do: @before_closing_head_tag_content_html defp before_closing_body_tag(:html), do: @before_closing_body_tag_content_html - defp doc_config do + defp doc_config(%{tmp_dir: tmp_dir} = _context) do [ apps: [:elixir], project: "Elixir", version: "1.0.1", formatter: "html", assets: "test/tmp/html_assets", - output: output_dir(), - source_beam: beam_dir(), + output: tmp_dir <> "/html", + source_beam: "test/tmp/beam", source_url: "https://github.com/elixir-lang/elixir", logo: "test/fixtures/elixir.png", extras: [] ] end - defp doc_config(config) do - Keyword.merge(doc_config(), config) + defp doc_config(context, config) when is_map(context) and is_list(config) do + Keyword.merge(doc_config(context), config) end defp generate_docs(config) do @@ -52,17 +41,17 @@ defmodule ExDoc.Formatter.HTMLTest do ExDoc.generate_docs(config[:project], config[:version], config) end - test "normalizes options" do + test "normalizes options", %{tmp_dir: tmp_dir} = context do # 1. Check for output dir having trailing "/" stripped # 2. Check for default [main: "api-reference"] - generate_docs(doc_config(output: "#{output_dir()}//", main: nil)) + generate_docs(doc_config(context, output: tmp_dir <> "/html//", main: nil)) - content = File.read!("#{output_dir()}/index.html") + content = File.read!(tmp_dir <> "/html/index.html") assert content =~ ~r{} - assert File.regular?("#{output_dir()}/api-reference.html") + assert File.regular?(tmp_dir <> "/html/api-reference.html") # 3. main as index is not allowed - config = doc_config(main: "index") + config = doc_config(context, main: "index") assert_raise ArgumentError, ~S("main" cannot be set to "index", otherwise it will recursively link to itself), @@ -91,21 +80,22 @@ defmodule ExDoc.Formatter.HTMLTest do end end - test "warns when generating an index.html file with an invalid redirect" do + test "warns when generating an index.html file with an invalid redirect", + %{tmp_dir: tmp_dir} = context do output = capture_io(:stderr, fn -> - generate_docs(doc_config(main: "Randomerror")) + generate_docs(doc_config(context, main: "Randomerror")) end) assert output == "warning: index.html redirects to Randomerror.html, which does not exist\n" - assert File.regular?("#{output_dir()}/index.html") - assert File.regular?("#{output_dir()}/RandomError.html") + assert File.regular?(tmp_dir <> "/html/index.html") + assert File.regular?(tmp_dir <> "/html/RandomError.html") end - test "warns on undefined functions" do + test "warns on undefined functions", context do output = capture_io(:stderr, fn -> - generate_docs(doc_config(skip_undefined_reference_warnings_on: [])) + generate_docs(doc_config(context, skip_undefined_reference_warnings_on: [])) end) assert output =~ ~r"Warnings.bar/0.*\n test/fixtures/warnings.ex:2: Warnings" @@ -114,21 +104,21 @@ defmodule ExDoc.Formatter.HTMLTest do assert output =~ ~r"Warnings.bar/0.*\n test/fixtures/warnings.ex:8: t:Warnings.t/0" end - test "warns on undefined functions in file" do + test "warns on undefined functions in file", context do output = capture_io(:stderr, fn -> generate_docs( - doc_config(skip_undefined_reference_warnings_on: ["test/fixtures/warnings.ex"]) + doc_config(context, skip_undefined_reference_warnings_on: ["test/fixtures/warnings.ex"]) ) end) assert output == "" end - test "generates headers for index.html and module pages" do - generate_docs(doc_config(main: "RandomError")) - content_index = File.read!("#{output_dir()}/index.html") - content_module = File.read!("#{output_dir()}/RandomError.html") + test "generates headers for index.html and module pages", %{tmp_dir: tmp_dir} = context do + generate_docs(doc_config(context, main: "RandomError")) + content_index = File.read!(tmp_dir <> "/html/index.html") + content_module = File.read!(tmp_dir <> "/html/RandomError.html") # Regular Expressions re = %{ @@ -164,30 +154,31 @@ defmodule ExDoc.Formatter.HTMLTest do refute content_module =~ re[:index][:refresh] end - test "allows to set the authors of the document" do - generate_docs(doc_config(authors: ["John Doe", "Jane Doe"])) - content_index = File.read!("#{output_dir()}/api-reference.html") + test "allows to set the authors of the document", %{tmp_dir: tmp_dir} = context do + generate_docs(doc_config(context, authors: ["John Doe", "Jane Doe"])) + content_index = File.read!(tmp_dir <> "/html/api-reference.html") assert content_index =~ ~r{} end - test "generates in default directory with redirect index.html file" do - generate_docs(doc_config()) + test "generates in default directory with redirect index.html file", + %{tmp_dir: tmp_dir} = context do + generate_docs(doc_config(context)) - assert File.regular?("#{output_dir()}/CompiledWithDocs.html") - assert File.regular?("#{output_dir()}/CompiledWithDocs.Nested.html") + assert File.regular?(tmp_dir <> "/html/CompiledWithDocs.html") + assert File.regular?(tmp_dir <> "/html/CompiledWithDocs.Nested.html") - assert [_] = Path.wildcard("#{output_dir()}/dist/app-*.js") - assert [_] = Path.wildcard("#{output_dir()}/dist/elixir-*.css") + assert [_] = Path.wildcard(tmp_dir <> "/html/dist/app-*.js") + assert [_] = Path.wildcard(tmp_dir <> "/html/dist/elixir-*.css") - content = File.read!("#{output_dir()}/index.html") + content = File.read!(tmp_dir <> "/html/index.html") assert content =~ ~r{} end - test "generates all listing files" do - generate_docs(doc_config()) + test "generates all listing files", %{tmp_dir: tmp_dir} = context do + generate_docs(doc_config(context)) - content = read_wildcard!("#{output_dir()}/dist/sidebar_items-*.js") + content = read_wildcard!(tmp_dir <> "/html/dist/sidebar_items-*.js") assert content =~ ~r{"id":"CompiledWithDocs",.*"title":"CompiledWithDocs"}ms assert content =~ ~r("id":"CompiledWithDocs",.*"key":"functions".*"example/2")ms assert content =~ ~r{"id":"CompiledWithDocs\.Nested",.*"title":"CompiledWithDocs\.Nested"}ms @@ -199,10 +190,10 @@ defmodule ExDoc.Formatter.HTMLTest do assert content =~ ~r{"id":"Mix\.Tasks\.TaskWithDocs",.*"title":"mix task_with_docs"}ms end - test "generates the api reference file" do - generate_docs(doc_config()) + test "generates the api reference file", %{tmp_dir: tmp_dir} = context do + generate_docs(doc_config(context)) - content = File.read!("#{output_dir()}/api-reference.html") + content = File.read!(tmp_dir <> "/html/api-reference.html") assert content =~ ~r{CompiledWithDocs} assert content =~ ~r{

    moduledoc

    } @@ -213,12 +204,12 @@ defmodule ExDoc.Formatter.HTMLTest do ~r{mix task_with_docs} end - test "groups modules by nesting" do - doc_config() + test "groups modules by nesting", %{tmp_dir: tmp_dir} = context do + doc_config(context) |> Keyword.put(:nest_modules_by_prefix, [Common.Nesting.Prefix.B, Common.Nesting.Prefix.B.B]) |> generate_docs() - "sidebarNodes=" <> content = read_wildcard!("#{output_dir()}/dist/sidebar_items-*.js") + "sidebarNodes=" <> content = read_wildcard!(tmp_dir <> "/html/dist/sidebar_items-*.js") assert {:ok, %{"modules" => modules}} = Jason.decode(content) assert %{"nested_context" => "Common.Nesting.Prefix.B"} = @@ -228,7 +219,7 @@ defmodule ExDoc.Formatter.HTMLTest do Enum.find(modules, fn %{"id" => id} -> id == "Common.Nesting.Prefix.B.B.A" end) end - test "groups modules by nesting respecting groups" do + test "groups modules by nesting respecting groups", %{tmp_dir: tmp_dir} = context do groups = [ Group1: [ Common.Nesting.Prefix.B.A, @@ -240,12 +231,12 @@ defmodule ExDoc.Formatter.HTMLTest do ] ] - doc_config() + doc_config(context) |> Keyword.put(:nest_modules_by_prefix, [Common.Nesting.Prefix.B, Common.Nesting.Prefix.B.B]) |> Keyword.put(:groups_for_modules, groups) |> generate_docs() - "sidebarNodes=" <> content = read_wildcard!("#{output_dir()}/dist/sidebar_items-*.js") + "sidebarNodes=" <> content = read_wildcard!(tmp_dir <> "/html/dist/sidebar_items-*.js") assert {:ok, %{"modules" => modules}} = Jason.decode(content) assert %{"Group1" => [_, _], "Group2" => [_, _]} = @@ -253,15 +244,15 @@ defmodule ExDoc.Formatter.HTMLTest do end describe "generates logo" do - test "overriding previous entries" do - File.mkdir_p!("#{output_dir()}/assets") - File.touch!("#{output_dir()}/assets/logo.png") - generate_docs(doc_config(logo: "test/fixtures/elixir.png")) - assert File.read!("#{output_dir()}/assets/logo.png") != "" + test "overriding previous entries", %{tmp_dir: tmp_dir} = context do + File.mkdir_p!(tmp_dir <> "/html/assets") + File.touch!(tmp_dir <> "/html/assets/logo.png") + generate_docs(doc_config(context, logo: "test/fixtures/elixir.png")) + assert File.read!(tmp_dir <> "/html/assets/logo.png") != "" end - test "fails when logo is not an allowed format" do - config = doc_config(logo: "README.md") + test "fails when logo is not an allowed format", context do + config = doc_config(context, logo: "README.md") assert_raise ArgumentError, "image format not recognized, allowed formats are: .jpg, .png", @@ -270,22 +261,25 @@ defmodule ExDoc.Formatter.HTMLTest do end describe "canonical URL" do - test "is included when canonical options is specified" do + test "is included when canonical options is specified", %{tmp_dir: tmp_dir} = context do config = - doc_config(extras: ["test/fixtures/README.md"], canonical: "https://hexdocs.pm/elixir/") + doc_config(context, + extras: ["test/fixtures/README.md"], + canonical: "https://hexdocs.pm/elixir/" + ) generate_docs(config) - content = File.read!("#{output_dir()}/api-reference.html") + content = File.read!(tmp_dir <> "/html/api-reference.html") assert content =~ ~r{ "/html/readme.html") assert content =~ ~r{ "/html/api-reference.html") refute content =~ ~r{ "/html/LICENSE") + refute File.exists?(tmp_dir <> "/html/license") + refute File.exists?(tmp_dir <> "/html/PlainText.txt") + refute File.exists?(tmp_dir <> "/html/plaintext.txt") + refute File.exists?(tmp_dir <> "/html/PlainTextFiles.md") + refute File.exists?(tmp_dir <> "/html/plaintextfiles.md") + refute File.exists?(tmp_dir <> "/html/README.md") + refute File.exists?(tmp_dir <> "/html/readme.md") assert File.read!("test/fixtures/LivebookFile.livemd") == - File.read!("#{output_dir()}/livebookfile.livemd") + File.read!(tmp_dir <> "/html/livebookfile.livemd") end - test "alongside other content" do - config = doc_config(main: "readme", extras: @extras) + test "alongside other content", %{tmp_dir: tmp_dir} = context do + config = doc_config(context, main: "readme", extras: @extras) generate_docs(config) - content = File.read!("#{output_dir()}/index.html") + content = File.read!(tmp_dir <> "/html/index.html") assert content =~ ~r{} - content = File.read!("#{output_dir()}/readme.html") + content = File.read!(tmp_dir <> "/html/readme.html") assert content =~ ~r{README [^<]*} assert content =~ @@ -356,14 +350,14 @@ defmodule ExDoc.Formatter.HTMLTest do assert content =~ ~s{ "/html/plaintextfiles.html") assert content =~ ~r{Plain Text Files.*}s assert content =~ ~R{

    Read the license and the plain-text file.} - plain_text_file = File.read!("#{output_dir()}/plaintext.html") + plain_text_file = File.read!(tmp_dir <> "/html/plaintext.html") assert plain_text_file =~ ~r{PlainText.*}s @@ -373,14 +367,14 @@ defmodule ExDoc.Formatter.HTMLTest do assert plain_text_file =~ ~s{\n## Neither formatted\n} assert plain_text_file =~ ~s{\n `t:term/0`\n} - license = File.read!("#{output_dir()}/license.html") + license = File.read!(tmp_dir <> "/html/license.html") assert license =~ ~r{LICENSE.*}s assert license =~ ~s{

    \nLicensed under the Apache License, Version 2.0 (the "License")}
     
    -      content = File.read!("#{output_dir()}/livebookfile.html")
    +      content = File.read!(tmp_dir <> "/html/livebookfile.html")
     
           assert content =~
                    ~s{}
         end
     
    -    test "with absolute and dot-relative paths for extra" do
    +    test "with absolute and dot-relative paths for extra", %{tmp_dir: tmp_dir} = context do
           config =
    -        doc_config(
    +        doc_config(context,
               extras: ["./test/fixtures/README.md", Path.expand("test/fixtures/LivebookFile.livemd")]
             )
     
           generate_docs(config)
     
    -      content = File.read!("#{output_dir()}/readme.html")
    +      content = File.read!(tmp_dir <> "/html/readme.html")
     
           assert content =~
                    ~s{ "/html/livebookfile.html")
     
           assert content =~
                    ~s{ "/html/dist/sidebar_items-*.js")
           assert content =~ ~s("modules":[])
     
           assert content =~
    @@ -424,15 +418,16 @@ defmodule ExDoc.Formatter.HTMLTest do
                    ~s({"group":"","headers":[{"anchor":"heading-without-content","id":"Heading without content"},{"anchor":"header-sample","id":"Header sample"},{"anchor":"more-than","id":"more > than"}],"id":"readme","title":"README"})
         end
     
    -    test "containing settext headers while discarding links on header" do
    +    test "containing settext headers while discarding links on header",
    +         %{tmp_dir: tmp_dir} = context do
           generate_docs(
    -        doc_config(
    +        doc_config(context,
               source_beam: "unknown",
               extras: ["test/fixtures/ExtraPageWithSettextHeader.md"]
             )
           )
     
    -      content = read_wildcard!("#{output_dir()}/dist/sidebar_items-*.js")
    +      content = read_wildcard!(tmp_dir <> "/html/dist/sidebar_items-*.js")
     
           assert content =~
                    ~s("extras":[{"group":"","headers":[],"id":"api-reference","title":"API Reference"},)
    @@ -442,9 +437,9 @@ defmodule ExDoc.Formatter.HTMLTest do
                      ~s(id":"extrapagewithsettextheader","title":"Extra Page Title"}])
         end
     
    -    test "with custom names" do
    +    test "with custom names", %{tmp_dir: tmp_dir} = context do
           generate_docs(
    -        doc_config(
    +        doc_config(context,
               extras: [
                 "test/fixtures/PlainTextFiles.md",
                 "test/fixtures/LICENSE": [filename: "linked-license"],
    @@ -453,65 +448,73 @@ defmodule ExDoc.Formatter.HTMLTest do
             )
           )
     
    -      refute File.regular?("#{output_dir()}/license.html")
    -      assert File.regular?("#{output_dir()}/linked-license.html")
    +      refute File.regular?(tmp_dir <> "/html/license.html")
    +      assert File.regular?(tmp_dir <> "/html/linked-license.html")
     
    -      refute File.regular?("#{output_dir()}/plaintext.html")
    -      assert File.regular?("#{output_dir()}/plain_text.html")
    +      refute File.regular?(tmp_dir <> "/html/plaintext.html")
    +      assert File.regular?(tmp_dir <> "/html/plain_text.html")
     
    -      content = File.read!("#{output_dir()}/plaintextfiles.html")
    +      content = File.read!(tmp_dir <> "/html/plaintextfiles.html")
     
           assert content =~ ~r{Plain Text Files.*}s
     
           assert content =~
                    ~R{

    Read the license and the plain-text file.} - content = read_wildcard!("#{output_dir()}/dist/sidebar_items-*.js") + content = read_wildcard!(tmp_dir <> "/html/dist/sidebar_items-*.js") assert content =~ ~r{"id":"linked-license","title":"LICENSE"} end - test "with custom title" do - generate_docs(doc_config(extras: ["test/fixtures/README.md": [title: "Getting Started"]])) - content = File.read!("#{output_dir()}/readme.html") + test "with custom title", %{tmp_dir: tmp_dir} = context do + generate_docs( + doc_config(context, extras: ["test/fixtures/README.md": [title: "Getting Started"]]) + ) + + content = File.read!(tmp_dir <> "/html/readme.html") assert content =~ ~r{Getting Started — Elixir v1.0.1} - content = read_wildcard!("#{output_dir()}/dist/sidebar_items-*.js") + content = read_wildcard!(tmp_dir <> "/html/dist/sidebar_items-*.js") assert content =~ ~r{"group":"","headers":\[[^\]]+\],"id":"readme","title":"Getting Started"} end - test "with custom groups" do + test "with custom groups", %{tmp_dir: tmp_dir} = context do extra_config = [ extras: ["test/fixtures/README.md"], groups_for_extras: [Intro: ~r/fixtures\/READ.?/] ] - generate_docs(doc_config(extra_config)) - content = read_wildcard!("#{output_dir()}/dist/sidebar_items-*.js") + generate_docs(doc_config(context, extra_config)) + content = read_wildcard!(tmp_dir <> "/html/dist/sidebar_items-*.js") assert content =~ ~r{"group":"Intro","headers":\[[^\]]+\],"id":"readme","title":"README"} end - test "with auto-extracted titles" do - generate_docs(doc_config(extras: ["test/fixtures/ExtraPage.md"])) - content = File.read!("#{output_dir()}/extrapage.html") + test "with auto-extracted titles", %{tmp_dir: tmp_dir} = context do + generate_docs(doc_config(context, extras: ["test/fixtures/ExtraPage.md"])) + content = File.read!(tmp_dir <> "/html/extrapage.html") assert content =~ ~r{Extra Page Title — Elixir v1.0.1} - content = read_wildcard!("#{output_dir()}/dist/sidebar_items-*.js") + content = read_wildcard!(tmp_dir <> "/html/dist/sidebar_items-*.js") assert content =~ ~r{"id":"extrapage","title":"Extra Page Title"} end - test "without api-reference" do + test "without api-reference", %{tmp_dir: tmp_dir} = context do generate_docs( - doc_config(api_reference: false, extras: ["test/fixtures/README.md"], main: "readme") + doc_config(context, + api_reference: false, + extras: ["test/fixtures/README.md"], + main: "readme" + ) ) - refute File.exists?("#{output_dir()}/api-reference.html") - content = read_wildcard!("#{output_dir()}/dist/sidebar_items-*.js") + refute File.exists?(tmp_dir <> "/html/api-reference.html") + content = read_wildcard!(tmp_dir <> "/html/dist/sidebar_items-*.js") refute content =~ ~r{"id":"api-reference","title":"API Reference"} end - test "pages include links to the previous/next page if applicable" do + test "pages include links to the previous/next page if applicable", + %{tmp_dir: tmp_dir} = context do generate_docs( - doc_config( + doc_config(context, extras: [ "test/fixtures/LICENSE", "test/fixtures/README.md" @@ -521,14 +524,14 @@ defmodule ExDoc.Formatter.HTMLTest do # We have three extras: API Reference, LICENSE and README - content_first = File.read!("#{output_dir()}/api-reference.html") + content_first = File.read!(tmp_dir <> "/html/api-reference.html") refute content_first =~ ~r{Previous Page} assert content_first =~ ~r{} - content_middle = File.read!("#{output_dir()}/license.html") + content_middle = File.read!(tmp_dir <> "/html/license.html") assert content_middle =~ ~r{} @@ -536,7 +539,7 @@ defmodule ExDoc.Formatter.HTMLTest do assert content_middle =~ ~r{} - content_last = File.read!("#{output_dir()}/readme.html") + content_last = File.read!(tmp_dir <> "/html/readme.html") assert content_last =~ ~r{} @@ -544,32 +547,37 @@ defmodule ExDoc.Formatter.HTMLTest do refute content_last =~ ~r{Next Page} end - test "before_closing_*_tags required by the user are placed in the right place" do + test "before_closing_*_tags required by the user are placed in the right place", + %{ + tmp_dir: tmp_dir + } = context do generate_docs( - doc_config( + doc_config(context, before_closing_head_tag: &before_closing_head_tag/1, before_closing_body_tag: &before_closing_body_tag/1, extras: ["test/fixtures/README.md"] ) ) - content = File.read!("#{output_dir()}/api-reference.html") + content = File.read!(tmp_dir <> "/html/api-reference.html") assert content =~ ~r[#{@before_closing_head_tag_content_html}\s*] assert content =~ ~r[#{@before_closing_body_tag_content_html}\s*] - content = File.read!("#{output_dir()}/readme.html") + content = File.read!(tmp_dir <> "/html/readme.html") assert content =~ ~r[#{@before_closing_head_tag_content_html}\s*] assert content =~ ~r[#{@before_closing_body_tag_content_html}\s*] end end describe ".build" do - test "stores generated content" do - config = doc_config(extras: ["test/fixtures/README.md"], logo: "test/fixtures/elixir.png") + test "stores generated content", %{tmp_dir: tmp_dir} = context do + config = + doc_config(context, extras: ["test/fixtures/README.md"], logo: "test/fixtures/elixir.png") + generate_docs(config) - content = File.read!("#{output_dir()}/.build") # Verify necessary files in .build + content = File.read!(tmp_dir <> "/html/.build") assert content =~ ~r(^readme\.html$)m assert content =~ ~r(^api-reference\.html$)m assert content =~ ~r(^dist/sidebar_items-[\w]{10}\.js$)m @@ -584,31 +592,35 @@ defmodule ExDoc.Formatter.HTMLTest do files = content |> String.split("\n", trim: true) - |> Enum.map(&Path.join(output_dir(), &1)) + |> Enum.map(&Path.join(tmp_dir <> "/html", &1)) for file <- files do assert File.exists?(file) end end - test "does not delete files not listed in .build" do - keep = "#{output_dir()}/keep" - config = doc_config() + test "does not delete files not listed in .build", %{tmp_dir: tmp_dir} = context do + keep = tmp_dir <> "/html/keep" + config = doc_config(context) generate_docs(config) File.touch!(keep) generate_docs(config) assert File.exists?(keep) - content = File.read!("#{output_dir()}/.build") + content = File.read!(tmp_dir <> "/html/.build") refute content =~ ~r{keep} end end - test "assets required by the user end up in the right place" do + test "assets required by the user end up in the right place", %{tmp_dir: tmp_dir} = context do File.mkdir_p!("test/tmp/html_assets/hello") File.touch!("test/tmp/html_assets/hello/world") - generate_docs(doc_config(assets: "test/tmp/html_assets", logo: "test/fixtures/elixir.png")) - assert File.regular?("#{output_dir()}/assets/logo.png") - assert File.regular?("#{output_dir()}/assets/hello/world") + + generate_docs( + doc_config(context, assets: "test/tmp/html_assets", logo: "test/fixtures/elixir.png") + ) + + assert File.regular?(tmp_dir <> "/html/assets/logo.png") + assert File.regular?(tmp_dir <> "/html/assets/hello/world") after File.rm_rf!("test/tmp/html_assets") end