From 478ec8af0c350a88342df3e3a783609533bcbd09 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Tue, 18 Mar 2025 10:16:40 +0100 Subject: [PATCH 01/18] Add MIX_DEPS_COMPILE_PARALLEL_COUNT for parallel app compilation --- lib/mix/lib/mix/tasks/deps.compile.ex | 127 ++++++++-------- lib/mix/lib/mix/tasks/deps.parallel.ex | 192 +++++++++++++++++++++++++ 2 files changed, 259 insertions(+), 60 deletions(-) create mode 100644 lib/mix/lib/mix/tasks/deps.parallel.ex diff --git a/lib/mix/lib/mix/tasks/deps.compile.ex b/lib/mix/lib/mix/tasks/deps.compile.ex index 7ce84b4da32..1760fa4ff9c 100644 --- a/lib/mix/lib/mix/tasks/deps.compile.ex +++ b/lib/mix/lib/mix/tasks/deps.compile.ex @@ -75,86 +75,82 @@ defmodule Mix.Tasks.Deps.Compile do @doc false def compile(deps, options \\ []) do - shell = Mix.shell() - config = Mix.Project.deps_config() Mix.Task.run("deps.precompile") + force? = Keyword.get(options, :force, false) - compiled = + deps = deps |> reject_umbrella_children(options) |> reject_local_deps(options) - |> Enum.map(fn %Mix.Dep{app: app, status: status, opts: opts, scm: scm} = dep -> - check_unavailable!(app, scm, status) - maybe_clean(dep, options) - compiled? = - cond do - not is_nil(opts[:compile]) -> - do_compile(dep, config) + count = System.get_env("MIX_DEPS_COMPILE_PARALLEL_COUNT", "0") |> String.to_integer() - Mix.Dep.mix?(dep) -> - do_mix(dep, config) + compiled? = + if count > 1 and length(deps) > count do + Mix.shell().info("mix deps.compile running in parallel with count=#{count}") + Mix.Tasks.Deps.Parallel.server(deps, count, force?) + else + config = Mix.Project.deps_config() + true in Enum.map(deps, &compile_single(&1, force?, config)) + end - Mix.Dep.make?(dep) -> - do_make(dep, config) + if compiled?, do: Mix.Task.run("will_recompile"), else: :ok + end - dep.manager == :rebar3 -> - do_rebar3(dep, config) + @doc false + def compile_single(%Mix.Dep{} = dep, force?, config) do + %{app: app, status: status, opts: opts, scm: scm} = dep + check_unavailable!(app, scm, status) - true -> - shell.error( - "Could not compile #{inspect(app)}, no \"mix.exs\", \"rebar.config\" or \"Makefile\" " <> - "(pass :compile as an option to customize compilation, set it to \"false\" to do nothing)" - ) + # If a dependency was marked as fetched or with an out of date lock + # or missing the app file, we always compile it from scratch. + if force? or Mix.Dep.compilable?(dep) do + File.rm_rf!(Path.join([Mix.Project.build_path(), "lib", Atom.to_string(dep.app)])) + end - false - end + compiled? = + cond do + not is_nil(opts[:compile]) -> + do_compile(dep, config) - if compiled? do - build_path = Mix.Project.build_path(config) + Mix.Dep.mix?(dep) -> + do_mix(dep, config) - lazy_message = fn -> - info = %{ - app: dep.app, - scm: dep.scm, - manager: dep.manager, - os_pid: System.pid() - } + Mix.Dep.make?(dep) -> + do_make(dep, config) - {:dep_compiled, info} - end + dep.manager == :rebar3 -> + do_rebar3(dep, config) - Mix.Sync.PubSub.broadcast(build_path, lazy_message) - end + true -> + Mix.shell().error( + "Could not compile #{inspect(app)}, no \"mix.exs\", \"rebar.config\" or \"Makefile\" " <> + "(pass :compile as an option to customize compilation, set it to \"false\" to do nothing)" + ) - # We should touch fetchable dependencies even if they - # did not compile otherwise they will always be marked - # as stale, even when there is nothing to do. - fetchable? = touch_fetchable(scm, opts[:build]) + false + end - compiled? and fetchable? + if compiled? do + config + |> Mix.Project.build_path() + |> Mix.Sync.PubSub.broadcast(fn -> + info = %{ + app: dep.app, + scm: dep.scm, + manager: dep.manager, + os_pid: System.pid() + } + + {:dep_compiled, info} end) - - if true in compiled, do: Mix.Task.run("will_recompile"), else: :ok - end - - defp maybe_clean(dep, opts) do - # If a dependency was marked as fetched or with an out of date lock - # or missing the app file, we always compile it from scratch. - if Keyword.get(opts, :force, false) or Mix.Dep.compilable?(dep) do - File.rm_rf!(Path.join([Mix.Project.build_path(), "lib", Atom.to_string(dep.app)])) end - end - defp touch_fetchable(scm, path) do - if scm.fetchable?() do - path = Path.join(path, ".mix") - File.mkdir_p!(path) - File.touch!(Path.join(path, "compile.fetch")) - true - else - false - end + # We should touch fetchable dependencies even if they + # did not compile otherwise they will always be marked + # as stale, even when there is nothing to do. + fetchable? = touch_fetchable(scm, opts[:build]) + compiled? and fetchable? end defp check_unavailable!(app, scm, {:unavailable, path}) do @@ -176,6 +172,17 @@ defmodule Mix.Tasks.Deps.Compile do :ok end + defp touch_fetchable(scm, path) do + if scm.fetchable?() do + path = Path.join(path, ".mix") + File.mkdir_p!(path) + File.touch!(Path.join(path, "compile.fetch")) + true + else + false + end + end + defp do_mix(dep, _config) do Mix.Dep.in_dependency(dep, fn _ -> config = Mix.Project.config() diff --git a/lib/mix/lib/mix/tasks/deps.parallel.ex b/lib/mix/lib/mix/tasks/deps.parallel.ex new file mode 100644 index 00000000000..38cb8710b6f --- /dev/null +++ b/lib/mix/lib/mix/tasks/deps.parallel.ex @@ -0,0 +1,192 @@ +defmodule Mix.Tasks.Deps.Parallel do + @moduledoc false + use Mix.Task + + ## Server + + def server(deps, count, force?) do + elixir = + System.find_executable("elixir") || + raise "cannot find elixir executable for parallel compilation" + + {:ok, socket} = :gen_tcp.listen(0, [:binary, packet: :line, active: true, reuseaddr: true]) + {:ok, {ip, port}} = :inet.sockname(socket) + ansi_flag = if IO.ANSI.enabled?(), do: ~c"--color", else: ~c"--no-color" + force_flag = if force?, do: ~c"--force", else: ~c"--no-force" + + args = [ + ansi_flag, + ~c"-e", + ~c"Mix.CLI.main()", + ~c"deps.parallel", + force_flag, + ~c"--port", + Integer.to_charlist(port), + ~c"--host", + :inet.ntoa(ip) + ] + + options = [ + :binary, + :hide, + :use_stdio, + :stderr_to_stdout, + line: 1_000_000, + args: args, + env: [{~c"MIX_OS_CONCURRENCY_LOCK", ~c"false"}] + ] + + clients = + Enum.map(1..count//1, fn index -> + if Mix.debug?() do + IO.puts("-> Starting mix deps.parallel ##{index}") + end + + port = Port.open({:spawn_executable, String.to_charlist(elixir)}, options) + + case :gen_tcp.accept(socket, 15000) do + {:ok, client} -> + %{port: port, index: index, socket: client} + + error -> + raise """ + could not start parallel dependency compiler, no connection made to TCP port: #{inspect(error)} + + The spawned operating system process wrote the following output: + #{collect_data(port, "")} + """ + end + end) + + send_deps_and_server_loop(clients, [], deps, []) + end + + defp send_deps_and_server_loop(available, busy, deps, completed) do + {available, busy, deps} = send_deps(available, busy, deps, completed) + server_loop(available, busy, deps, completed) + end + + defp send_deps([client | available], busy, deps, completed) do + case pop_with(deps, fn dep -> Enum.all?(dep.deps, &Keyword.has_key?(completed, &1.app)) end) do + :error -> + {[client | available], busy, deps} + + {dep, deps} -> + if Mix.debug?() do + Mix.shell().info("-- Sending #{dep.app} to mix deps.parallel #{client.index}") + end + + :gen_tcp.send(client.socket, "#{dep.app}\n") + send_deps(available, [client | busy], deps, completed) + end + end + + defp send_deps([], busy, deps, _completed) do + {[], busy, deps} + end + + defp server_loop(available, _busy = [], _deps = [], completed) do + shutdown_clients(available) + Enum.any?(completed, &(elem(&1, 1) == true)) + end + + defp server_loop(available, busy, deps, completed) do + receive do + {:tcp, socket, data} -> + [app, status] = data |> String.trim() |> String.split(":") |> Enum.map(&String.to_atom/1) + deps = Enum.reject(deps, &(&1.app == app)) + {client, busy} = pop_with(busy, &(&1.socket == socket)) + + if Mix.debug?() do + Mix.shell().info("-- mix deps.parallel #{client.index} compiled #{app}") + end + + send_deps_and_server_loop([client | available], busy, deps, [{app, status} | completed]) + + {:tcp_closed, socket} -> + shutdown_clients(available ++ busy) + raise "socket #{inspect(socket)} closed unexpectedly" + + {:tcp_error, socket, error} -> + shutdown_clients(available ++ busy) + raise "socket #{inspect(socket)} errored: #{inspect(error)}" + + {port, {:data, {eol, data}}} -> + with %{index: index} <- + Enum.find(busy, &(&1.port == port)) || Enum.find(available, &(&1.port == port)) do + terminator = if eol == :eol, do: "\n", else: "" + IO.write([Integer.to_string(index), "> ", data, terminator]) + end + + server_loop(available, busy, deps, completed) + end + end + + defp pop_with(list, fun) do + case Enum.split_while(list, &(not fun.(&1))) do + {_, []} -> :error + {pre, [result | post]} -> {result, pre ++ post} + end + end + + defp shutdown_clients(clients) do + Enum.each(clients, fn %{socket: socket, port: port, index: index} -> + if Mix.debug?() do + IO.puts("-> Closing mix deps.parallel ##{index}") + end + + _ = :gen_tcp.close(socket) + IO.write(collect_data(port, "#{index}> ")) + end) + end + + defp collect_data(port, prefix) do + receive do + {^port, {:data, {:eol, data}}} -> [prefix, data, ?\n | collect_data(port, prefix)] + {^port, {:data, {:noeol, data}}} -> [data | collect_data(port, prefix)] + after + 0 -> [] + end + end + + ## Client + + @switches [port: :integer, host: :string, force: :boolean] + + @impl true + def run(args) do + # If stdin closes, we shutdown the VM + spawn(fn -> + _ = IO.gets("") + System.halt(0) + end) + + {opts, []} = OptionParser.parse!(args, strict: @switches) + host = Keyword.fetch!(opts, :host) + port = Keyword.fetch!(opts, :port) + force? = Keyword.get(opts, :force, false) + + {:ok, socket} = + :gen_tcp.connect(String.to_charlist(host), port, [:binary, packet: :line, active: false]) + + deps = Mix.Dep.load_and_cache() + client_loop(socket, deps, force?, Mix.Project.deps_config()) + end + + def client_loop(socket, deps, force?, config) do + case :gen_tcp.recv(socket, 0, :infinity) do + {:ok, app} -> + app = app |> String.trim() |> String.to_atom() + + dep = + Enum.find(deps, &(&1.app == app)) || raise "could not find dependency #{inspect(app)}" + + compiled? = Mix.Tasks.Deps.Compile.compile_single(dep, force?, config) + :ok = :gen_tcp.send(socket, "#{app}:#{compiled?}\n") + client_loop(socket, deps, force?, config) + + {:error, :closed} -> + :ok + end + end +end From dd8263aecb1a8c1757b0fb534b38898bedb8da5a Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Tue, 18 Mar 2025 14:20:14 +0100 Subject: [PATCH 02/18] Close resources --- lib/mix/lib/mix/tasks/deps.parallel.ex | 32 ++++++++++++++++++-------- 1 file changed, 23 insertions(+), 9 deletions(-) diff --git a/lib/mix/lib/mix/tasks/deps.parallel.ex b/lib/mix/lib/mix/tasks/deps.parallel.ex index 38cb8710b6f..734e2f95694 100644 --- a/lib/mix/lib/mix/tasks/deps.parallel.ex +++ b/lib/mix/lib/mix/tasks/deps.parallel.ex @@ -5,11 +5,20 @@ defmodule Mix.Tasks.Deps.Parallel do ## Server def server(deps, count, force?) do + {:ok, socket} = :gen_tcp.listen(0, [:binary, packet: :line, active: true, reuseaddr: true]) + + try do + server(socket, deps, count, force?) + after + :gen_tcp.close(socket) + end + end + + defp server(socket, deps, count, force?) do elixir = System.find_executable("elixir") || raise "cannot find elixir executable for parallel compilation" - {:ok, socket} = :gen_tcp.listen(0, [:binary, packet: :line, active: true, reuseaddr: true]) {:ok, {ip, port}} = :inet.sockname(socket) ansi_flag = if IO.ANSI.enabled?(), do: ~c"--color", else: ~c"--no-color" force_flag = if force?, do: ~c"--force", else: ~c"--no-force" @@ -53,7 +62,7 @@ defmodule Mix.Tasks.Deps.Parallel do could not start parallel dependency compiler, no connection made to TCP port: #{inspect(error)} The spawned operating system process wrote the following output: - #{collect_data(port, "")} + #{close_port(port, "")} """ end end) @@ -105,11 +114,14 @@ defmodule Mix.Tasks.Deps.Parallel do {:tcp_closed, socket} -> shutdown_clients(available ++ busy) - raise "socket #{inspect(socket)} closed unexpectedly" + Mix.shell().error("ERROR! mix deps.parallel #{inspect(socket)} closed unexpectedly") {:tcp_error, socket, error} -> shutdown_clients(available ++ busy) - raise "socket #{inspect(socket)} errored: #{inspect(error)}" + + Mix.shell().error( + "ERROR! mix deps.parallel #{inspect(socket)} errored: #{inspect(error)}" + ) {port, {:data, {eol, data}}} -> with %{index: index} <- @@ -136,16 +148,18 @@ defmodule Mix.Tasks.Deps.Parallel do end _ = :gen_tcp.close(socket) - IO.write(collect_data(port, "#{index}> ")) + IO.write(close_port(port, "#{index}> ")) end) end - defp collect_data(port, prefix) do + defp close_port(port, prefix) do receive do - {^port, {:data, {:eol, data}}} -> [prefix, data, ?\n | collect_data(port, prefix)] - {^port, {:data, {:noeol, data}}} -> [data | collect_data(port, prefix)] + {^port, {:data, {:eol, data}}} -> [prefix, data, ?\n | close_port(port, prefix)] + {^port, {:data, {:noeol, data}}} -> [data | close_port(port, prefix)] after - 0 -> [] + 0 -> + Port.close(port) + [] end end From e3fa67a194e8a3197b9224c3f0f4447fd1088716 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Tue, 18 Mar 2025 14:23:34 +0100 Subject: [PATCH 03/18] Add license --- lib/mix/lib/mix/tasks/deps.parallel.ex | 3 +++ 1 file changed, 3 insertions(+) diff --git a/lib/mix/lib/mix/tasks/deps.parallel.ex b/lib/mix/lib/mix/tasks/deps.parallel.ex index 734e2f95694..fc723d90782 100644 --- a/lib/mix/lib/mix/tasks/deps.parallel.ex +++ b/lib/mix/lib/mix/tasks/deps.parallel.ex @@ -1,3 +1,6 @@ +# SPDX-License-Identifier: Apache-2.0 +# SPDX-FileCopyrightText: 2021 The Elixir Team + defmodule Mix.Tasks.Deps.Parallel do @moduledoc false use Mix.Task From 9708e775875346f4d338a4e0089e4b7890d03e2a Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Tue, 18 Mar 2025 17:46:10 +0100 Subject: [PATCH 04/18] Rename env var --- lib/mix/lib/mix/tasks/deps.compile.ex | 6 +++--- lib/mix/lib/mix/tasks/deps.parallel.ex | 20 ++++++++++---------- 2 files changed, 13 insertions(+), 13 deletions(-) diff --git a/lib/mix/lib/mix/tasks/deps.compile.ex b/lib/mix/lib/mix/tasks/deps.compile.ex index 1760fa4ff9c..416f35bb4d3 100644 --- a/lib/mix/lib/mix/tasks/deps.compile.ex +++ b/lib/mix/lib/mix/tasks/deps.compile.ex @@ -83,12 +83,12 @@ defmodule Mix.Tasks.Deps.Compile do |> reject_umbrella_children(options) |> reject_local_deps(options) - count = System.get_env("MIX_DEPS_COMPILE_PARALLEL_COUNT", "0") |> String.to_integer() + count = System.get_env("MIX_OS_DEPS_COMPILE_PARTITION_COUNT", "0") |> String.to_integer() compiled? = if count > 1 and length(deps) > count do - Mix.shell().info("mix deps.compile running in parallel with count=#{count}") - Mix.Tasks.Deps.Parallel.server(deps, count, force?) + Mix.shell().info("mix deps.compile running across #{count} OS processes") + Mix.Tasks.Deps.Partition.server(deps, count, force?) else config = Mix.Project.deps_config() true in Enum.map(deps, &compile_single(&1, force?, config)) diff --git a/lib/mix/lib/mix/tasks/deps.parallel.ex b/lib/mix/lib/mix/tasks/deps.parallel.ex index fc723d90782..c513ce1d731 100644 --- a/lib/mix/lib/mix/tasks/deps.parallel.ex +++ b/lib/mix/lib/mix/tasks/deps.parallel.ex @@ -1,7 +1,7 @@ # SPDX-License-Identifier: Apache-2.0 # SPDX-FileCopyrightText: 2021 The Elixir Team -defmodule Mix.Tasks.Deps.Parallel do +defmodule Mix.Tasks.Deps.Partition do @moduledoc false use Mix.Task @@ -20,7 +20,7 @@ defmodule Mix.Tasks.Deps.Parallel do defp server(socket, deps, count, force?) do elixir = System.find_executable("elixir") || - raise "cannot find elixir executable for parallel compilation" + raise "cannot find elixir executable for partition compilation" {:ok, {ip, port}} = :inet.sockname(socket) ansi_flag = if IO.ANSI.enabled?(), do: ~c"--color", else: ~c"--no-color" @@ -30,7 +30,7 @@ defmodule Mix.Tasks.Deps.Parallel do ansi_flag, ~c"-e", ~c"Mix.CLI.main()", - ~c"deps.parallel", + ~c"deps.partition", force_flag, ~c"--port", Integer.to_charlist(port), @@ -51,7 +51,7 @@ defmodule Mix.Tasks.Deps.Parallel do clients = Enum.map(1..count//1, fn index -> if Mix.debug?() do - IO.puts("-> Starting mix deps.parallel ##{index}") + IO.puts("-> Starting mix deps.partition ##{index}") end port = Port.open({:spawn_executable, String.to_charlist(elixir)}, options) @@ -62,7 +62,7 @@ defmodule Mix.Tasks.Deps.Parallel do error -> raise """ - could not start parallel dependency compiler, no connection made to TCP port: #{inspect(error)} + could not start partition dependency compiler, no connection made to TCP port: #{inspect(error)} The spawned operating system process wrote the following output: #{close_port(port, "")} @@ -85,7 +85,7 @@ defmodule Mix.Tasks.Deps.Parallel do {dep, deps} -> if Mix.debug?() do - Mix.shell().info("-- Sending #{dep.app} to mix deps.parallel #{client.index}") + Mix.shell().info("-- Sending #{dep.app} to mix deps.partition #{client.index}") end :gen_tcp.send(client.socket, "#{dep.app}\n") @@ -110,20 +110,20 @@ defmodule Mix.Tasks.Deps.Parallel do {client, busy} = pop_with(busy, &(&1.socket == socket)) if Mix.debug?() do - Mix.shell().info("-- mix deps.parallel #{client.index} compiled #{app}") + Mix.shell().info("-- mix deps.partition #{client.index} compiled #{app}") end send_deps_and_server_loop([client | available], busy, deps, [{app, status} | completed]) {:tcp_closed, socket} -> shutdown_clients(available ++ busy) - Mix.shell().error("ERROR! mix deps.parallel #{inspect(socket)} closed unexpectedly") + Mix.shell().error("ERROR! mix deps.partition #{inspect(socket)} closed unexpectedly") {:tcp_error, socket, error} -> shutdown_clients(available ++ busy) Mix.shell().error( - "ERROR! mix deps.parallel #{inspect(socket)} errored: #{inspect(error)}" + "ERROR! mix deps.partition #{inspect(socket)} errored: #{inspect(error)}" ) {port, {:data, {eol, data}}} -> @@ -147,7 +147,7 @@ defmodule Mix.Tasks.Deps.Parallel do defp shutdown_clients(clients) do Enum.each(clients, fn %{socket: socket, port: port, index: index} -> if Mix.debug?() do - IO.puts("-> Closing mix deps.parallel ##{index}") + IO.puts("-> Closing mix deps.partition ##{index}") end _ = :gen_tcp.close(socket) From 91e94ce5512b2c4ba1e64c914377f9af31ad5ce5 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Tue, 18 Mar 2025 23:16:43 +0100 Subject: [PATCH 05/18] Rename file --- .../{deps.parallel.ex => deps.partition.ex} | 19 ++++++++++--------- 1 file changed, 10 insertions(+), 9 deletions(-) rename lib/mix/lib/mix/tasks/{deps.parallel.ex => deps.partition.ex} (93%) diff --git a/lib/mix/lib/mix/tasks/deps.parallel.ex b/lib/mix/lib/mix/tasks/deps.partition.ex similarity index 93% rename from lib/mix/lib/mix/tasks/deps.parallel.ex rename to lib/mix/lib/mix/tasks/deps.partition.ex index c513ce1d731..5b042c6747c 100644 --- a/lib/mix/lib/mix/tasks/deps.parallel.ex +++ b/lib/mix/lib/mix/tasks/deps.partition.ex @@ -61,12 +61,12 @@ defmodule Mix.Tasks.Deps.Partition do %{port: port, index: index, socket: client} error -> - raise """ + Mix.raise(""" could not start partition dependency compiler, no connection made to TCP port: #{inspect(error)} The spawned operating system process wrote the following output: #{close_port(port, "")} - """ + """) end end) @@ -117,14 +117,11 @@ defmodule Mix.Tasks.Deps.Partition do {:tcp_closed, socket} -> shutdown_clients(available ++ busy) - Mix.shell().error("ERROR! mix deps.partition #{inspect(socket)} closed unexpectedly") + Mix.raise("ERROR! mix deps.partition #{inspect(socket)} closed unexpectedly") {:tcp_error, socket, error} -> shutdown_clients(available ++ busy) - - Mix.shell().error( - "ERROR! mix deps.partition #{inspect(socket)} errored: #{inspect(error)}" - ) + Mix.raise("ERROR! mix deps.partition #{inspect(socket)} errored: #{inspect(error)}") {port, {:data, {eol, data}}} -> with %{index: index} <- @@ -186,8 +183,12 @@ defmodule Mix.Tasks.Deps.Partition do {:ok, socket} = :gen_tcp.connect(String.to_charlist(host), port, [:binary, packet: :line, active: false]) - deps = Mix.Dep.load_and_cache() - client_loop(socket, deps, force?, Mix.Project.deps_config()) + try do + deps = Mix.Dep.load_and_cache() + client_loop(socket, deps, force?, Mix.Project.deps_config()) + after + :gen_tcp.close(socket) + end end def client_loop(socket, deps, force?, config) do From 6c3f308c7a72d83c9041f1eeaa2963a36000e1ab Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Tue, 18 Mar 2025 23:32:39 +0100 Subject: [PATCH 06/18] Only wait for dependency if it is in list --- lib/mix/lib/mix/tasks/deps.partition.ex | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/lib/mix/lib/mix/tasks/deps.partition.ex b/lib/mix/lib/mix/tasks/deps.partition.ex index 5b042c6747c..70329040dc8 100644 --- a/lib/mix/lib/mix/tasks/deps.partition.ex +++ b/lib/mix/lib/mix/tasks/deps.partition.ex @@ -79,7 +79,7 @@ defmodule Mix.Tasks.Deps.Partition do end defp send_deps([client | available], busy, deps, completed) do - case pop_with(deps, fn dep -> Enum.all?(dep.deps, &Keyword.has_key?(completed, &1.app)) end) do + case pop_with(deps, fn dep -> Enum.all?(dep.deps, ¬_pending?(&1.app, deps, completed)) end) do :error -> {[client | available], busy, deps} @@ -97,6 +97,10 @@ defmodule Mix.Tasks.Deps.Partition do {[], busy, deps} end + defp not_pending?(app, deps, completed) do + Keyword.has_key?(completed, app) or not Enum.any?(deps, &(&1.app == app)) + end + defp server_loop(available, _busy = [], _deps = [], completed) do shutdown_clients(available) Enum.any?(completed, &(elem(&1, 1) == true)) From 0d7b673fab1bb249a240e1a118fde60b33f812e6 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Wed, 19 Mar 2025 09:08:43 +0100 Subject: [PATCH 07/18] Address race condition --- lib/mix/lib/mix/tasks/deps.partition.ex | 38 +++++++++++++------------ 1 file changed, 20 insertions(+), 18 deletions(-) diff --git a/lib/mix/lib/mix/tasks/deps.partition.ex b/lib/mix/lib/mix/tasks/deps.partition.ex index 70329040dc8..a52a026c92e 100644 --- a/lib/mix/lib/mix/tasks/deps.partition.ex +++ b/lib/mix/lib/mix/tasks/deps.partition.ex @@ -70,16 +70,19 @@ defmodule Mix.Tasks.Deps.Partition do end end) - send_deps_and_server_loop(clients, [], deps, []) + status = Map.new(deps, &{&1.app, :pending}) + send_deps_and_server_loop(clients, [], deps, status) end - defp send_deps_and_server_loop(available, busy, deps, completed) do - {available, busy, deps} = send_deps(available, busy, deps, completed) - server_loop(available, busy, deps, completed) + defp send_deps_and_server_loop(available, busy, deps, status) do + {available, busy, deps} = send_deps(available, busy, deps, status) + server_loop(available, busy, deps, status) end - defp send_deps([client | available], busy, deps, completed) do - case pop_with(deps, fn dep -> Enum.all?(dep.deps, ¬_pending?(&1.app, deps, completed)) end) do + defp send_deps([client | available], busy, deps, status) do + case pop_with(deps, fn dep -> + Enum.all?(dep.deps, &(Map.get(status, &1.app, :unknown) != :pending)) + end) do :error -> {[client | available], busy, deps} @@ -89,35 +92,34 @@ defmodule Mix.Tasks.Deps.Partition do end :gen_tcp.send(client.socket, "#{dep.app}\n") - send_deps(available, [client | busy], deps, completed) + send_deps(available, [client | busy], deps, status) end end - defp send_deps([], busy, deps, _completed) do + defp send_deps([], busy, deps, _status) do {[], busy, deps} end - defp not_pending?(app, deps, completed) do - Keyword.has_key?(completed, app) or not Enum.any?(deps, &(&1.app == app)) - end - - defp server_loop(available, _busy = [], _deps = [], completed) do + defp server_loop(available, _busy = [], _deps = [], status) do shutdown_clients(available) - Enum.any?(completed, &(elem(&1, 1) == true)) + Enum.any?(status, &(elem(&1, 1) == true)) end - defp server_loop(available, busy, deps, completed) do + defp server_loop(available, busy, deps, status) do receive do {:tcp, socket, data} -> - [app, status] = data |> String.trim() |> String.split(":") |> Enum.map(&String.to_atom/1) + [app, compiled?] = + data |> String.trim() |> String.split(":") |> Enum.map(&String.to_atom/1) + deps = Enum.reject(deps, &(&1.app == app)) + status = Map.replace!(status, app, compiled?) {client, busy} = pop_with(busy, &(&1.socket == socket)) if Mix.debug?() do Mix.shell().info("-- mix deps.partition #{client.index} compiled #{app}") end - send_deps_and_server_loop([client | available], busy, deps, [{app, status} | completed]) + send_deps_and_server_loop([client | available], busy, deps, status) {:tcp_closed, socket} -> shutdown_clients(available ++ busy) @@ -134,7 +136,7 @@ defmodule Mix.Tasks.Deps.Partition do IO.write([Integer.to_string(index), "> ", data, terminator]) end - server_loop(available, busy, deps, completed) + server_loop(available, busy, deps, status) end end From a616cc414ff624a08a4a1bc223409e73f0b4869e Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Wed, 19 Mar 2025 11:24:11 +0100 Subject: [PATCH 08/18] Docs --- lib/mix/lib/mix/tasks/deps.compile.ex | 21 +++++++++++++++++++-- 1 file changed, 19 insertions(+), 2 deletions(-) diff --git a/lib/mix/lib/mix/tasks/deps.compile.ex b/lib/mix/lib/mix/tasks/deps.compile.ex index 416f35bb4d3..541fc922595 100644 --- a/lib/mix/lib/mix/tasks/deps.compile.ex +++ b/lib/mix/lib/mix/tasks/deps.compile.ex @@ -35,6 +35,24 @@ defmodule Mix.Tasks.Deps.Compile do recompiled without propagating those changes upstream. To ensure `b` is included in the compilation step, pass `--include-children`. + ## Compiling dependencies across multiple OSes processes + + If you set the environment variable `MIX_OS_DEPS_COMPILE_PARTITION_COUNT` + to a number greater than 1, Mix will start multiple operating system + processes to compile your dependencies concurrently. + + While Mix and Rebar will compile all files in a given project in parallel, + enabling this environment variable can still yield useful gains in several + cases, such as when compiling dependencies with native code, dependencies + that must download assets, or dependencies where the compilation time is not + evenly distributed (for example, one file takes much longer to compile than + all others). + + While most configuration in Mix is done via command line flags, this particular + environment variable exists because the best number will vary per machine + (and often per project too). The environment variable also makes it more accessible + to enable concurrent compilation in CI and also during `Mix.install/2` commands. + ## Command line options * `--force` - force compilation of deps @@ -57,7 +75,6 @@ defmodule Mix.Tasks.Deps.Compile do end Mix.Project.get!() - config = Mix.Project.config() Mix.Project.with_build_lock(config, fn -> @@ -86,7 +103,7 @@ defmodule Mix.Tasks.Deps.Compile do count = System.get_env("MIX_OS_DEPS_COMPILE_PARTITION_COUNT", "0") |> String.to_integer() compiled? = - if count > 1 and length(deps) > count do + if count > 1 and length(deps) > 1 do Mix.shell().info("mix deps.compile running across #{count} OS processes") Mix.Tasks.Deps.Partition.server(deps, count, force?) else From 24e3c2e7f07542b25030c3485c2ee8fc5d31ab47 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Wed, 19 Mar 2025 11:34:15 +0100 Subject: [PATCH 09/18] Add support for Mix.install/2 in deps.partition --- lib/mix/lib/mix.ex | 20 ++++++----- lib/mix/lib/mix/tasks/deps.partition.ex | 40 +++++++++++++++++++--- lib/mix/lib/mix/tasks/loadconfig.ex | 6 ++-- lib/mix/test/mix/tasks/loadconfig_test.exs | 5 +++ 4 files changed, 55 insertions(+), 16 deletions(-) diff --git a/lib/mix/lib/mix.ex b/lib/mix/lib/mix.ex index 55efee375a9..24dbe5627ba 100644 --- a/lib/mix/lib/mix.ex +++ b/lib/mix/lib/mix.ex @@ -420,7 +420,7 @@ defmodule Mix do """ - @mix_install_project __MODULE__.InstallProject + @mix_install_project Mix.InstallProject @mix_install_app :mix_install @mix_install_app_string Atom.to_string(@mix_install_app) @@ -905,9 +905,7 @@ defmodule Mix do case Mix.State.get(:installed) do nil -> - Application.put_all_env(config, persistent: true) System.put_env(system_env) - install_project_dir = install_project_dir(id) if Keyword.fetch!(opts, :verbose) do @@ -924,10 +922,14 @@ defmodule Mix do config_path: config_path ] - config = install_project_config(dynamic_config) + :ok = + Mix.ProjectStack.push( + @mix_install_project, + [compile_config: config] ++ install_project_config(dynamic_config), + "nofile" + ) started_apps = Application.started_applications() - :ok = Mix.ProjectStack.push(@mix_install_project, config, "nofile") build_dir = Path.join(install_project_dir, "_build") external_lockfile = expand_path(opts[:lockfile], deps, :lockfile, "mix.lock") @@ -944,9 +946,9 @@ defmodule Mix do File.mkdir_p!(install_project_dir) File.cd!(install_project_dir, fn -> - if config_path do - Mix.Task.rerun("loadconfig") - end + # This steps need to be mirror in mix deps.partition + Application.put_all_env(config, persistent: true) + Mix.Task.rerun("loadconfig") cond do external_lockfile -> @@ -1079,7 +1081,7 @@ defmodule Mix do defp install_project_config(dynamic_config) do [ - version: "0.1.0", + version: "1.0.0", build_per_environment: true, build_path: "_build", lockfile: "mix.lock", diff --git a/lib/mix/lib/mix/tasks/deps.partition.ex b/lib/mix/lib/mix/tasks/deps.partition.ex index a52a026c92e..e41528c1f69 100644 --- a/lib/mix/lib/mix/tasks/deps.partition.ex +++ b/lib/mix/lib/mix/tasks/deps.partition.ex @@ -7,6 +7,8 @@ defmodule Mix.Tasks.Deps.Partition do ## Server + @deps_partition_install_mix_exs ~c"deps.partition.mix.exs" + def server(deps, count, force?) do {:ok, socket} = :gen_tcp.listen(0, [:binary, packet: :line, active: true, reuseaddr: true]) @@ -26,6 +28,31 @@ defmodule Mix.Tasks.Deps.Partition do ansi_flag = if IO.ANSI.enabled?(), do: ~c"--color", else: ~c"--no-color" force_flag = if force?, do: ~c"--force", else: ~c"--no-force" + env_vars = + if Mix.install?() do + blob = + Mix.Project.config() + |> :erlang.term_to_binary() + |> :binary.bin_to_list() + |> Enum.join(",") + + # We replicate the initialization logic from Mix.install/2 as part of mix.exs + File.write!(@deps_partition_install_mix_exs, """ + config = <<#{blob}>> + project = :erlang.binary_to_term(config) + + if compile_config = project[:compile_config] do + Application.put_all_env(compile_config, persistent: true) + end + + Mix.ProjectStack.push(Mix.InstallProject, project, "nofile") + """) + + [{~c"MIX_EXS", @deps_partition_install_mix_exs}] + else + [] + end + args = [ ansi_flag, ~c"-e", @@ -45,7 +72,7 @@ defmodule Mix.Tasks.Deps.Partition do :stderr_to_stdout, line: 1_000_000, args: args, - env: [{~c"MIX_OS_CONCURRENCY_LOCK", ~c"false"}] + env: [{~c"MIX_OS_CONCURRENCY_LOCK", ~c"false"} | env_vars] ] clients = @@ -123,11 +150,11 @@ defmodule Mix.Tasks.Deps.Partition do {:tcp_closed, socket} -> shutdown_clients(available ++ busy) - Mix.raise("ERROR! mix deps.partition #{inspect(socket)} closed unexpectedly") + Mix.raise("mix deps.partition #{inspect(socket)} closed unexpectedly") {:tcp_error, socket, error} -> shutdown_clients(available ++ busy) - Mix.raise("ERROR! mix deps.partition #{inspect(socket)} errored: #{inspect(error)}") + Mix.raise("mix deps.partition #{inspect(socket)} errored: #{inspect(error)}") {port, {:data, {eol, data}}} -> with %{index: index} <- @@ -164,7 +191,12 @@ defmodule Mix.Tasks.Deps.Partition do {^port, {:data, {:noeol, data}}} -> [data | close_port(port, prefix)] after 0 -> - Port.close(port) + try do + Port.close(port) + catch + _, _ -> :ok + end + [] end end diff --git a/lib/mix/lib/mix/tasks/loadconfig.ex b/lib/mix/lib/mix/tasks/loadconfig.ex index 61e058e5a10..22dff3606c2 100644 --- a/lib/mix/lib/mix/tasks/loadconfig.ex +++ b/lib/mix/lib/mix/tasks/loadconfig.ex @@ -40,10 +40,10 @@ defmodule Mix.Tasks.Loadconfig do end defp load_default do - config = Mix.Project.config() + config_path = Mix.Project.config()[:config_path] - if File.regular?(config[:config_path]) or config[:config_path] != "config/config.exs" do - load_compile(config[:config_path]) + if config_path != nil and (File.regular?(config_path) or config_path != "config/config.exs") do + load_compile(config_path) else [] end diff --git a/lib/mix/test/mix/tasks/loadconfig_test.exs b/lib/mix/test/mix/tasks/loadconfig_test.exs index 1b78e23190e..715bfc62238 100644 --- a/lib/mix/test/mix/tasks/loadconfig_test.exs +++ b/lib/mix/test/mix/tasks/loadconfig_test.exs @@ -67,6 +67,11 @@ defmodule Mix.Tasks.LoadconfigTest do end) end + test "is a no-op with nil custom config_path" do + Mix.ProjectStack.post_config(config_path: nil) + assert Mix.Task.run("loadconfig", []) == [] + end + test "updates config files and config mtime", context do in_tmp(context.test, fn -> Mix.Project.push(MixTest.Case.Sample) From 8cedb9317465e9358b63785a5150ddeb66f231bb Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Wed, 19 Mar 2025 11:48:44 +0100 Subject: [PATCH 10/18] More docs --- lib/mix/lib/mix.ex | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/lib/mix/lib/mix.ex b/lib/mix/lib/mix.ex index 24dbe5627ba..46785e60220 100644 --- a/lib/mix/lib/mix.ex +++ b/lib/mix/lib/mix.ex @@ -359,7 +359,11 @@ defmodule Mix do * `MIX_OS_CONCURRENCY_LOCK` - when set to `0` or `false`, disables mix compilation locking. While not recommended, this may be necessary in cases where hard links or TCP sockets are not available. When opting for this behaviour, make sure to not start concurrent compilations - of the same project. + of the same project + + * `MIX_OS_DEPS_COMPILE_PARTITION_COUNT` - when set to a number greater than 1, it enables + compilation of dependencies over multiple operating system processes. See `mix help deps.compile` + for more information * `MIX_PATH` - appends extra code paths From 60163282c9d98adc582c14aa17e4b709a1ba7ad7 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Wed, 19 Mar 2025 16:38:26 +0100 Subject: [PATCH 11/18] Boot partitions in parallel --- lib/mix/lib/mix/tasks/deps.partition.ex | 34 +++++++++++++++++-------- 1 file changed, 23 insertions(+), 11 deletions(-) diff --git a/lib/mix/lib/mix/tasks/deps.partition.ex b/lib/mix/lib/mix/tasks/deps.partition.ex index e41528c1f69..fa6589d802b 100644 --- a/lib/mix/lib/mix/tasks/deps.partition.ex +++ b/lib/mix/lib/mix/tasks/deps.partition.ex @@ -10,7 +10,7 @@ defmodule Mix.Tasks.Deps.Partition do @deps_partition_install_mix_exs ~c"deps.partition.mix.exs" def server(deps, count, force?) do - {:ok, socket} = :gen_tcp.listen(0, [:binary, packet: :line, active: true, reuseaddr: true]) + {:ok, socket} = :gen_tcp.listen(0, [:binary, packet: :line, active: false]) try do server(socket, deps, count, force?) @@ -71,28 +71,37 @@ defmodule Mix.Tasks.Deps.Partition do :use_stdio, :stderr_to_stdout, line: 1_000_000, - args: args, env: [{~c"MIX_OS_CONCURRENCY_LOCK", ~c"false"} | env_vars] ] - clients = - Enum.map(1..count//1, fn index -> + ports = + Map.new(1..count//1, fn index -> if Mix.debug?() do IO.puts("-> Starting mix deps.partition ##{index}") end - port = Port.open({:spawn_executable, String.to_charlist(elixir)}, options) + args = args ++ [~c"--index", Integer.to_charlist(index)] + port = Port.open({:spawn_executable, String.to_charlist(elixir)}, [args: args] ++ options) - case :gen_tcp.accept(socket, 15000) do - {:ok, client} -> - %{port: port, index: index, socket: client} + {index, port} + end) + clients = + Enum.map(1..count//1, fn _ -> + with {:ok, client} <- :gen_tcp.accept(socket, 15000), + {:ok, message} <- :gen_tcp.recv(socket, 0, 15000) do + :inet.setopts(client, active: true) + index = message |> String.trim() |> String.to_integer() + %{port: Map.fetch!(ports, index), index: index, socket: client} + else error -> + logs = + Enum.map_join(ports, "\n", fn {index, port} -> close_port(port, "#{index} >") end) + Mix.raise(""" could not start partition dependency compiler, no connection made to TCP port: #{inspect(error)} - The spawned operating system process wrote the following output: - #{close_port(port, "")} + #{logs} """) end end) @@ -203,7 +212,7 @@ defmodule Mix.Tasks.Deps.Partition do ## Client - @switches [port: :integer, host: :string, force: :boolean] + @switches [port: :integer, host: :string, force: :boolean, index: :string] @impl true def run(args) do @@ -216,11 +225,14 @@ defmodule Mix.Tasks.Deps.Partition do {opts, []} = OptionParser.parse!(args, strict: @switches) host = Keyword.fetch!(opts, :host) port = Keyword.fetch!(opts, :port) + index = Keyword.fetch!(opts, :index) force? = Keyword.get(opts, :force, false) {:ok, socket} = :gen_tcp.connect(String.to_charlist(host), port, [:binary, packet: :line, active: false]) + :gen_tcp.send(socket, "#{index}\n") + try do deps = Mix.Dep.load_and_cache() client_loop(socket, deps, force?, Mix.Project.deps_config()) From e3b5d9063955699028ab82c89783c6d4903c320f Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Wed, 19 Mar 2025 17:32:27 +0100 Subject: [PATCH 12/18] Fix client/socket --- lib/mix/lib/mix/tasks/deps.partition.ex | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/mix/lib/mix/tasks/deps.partition.ex b/lib/mix/lib/mix/tasks/deps.partition.ex index fa6589d802b..ecaa0d8cd36 100644 --- a/lib/mix/lib/mix/tasks/deps.partition.ex +++ b/lib/mix/lib/mix/tasks/deps.partition.ex @@ -89,7 +89,7 @@ defmodule Mix.Tasks.Deps.Partition do clients = Enum.map(1..count//1, fn _ -> with {:ok, client} <- :gen_tcp.accept(socket, 15000), - {:ok, message} <- :gen_tcp.recv(socket, 0, 15000) do + {:ok, message} <- :gen_tcp.recv(client, 0, 15000) do :inet.setopts(client, active: true) index = message |> String.trim() |> String.to_integer() %{port: Map.fetch!(ports, index), index: index, socket: client} From 284fa5df768184148d5138568220bb6e95132ad2 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Wed, 19 Mar 2025 22:18:52 +0100 Subject: [PATCH 13/18] Apply suggestions from code review Co-authored-by: felipe stival <14948182+v0idpwn@users.noreply.github.com> --- lib/mix/lib/mix/tasks/deps.compile.ex | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/lib/mix/lib/mix/tasks/deps.compile.ex b/lib/mix/lib/mix/tasks/deps.compile.ex index 541fc922595..962b7be9f3f 100644 --- a/lib/mix/lib/mix/tasks/deps.compile.ex +++ b/lib/mix/lib/mix/tasks/deps.compile.ex @@ -35,13 +35,13 @@ defmodule Mix.Tasks.Deps.Compile do recompiled without propagating those changes upstream. To ensure `b` is included in the compilation step, pass `--include-children`. - ## Compiling dependencies across multiple OSes processes + ## Compiling dependencies across multiple OS processes If you set the environment variable `MIX_OS_DEPS_COMPILE_PARTITION_COUNT` to a number greater than 1, Mix will start multiple operating system processes to compile your dependencies concurrently. - While Mix and Rebar will compile all files in a given project in parallel, + While Mix and Rebar compile all files within a given project in parallel, enabling this environment variable can still yield useful gains in several cases, such as when compiling dependencies with native code, dependencies that must download assets, or dependencies where the compilation time is not From 8216f0e5df70c8e275b14184c54be1b0f4f084ab Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Mon, 24 Mar 2025 13:47:13 +0100 Subject: [PATCH 14/18] Tests --- lib/mix/lib/mix/tasks/deps.loadpaths.ex | 11 +----- lib/mix/test/fixtures/umbrella_dep/mix.exs | 1 + lib/mix/test/mix/tasks/deps_test.exs | 40 +++++++++++++++++++--- lib/mix/test/mix/umbrella_test.exs | 21 ++++++++++-- lib/mix/test/test_helper.exs | 15 ++++---- 5 files changed, 63 insertions(+), 25 deletions(-) diff --git a/lib/mix/lib/mix/tasks/deps.loadpaths.ex b/lib/mix/lib/mix/tasks/deps.loadpaths.ex index 30c6fa2d49f..ccd084e5bea 100644 --- a/lib/mix/lib/mix/tasks/deps.loadpaths.ex +++ b/lib/mix/lib/mix/tasks/deps.loadpaths.ex @@ -139,11 +139,7 @@ defmodule Mix.Tasks.Deps.Loadpaths do defp partition([dep | deps], not_ok, compile) do cond do Mix.Dep.compilable?(dep) or (Mix.Dep.ok?(dep) and local?(dep)) -> - if from_umbrella?(dep) do - partition(deps, not_ok, compile) - else - partition(deps, not_ok, [dep | compile]) - end + partition(deps, not_ok, [dep | compile]) Mix.Dep.ok?(dep) -> partition(deps, not_ok, compile) @@ -163,11 +159,6 @@ defmodule Mix.Tasks.Deps.Loadpaths do |> Mix.Dep.filter_by_name(Mix.Dep.load_and_cache()) end - # Those are compiled by umbrella. - defp from_umbrella?(dep) do - dep.opts[:from_umbrella] - end - # Every local dependency (i.e. that are not fetchable) # are automatically recompiled if they are ok. defp local?(dep) do diff --git a/lib/mix/test/fixtures/umbrella_dep/mix.exs b/lib/mix/test/fixtures/umbrella_dep/mix.exs index 9fefc54fdde..99b72b6c7e0 100644 --- a/lib/mix/test/fixtures/umbrella_dep/mix.exs +++ b/lib/mix/test/fixtures/umbrella_dep/mix.exs @@ -4,6 +4,7 @@ defmodule UmbrellaDep.MixProject do def project do [ app: :umbrella_dep, + version: "0.1.0", deps: deps() ] end diff --git a/lib/mix/test/mix/tasks/deps_test.exs b/lib/mix/test/mix/tasks/deps_test.exs index 7e9cf12a5e1..a1f04e386cf 100644 --- a/lib/mix/test/mix/tasks/deps_test.exs +++ b/lib/mix/test/mix/tasks/deps_test.exs @@ -61,7 +61,7 @@ defmodule Mix.Tasks.DepsTest do end end - defmodule RawRepoDep do + defmodule RawRepoDepApp do def project do [ app: :raw_sample, @@ -219,6 +219,38 @@ defmodule Mix.Tasks.DepsTest do end) end + test "compiles deps using os partitions" do + System.put_env("MIX_OS_DEPS_COMPILE_PARTITION_COUNT", "2") + + in_fixture("deps_status", fn -> + File.write!("mix.exs", """ + defmodule ParDepsApp do + use Mix.Project + + def project do + [ + app: :par_sample, + version: "0.1.0", + deps: [ + {:raw_repo, "0.1.0", path: "custom/raw_repo"}, + {:git_repo, "0.1.0", path: #{inspect(fixture_path("git_repo"))}} + ] + ] + end + end + """) + + Mix.Project.in_project(:par_sample, ".", fn _ -> + output = ExUnit.CaptureIO.capture_io(fn -> Mix.Tasks.Deps.Compile.run([]) end) + assert output =~ ~r/\d> Generated git_repo app/ + assert output =~ ~r/\d> Generated raw_repo app/ + assert_received {:mix_shell, :info, ["mix deps.compile running across 2 OS processes"]} + end) + end) + after + System.delete_env("MIX_OS_DEPS_COMPILE_PARTITION_COUNT") + end + test "doesn't compile any umbrella apps if --skip-umbrella-children is given" do in_fixture("umbrella_dep/deps/umbrella", fn -> Mix.Project.in_project(:umbrella, ".", fn _ -> @@ -414,7 +446,7 @@ defmodule Mix.Tasks.DepsTest do test "sets deps env to prod by default" do in_fixture("deps_status", fn -> - Mix.Project.push(RawRepoDep) + Mix.Project.push(RawRepoDepApp) Mix.Tasks.Deps.Update.run(["--all"]) assert_received {:mix_shell, :info, [":raw_repo env is prod"]} @@ -751,7 +783,7 @@ defmodule Mix.Tasks.DepsTest do test "checks if compile env changed" do in_fixture("deps_status", fn -> - Mix.Project.push(RawRepoDep) + Mix.Project.push(RawRepoDepApp) Mix.Tasks.Deps.Loadpaths.run([]) assert_receive {:mix_shell, :info, ["Generated raw_repo app"]} assert Application.spec(:raw_repo, :vsn) @@ -766,7 +798,7 @@ defmodule Mix.Tasks.DepsTest do Application.unload(:raw_repo) Mix.ProjectStack.pop() Mix.Task.clear() - Mix.Project.push(RawRepoDep) + Mix.Project.push(RawRepoDepApp) purge([RawRepo]) Mix.Tasks.Loadconfig.load_compile("config/config.exs") diff --git a/lib/mix/test/mix/umbrella_test.exs b/lib/mix/test/mix/umbrella_test.exs index 76ac93aec5a..37303777352 100644 --- a/lib/mix/test/mix/umbrella_test.exs +++ b/lib/mix/test/mix/umbrella_test.exs @@ -276,10 +276,27 @@ defmodule Mix.UmbrellaTest do test "compile for umbrella as dependency" do in_fixture("umbrella_dep", fn -> Mix.Project.in_project(:umbrella_dep, ".", fn _ -> - Mix.Task.run("deps.compile") + Mix.Task.run("compile") + assert Bar.bar() == "hello world" + end) + end) + end + + test "compile for umbrella as dependency with os partitions" do + System.put_env("MIX_OS_DEPS_COMPILE_PARTITION_COUNT", "2") + + in_fixture("umbrella_dep", fn -> + Mix.Project.in_project(:umbrella_dep, ".", fn _ -> + output = ExUnit.CaptureIO.capture_io(fn -> Mix.Task.run("compile") end) + assert output =~ ~r/\d> :foo env is prod/ + assert output =~ ~r/\d> :bar env is prod/ + + assert_received {:mix_shell, :info, ["mix deps.compile running across 2 OS processes"]} assert Bar.bar() == "hello world" end) end) + after + System.delete_env("MIX_OS_DEPS_COMPILE_PARTITION_COUNT") end defmodule CycleDeps do @@ -351,7 +368,7 @@ defmodule Mix.UmbrellaTest do def project do [app: :bar, version: "0.1.0", - aliases: ["compile.all": fn _ -> Mix.shell().info "no compile bar" end]] + aliases: ["compile.elixir": fn _ -> Mix.shell().info "no compile bar" end]] end end """) diff --git a/lib/mix/test/test_helper.exs b/lib/mix/test/test_helper.exs index 0d9a96addba..aaf16b55f32 100644 --- a/lib/mix/test/test_helper.exs +++ b/lib/mix/test/test_helper.exs @@ -10,9 +10,6 @@ mix = Path.expand("../tmp/.mix", __DIR__) File.mkdir_p!(mix) System.put_env("MIX_HOME", mix) -System.delete_env("XDG_DATA_HOME") -System.delete_env("XDG_CONFIG_HOME") - # Load protocols to make sure they are not unloaded during tests [Collectable, Enumerable, Inspect, String.Chars, List.Chars] |> Enum.each(& &1.__protocol__(:module)) @@ -53,12 +50,12 @@ ExUnit.start( ) # Clear environment variables that may affect tests -System.delete_env("http_proxy") -System.delete_env("https_proxy") -System.delete_env("HTTP_PROXY") -System.delete_env("HTTPS_PROXY") -System.delete_env("MIX_ENV") -System.delete_env("MIX_TARGET") +Enum.each( + ~w(http_proxy https_proxy HTTP_PROXY HTTPS_PROXY) ++ + ~w(MIX_ENV MIX_OS_DEPS_COMPILE_PARTITION_COUNT MIX_TARGET) ++ + ~w(XDG_DATA_HOME XDG_CONFIG_HOME), + &System.delete_env/1 +) defmodule MixTest.Case do use ExUnit.CaseTemplate From 4f7d0bf1ab8323271ac5149e65dac61945c4ce12 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Mon, 24 Mar 2025 14:23:56 +0100 Subject: [PATCH 15/18] Explicitly set env var --- lib/mix/lib/mix/tasks/deps.partition.ex | 3 ++- lib/mix/test/test_helper.exs | 22 ++++++++++++++-------- 2 files changed, 16 insertions(+), 9 deletions(-) diff --git a/lib/mix/lib/mix/tasks/deps.partition.ex b/lib/mix/lib/mix/tasks/deps.partition.ex index ecaa0d8cd36..6529fa68d82 100644 --- a/lib/mix/lib/mix/tasks/deps.partition.ex +++ b/lib/mix/lib/mix/tasks/deps.partition.ex @@ -21,7 +21,8 @@ defmodule Mix.Tasks.Deps.Partition do defp server(socket, deps, count, force?) do elixir = - System.find_executable("elixir") || + System.get_env("MIX_OS_DEPS_COMPILE_PARTITION_ELIXIR_EXECUTABLE") || + System.find_executable("elixir") || raise "cannot find elixir executable for partition compilation" {:ok, {ip, port}} = :inet.sockname(socket) diff --git a/lib/mix/test/test_helper.exs b/lib/mix/test/test_helper.exs index aaf16b55f32..032794f5ced 100644 --- a/lib/mix/test/test_helper.exs +++ b/lib/mix/test/test_helper.exs @@ -49,14 +49,6 @@ ExUnit.start( include: line_include ) -# Clear environment variables that may affect tests -Enum.each( - ~w(http_proxy https_proxy HTTP_PROXY HTTPS_PROXY) ++ - ~w(MIX_ENV MIX_OS_DEPS_COMPILE_PARTITION_COUNT MIX_TARGET) ++ - ~w(XDG_DATA_HOME XDG_CONFIG_HOME), - &System.delete_env/1 -) - defmodule MixTest.Case do use ExUnit.CaseTemplate @@ -249,6 +241,20 @@ defmodule MixTest.Case do end end +# Prepare and clear environment variables +System.put_env( + "MIX_OS_DEPS_COMPILE_PARTITION_ELIXIR_EXECUTABLE", + MixTest.Case.elixir_executable() +) + +# Clear environment variables that may affect tests +Enum.each( + ~w(http_proxy https_proxy HTTP_PROXY HTTPS_PROXY) ++ + ~w(MIX_ENV MIX_OS_DEPS_COMPILE_PARTITION_COUNT MIX_TARGET) ++ + ~w(XDG_DATA_HOME XDG_CONFIG_HOME), + &System.delete_env/1 +) + ## Set up Rebar fixtures rebar3_source = System.get_env("REBAR3") || Path.expand("fixtures/rebar3", __DIR__) From 670ee0a284b69853c8aaf1501c28c7f22b5dbea5 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Mon, 24 Mar 2025 14:27:23 +0100 Subject: [PATCH 16/18] Make it public --- lib/mix/test/test_helper.exs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/lib/mix/test/test_helper.exs b/lib/mix/test/test_helper.exs index 032794f5ced..05f21bc2df9 100644 --- a/lib/mix/test/test_helper.exs +++ b/lib/mix/test/test_helper.exs @@ -221,11 +221,11 @@ defmodule MixTest.Case do File.write!(file, File.read!(file) <> "\n") end - defp mix_executable do + def mix_executable do Path.expand("../../../bin/mix", __DIR__) end - defp elixir_executable do + def elixir_executable do Path.expand("../../../bin/elixir", __DIR__) end From a0c5603726e41baa908ff8fb503f6fc9f3d528e7 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Mon, 24 Mar 2025 14:50:53 +0100 Subject: [PATCH 17/18] Remove parens --- lib/mix/lib/mix/tasks/deps.partition.ex | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/mix/lib/mix/tasks/deps.partition.ex b/lib/mix/lib/mix/tasks/deps.partition.ex index 6529fa68d82..853b42bb606 100644 --- a/lib/mix/lib/mix/tasks/deps.partition.ex +++ b/lib/mix/lib/mix/tasks/deps.partition.ex @@ -57,7 +57,7 @@ defmodule Mix.Tasks.Deps.Partition do args = [ ansi_flag, ~c"-e", - ~c"Mix.CLI.main()", + ~c"Mix.CLI.main", ~c"deps.partition", force_flag, ~c"--port", From f3f8049ec99a4b353912b0c4cb821081c69f4fc3 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Mon, 24 Mar 2025 15:12:40 +0100 Subject: [PATCH 18/18] Use explicit loopback --- lib/mix/lib/mix/tasks/deps.partition.ex | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/lib/mix/lib/mix/tasks/deps.partition.ex b/lib/mix/lib/mix/tasks/deps.partition.ex index 853b42bb606..301a6443710 100644 --- a/lib/mix/lib/mix/tasks/deps.partition.ex +++ b/lib/mix/lib/mix/tasks/deps.partition.ex @@ -25,7 +25,7 @@ defmodule Mix.Tasks.Deps.Partition do System.find_executable("elixir") || raise "cannot find elixir executable for partition compilation" - {:ok, {ip, port}} = :inet.sockname(socket) + {:ok, {_ip, port}} = :inet.sockname(socket) ansi_flag = if IO.ANSI.enabled?(), do: ~c"--color", else: ~c"--no-color" force_flag = if force?, do: ~c"--force", else: ~c"--no-force" @@ -63,7 +63,7 @@ defmodule Mix.Tasks.Deps.Partition do ~c"--port", Integer.to_charlist(port), ~c"--host", - :inet.ntoa(ip) + ~c"127.0.0.1" ] options = [