Skip to content

Commit 792e604

Browse files
committed
Prepare for local inference
1 parent 485ca72 commit 792e604

File tree

3 files changed

+85
-65
lines changed

3 files changed

+85
-65
lines changed

lib/elixir/lib/module/parallel_checker.ex

Lines changed: 69 additions & 50 deletions
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,6 @@ defmodule Module.ParallelChecker do
55

66
@type cache() :: {pid(), :ets.tid()}
77
@type warning() :: term()
8-
@type kind() :: :def | :defmacro
98
@type mode() :: :elixir | :erlang
109

1110
@doc """
@@ -48,7 +47,25 @@ defmodule Module.ParallelChecker do
4847
@doc """
4948
Spawns a process that runs the parallel checker.
5049
"""
51-
def spawn({pid, checker}, module, info, log?) do
50+
def spawn(pid_checker, module_map, log?, infer_types?, env) do
51+
%{module: module, definitions: definitions, file: file} = module_map
52+
53+
module_map =
54+
if infer_types? do
55+
%{module_map | signatures: Module.Types.infer(module, file, definitions, env)}
56+
else
57+
module_map
58+
end
59+
60+
with {pid, checker} <- pid_checker do
61+
ets = :gen_server.call(checker, :ets, :infinity)
62+
inner_spawn(pid, checker, module, cache_from_module_map(ets, module_map), log?)
63+
end
64+
65+
module_map
66+
end
67+
68+
defp inner_spawn(pid, checker, module, info, log?) do
5269
ref = make_ref()
5370

5471
spawned =
@@ -59,17 +76,22 @@ defmodule Module.ParallelChecker do
5976
{^ref, :cache, ets} ->
6077
Process.link(pid)
6178

62-
module_map =
63-
if is_map(info) do
64-
info
65-
else
66-
case File.read(info) do
67-
{:ok, binary} -> maybe_module_map(binary, module)
68-
{:error, _} -> nil
69-
end
79+
module_tuple =
80+
cond do
81+
is_tuple(info) ->
82+
info
83+
84+
is_binary(info) ->
85+
with {:ok, binary} <- File.read(info),
86+
{:ok, {_, [debug_info: chunk]}} <- :beam_lib.chunks(binary, [:debug_info]),
87+
{:debug_info_v1, backend, data} = chunk,
88+
{:ok, module_map} <- backend.debug_info(:elixir_v1, module, data, []) do
89+
cache_from_module_map(ets, module_map)
90+
else
91+
_ -> nil
92+
end
7093
end
7194

72-
module_map && cache_from_module_map(ets, module_map)
7395
send(checker, {ref, :cached})
7496

7597
receive do
@@ -78,8 +100,8 @@ defmodule Module.ParallelChecker do
78100
:erlang.put(:elixir_compiler_info, {pid, self()})
79101

80102
warnings =
81-
if module_map do
82-
check_module(module_map, {checker, ets}, log?)
103+
if module_tuple do
104+
check_module(module_tuple, {checker, ets}, log?)
83105
else
84106
[]
85107
end
@@ -147,7 +169,7 @@ defmodule Module.ParallelChecker do
147169
log? = not match?({_, false}, value)
148170

149171
for {module, file} <- runtime_files do
150-
spawn({self(), checker}, module, file, log?)
172+
inner_spawn(self(), checker, module, file, log?)
151173
end
152174

153175
count = :gen_server.call(checker, :start, :infinity)
@@ -212,14 +234,43 @@ defmodule Module.ParallelChecker do
212234

213235
## Module checking
214236

215-
defp check_module(module_map, cache, log?) do
237+
defp check_module(module_tuple, cache, log?) do
238+
{module, file, line, definitions, no_warn_undefined, behaviours, impls, after_verify} =
239+
module_tuple
240+
241+
behaviour_warnings =
242+
Module.Behaviour.check_behaviours_and_impls(
243+
module,
244+
file,
245+
line,
246+
behaviours,
247+
impls,
248+
definitions
249+
)
250+
251+
diagnostics =
252+
module
253+
|> Module.Types.warnings(file, definitions, no_warn_undefined, cache)
254+
|> Kernel.++(behaviour_warnings)
255+
|> group_warnings()
256+
|> emit_warnings(log?)
257+
258+
Enum.each(after_verify, fn {verify_mod, verify_fun} ->
259+
apply(verify_mod, verify_fun, [module])
260+
end)
261+
262+
diagnostics
263+
end
264+
265+
defp module_map_to_module_tuple(module_map) do
216266
%{
217267
module: module,
218268
file: file,
219269
compile_opts: compile_opts,
220270
definitions: definitions,
221271
attributes: attributes,
222-
impls: impls
272+
impls: impls,
273+
after_verify: after_verify
223274
} = module_map
224275

225276
# TODO: Match on anno directly in Elixir v1.22+
@@ -236,28 +287,7 @@ defmodule Module.ParallelChecker do
236287
|> extract_no_warn_undefined()
237288
|> merge_compiler_no_warn_undefined()
238289

239-
behaviour_warnings =
240-
Module.Behaviour.check_behaviours_and_impls(
241-
module,
242-
file,
243-
line,
244-
behaviours,
245-
impls,
246-
definitions
247-
)
248-
249-
diagnostics =
250-
module
251-
|> Module.Types.warnings(file, definitions, no_warn_undefined, cache)
252-
|> Kernel.++(behaviour_warnings)
253-
|> group_warnings()
254-
|> emit_warnings(log?)
255-
256-
module_map
257-
|> Map.get(:after_verify, [])
258-
|> Enum.each(fn {verify_mod, verify_fun} -> apply(verify_mod, verify_fun, [module]) end)
259-
260-
diagnostics
290+
{module, file, line, definitions, no_warn_undefined, behaviours, impls, after_verify}
261291
end
262292

263293
defp extract_no_warn_undefined(compile_opts) do
@@ -400,25 +430,14 @@ defmodule Module.ParallelChecker do
400430
_ -> %{}
401431
end
402432

403-
defp maybe_module_map(binary, module) when is_binary(binary) do
404-
# If a module was compiled without debug_info,
405-
# then there is no module_map for further verification.
406-
with {:ok, {_, [debug_info: chunk]}} <- :beam_lib.chunks(binary, [:debug_info]),
407-
{:debug_info_v1, backend, data} = chunk,
408-
{:ok, module_map} <- backend.debug_info(:elixir_v1, module, data, []) do
409-
module_map
410-
else
411-
_ -> nil
412-
end
413-
end
414-
415433
defp cache_from_module_map(ets, map) do
416434
exports =
417435
[{:__info__, 1}] ++
418436
behaviour_exports(map) ++
419437
for({function, :def, _meta, _clauses} <- map.definitions, do: function)
420438

421439
cache_info(ets, map.module, exports, Map.new(map.deprecated), map.signatures, :elixir)
440+
module_map_to_module_tuple(map)
422441
end
423442

424443
defp cache_info(ets, module, exports, deprecated, sigs, mode) do

lib/elixir/lib/module/types.ex

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,6 @@ defmodule Module.Types do
2929
end
3030
end)
3131

32-
# TODO: Reuse context from patterns and guards
3332
{{fun, arity}, {:infer, Enum.reverse(pair_types)}}
3433
end
3534
end

lib/elixir/src/elixir_module.erl

Lines changed: 16 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -173,12 +173,7 @@ compile(Meta, Module, ModuleAsCharlist, Block, Vars, Prune, E) ->
173173
false -> ok
174174
end,
175175

176-
Signatures = case elixir_config:get(infer_signatures) of
177-
true -> 'Elixir.Module.Types':infer(Module, File, AllDefinitions, CallbackE);
178-
false -> #{}
179-
end,
180-
181-
ModuleMap = #{
176+
ModuleMapWithoutSignatures = #{
182177
struct => get_struct(DataSet),
183178
module => Module,
184179
anno => Anno,
@@ -192,12 +187,12 @@ compile(Meta, Module, ModuleAsCharlist, Block, Vars, Prune, E) ->
192187
deprecated => get_deprecated(DataBag),
193188
defines_behaviour => defines_behaviour(DataBag),
194189
impls => Impls,
195-
signatures => Signatures
190+
signatures => #{}
196191
},
197192

193+
ModuleMap = spawn_parallel_checker(CheckerInfo, ModuleMapWithoutSignatures, CallbackE),
198194
Binary = elixir_erl:compile(ModuleMap),
199195
Autoload = proplists:get_value(autoload, CompileOpts, true),
200-
spawn_parallel_checker(CheckerInfo, Module, ModuleMap),
201196
{Binary, PersistedAttributes, Autoload}
202197
end),
203198

@@ -207,7 +202,7 @@ compile(Meta, Module, ModuleAsCharlist, Block, Vars, Prune, E) ->
207202
elixir_env:trace({on_module, Binary, none}, ModuleE),
208203
warn_unused_attributes(DataSet, DataBag, PersistedAttributes, E),
209204
make_module_available(Module, Binary),
210-
(CheckerInfo == undefined) andalso
205+
(CheckerInfo == nil) andalso
211206
[VerifyMod:VerifyFun(Module) ||
212207
{VerifyMod, VerifyFun} <- bag_lookup_element(DataBag, {accumulate, after_verify}, 2)],
213208
{module, Module, Binary, Result}
@@ -534,19 +529,26 @@ beam_location(ModuleAsCharlist) ->
534529

535530
checker_info() ->
536531
case get(elixir_checker_info) of
537-
undefined -> undefined;
532+
undefined -> nil;
538533
_ -> 'Elixir.Module.ParallelChecker':get()
539534
end.
540535

541-
spawn_parallel_checker(undefined, _Module, _ModuleMap) ->
542-
ok;
543-
spawn_parallel_checker(CheckerInfo, Module, ModuleMap) ->
536+
spawn_parallel_checker(CheckerInfo, ModuleMap, E) ->
544537
Log =
545538
case erlang:get(elixir_code_diagnostics) of
546539
{_, false} -> false;
547540
_ -> true
548541
end,
549-
'Elixir.Module.ParallelChecker':spawn(CheckerInfo, Module, ModuleMap, Log).
542+
543+
Infer = elixir_config:get(infer_signatures),
544+
545+
if
546+
%% We need this clause for bootstrap reasons
547+
CheckerInfo /= nil; Infer ->
548+
'Elixir.Module.ParallelChecker':spawn(CheckerInfo, ModuleMap, Log, Infer, E);
549+
true ->
550+
ModuleMap
551+
end.
550552

551553
make_module_available(Module, Binary) ->
552554
case get(elixir_module_binaries) of

0 commit comments

Comments
 (0)