Skip to content

Commit 41690a3

Browse files
authored
Add :depth option to git deps (#13128)
This allows for faster clones that transfer less data over the network and take less space in disk, for cases when the full history is not needed.
1 parent e952256 commit 41690a3

File tree

5 files changed

+282
-18
lines changed

5 files changed

+282
-18
lines changed

lib/mix/lib/mix/scm/git.ex

Lines changed: 69 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -125,14 +125,18 @@ defmodule Mix.SCM.Git do
125125
sparse_toggle(opts)
126126
update_origin(opts[:git])
127127

128+
rev = get_lock_rev(opts[:lock], opts) || get_opts_rev(opts)
129+
128130
# Fetch external data
129131
["--git-dir=.git", "fetch", "--force", "--quiet"]
130132
|> Kernel.++(progress_switch(git_version()))
131133
|> Kernel.++(tags_switch(opts[:tag]))
134+
|> Kernel.++(depth_switch(opts[:depth]))
135+
|> Kernel.++(if rev, do: ["origin", rev], else: [])
132136
|> git!()
133137

134138
# Migrate the Git repo
135-
rev = get_lock_rev(opts[:lock], opts) || get_opts_rev(opts) || default_branch()
139+
rev = rev || default_branch()
136140
git!(["--git-dir=.git", "checkout", "--quiet", rev])
137141

138142
if opts[:submodules] do
@@ -164,7 +168,7 @@ defmodule Mix.SCM.Git do
164168
defp sparse_toggle(opts) do
165169
cond do
166170
sparse = opts[:sparse] ->
167-
sparse_check(git_version())
171+
check_sparse_support(git_version())
168172
git!(["--git-dir=.git", "config", "core.sparsecheckout", "true"])
169173
File.mkdir_p!(".git/info")
170174
File.write!(".git/info/sparse-checkout", sparse)
@@ -180,27 +184,50 @@ defmodule Mix.SCM.Git do
180184
end
181185
end
182186

183-
defp sparse_check(version) do
184-
unless {1, 7, 4} <= version do
185-
version = version |> Tuple.to_list() |> Enum.join(".")
187+
@min_git_version_sparse {1, 7, 4}
188+
@min_git_version_depth {1, 5, 0}
189+
@min_git_version_progress {1, 7, 1}
190+
191+
defp check_sparse_support(version) do
192+
ensure_feature_compatibility(version, @min_git_version_sparse, "sparse checkout")
193+
end
194+
195+
defp check_depth_support(version) do
196+
ensure_feature_compatibility(version, @min_git_version_depth, "depth (shallow clone)")
197+
end
186198

199+
defp ensure_feature_compatibility(version, required_version, feature) do
200+
unless required_version <= version do
187201
Mix.raise(
188-
"Git >= 1.7.4 is required to use sparse checkout. " <>
189-
"You are running version #{version}"
202+
"Git >= #{format_version(required_version)} is required to use #{feature}. " <>
203+
"You are running version #{format_version(version)}"
190204
)
191205
end
192206
end
193207

194208
defp progress_switch(version) do
195-
if {1, 7, 1} <= version, do: ["--progress"], else: []
209+
if @min_git_version_progress <= version, do: ["--progress"], else: []
196210
end
197211

198212
defp tags_switch(nil), do: []
199213
defp tags_switch(_), do: ["--tags"]
200214

215+
defp depth_switch(nil), do: []
216+
217+
defp depth_switch(n) when is_integer(n) and n > 0 do
218+
check_depth_support(git_version())
219+
["--depth=#{n}"]
220+
end
221+
201222
## Helpers
202223

203224
defp validate_git_options(opts) do
225+
opts
226+
|> validate_refspec()
227+
|> validate_depth()
228+
end
229+
230+
defp validate_refspec(opts) do
204231
case Keyword.take(opts, [:branch, :ref, :tag]) do
205232
[] ->
206233
opts
@@ -222,6 +249,22 @@ defmodule Mix.SCM.Git do
222249
end
223250
end
224251

252+
defp validate_depth(opts) do
253+
case Keyword.take(opts, [:depth]) do
254+
[] ->
255+
opts
256+
257+
[{:depth, depth}] when is_integer(depth) and depth > 0 ->
258+
opts
259+
260+
invalid_depth ->
261+
Mix.raise(
262+
"The depth must be a positive integer, and be specified only once, got: #{inspect(invalid_depth)}. " <>
263+
"Error on Git dependency: #{redact_uri(opts[:git])}"
264+
)
265+
end
266+
end
267+
225268
defp get_lock(opts) do
226269
%{rev: rev} = get_rev_info()
227270
{:git, opts[:git], rev, get_lock_opts(opts)}
@@ -238,7 +281,7 @@ defmodule Mix.SCM.Git do
238281
defp get_lock_rev(_, _), do: nil
239282

240283
defp get_lock_opts(opts) do
241-
lock_opts = Keyword.take(opts, [:branch, :ref, :tag, :sparse, :subdir])
284+
lock_opts = Keyword.take(opts, [:branch, :ref, :tag, :sparse, :subdir, :depth])
242285

243286
if opts[:submodules] do
244287
lock_opts ++ [submodules: true]
@@ -248,11 +291,7 @@ defmodule Mix.SCM.Git do
248291
end
249292

250293
defp get_opts_rev(opts) do
251-
if branch = opts[:branch] do
252-
"origin/#{branch}"
253-
else
254-
opts[:ref] || opts[:tag]
255-
end
294+
opts[:branch] || opts[:ref] || opts[:tag]
256295
end
257296

258297
defp redact_uri(git) do
@@ -282,6 +321,8 @@ defmodule Mix.SCM.Git do
282321
end
283322

284323
defp default_branch() do
324+
# Note: the `set-head -a` command requires the remote reference to be
325+
# fetched first.
285326
git!(["--git-dir=.git", "remote", "set-head", "origin", "-a"])
286327
"origin/HEAD"
287328
end
@@ -328,9 +369,17 @@ defmodule Mix.SCM.Git do
328369
end
329370
end
330371

331-
# Also invoked by lib/mix/test/test_helper.exs
372+
# Invoked by lib/mix/test/test_helper.exs
332373
@doc false
333-
def git_version do
374+
def unsupported_options do
375+
git_version = git_version()
376+
377+
[]
378+
|> Kernel.++(if git_version < @min_git_version_sparse, do: [:sparse], else: [])
379+
|> Kernel.++(if git_version < @min_git_version_depth, do: [:depth], else: [])
380+
end
381+
382+
defp git_version do
334383
case Mix.State.fetch(:git_version) do
335384
{:ok, version} ->
336385
version
@@ -354,6 +403,10 @@ defmodule Mix.SCM.Git do
354403
|> List.to_tuple()
355404
end
356405

406+
defp format_version(version) do
407+
version |> Tuple.to_list() |> Enum.join(".")
408+
end
409+
357410
defp to_integer(string) do
358411
{int, _} = Integer.parse(string)
359412
int

lib/mix/lib/mix/tasks/deps.ex

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -120,6 +120,10 @@ defmodule Mix.Tasks.Deps do
120120
* `:subdir` - (since v1.13.0) search for the project in the given directory
121121
relative to the git checkout. This is similar to `:sparse` option but instead
122122
of a doing a sparse checkout it does a full checkout.
123+
* `:depth` - (since v1.17.0) creates a shallow clone of the Git repository,
124+
limiting the history to the specified number of commits. This can significantly
125+
improve clone speed for large repositories when full history is not needed.
126+
The value must be a positive integer, typically `1`.
123127
124128
If your Git repository requires authentication, such as basic username:password
125129
HTTP authentication via URLs, it can be achieved via Git configuration, keeping

lib/mix/test/mix/scm/git_test.exs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,7 @@ defmodule Mix.SCM.GitTest do
3232
"https://github.com/elixir-lang/some_dep.git - v1"
3333

3434
assert Mix.SCM.Git.format(Keyword.put(opts, :branch, "b")) ==
35-
"https://github.com/elixir-lang/some_dep.git - origin/b"
35+
"https://github.com/elixir-lang/some_dep.git - b"
3636

3737
assert Mix.SCM.Git.format(Keyword.put(opts, :ref, "abcdef")) ==
3838
"https://github.com/elixir-lang/some_dep.git - abcdef"

lib/mix/test/mix/tasks/deps.git_test.exs

Lines changed: 201 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -478,6 +478,207 @@ defmodule Mix.Tasks.DepsGitTest do
478478
purge([GitRepo, GitRepo.MixProject])
479479
end
480480

481+
describe "Git depth option" do
482+
@describetag :git_depth
483+
484+
test "gets and updates Git repos with depth option" do
485+
Process.put(:git_repo_opts, depth: 1)
486+
487+
in_fixture("no_mixfile", fn ->
488+
Mix.Project.push(GitApp)
489+
490+
Mix.Tasks.Deps.Get.run([])
491+
message = "* Getting git_repo (#{fixture_path("git_repo")})"
492+
assert_received {:mix_shell, :info, [^message]}
493+
assert_shallow("deps/git_repo", 1)
494+
495+
# Expand depth
496+
update_dep(depth: 2)
497+
Mix.Tasks.Deps.Get.run([])
498+
assert_shallow("deps/git_repo", 2)
499+
500+
# Reduce depth
501+
update_dep(depth: 1)
502+
Mix.Tasks.Deps.Get.run([])
503+
assert_shallow("deps/git_repo", 1)
504+
end)
505+
end
506+
507+
test "with tag" do
508+
Process.put(:git_repo_opts, depth: 1, tag: "with_module")
509+
510+
in_fixture("no_mixfile", fn ->
511+
Mix.Project.push(GitApp)
512+
513+
Mix.Tasks.Deps.Get.run([])
514+
message = "* Getting git_repo (#{fixture_path("git_repo")} - with_module)"
515+
assert_received {:mix_shell, :info, [^message]}
516+
assert_shallow("deps/git_repo", 1)
517+
end)
518+
end
519+
520+
test "with branch" do
521+
Process.put(:git_repo_opts, depth: 1, branch: "main")
522+
523+
in_fixture("no_mixfile", fn ->
524+
Mix.Project.push(GitApp)
525+
526+
Mix.Tasks.Deps.Get.run([])
527+
message = "* Getting git_repo (#{fixture_path("git_repo")} - main)"
528+
assert_received {:mix_shell, :info, [^message]}
529+
assert_shallow("deps/git_repo", 1)
530+
end)
531+
end
532+
533+
test "with ref" do
534+
[last, _ | _] = get_git_repo_revs("git_repo")
535+
536+
Process.put(:git_repo_opts, depth: 1, ref: last)
537+
538+
in_fixture("no_mixfile", fn ->
539+
Mix.Project.push(GitApp)
540+
541+
Mix.Tasks.Deps.Get.run([])
542+
message = "* Getting git_repo (#{fixture_path("git_repo")} - #{last})"
543+
assert_received {:mix_shell, :info, [^message]}
544+
assert_shallow("deps/git_repo", 1)
545+
end)
546+
end
547+
548+
test "changing refspec updates retaining depth" do
549+
[last, first | _] = get_git_repo_revs("git_repo")
550+
551+
Process.put(:git_repo_opts, ref: first, depth: 1)
552+
553+
in_fixture("no_mixfile", fn ->
554+
Mix.Project.push(GitApp)
555+
556+
Mix.Tasks.Deps.Get.run([])
557+
message = "* Getting git_repo (#{fixture_path("git_repo")} - #{first})"
558+
assert_received {:mix_shell, :info, [^message]}
559+
assert_shallow("deps/git_repo", 1)
560+
assert File.read!("mix.lock") =~ first
561+
562+
# Change refspec
563+
update_dep(ref: last, depth: 1)
564+
Mix.Tasks.Deps.Get.run([])
565+
assert_shallow("deps/git_repo", 1)
566+
assert File.read!("mix.lock") =~ last
567+
end)
568+
end
569+
570+
test "removing depth retains shallow repository" do
571+
# For compatibility and simplicity, we follow Git's behavior and do not
572+
# attempt to unshallow an existing repository. This should not be a
573+
# problem, because all we guarantee is that the correct source code is
574+
# available whenever mix.exs or mix.lock change. If one wanted to have a
575+
# full clone, they can always run `deps.clean` and `deps.get` again.
576+
Process.put(:git_repo_opts, depth: 1)
577+
578+
in_fixture("no_mixfile", fn ->
579+
Mix.Project.push(GitApp)
580+
581+
Mix.Tasks.Deps.Get.run([])
582+
message = "* Getting git_repo (#{fixture_path("git_repo")})"
583+
assert_received {:mix_shell, :info, [^message]}
584+
assert_shallow("deps/git_repo", 1)
585+
586+
# Remove depth
587+
update_dep([])
588+
Mix.Tasks.Deps.Get.run([])
589+
refute File.read!("mix.lock") =~ "depth:"
590+
assert File.exists?("deps/git_repo/.git/shallow")
591+
592+
assert System.cmd("git", ~w[--git-dir=deps/git_repo/.git rev-list --count HEAD]) ==
593+
{"1\n", 0}
594+
end)
595+
end
596+
597+
@tag :git_sparse
598+
test "with sparse checkout" do
599+
Process.put(:git_repo_opts, sparse: "sparse_dir", depth: 1)
600+
601+
in_fixture("no_mixfile", fn ->
602+
Mix.Project.push(GitApp)
603+
604+
Mix.Tasks.Deps.Get.run([])
605+
message = "* Getting git_repo (#{fixture_path("git_repo")})"
606+
assert_received {:mix_shell, :info, [^message]}
607+
assert_shallow("deps/git_repo", 1)
608+
609+
refute File.exists?("deps/git_repo/mix.exs")
610+
assert File.exists?("deps/git_repo/sparse_dir/mix.exs")
611+
assert File.read!("mix.lock") =~ "sparse: \"sparse_dir\""
612+
end)
613+
end
614+
615+
test "with subdir" do
616+
Process.put(:git_repo_opts, subdir: "sparse_dir", depth: 1)
617+
618+
in_fixture("no_mixfile", fn ->
619+
Mix.Project.push(GitApp)
620+
621+
Mix.Tasks.Deps.Get.run([])
622+
message = "* Getting git_repo (#{fixture_path("git_repo")})"
623+
assert_received {:mix_shell, :info, [^message]}
624+
assert_shallow("deps/git_repo", 1)
625+
626+
assert File.exists?("deps/git_repo/mix.exs")
627+
assert File.exists?("deps/git_repo/sparse_dir/mix.exs")
628+
assert File.read!("mix.lock") =~ "subdir: \"sparse_dir\""
629+
end)
630+
end
631+
632+
test "does not affect submodules depth" do
633+
# The expectation is that we can add an explicit option in the future,
634+
# just like git-clone has `--shallow-submodules`.
635+
Process.put(:git_repo_opts, submodules: true, depth: 1)
636+
637+
in_fixture("no_mixfile", fn ->
638+
Mix.Project.push(GitApp)
639+
640+
Mix.Tasks.Deps.Get.run([])
641+
message = "* Getting git_repo (#{fixture_path("git_repo")})"
642+
assert_received {:mix_shell, :info, [^message]}
643+
assert_shallow("deps/git_repo", 1)
644+
645+
assert File.read!("mix.lock") =~ "submodules: true"
646+
# TODO: assert submodule is not shallow. This would likely require
647+
# changes to the fixtures. Apparently, not even the submodules-specific
648+
# tests check that the cloned repo contains submodules as expected.
649+
end)
650+
end
651+
652+
defp update_dep(git_repo_opts) do
653+
# Flush the errors we got, move to a clean slate
654+
Mix.shell().flush()
655+
Mix.Task.clear()
656+
Process.put(:git_repo_opts, git_repo_opts)
657+
Mix.Project.pop()
658+
Mix.Project.push(GitApp)
659+
end
660+
661+
defp assert_shallow(repo_path, depth) do
662+
assert File.read!("mix.lock") =~ "depth: #{depth}"
663+
664+
# Check if the repository is a shallow clone
665+
assert File.exists?(repo_path <> "/.git/shallow")
666+
667+
# Check the number of commits in the current branch.
668+
#
669+
# We could consider all branches with `git rev-list --count --all`, as in
670+
# practice there should be only a single branch. However, the test fixture
671+
# sets up two branches, and that brings us to an interesting situation:
672+
# instead of guaranteeing that the `:depth` option would keep the
673+
# repository lean even after refspec changes, we only guarantee the number
674+
# of commits in the current branch, perhaps leaving more objects around
675+
# than strictly necessary. This allows us to keep the implementation
676+
# simple, while still providing a reasonable guarantee.
677+
assert System.cmd("git", ~w[--git-dir=#{repo_path}/.git rev-list --count HEAD]) ==
678+
{"#{depth}\n", 0}
679+
end
680+
end
681+
481682
defp refresh(post_config) do
482683
%{name: name, file: file} = Mix.Project.pop()
483684
Mix.ProjectStack.post_config(post_config)

0 commit comments

Comments
 (0)