Skip to content

Commit c31d1b3

Browse files
committed
Optimize application tracer
1 parent 6730d66 commit c31d1b3

File tree

1 file changed

+43
-13
lines changed

1 file changed

+43
-13
lines changed

lib/mix/lib/mix/compilers/application_tracer.ex

Lines changed: 43 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -107,17 +107,18 @@ defmodule Mix.Compilers.ApplicationTracer do
107107
:ets.delete(table, module)
108108
end
109109

110-
warnings =
110+
{warnings, _} =
111111
:ets.foldl(
112-
fn {module, function, arity, env_module, env_function, env_file, env_line}, acc ->
112+
fn {module, function, arity, env_module, env_function, env_file, env_line},
113+
{acc, cache} ->
113114
# If the module is preloaded, it is always available, so we skip it.
114115
# If the module is non existing, the compiler will warn, so we skip it.
115116
# If the module belongs to this application (from another compiler), we skip it.
116117
# If the module is excluded, we skip it.
117-
with path when is_list(path) <- :code.which(module),
118-
{:ok, module_app} <- app(path),
119-
true <- module_app != app,
120-
false <- module in excludes or {module, function, arity} in excludes do
118+
{module_app, cache} = app_for_module(module, cache)
119+
120+
if module_app != nil and module_app != app and module not in excludes and
121+
{module, function, arity} not in excludes do
121122
env_mfa =
122123
if env_function do
123124
{env_module, elem(env_function, 0), elem(env_function, 1)}
@@ -126,12 +127,12 @@ defmodule Mix.Compilers.ApplicationTracer do
126127
end
127128

128129
warning = {:undefined_app, module_app, module, function, arity}
129-
[{__MODULE__, warning, {env_file, env_line, env_mfa}} | acc]
130+
{[{__MODULE__, warning, {env_file, env_line, env_mfa}} | acc], cache}
130131
else
131-
_ -> acc
132+
{acc, cache}
132133
end
133134
end,
134-
[],
135+
{[], %{}},
135136
table
136137
)
137138

@@ -140,15 +141,44 @@ defmodule Mix.Compilers.ApplicationTracer do
140141
|> Module.ParallelChecker.emit_warnings()
141142
end
142143

144+
defp app_for_module(module, cache) do
145+
case cache do
146+
%{^module => maybe_app} ->
147+
{maybe_app, cache}
148+
149+
%{} ->
150+
maybe_app = app_for_module(module)
151+
{maybe_app, Map.put(cache, module, maybe_app)}
152+
end
153+
end
154+
143155
# ../elixir/ebin/elixir.beam -> elixir
144156
# ../ssl-9.6/ebin/ssl.beam -> ssl
145-
defp app(path) do
146-
case path |> Path.split() |> Enum.take(-3) do
147-
[dir, "ebin", _beam] -> {:ok, dir |> String.split("-") |> hd()}
148-
_ -> :error
157+
defp app_for_module(module) do
158+
with [_ | _] = path when is_list(path) <- :code.which(module),
159+
[_ | _] = app <-
160+
path |> Enum.reverse() |> discard_dir() |> discard_ebin() |> collect_dir([]) do
161+
List.to_string(app)
162+
else
163+
_ -> nil
149164
end
150165
end
151166

167+
defp discard_dir([?\\ | path]), do: path
168+
defp discard_dir([?/ | path]), do: path
169+
defp discard_dir([_ | path]), do: discard_dir(path)
170+
defp discard_dir([]), do: []
171+
172+
defp discard_ebin(~c"nibe/" ++ path), do: path
173+
defp discard_ebin(~c"nibe\\" ++ path), do: path
174+
defp discard_ebin(_), do: []
175+
176+
defp collect_dir([?\\ | _], acc), do: acc
177+
defp collect_dir([?/ | _], acc), do: acc
178+
defp collect_dir([?- | path], _acc), do: collect_dir(path, [])
179+
defp collect_dir([head | path], acc), do: collect_dir(path, [head | acc])
180+
defp collect_dir([], acc), do: acc
181+
152182
def stop(pending_save_manifest \\ nil) do
153183
try do
154184
:ets.delete(warnings_table())

0 commit comments

Comments
 (0)