@@ -6,7 +6,7 @@ defmodule Mix.Compilers.Elixir do
66 @ moduledoc false
77
88 @ manifest_vsn 28
9- @ checkpoint_vsn 3
9+ @ checkpoint_vsn 4
1010
1111 import Record
1212
@@ -53,6 +53,16 @@ defmodule Mix.Compilers.Elixir do
5353 old_project_mtime , old_config_mtime , old_protocols_and_impls } =
5454 parse_manifest ( manifest , dest )
5555
56+ # In case we aborted in the middle of a verification,
57+ # we need to delete all modules that we wrote to disk.
58+ # In the future, we may want to make it so we only run
59+ # the verification again.
60+ with { :ok , modules } <- parse_checkpoint ( :verify , manifest ) do
61+ for module <- modules do
62+ File . rm ( Path . join ( dest , Atom . to_string ( module ) <> ".beam" ) )
63+ end
64+ end
65+
5666 # Prepend ourselves early because of __mix_recompile__? checks
5767 # and also that, in case of nothing compiled, we already need
5868 # ourselves available in the path.
@@ -197,7 +207,7 @@ defmodule Mix.Compilers.Elixir do
197207 consolidation: consolidation
198208 }
199209
200- compiler_loop ( stale , stale_modules , dest , timestamp , opts , state )
210+ compiler_loop ( manifest , stale , stale_modules , dest , timestamp , opts , state )
201211 else
202212 { :ok , % { runtime_warnings: runtime_warnings , compile_warnings: compile_warnings } , state } ->
203213 % {
@@ -354,13 +364,28 @@ defmodule Mix.Compilers.Elixir do
354364 dest ,
355365 timestamp
356366 ) do
357- { checkpoint_stale_modules , checkpoint_stale_exports } = parse_checkpoint ( manifest )
367+ { checkpoint_stale_modules , checkpoint_stale_exports } =
368+ case parse_checkpoint ( :update , manifest ) do
369+ { :ok , { _ , _ } = data } -> data
370+ :error -> { % { } , % { } }
371+ end
372+
358373 stale_modules = Map . merge ( checkpoint_stale_modules , stale_modules )
359374 stale_exports = Map . merge ( checkpoint_stale_exports , stale_exports )
360375
376+ # Once we added semantic recompilation, the following can happen:
377+ #
378+ # 1. The user changes config/mix.exs/__mix_recompile__?
379+ # 2. We detect the change, remove .beam files and start recompilation
380+ # 3. Recompilation fails
381+ # 4. The user reverts the change
382+ # 5. The compiler no longer recompiles and the .beam files are missing
383+ #
384+ # Therefore, it is important for us to checkpoint any state that may
385+ # have lead to a compilation and which can now be reverted.
361386 if map_size ( stale_modules ) != map_size ( checkpoint_stale_modules ) or
362387 map_size ( stale_exports ) != map_size ( checkpoint_stale_exports ) do
363- write_checkpoint ( manifest , stale_modules , stale_exports )
388+ write_checkpoint ( :update , manifest , { stale_modules , stale_exports } )
364389 end
365390
366391 # We don't need to store those in the checkpoint because
@@ -932,7 +957,7 @@ defmodule Mix.Compilers.Elixir do
932957 manifest_data = :erlang . term_to_binary ( term , [ :compressed ] )
933958 File . write! ( manifest , manifest_data )
934959 File . touch! ( manifest , timestamp )
935- delete_checkpoint ( manifest )
960+ delete_checkpoints ( manifest )
936961
937962 # Since Elixir is a dependency itself, we need to touch the lock
938963 # so the current Elixir version, used to compile the files above,
@@ -945,36 +970,27 @@ defmodule Mix.Compilers.Elixir do
945970 Path . join ( compile_path , Atom . to_string ( module ) <> ".beam" )
946971 end
947972
948- # Once we added semantic recompilation, the following can happen:
949- #
950- # 1. The user changes config/mix.exs/__mix_recompile__?
951- # 2. We detect the change, remove .beam files and start recompilation
952- # 3. Recompilation fails
953- # 4. The user reverts the change
954- # 5. The compiler no longer recompiles and the .beam files are missing
955- #
956- # Therefore, it is important for us to checkpoint any state that may
957- # have lead to a compilation and which can now be reverted.
958- defp parse_checkpoint ( manifest ) do
973+ defp parse_checkpoint ( type , manifest ) when type in [ :update , :verify ] do
959974 try do
960- ( manifest <> ".checkpoint " ) |> File . read! ( ) |> :erlang . binary_to_term ( )
975+ ( manifest <> ".#{ type } .cp " ) |> File . read! ( ) |> :erlang . binary_to_term ( )
961976 rescue
962- _ -> { % { } , % { } }
977+ _ -> :error
963978 else
964- { @ checkpoint_vsn , stale_modules , stale_exports } -> { stale_modules , stale_exports }
965- _ -> { % { } , % { } }
979+ { @ checkpoint_vsn , data } -> { :ok , data }
980+ _ -> :error
966981 end
967982 end
968983
969- defp write_checkpoint ( manifest , stale_modules , stale_exports ) do
984+ defp write_checkpoint ( type , manifest , data ) when type in [ :update , :verify ] do
970985 File . mkdir_p! ( Path . dirname ( manifest ) )
971- term = { @ checkpoint_vsn , stale_modules , stale_exports }
972- checkpoint_data = :erlang . term_to_binary ( term , [ :compressed ] )
973- File . write! ( manifest <> ".checkpoint " , checkpoint_data )
986+ term = { @ checkpoint_vsn , data }
987+ checkpoint_data = :erlang . term_to_binary ( term )
988+ File . write! ( manifest <> ".#{ type } .cp " , checkpoint_data )
974989 end
975990
976- defp delete_checkpoint ( manifest ) do
977- File . rm ( manifest <> ".checkpoint" )
991+ defp delete_checkpoints ( manifest ) do
992+ File . rm ( manifest <> ".update.cp" )
993+ File . rm ( manifest <> ".verify.cp" )
978994 end
979995
980996 defp unless_warnings_as_errors ( opts , { status , all_warnings } ) do
@@ -1008,7 +1024,7 @@ defmodule Mix.Compilers.Elixir do
10081024 ## Compiler loop
10091025 # The compiler is invoked in a separate process so we avoid blocking its main loop.
10101026
1011- defp compiler_loop ( stale , stale_modules , dest , timestamp , opts , state ) do
1027+ defp compiler_loop ( manifest , stale , stale_modules , dest , timestamp , opts , state ) do
10121028 ref = make_ref ( )
10131029 parent = self ( )
10141030 compilation_threshold = opts [ :long_compilation_threshold ] || 10
@@ -1025,7 +1041,7 @@ defmodule Mix.Compilers.Elixir do
10251041 spawn_link ( fn ->
10261042 compile_opts = [
10271043 after_compile: fn ->
1028- compiler_call ( parent , ref , { :after_compile , dest , opts } )
1044+ compiler_call ( parent , ref , { :after_compile , manifest , opts } )
10291045 end ,
10301046 each_cycle: fn ->
10311047 compiler_call ( parent , ref , { :each_cycle , stale_modules , dest , timestamp } )
@@ -1073,8 +1089,8 @@ defmodule Mix.Compilers.Elixir do
10731089
10741090 defp compiler_loop ( ref , pid , state , cwd ) do
10751091 receive do
1076- { ^ ref , { :after_compile , dest , opts } } ->
1077- { response , state } = after_compile ( dest , state , opts )
1092+ { ^ ref , { :after_compile , manifest , opts } } ->
1093+ { response , state } = after_compile ( manifest , state , opts )
10781094 send ( pid , { ref , response } )
10791095 compiler_loop ( ref , pid , state , cwd )
10801096
@@ -1111,8 +1127,9 @@ defmodule Mix.Compilers.Elixir do
11111127 end
11121128 end
11131129
1114- defp after_compile ( _dest , state , opts ) do
1130+ defp after_compile ( manifest , state , opts ) do
11151131 % { modules: modules , pending_modules: pending_modules , consolidation: consolidation } = state
1132+ write_checkpoint ( :verify , manifest , Map . keys ( modules ) )
11161133 consolidation = maybe_consolidate ( consolidation , modules , pending_modules , opts )
11171134 { :ok , % { state | consolidation: consolidation } }
11181135 end
0 commit comments