Skip to content

Commit

Permalink
fix magic lookup with several branches
Browse files Browse the repository at this point in the history
  • Loading branch information
rjbou committed Mar 5, 2025
1 parent a3b25a9 commit ff6dae3
Show file tree
Hide file tree
Showing 3 changed files with 28 additions and 14 deletions.
28 changes: 23 additions & 5 deletions src/client/opamPinCommand.ml
Original file line number Diff line number Diff line change
Expand Up @@ -66,7 +66,7 @@ exception Fetch_Fail of string

let get_source_definition ?version ?subpath ?locked st nv url =
let root = st.switch_global.root in
let srcdir = OpamPath.Switch.pinned_package root st.switch nv.name in
let internal_pindir = OpamPath.Switch.pinned_package root st.switch nv.name in
let fix opam =
OpamFile.OPAM.with_url url @@
(match version with
Expand All @@ -75,15 +75,31 @@ let get_source_definition ?version ?subpath ?locked st nv url =
opam
in
let open OpamProcess.Job.Op in
OpamUpdate.fetch_dev_package url srcdir ?subpath nv @@| function
OpamUpdate.fetch_dev_package url internal_pindir ?subpath nv @@+ function
| Not_available (_,s) -> raise (Fetch_Fail s)
| Up_to_date _ | Result _ ->
let srcdir =
let opam_dir_lookup () =
let u = OpamFile.URL.url url in
match OpamUrl.local_dir u, u.OpamUrl.backend with
| Some dir, #OpamUrl.version_control -> dir
| _, _ -> srcdir
| Some dir, #OpamUrl.version_control ->
let get_branch d =
let url = OpamUrl.of_string (OpamFilename.Dir.to_string d) in
OpamRepository.revision d
{ url with
OpamUrl.transport = u.transport;
backend = u.backend}
in
get_branch dir @@+ fun local_branch ->
get_branch internal_pindir @@| fun distant_branch ->
(match local_branch, distant_branch with
| Some l, Some d when OpamPackage.Version.equal l d -> dir
| Some _, Some _ -> internal_pindir
| None, Some _ -> internal_pindir
| Some _, None -> dir
| None, None -> dir)
| _, _ -> Done (internal_pindir)
in
opam_dir_lookup () @@| fun srcdir ->
let srcdir = OpamFilename.SubPath.(srcdir /? subpath) in
match OpamPinned.find_opam_file_in_source ?locked nv.name srcdir with
| None -> None
Expand Down Expand Up @@ -455,6 +471,7 @@ and source_pin
(slog (OpamStd.Option.to_string OpamPackage.Version.to_string)) version
(slog (OpamStd.Option.to_string ~none:"none"
(OpamUrl.to_string_w_subpath subpath))) target_url;
(* OpamConsole.error "I have opam_opt : %s" (OpamStd.Option.to_string OpamFile.OPAM.write_to_string opam_opt); *)
(* let installed_version =
try
Some (OpamPackage.version
Expand Down Expand Up @@ -534,6 +551,7 @@ and source_pin
(OpamStd.Option.to_string OpamUrl.to_string target_url)
(OpamStd.Format.itemize (fun x -> x) [err]));
in
(* OpamConsole.error "Source def I have opam_opt : %s" (OpamStd.Option.to_string OpamFile.OPAM.write_to_string opam_opt); *)
let opam_opt = opam_opt >>| OpamFormatUpgrade.opam_file in

let nv =
Expand Down
5 changes: 4 additions & 1 deletion src/state/opamPinned.ml
Original file line number Diff line number Diff line change
Expand Up @@ -140,8 +140,11 @@ let check_locked ?locked default =
locked, Some ext)

let find_opam_file_in_source ?locked name dir =
(* OpamConsole.error "find : %s in %s" (OpamPackage.Name.to_string name) (OpamFilename.Dir.to_string dir); *)
let opt =
OpamStd.List.find_opt OpamFilename.exists
OpamStd.List.find_opt
(* (fun f -> OpamConsole.note "....%s -> %B" (OpamFilename.to_string f) (OpamFilename.exists f); OpamFilename.exists f) *)
OpamFilename.exists
(possible_definition_filenames dir name)
in
opt
Expand Down
9 changes: 1 addition & 8 deletions tests/reftests/pin.test
Original file line number Diff line number Diff line change
Expand Up @@ -1070,13 +1070,6 @@ fst
### opam pin snd ./local#snd -n
[NOTE] Package snd does not exist in opam repositories registered in the current switch.
[snd.dev] synchronised (git+file://${BASEDIR}/local#snd)
[NOTE] No package definition found for snd.dev: please complete the template
[WARNING] The opam file didn't pass validation:
error 22: Some fields are present but empty; remove or fill them: "homepage", "license", "bug_reports"
error 57: Synopsis must not be empty
warning 62: License doesn't adhere to the SPDX standard, see https://spdx.org/licenses/ : ""
Proceed anyway ('no' will re-edit)? [Y/n] y
You can edit this file again with "opam pin edit snd", export it with "opam show snd --raw"
snd is now pinned to git+file://${BASEDIR}/local#snd (version dev)
### opam show snd --field synopsis

I'm the second package

0 comments on commit ff6dae3

Please sign in to comment.