Skip to content

Commit 8329c53

Browse files
committed
Load modules lazily
1 parent 7e01628 commit 8329c53

File tree

4 files changed

+76
-28
lines changed

4 files changed

+76
-28
lines changed

lib/elixir/lib/kernel/parallel_compiler.ex

+61-16
Original file line numberDiff line numberDiff line change
@@ -181,7 +181,7 @@ defmodule Kernel.ParallelCompiler do
181181
{:ok, [atom], [warning] | info()}
182182
| {:error, [error] | [Code.diagnostic(:error)], [warning] | info()}
183183
def compile_to_path(files, path, options \\ []) when is_binary(path) and is_list(options) do
184-
spawn_workers(files, {:compile, path}, options)
184+
spawn_workers(files, {:compile, path}, Keyword.put(options, :dest, path))
185185
end
186186

187187
@doc """
@@ -320,6 +320,9 @@ defmodule Kernel.ParallelCompiler do
320320
end
321321

322322
defp write_module_binaries(result, {:compile, path}, timestamp) do
323+
File.mkdir_p!(path)
324+
Code.prepend_path(path)
325+
323326
Enum.flat_map(result, fn
324327
{{:module, module}, binary} when is_binary(binary) ->
325328
full_path = Path.join(path, Atom.to_string(module) <> ".beam")
@@ -420,8 +423,8 @@ defmodule Kernel.ParallelCompiler do
420423

421424
try do
422425
case output do
423-
{:compile, path} -> compile_file(file, path, parent)
424-
:compile -> compile_file(file, dest, parent)
426+
{:compile, _} -> compile_file(file, dest, false, parent)
427+
:compile -> compile_file(file, dest, true, parent)
425428
:require -> require_file(file, parent)
426429
end
427430
catch
@@ -527,9 +530,9 @@ defmodule Kernel.ParallelCompiler do
527530
wait_for_messages([], spawned, waiting, files, result, warnings, errors, state)
528531
end
529532

530-
defp compile_file(file, path, parent) do
533+
defp compile_file(file, path, force_load?, parent) do
531534
:erlang.process_flag(:error_handler, Kernel.ErrorHandler)
532-
:erlang.put(:elixir_compiler_dest, path)
535+
:erlang.put(:elixir_compiler_dest, {path, force_load?})
533536
:elixir_compiler.file(file, &each_file(&1, &2, parent))
534537
end
535538

@@ -630,19 +633,28 @@ defmodule Kernel.ParallelCompiler do
630633
state
631634
)
632635

633-
{:module_available, child, ref, file, module, binary} ->
636+
{:module_available, child, ref, file, module, binary, loaded?} ->
634637
state.each_module.(file, module, binary)
635638

639+
available =
640+
case Map.get(result, {:module, module}) do
641+
[_ | _] = pids ->
642+
loaded? or load_module(module, binary, state)
643+
Enum.map(pids, &{&1, :found})
644+
645+
_ ->
646+
[]
647+
end
648+
636649
# Release the module loader which is waiting for an ack
637650
send(child, {ref, :ack})
638-
{available, result} = update_result(result, :module, module, binary)
639651

640652
spawn_workers(
641653
available ++ queue,
642654
spawned,
643655
waiting,
644656
files,
645-
result,
657+
Map.put(result, {:module, module}, binary),
646658
warnings,
647659
errors,
648660
state
@@ -660,14 +672,31 @@ defmodule Kernel.ParallelCompiler do
660672
available_or_pending = Map.get(result, {kind, on}, [])
661673

662674
{waiting, files, result} =
663-
if not is_list(available_or_pending) or on in defining do
664-
send(child_pid, {ref, :found})
665-
{waiting, files, result}
666-
else
667-
waiting = Map.put(waiting, child_pid, {kind, ref, file_pid, on, defining, deadlock})
668-
files = update_timing(files, file_pid, :compiling)
669-
result = Map.put(result, {kind, on}, [child_pid | available_or_pending])
670-
{waiting, files, result}
675+
cond do
676+
# TODO: Refactor me
677+
kind == :struct and is_binary(Map.get(result, {:module, on})) and
678+
not :erlang.module_loaded(on) ->
679+
load_module(on, Map.get(result, {:module, on}), state)
680+
send(child_pid, {ref, :found})
681+
{waiting, files, result}
682+
683+
# We have the module but it was not loaded yet, so we load it
684+
kind == :module and is_binary(available_or_pending) and not :erlang.module_loaded(on) ->
685+
load_module(on, available_or_pending, state)
686+
send(child_pid, {ref, :found})
687+
{waiting, files, result}
688+
689+
# Whatever we have is available, return it
690+
not is_list(available_or_pending) or on in defining ->
691+
send(child_pid, {ref, :found})
692+
{waiting, files, result}
693+
694+
# We need to wait for it
695+
true ->
696+
waiting = Map.put(waiting, child_pid, {kind, ref, file_pid, on, defining, deadlock})
697+
files = update_timing(files, file_pid, :compiling)
698+
result = Map.put(result, {kind, on}, [child_pid | available_or_pending])
699+
{waiting, files, result}
671700
end
672701

673702
spawn_workers(queue, spawned, waiting, files, result, warnings, errors, state)
@@ -755,6 +784,22 @@ defmodule Kernel.ParallelCompiler do
755784
{{:error, Enum.reverse(errors, fun.()), info}, state}
756785
end
757786

787+
defp load_module(module, binary, state) do
788+
beam_location =
789+
case state.dest do
790+
nil ->
791+
[]
792+
793+
dest ->
794+
:filename.join(
795+
:elixir_utils.characters_to_list(dest),
796+
Atom.to_charlist(module) ++ ~c".beam"
797+
)
798+
end
799+
800+
:code.load_binary(module, beam_location, binary)
801+
end
802+
758803
defp update_result(result, kind, module, value) do
759804
available =
760805
case Map.get(result, {kind, module}) do

lib/elixir/src/elixir_erl_compiler.erl

+2
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44

55
spawn(Fun) ->
66
CompilerInfo = get(elixir_compiler_info),
7+
{error_handler, ErrorHandler} = erlang:process_info(self(), error_handler),
78

89
CodeDiagnostics =
910
case get(elixir_code_diagnostics) of
@@ -13,6 +14,7 @@ spawn(Fun) ->
1314

1415
{_, Ref} =
1516
spawn_monitor(fun() ->
17+
erlang:process_flag(error_handler, ErrorHandler),
1618
put(elixir_compiler_info, CompilerInfo),
1719
put(elixir_code_diagnostics, CodeDiagnostics),
1820

lib/elixir/src/elixir_module.erl

+13-9
Original file line numberDiff line numberDiff line change
@@ -155,7 +155,7 @@ compile(Meta, Module, ModuleAsCharlist, Block, Vars, Prune, E) ->
155155
put_compiler_modules([Module | CompilerModules]),
156156
{Result, ModuleE, CallbackE} = eval_form(Line, Module, DataBag, Block, Vars, Prune, E),
157157
CheckerInfo = checker_info(),
158-
BeamLocation = beam_location(ModuleAsCharlist),
158+
{BeamLocation, Forceload} = beam_location(ModuleAsCharlist),
159159

160160
{Binary, PersistedAttributes, Autoload} =
161161
elixir_erl_compiler:spawn(fun() ->
@@ -215,17 +215,19 @@ compile(Meta, Module, ModuleAsCharlist, Block, Vars, Prune, E) ->
215215

216216
compile_error_if_tainted(DataSet, E),
217217
Binary = elixir_erl:compile(ModuleMap),
218-
Autoload = proplists:get_value(autoload, CompileOpts, true),
218+
%% TODO: Change docs
219+
Autoload = proplists:get_value(autoload, CompileOpts, false),
219220
spawn_parallel_checker(CheckerInfo, Module, ModuleMap),
220221
{Binary, PersistedAttributes, Autoload}
221222
end),
222223

223-
Autoload andalso code:load_binary(Module, BeamLocation, Binary),
224+
(Forceload or Autoload) andalso code:load_binary(Module, BeamLocation, Binary),
224225
put_compiler_modules(CompilerModules),
226+
%% TODO: Do not check twice
227+
make_module_available(Module, Binary, Forceload or Autoload),
225228
eval_callbacks(Line, DataBag, after_compile, [CallbackE, Binary], CallbackE),
226229
elixir_env:trace({on_module, Binary, none}, ModuleE),
227230
warn_unused_attributes(DataSet, DataBag, PersistedAttributes, E),
228-
make_module_available(Module, Binary),
229231
(element(2, CheckerInfo) == nil) andalso
230232
[VerifyMod:VerifyFun(Module) ||
231233
{VerifyMod, VerifyFun} <- bag_lookup_element(DataBag, {accumulate, after_verify}, 2)],
@@ -544,10 +546,12 @@ bag_lookup_element(Table, Name, Pos) ->
544546

545547
beam_location(ModuleAsCharlist) ->
546548
case get(elixir_compiler_dest) of
547-
Dest when is_binary(Dest) ->
548-
filename:join(elixir_utils:characters_to_list(Dest), ModuleAsCharlist ++ ".beam");
549+
{Dest, ForceLoad} when is_binary(Dest) ->
550+
BeamLocation =
551+
filename:join(elixir_utils:characters_to_list(Dest), ModuleAsCharlist ++ ".beam"),
552+
{BeamLocation, ForceLoad};
549553
_ ->
550-
""
554+
{"", true}
551555
end.
552556

553557
%% Integration with elixir_compiler that makes the module available
@@ -568,7 +572,7 @@ spawn_parallel_checker(CheckerInfo, Module, ModuleMap) ->
568572
end,
569573
'Elixir.Module.ParallelChecker':spawn(CheckerInfo, Module, ModuleMap, Log).
570574

571-
make_module_available(Module, Binary) ->
575+
make_module_available(Module, Binary, Loaded) ->
572576
case get(elixir_module_binaries) of
573577
Current when is_list(Current) ->
574578
put(elixir_module_binaries, [{Module, Binary} | Current]);
@@ -581,7 +585,7 @@ make_module_available(Module, Binary) ->
581585
ok;
582586
{PID, _} ->
583587
Ref = make_ref(),
584-
PID ! {module_available, self(), Ref, get(elixir_compiler_file), Module, Binary},
588+
PID ! {module_available, self(), Ref, get(elixir_compiler_file), Module, Binary, Loaded},
585589
receive {Ref, ack} -> ok end
586590
end.
587591

lib/mix/lib/mix/compilers/elixir.ex

-3
Original file line numberDiff line numberDiff line change
@@ -166,9 +166,6 @@ defmodule Mix.Compilers.Elixir do
166166

167167
Mix.Utils.compiling_n(length(stale), :ex)
168168
Mix.Project.ensure_structure()
169-
170-
# We don't want to cache this path as we will write to it
171-
true = Code.prepend_path(dest)
172169
previous_opts = set_compiler_opts(opts)
173170

174171
try do

0 commit comments

Comments
 (0)