@@ -6,7 +6,7 @@ defmodule Mix.Compilers.Elixir do
66 @ moduledoc false
77
88 @ manifest_vsn 28
9- @ checkpoint_vsn 2
9+ @ checkpoint_vsn 3
1010
1111 import Record
1212
@@ -152,7 +152,8 @@ defmodule Mix.Compilers.Elixir do
152152 removed ,
153153 Map . merge ( stale_modules , removed_modules ) ,
154154 Map . merge ( stale_exports , removed_modules ) ,
155- dest
155+ dest ,
156+ timestamp
156157 )
157158 end
158159
@@ -320,8 +321,11 @@ defmodule Mix.Compilers.Elixir do
320321 { % { } , % { } , all_paths , sources_stats }
321322 end
322323
323- # If any .beam file is missing, the first one will the first to miss,
324- # so we always check that. If there are no modules, then we can rely
324+ # If the user does a change, compilation fails, and then they revert
325+ # the change, the mtime will have changed but the .beam files will
326+ # be missing and the digest is the same, so we need to check if .beam
327+ # files are available. Checking the first .beam file is enough, as
328+ # they would be all removed. If there are no modules, then we can rely
325329 # purely on digests.
326330 defp missing_beam_file? ( dest , [ mod | _ ] ) , do: not File . exists? ( beam_path ( dest , mod ) )
327331 defp missing_beam_file? ( _dest , [ ] ) , do: false
@@ -334,55 +338,43 @@ defmodule Mix.Compilers.Elixir do
334338 removed ,
335339 stale_modules ,
336340 stale_exports ,
337- dest
341+ dest ,
342+ timestamp
338343 ) do
339- { modules_to_recompile , modules_to_mix_check } =
340- for { module , module ( recompile?: recompile? ) } <- all_modules , reduce: { [ ] , [ ] } do
341- { modules_to_recompile , modules_to_mix_check } ->
342- cond do
343- Map . has_key? ( stale_modules , module ) ->
344- { [ module | modules_to_recompile ] , modules_to_mix_check }
344+ { checkpoint_stale_modules , checkpoint_stale_exports } = parse_checkpoint ( manifest )
345+ stale_modules = Map . merge ( checkpoint_stale_modules , stale_modules )
346+ stale_exports = Map . merge ( checkpoint_stale_exports , stale_exports )
345347
346- recompile? ->
347- { modules_to_recompile , [ module | modules_to_mix_check ] }
348+ if map_size ( stale_modules ) != map_size ( checkpoint_stale_modules ) or
349+ map_size ( stale_exports ) != map_size ( checkpoint_stale_exports ) do
350+ write_checkpoint ( manifest , stale_modules , stale_exports )
351+ end
348352
349- true ->
350- { modules_to_recompile , modules_to_mix_check }
351- end
352- end
353+ # We don't need to store those in the checkpoint because
354+ # these changes come from modules and, when they are stale,
355+ # we remove the .beam files and touch sources.
356+ modules_to_mix_check =
357+ for { module , module ( recompile?: true ) } <- all_modules ,
358+ not Map . has_key? ( stale_modules , module ) ,
359+ do: module
353360
354361 _ = Code . ensure_all_loaded ( modules_to_mix_check )
355362
356363 modules_to_recompile =
357- modules_to_recompile ++
358- for { :ok , { module , true } } <-
359- Task . async_stream (
360- modules_to_mix_check ,
361- fn module ->
362- { module ,
363- function_exported? ( module , :__mix_recompile__? , 0 ) and
364- module . __mix_recompile__? ( ) }
365- end ,
366- ordered: false ,
367- timeout: :infinity
368- ) do
369- module
370- end
371-
372- { checkpoint_stale_modules , checkpoint_stale_exports , checkpoint_modules } =
373- parse_checkpoint ( manifest )
374-
375- modules_to_recompile =
376- Map . merge ( checkpoint_modules , Map . from_keys ( modules_to_recompile , true ) )
377-
378- stale_modules = Map . merge ( checkpoint_stale_modules , stale_modules )
379- stale_exports = Map . merge ( checkpoint_stale_exports , stale_exports )
380-
381- if map_size ( stale_modules ) != map_size ( checkpoint_stale_modules ) or
382- map_size ( stale_exports ) != map_size ( checkpoint_stale_exports ) or
383- map_size ( modules_to_recompile ) != map_size ( checkpoint_modules ) do
384- write_checkpoint ( manifest , stale_modules , stale_exports , modules_to_recompile )
385- end
364+ for { :ok , { module , true } } <-
365+ Task . async_stream (
366+ modules_to_mix_check ,
367+ fn module ->
368+ { module ,
369+ function_exported? ( module , :__mix_recompile__? , 0 ) and
370+ module . __mix_recompile__? ( ) }
371+ end ,
372+ ordered: false ,
373+ timeout: :infinity
374+ ) ,
375+ into: % { } do
376+ { module , true }
377+ end
386378
387379 sources_stats =
388380 for path <- new_paths ,
@@ -392,20 +384,30 @@ defmodule Mix.Compilers.Elixir do
392384 # Sources that have changed on disk or
393385 # any modules associated with them need to be recompiled
394386 changed =
395- for { source ,
396- source ( external: external , size: size , mtime: mtime , digest: digest , modules: modules ) } <-
397- all_sources ,
398- { last_mtime , last_size } = Map . fetch! ( sources_stats , source ) ,
399- # If the user does a change, compilation fails, and then they revert
400- # the change, the mtime will have changed but the .beam files will
401- # be missing and the digest is the same, so we need to check if .beam
402- # files are available.
403- size != last_size or
404- Enum . any? ( modules , & Map . has_key? ( modules_to_recompile , & 1 ) ) or
387+ Enum . flat_map ( all_sources , fn
388+ { source ,
389+ source ( external: external , size: size , mtime: mtime , digest: digest , modules: modules ) } ->
390+ { last_mtime , last_size } = Map . fetch! ( sources_stats , source )
391+
392+ cond do
405393 Enum . any? ( external , & stale_external? ( & 1 , sources_stats ) ) or
406- ( last_mtime > mtime and
407- ( missing_beam_file? ( dest , modules ) or digest_changed? ( source , digest ) ) ) ,
408- do: source
394+ has_any_key? ( modules_to_recompile , modules ) ->
395+ # Mark the source as changed so the combination of a timestamp
396+ # plus removed beam files (which are removed by update_stale_entries)
397+ # causes it to be recompiled
398+ File . touch! ( source , timestamp + 1 )
399+ [ source ]
400+
401+ size != last_size or
402+ has_any_key? ( stale_modules , modules ) or
403+ ( last_mtime > mtime and
404+ ( missing_beam_file? ( dest , modules ) or digest_changed? ( source , digest ) ) ) ->
405+ [ source ]
406+
407+ true ->
408+ [ ]
409+ end
410+ end )
409411
410412 changed = new_paths ++ changed
411413
@@ -576,7 +578,7 @@ defmodule Mix.Compilers.Elixir do
576578 end
577579
578580 defp has_any_key? ( map , enumerable ) do
579- Enum . any? ( enumerable , & Map . has_key? ( map , & 1 ) )
581+ map != % { } and Enum . any? ( enumerable , & Map . has_key? ( map , & 1 ) )
580582 end
581583
582584 defp stale_local_deps ( local_deps , manifest , stale_modules , modified , deps_exports ) do
@@ -940,25 +942,20 @@ defmodule Mix.Compilers.Elixir do
940942 #
941943 # Therefore, it is important for us to checkpoint any state that may
942944 # have lead to a compilation and which can now be reverted.
943-
944945 defp parse_checkpoint ( manifest ) do
945946 try do
946947 ( manifest <> ".checkpoint" ) |> File . read! ( ) |> :erlang . binary_to_term ( )
947948 rescue
948- _ ->
949- { % { } , % { } , % { } }
949+ _ -> { % { } , % { } }
950950 else
951- { @ checkpoint_vsn , stale_modules , stale_exports , recompile_modules } ->
952- { stale_modules , stale_exports , recompile_modules }
953-
954- _ ->
955- { % { } , % { } , % { } }
951+ { @ checkpoint_vsn , stale_modules , stale_exports } -> { stale_modules , stale_exports }
952+ _ -> { % { } , % { } }
956953 end
957954 end
958955
959- defp write_checkpoint ( manifest , stale_modules , stale_exports , recompile_modules ) do
956+ defp write_checkpoint ( manifest , stale_modules , stale_exports ) do
960957 File . mkdir_p! ( Path . dirname ( manifest ) )
961- term = { @ checkpoint_vsn , stale_modules , stale_exports , recompile_modules }
958+ term = { @ checkpoint_vsn , stale_modules , stale_exports }
962959 checkpoint_data = :erlang . term_to_binary ( term , [ :compressed ] )
963960 File . write! ( manifest <> ".checkpoint" , checkpoint_data )
964961 end
@@ -1117,8 +1114,10 @@ defmodule Mix.Compilers.Elixir do
11171114 { pending_modules , exports , changed } =
11181115 update_stale_entries ( pending_modules , sources , changed , % { } , stale_exports , compile_path )
11191116
1120- # For each changed file, mark it as changed.
1121- # If compilation fails mid-cycle, they will be picked next time around.
1117+ # Those files have been changed transitively, so we mark them as changed
1118+ # in case compilation fails mid-cycle. The combination of the outdated
1119+ # timestamp plus the missing BEAM files (which were removed in
1120+ # update_stale_entries above) will cause them to be recompiled next time.
11221121 for file <- changed do
11231122 File . touch! ( file , timestamp )
11241123 end
0 commit comments