Skip to content

Commit

Permalink
Merge pull request #5888 from moyodiallo/full-fetch
Browse files Browse the repository at this point in the history
`opam source --dev` fetching git repositories without `--depth 1`
  • Loading branch information
kit-ty-kate authored Apr 5, 2024
2 parents f013288 + 10882b2 commit f7def5c
Show file tree
Hide file tree
Showing 15 changed files with 111 additions and 33 deletions.
3 changes: 3 additions & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -61,6 +61,7 @@ users)
## Exec

## Source
* Using `opam source --dev` with git repositories doesn't fetch with `--depth 1` [#5888 @moyodiallo - fix #5061]

## Lint
* Add warning 69: Warn for new syntax when package name in variable in string interpolation contains several '+' [#5840 @rjbou]
Expand Down Expand Up @@ -151,6 +152,7 @@ users)
+ Add a test testing showing the current behaviour of opam with variable expansion, in particular when the package contains pluses [#5840 @kit-ty-kate]
* Update lint test: W41 [#5840 @rjbou]
* Update lint test: W41 and W69 [#5840 @rjbou]
* Add test in `source` to show retrieval of full git repository history when retrieved with `opam source --dev` [#5888 @moyodiallo @rjbou @kit-ty-kate]

### Engine

Expand All @@ -177,6 +179,7 @@ users)
* `OpamArg.apply_global_options`: load MSYS2 Cygwin binary path too [#5843 @rjbou]

## opam-repository
* `OpamRepositoryBackend.S.pull_url`, `OpamVCS.fetch`, `OpamRepository.pull_tree`: add `full_fetch` optional argument to pull full history if url is a `VCS` [#5888 @moyodiallo - fix #5061]

## opam-state
* `OpamEnv.env_expansion`: Fix detection of out-of-date environment variables, a filter predicate was inverted [#5837 @dra27]
Expand Down
1 change: 1 addition & 0 deletions src/client/opamCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -3696,6 +3696,7 @@ let source cli =
match
OpamProcess.Job.run
(OpamRepository.pull_tree
~full_fetch:true
~cache_dir:(OpamRepositoryPath.download_cache
OpamStateConfig.(!r.root_dir))
?subpath
Expand Down
2 changes: 1 addition & 1 deletion src/repository/opamDarcs.ml
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,7 @@ module VCS = struct
(* Marks the current state, in the form of a reversing patch on top of the
fetched state *)

let fetch ?cache_dir:_ ?subpath:_ repo_root repo_url =
let fetch ?full_fetch:_ ?cache_dir:_ ?subpath:_ repo_root repo_url =
(* Just do a fresh pull into a temp directory, and replace _darcs/
There is no easy way to diff or make sure darcs forgets about local
patches otherwise. *)
Expand Down
7 changes: 5 additions & 2 deletions src/repository/opamGit.ml
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,7 @@ module VCS : OpamVCS.VCS = struct
| Some h -> "refs/remotes/opam-ref-"^h
| None -> "refs/remotes/opam-ref"

let fetch ?cache_dir ?subpath repo_root repo_url =
let fetch ?(full_fetch = false) ?cache_dir ?subpath repo_root repo_url =
(match subpath with
| Some sp ->
git repo_root [ "config"; "--local"; "core.sparseCheckout"; "true" ]
Expand Down Expand Up @@ -95,7 +95,10 @@ module VCS : OpamVCS.VCS = struct
OpamFilename.write alternates
(OpamFilename.Dir.to_string (cache / "objects")))
global_cache;
git repo_root [ "fetch" ; "-q"; origin; "--update-shallow"; "--depth=1"; refspec ]
(if full_fetch then
git repo_root [ "fetch" ; "-q"; origin; "--update-shallow"; refspec ]
else
git repo_root [ "fetch" ; "-q"; origin; "--update-shallow"; "--depth=1"; refspec ])
@@> fun r ->
if OpamProcess.check_success_and_cleanup r then
let refspec =
Expand Down
2 changes: 1 addition & 1 deletion src/repository/opamHTTP.ml
Original file line number Diff line number Diff line change
Expand Up @@ -68,7 +68,7 @@ module B = struct

let repo_update_complete _ _ = Done ()

let pull_url ?cache_dir:_ ?subpath:_ dirname checksum remote_url =
let pull_url ?full_fetch:_ ?cache_dir:_ ?subpath:_ dirname checksum remote_url =
log "pull-file into %a: %a"
(slog OpamFilename.Dir.to_string) dirname
(slog OpamUrl.to_string) remote_url;
Expand Down
2 changes: 1 addition & 1 deletion src/repository/opamHg.ml
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@ module VCS = struct
| None -> mark_prefix
| Some fragment -> mark_prefix ^ "-" ^ fragment

let fetch ?cache_dir:_ ?subpath:_ repo_root repo_url =
let fetch ?full_fetch:_ ?cache_dir:_ ?subpath:_ repo_root repo_url =
let src = OpamUrl.base_url repo_url in
let rev = OpamStd.Option.default "default" repo_url.OpamUrl.hash in
let mark = mark_from_url repo_url in
Expand Down
2 changes: 1 addition & 1 deletion src/repository/opamLocal.ml
Original file line number Diff line number Diff line change
Expand Up @@ -190,7 +190,7 @@ module B = struct

let repo_update_complete _ _ = Done ()

let pull_url ?cache_dir:_ ?subpath local_dirname _checksum remote_url =
let pull_url ?full_fetch:_ ?cache_dir:_ ?subpath local_dirname _checksum remote_url =
let local_dirname = OpamFilename.SubPath.(local_dirname /? subpath) in
OpamFilename.mkdir local_dirname;
let dir = OpamFilename.Dir.to_string local_dirname in
Expand Down
29 changes: 17 additions & 12 deletions src/repository/opamRepository.ml
Original file line number Diff line number Diff line change
Expand Up @@ -164,7 +164,8 @@ let validate_and_add_to_cache label url cache_dir file checksums =

(* [cache_dir] used to add to cache only *)
let pull_from_upstream
label ?(working_dir=false) ?subpath cache_dir destdir checksums url =
label ?full_fetch ?(working_dir=false) ?subpath
cache_dir destdir checksums url =
let module B = (val url_backend url: OpamRepositoryBackend.S) in
let cksum = match checksums with [] -> None | c::_ -> Some c in
let text =
Expand Down Expand Up @@ -206,7 +207,7 @@ let pull_from_upstream
)
else url, B.pull_url
in
pull ?cache_dir ?subpath destdir cksum url
pull ?full_fetch ?cache_dir ?subpath destdir cksum url
)
@@| function
| (Result (Some file) | Up_to_date (Some file)) as ret ->
Expand All @@ -219,14 +220,17 @@ let pull_from_upstream
| (Result None | Up_to_date None) as ret -> ret
| Not_available _ as na -> na

let pull_from_mirrors label ?working_dir ?subpath cache_dir destdir checksums urls =
let pull_from_mirrors label ?full_fetch ?working_dir ?subpath
cache_dir destdir checksums urls =
let rec aux = function
| [] -> invalid_arg "pull_from_mirrors: empty mirror list"
| [url] ->
pull_from_upstream label ?working_dir ?subpath cache_dir destdir checksums url
pull_from_upstream label ?full_fetch ?working_dir ?subpath
cache_dir destdir checksums url
@@| fun r -> url, r
| url::mirrors ->
pull_from_upstream label ?working_dir ?subpath cache_dir destdir checksums url
pull_from_upstream label ?full_fetch ?working_dir ?subpath
cache_dir destdir checksums url
@@+ function
| Not_available (_,s) ->
OpamConsole.warning "%s: download of %s failed (%s), trying mirror"
Expand All @@ -246,7 +250,7 @@ let pull_from_mirrors label ?working_dir ?subpath cache_dir destdir checksums ur

(* handle subpathes *)
let pull_tree_t
?cache_dir ?(cache_urls=[]) ?working_dir
?full_fetch ?cache_dir ?(cache_urls=[]) ?working_dir
dirnames checksums remote_urls =
let extract_archive =
let fallback success = function
Expand Down Expand Up @@ -342,13 +346,13 @@ let pull_tree_t
let pull label checksums remote_urls =
match dirnames with
| [ label, local_dirname, subpath ] ->
pull_from_mirrors label ?working_dir ?subpath cache_dir local_dirname
checksums remote_urls
pull_from_mirrors label ?full_fetch ?working_dir ?subpath
cache_dir local_dirname checksums remote_urls
@@| fun (url, res) ->
(OpamUrl.to_string_w_subpath subpath url),
res
| _ ->
pull_from_mirrors label ?working_dir cache_dir tmpdir
pull_from_mirrors label ?full_fetch ?working_dir cache_dir tmpdir
checksums remote_urls
@@| fun (url, res) -> OpamUrl.to_string url, res
in
Expand All @@ -361,10 +365,11 @@ let pull_tree_t
| _, (Not_available _ as na) -> Done na


let pull_tree label ?cache_dir ?(cache_urls=[]) ?working_dir ?subpath
let pull_tree label
?full_fetch ?cache_dir ?(cache_urls=[]) ?working_dir ?subpath
local_dirname =
pull_tree_t ?cache_dir ~cache_urls ?working_dir
[label, local_dirname, subpath]
pull_tree_t ?full_fetch ?cache_dir ~cache_urls ?working_dir
[label, local_dirname, subpath]

let pull_shared_tree ?cache_dir ?(cache_urls=[]) dirnames checksums remote_urls =
pull_tree_t ?cache_dir ~cache_urls dirnames checksums remote_urls
Expand Down
9 changes: 6 additions & 3 deletions src/repository/opamRepository.mli
Original file line number Diff line number Diff line change
Expand Up @@ -42,10 +42,13 @@ val pull_shared_tree:
(string * OpamFilename.Dir.t * subpath option) list -> OpamHash.t list ->
url list -> string download OpamProcess.job

(* Same as [pull_shared_tree], but for a unique label/dirname. *)
(* Same as [pull_shared_tree], but for a unique label/dirname.
If [full_fetch] is true, VCS repository is retrieved with full history (by
default, no history). *)
val pull_tree:
string -> ?cache_dir:dirname -> ?cache_urls:url list -> ?working_dir:bool ->
?subpath:subpath -> dirname -> OpamHash.t list -> url list ->
string -> ?full_fetch:bool -> ?cache_dir:dirname -> ?cache_urls:url list ->
?working_dir:bool -> ?subpath:subpath ->
dirname -> OpamHash.t list -> url list ->
string download OpamProcess.job

(** Same as [pull_tree], but for fetching a single file. *)
Expand Down
1 change: 1 addition & 0 deletions src/repository/opamRepositoryBackend.ml
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,7 @@ type update =
module type S = sig
val name: OpamUrl.backend
val pull_url:
?full_fetch:bool ->
?cache_dir:dirname -> ?subpath:subpath -> dirname -> OpamHash.t option -> url ->
filename option download OpamProcess.job
val fetch_repo_update:
Expand Down
13 changes: 10 additions & 3 deletions src/repository/opamRepositoryBackend.mli
Original file line number Diff line number Diff line change
Expand Up @@ -31,8 +31,8 @@ module type S = sig

val name: OpamUrl.backend

(** [pull_url local_dir checksum remote_url] pulls the contents of
[remote_url] into [local_dir].
(** [pull_url ?full_fetch ?cache_dir ?subpath local_dir checksum remote_url]
pulls the contents of [remote_url] into [local_dir].
Two kinds of results are allowed:
Expand All @@ -43,8 +43,15 @@ module type S = sig
been synchronised with its own, and [None] is returned
[checksum] can be used for retrieval but is NOT checked by this
function. *)
function.
If [full_fetch] is set to true, VCS repository is retrieved with full
history (by default, no history).
If [cache_dir] is given, the directory is used by VCS tool as a its cache
directory.
If [subpath] is given, only that [subpath] of the url is retrieved. *)
val pull_url:
?full_fetch:bool ->
?cache_dir:dirname -> ?subpath:subpath -> dirname -> OpamHash.t option ->
url -> filename option download OpamProcess.job

Expand Down
13 changes: 7 additions & 6 deletions src/repository/opamVCS.ml
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ module type VCS = sig
val exists: dirname -> bool
val init: dirname -> url -> unit OpamProcess.job
val fetch:
?cache_dir:dirname -> ?subpath:subpath -> dirname -> url ->
?full_fetch:bool -> ?cache_dir:dirname -> ?subpath:subpath -> dirname -> url ->
unit OpamProcess.job
val reset_tree: dirname -> url -> unit OpamProcess.job
val patch_applied: dirname -> url -> unit OpamProcess.job
Expand All @@ -42,11 +42,12 @@ module Make (VCS: VCS) = struct
let name = VCS.name

let fetch_repo_update repo_name ?cache_dir repo_root repo_url =
let full_fetch = false in
if VCS.exists repo_root then
OpamProcess.Job.catch (fun e -> Done (OpamRepositoryBackend.Update_err e))
@@ fun () ->
OpamRepositoryBackend.job_text repo_name "sync"
(VCS.fetch ?cache_dir repo_root repo_url)
(VCS.fetch ~full_fetch ?cache_dir repo_root repo_url)
@@+ fun () ->
OpamRepositoryBackend.job_text repo_name "diff"
(VCS.diff repo_root repo_url)
Expand All @@ -62,7 +63,7 @@ module Make (VCS: VCS) = struct
(VCS.init repo_root repo_url)
@@+ fun () ->
OpamRepositoryBackend.job_text repo_name "sync"
(VCS.fetch ?cache_dir repo_root repo_url)
(VCS.fetch ~full_fetch ?cache_dir repo_root repo_url)
@@+ fun () ->
let tmpdir = OpamFilename.Dir.(of_string (to_string repo_root ^".new")) in
OpamFilename.copy_dir ~src:repo_root ~dst:tmpdir;
Expand All @@ -75,7 +76,7 @@ module Make (VCS: VCS) = struct
VCS.patch_applied dirname url @@+ fun () ->
Done ()

let pull_url ?cache_dir ?subpath dirname checksum url =
let pull_url ?full_fetch ?cache_dir ?subpath dirname checksum url =
if checksum <> None then invalid_arg "VC pull_url doesn't allow checksums";
OpamProcess.Job.catch
(fun e ->
Expand All @@ -87,7 +88,7 @@ module Make (VCS: VCS) = struct
@@ fun () ->
if VCS.exists dirname then
VCS.clean dirname @@+ fun () ->
VCS.fetch ?cache_dir ?subpath dirname url @@+ fun () ->
VCS.fetch ?full_fetch ?cache_dir ?subpath dirname url @@+ fun () ->
VCS.is_up_to_date ?subpath dirname url @@+ function
| true -> Done (Up_to_date None)
| false ->
Expand All @@ -96,7 +97,7 @@ module Make (VCS: VCS) = struct
else
(OpamFilename.mkdir dirname;
VCS.init dirname url @@+ fun () ->
VCS.fetch ?cache_dir ?subpath dirname url @@+ fun () ->
VCS.fetch ?full_fetch ?cache_dir ?subpath dirname url @@+ fun () ->
VCS.reset_tree dirname url @@+ fun () ->
Done (Result None))

Expand Down
13 changes: 10 additions & 3 deletions src/repository/opamVCS.mli
Original file line number Diff line number Diff line change
Expand Up @@ -27,10 +27,17 @@ module type VCS = sig
(** Fetch changes from upstream. This is supposed to put the changes
in a staging area.
Be aware that the remote URL might have been changed, so make sure
to update accordingly. *)
to update accordingly.
If [full_fetch] is set to true, VCS repository is retrieved with full
history (by default, no history).
If [cache_dir] is given, the directory is used by VCS tool as a its cache
directory.
If [subpath] is given, only that [subpath] of the url is retrieved. *)
val fetch:
?cache_dir:dirname -> ?subpath:subpath -> dirname -> url ->
unit OpamProcess.job
?full_fetch:bool -> ?cache_dir:dirname -> ?subpath:subpath
-> dirname -> url
-> unit OpamProcess.job

(** Reset the master branch of the repository to match the remote repository
state. This might still fetch more data (git submodules...), so is
Expand Down
19 changes: 19 additions & 0 deletions tests/reftests/repository.test
Original file line number Diff line number Diff line change
Expand Up @@ -588,3 +588,22 @@ first --
<><> Repository configuration for switch repos ><><><><><><><><><><><><><><><><>
1 oper3 file://${BASEDIR}/OPER3
2 oper file://${BASEDIR}/OPER3
### : Ensure that git repository is retrieved not with full history
### OPAMREPOSITORYTARRING=0
### <TMCS/repo>
opam-version: "2.0"
### <TMCS/packages/first/first.1/opam>
opam-version: "2.0"
### git -C ./TMCS init -q
### git -C ./TMCS config core.autocrlf false
### git -C ./TMCS add repo
### git -C ./TMCS add packages/first
### git -C ./TMCS commit -qm "init"
### git -C ./TMCS commit --allow-empty -m "second empty commit" --quiet
### git -C ./TMCS commit --allow-empty -m "thirs empty commit" --quiet
### git -C ./TMCS rev-list --all --count
3
### opam repository add to-many-commits git+file://$BASEDIR/TMCS --this-switch
[to-many-commits] Initialised
### git -C ./OPAM/repo/to-many-commits rev-list --all --count
1
28 changes: 28 additions & 0 deletions tests/reftests/source.test
Original file line number Diff line number Diff line change
Expand Up @@ -109,3 +109,31 @@ pandore.3/src/src.ml
Switch phantom and all its packages will be wiped. Are you sure? [y/n] y
### opam source pandore
Successfully extracted to ${BASEDIR}/pandore.3
### : Full retrieval of git history when --dev is given :
### git -C ./pandev commit --allow-empty -m "second empty commit" --quiet
### git -C ./pandev rev-list --all --count
2
### <pkg:pandore.4>
opam-version: "2.0"
### <mkurl.sh>
p=pandore.4
file="REPO/packages/${p%.*}/$p/opam"
basedir=`echo $BASEDIR | sed "s/\\\\\\\\/\\\\\\\\\\\\\\\\/g"`
echo "url {" >> $file
echo "git: \"$basedir/pandev\"" >> $file
echo "}" >> $file
echo "dev-repo: \"git+file://${basedir}/pandev\"" >> $file
### sh mkurl.sh
### opam update

<><> Updating package repositories ><><><><><><><><><><><><><><><><><><><><><><>
[default] synchronised from file://${BASEDIR}/REPO
Now run 'opam upgrade' to apply any package updates.
### opam source pandore.4 --dir pandore5
Successfully extracted to ${BASEDIR}/pandore5
### git -C pandore5 rev-list --all --count
1
### opam source pandore.4 --dev --dir pandore6
Successfully fetched pandore development repo to ${BASEDIR}/pandore6
### git -C pandore6 rev-list --all --count
2

0 comments on commit f7def5c

Please sign in to comment.