@@ -145,8 +145,8 @@ defmodule Mix.Deps do
145145 provided in the project are in the wrong format.
146146 """
147147 def unfetched ( acc , callback ) do
148- { _deps , acc } = Mix.Deps.Converger . all ( acc , callback )
149- acc
148+ { deps , acc } = Mix.Deps.Converger . all ( acc , callback )
149+ { Mix.Deps.Converger . topsort ( deps ) , acc }
150150 end
151151
152152 @ doc """
@@ -170,32 +170,6 @@ defmodule Mix.Deps do
170170 end )
171171 end
172172
173- @ doc """
174- Receives a list of dependencies and returns the given list
175- with their depending dependencies, recursively. It is expected
176- the given list of dependencies to contain only fetched dependencies
177- (since unfetched dependencies did not have their dependencies
178- retrieved yet).
179- """
180- def with_depending( deps, all_deps // fetched ) do
181- ( deps ++ do_with_depending ( deps , all_deps ) )
182- |> Enum . uniq ( & ( & 1 . app ) )
183- end
184-
185- defp do_with_depending ( [ ] , _all_deps ) do
186- [ ]
187- end
188-
189- defp do_with_depending ( deps , all_deps ) do
190- dep_names = Enum . map ( deps , fn dep -> dep . app end )
191-
192- parents = Enum . filter all_deps , fn dep ->
193- Enum . any? ( dep . deps , fn child_dep -> child_dep . app in dep_names end )
194- end
195-
196- do_with_depending ( parents , all_deps ) ++ parents
197- end
198-
199173 @ doc """
200174 Runs the given `fun` inside the given dependency project by
201175 changing the current working directory and loading the given
@@ -240,7 +214,7 @@ defmodule Mix.Deps do
240214 def format_status(Mix.Dep[status: { :noappfile, path }]),
241215 do: "could not find an app file at #{Path.relative_to_cwd(path)}, " <>
242216 "this may happen when you specified the wrong application name in your deps " <>
243- "or if the dependency failed to compile (which can be amended with `mix deps.compile`)"
217+ "or if the dependency did not compile (which can be amended with `mix deps.compile`)"
244218
245219 def format_status ( Mix.Dep [ status : { :invalidapp , path } ] ) ,
246220 do: "the app file at #{ Path . relative_to_cwd ( path ) } is invalid"
@@ -278,6 +252,9 @@ defmodule Mix.Deps do
278252 def format_status ( Mix.Dep [ status : { :elixirlock , _ } ] ) ,
279253 do: "the dependency is built with an out-of-date elixir version, run `mix deps.get`"
280254
255+ def format_status ( Mix.Dep [ status : { :elixirreq , req } ] ) ,
256+ do: "the dependency requires Elixir #{ req } but you are running on v#{ System . version } "
257+
281258 defp dep_status ( Mix.Dep [ app : app , requirement: req , opts: opts , from: from ] ) do
282259 info = { app , req , Dict . drop ( opts , [ :dest , :lock , :env ] ) }
283260 "\n > In #{ Path . relative_to_cwd ( from ) } :\n #{ inspect info } \n "
@@ -308,26 +285,37 @@ defmodule Mix.Deps do
308285 Check if a dependency is ok.
309286 "" "
310287 def ok?(Mix.Dep[status: { :ok, _ }]), do: true
311- def ok? ( _ ) , do: false
288+ def ok?(Mix.Dep[] ), do: false
312289
313290 @doc """
314- Check if a dependency is available.
291+ Check if a dependency is available . Available dependencies
292+ are the ones that can be compiled , loaded , etc .
315293 "" "
316294 def available?(Mix.Dep[status: { :overriden, _ }]), do: false
317295 def available?(Mix.Dep[status: { :diverged, _ }]), do: false
296+ def available?(Mix.Dep[status: { :elixirreq, _ }]), do: false
318297 def available?(Mix.Dep[status: { :unavailable, _ }]), do: false
319- def available? ( _ ) , do: true
298+ def available?(Mix.Dep[] ), do: true
320299
321300 @doc """
322- Check if a dependency is out of date considering its
301+ Check if a dependency can be updated .
302+ "" "
303+ def updatable?(Mix.Dep[status: { :elixirreq, _ }]), do: true
304+ def updatable?(dep), do: available?(dep)
305+
306+ @doc " ""
307+ Check if a dependency is out of date , also considering its
323308 lock status . Therefore , be sure to call `check_lock ` before
324309 invoking this function .
310+
311+ Out of date dependencies are fixed by simply running `deps . get `.
325312 "" "
326313 def out_of_date?(Mix.Dep[status: { :lockmismatch, _ }]), do: true
327314 def out_of_date?(Mix.Dep[status: :lockoutdated]), do: true
328315 def out_of_date?(Mix.Dep[status: :nolock]), do: true
329316 def out_of_date?(Mix.Dep[status: { :elixirlock, _ }]), do: true
330- def out_of_date? ( dep ) , do: not available? ( dep )
317+ def out_of_date?(Mix.Dep[status: { :unavailable, _ }]), do: true
318+ def out_of_date?(Mix.Dep[]), do: false
331319
332320 @doc " ""
333321 Formats a dependency for printing.
@@ -406,6 +394,53 @@ defmodule Mix.Deps do
406394
407395 ## Helpers
408396
397+ @doc false
398+ # Called by deps.get and deps.update
399+ def finalize(all_deps, apps, lock, opts) do
400+ deps = fetched_by_name(apps, all_deps)
401+
402+ # Do not attempt to compile dependencies that are not available.
403+ # mix deps.check at the end will emit proper status in case they failed.
404+ deps = Enum.filter(deps, &available?/1)
405+
406+ # Note we only retrieve the parent dependencies of the updated
407+ # deps if all dependencies are available. This is because if a
408+ # dependency is missing, it could be a children of the parent
409+ # (aka a sibling) which would make parent compilation fail.
410+ if Enum.all?(all_deps, &available?/1) do
411+ deps = with_depending(deps, all_deps)
412+ end
413+
414+ apps = Enum.map(deps, &(&1.app))
415+ Mix.Deps.Lock.write(lock)
416+
417+ unless opts[:no_compile] do
418+ args = if opts[:quiet], do: [" --quiet "|apps], else: apps
419+ Mix.Task.run(" deps. compile ", args)
420+ unless opts[:no_deps_check] do
421+ Mix.Task.run(" deps. check ", [])
422+ end
423+ end
424+ end
425+
426+ defp with_depending(deps, all_deps) do
427+ (deps ++ do_with_depending(deps, all_deps)) |> Enum.uniq(&(&1.app))
428+ end
429+
430+ defp do_with_depending([], _all_deps) do
431+ []
432+ end
433+
434+ defp do_with_depending(deps, all_deps) do
435+ dep_names = Enum.map(deps, fn dep -> dep.app end)
436+
437+ parents = Enum.filter all_deps, fn dep ->
438+ Enum.any?(dep.deps, fn child_dep -> child_dep.app in dep_names end)
439+ end
440+
441+ do_with_depending(parents, all_deps) ++ parents
442+ end
443+
409444 defp to_app_names(given) do
410445 Enum.map given, fn(app) ->
411446 if is_binary(app), do: binary_to_atom(app), else: app
0 commit comments