File tree Expand file tree Collapse file tree 4 files changed +15
-12
lines changed
test/expect-tests/dune_pkg Expand file tree Collapse file tree 4 files changed +15
-12
lines changed Original file line number Diff line number Diff line change @@ -52,12 +52,14 @@ type resolve =
5252 | Resolved of Rev_store.Object .resolved
5353 | Unresolved of Rev_store.Object .t
5454
55- let not_found t =
55+ let not_found ~ git_output t =
5656 let url = base_url t in
5757 let rev = rev t in
58+ let git_output = List. map ~f: Pp. verbatim git_output in
5859 Error
5960 (User_message. make
60- [ (match rev with
61+ @@ git_output
62+ @ [ (match rev with
6163 | None -> Pp. textf " default branch not found in %s" url
6264 | Some rev -> Pp. textf " revision %S not found in %s" rev url)
6365 ])
@@ -89,7 +91,7 @@ let resolve t ~loc rev_store =
8991 | `Ref revision ->
9092 Rev_store. resolve_revision rev_store remote ~revision
9193 >> | (function
92- | None -> not_found t
94+ | None -> not_found ~git_output: [] t
9395 | Some o -> Ok (Resolved o))
9496;;
9597
@@ -101,8 +103,8 @@ let fetch_revision t ~loc resolve rev_store =
101103 | Unresolved o ->
102104 Rev_store. fetch_object rev_store remote o
103105 >> | (function
104- | None -> not_found t
105- | Some rev -> Ok rev)
106+ | Error git_output -> not_found ~git_output t
107+ | Ok rev -> Ok rev)
106108;;
107109
108110let set_rev (t : t ) rev = { t with hash = Some (Rev_store.Object. to_hex rev) }
Original file line number Diff line number Diff line change @@ -1163,8 +1163,8 @@ let resolve_revision t (remote : Remote.t) ~revision =
11631163let fetch_object t (remote : Remote.t ) revision =
11641164 fetch_allow_failure t ~url: remote.url revision
11651165 >> = function
1166- | `Not_found _ -> Fiber. return None
1167- | `Fetched -> At_rev. of_rev t ~revision >> | Option. some
1166+ | `Not_found git_output -> Fiber. return ( Error git_output)
1167+ | `Fetched -> At_rev. of_rev t ~revision >> | Result. ok
11681168;;
11691169
11701170let content_of_files t files =
Original file line number Diff line number Diff line change @@ -104,10 +104,10 @@ end
104104val resolve_revision : t -> Remote .t -> revision :string -> Object .resolved option Fiber .t
105105
106106(* * [fetch_object t remote object] ensures that an [object] from the [remote]
107- is present in the revision store [t]. If the reviison is already present,
108- no network I/O is performed. Returns [None ] if the remote reports "not
109- found". *)
110- val fetch_object : t -> Remote .t -> Object .t -> At_rev .t option Fiber .t
107+ is present in the revision store [t]. If the revision is already present,
108+ no network I/O is performed. Returns [Error git_error_lines ] if the remote
109+ reports "not found". *)
110+ val fetch_object : t -> Remote .t -> Object .t -> ( At_rev .t , string list ) result Fiber .t
111111
112112(* * Fetch the file contents of the repository at the given revision into the
113113 store and return the repository view. *)
Original file line number Diff line number Diff line change @@ -117,8 +117,9 @@ let%expect_test "fetching an object twice from the store" =
117117 Rev_store.Object. of_sha1 remote_revision
118118 |> Option. value_exn
119119 |> Rev_store. fetch_object rev_store remote
120- >> | Option. value_exn
120+ >> | Result. to_option
121121 in
122+ let at_rev = Option. value_exn at_rev in
122123 Rev_store.At_rev. directory_entries at_rev ~recursive: true Path.Local. root
123124 |> Rev_store.File.Set. find ~f: (fun f ->
124125 Path.Local. equal (Rev_store.File. path f) (Path.Local. of_string file))
You can’t perform that action at this time.
0 commit comments