Skip to content

Commit bab4c04

Browse files
committed
rev_store: document and improve API
Signed-off-by: Ali Caglayan <[email protected]>
1 parent 6ef1cce commit bab4c04

File tree

3 files changed

+104
-21
lines changed

3 files changed

+104
-21
lines changed

src/dune_pkg/opamUrl0.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -46,7 +46,7 @@ let classify url loc =
4646

4747
include Comparable.Make (T)
4848

49-
let remote t ~loc rev_store = Rev_store.remote rev_store ~url:(loc, OpamUrl.base_url t)
49+
let remote t ~loc rev_store = Rev_store.remote rev_store ~loc ~url:(OpamUrl.base_url t)
5050

5151
type resolve =
5252
| Resolved of Rev_store.Object.resolved

src/dune_pkg/rev_store.ml

Lines changed: 22 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -128,12 +128,20 @@ module File = struct
128128
end
129129

130130
module Remote = struct
131-
type nonrec t =
131+
type t =
132132
{ url : string
133133
; default_branch : Object.resolved option Fiber.t
134134
; refs : Object.resolved String.Map.t Fiber.t
135135
}
136136

137+
let to_dyn { url; default_branch; refs } =
138+
Dyn.record
139+
[ "url", Dyn.string url
140+
; "default_branch", Dyn.opaque default_branch
141+
; "refs", Dyn.opaque refs
142+
]
143+
;;
144+
137145
let default_branch t = t.default_branch
138146
end
139147

@@ -145,6 +153,18 @@ type t =
145153
; present_objects : (Object.t, unit) Table.t
146154
}
147155

156+
let to_dyn { dir; remotes; object_mutexes; present_objects } =
157+
Dyn.record
158+
[ (* This is an external path, so we relativize to sanitize. We don't use
159+
[Path.to_dyn] since it wouldn't be correct and therefore confusing. *)
160+
"dir", Path.Expert.try_localize_external dir |> Path.to_string |> Dyn.string
161+
; "remotes", Table.to_list remotes |> Dyn.list (Dyn.pair Dyn.string Remote.to_dyn)
162+
; "object_mutexes", Dyn.opaque object_mutexes
163+
; ( "present_objects"
164+
, Table.to_list present_objects |> Dyn.list (Dyn.pair Object.to_dyn Dyn.unit) )
165+
]
166+
;;
167+
148168
let with_mutex t obj ~f =
149169
let* () = Fiber.return () in
150170
let mutex =
@@ -843,7 +863,7 @@ let remote =
843863
let head_mark, head = Re.mark (Re.str "HEAD") in
844864
let ref = Re.(group (seq [ str "refs/"; rep1 any ])) in
845865
let re = Re.(compile @@ seq [ bol; group hash; rep1 space; alt [ head; ref ] ]) in
846-
fun t ~url:(url_loc, url) ->
866+
fun t ~loc:url_loc ~url ->
847867
let f url =
848868
let command = [ "ls-remote"; url ] in
849869
let refs =

src/dune_pkg/rev_store.mli

Lines changed: 81 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,32 @@
11
open Stdune
22

3+
(** * The Revision Store
4+
5+
The revision store is a single shared bare Git repository acting as a cache for
6+
packages and package repositories.
7+
8+
Git is used as a content-addressable file system. File content of both package
9+
repositories and opam repositories live here. Having a single place
10+
is advantageous because it saves space.
11+
12+
Dune is able to lookup any stored Git repository by its revision and see all
13+
the files that exist within. Those files can then have their contents
14+
fetched. *)
15+
16+
(** Abstract handle to the shared revision store. *)
317
type t
418

19+
val to_dyn : t -> Dyn.t
20+
21+
(** Get the revision store and initialise if it hasn't been already. *)
22+
val get : t Fiber.t
23+
24+
(* CR-soon Alizter: Remove this when we are able to set the XDG_HOME
25+
directories in the tests. *)
26+
val load_or_create : dir:Path.t -> t Fiber.t
27+
528
module Object : sig
6-
(** A git object that can exist in storage *)
29+
(** A git object that can exist in storage. *)
730
type t
831

932
(** An object that definitely exists in the storage, but might still not be
@@ -12,44 +35,84 @@ module Object : sig
1235

1336
val of_sha1 : string -> t option
1437
val to_hex : t -> string
15-
val equal : t -> t -> bool
16-
val to_dyn : t -> Dyn.t
1738
end
1839

1940
module File : sig
41+
(** A file entry at a particular revision. May be a direct blob or a redirect
42+
into a submodules file. *)
2043
type t
2144

22-
val path : t -> Path.Local.t
2345
val to_dyn : t -> Dyn.t
2446

47+
(** Path relative to the repository root at the given revision. *)
48+
val path : t -> Path.Local.t
49+
2550
module Set : Set.S with type elt = t
2651
end
2752

53+
(** [content_of_files t files] fetches the content of a list of [files] in one
54+
batch. It returns a list of strings consisting of the content of the
55+
corresponding files. *)
56+
val content_of_files : t -> File.t list -> string list Fiber.t
57+
58+
module Remote : sig
59+
(** A git remote repository known to the revision store. *)
60+
type t
61+
62+
val to_dyn : t -> Dyn.t
63+
64+
(** The [default_branch] of a remote repository. *)
65+
val default_branch : t -> Object.resolved option Fiber.t
66+
end
67+
68+
(** [remote ~loc ~url] gets the remote pointed to by [url] and makes
69+
the revision store aware of it. This is idempotent and is memoized by
70+
[url]. *)
71+
val remote : t -> loc:Loc.t -> url:string -> Remote.t
72+
2873
module At_rev : sig
74+
(** An immutable Git repository view at a specific commit. *)
2975
type t
3076

31-
module Config : sig
32-
val parse : string -> (string * string option * string * string) option
33-
end
77+
val equal : t -> t -> bool
3478

79+
(** The underlying commit. *)
3580
val rev : t -> Object.t
81+
82+
(** Read file content at this revision. Returns [None] if the file does not
83+
exist or is not a blob. *)
3684
val content : t -> Path.Local.t -> string option Fiber.t
85+
86+
(** [directory_entries t ~recursive path] lists the files under [path]. If
87+
[recursive] then lists the full subtree. Symbolic links are returned as
88+
files. *)
3789
val directory_entries : t -> recursive:bool -> Path.Local.t -> File.Set.t
38-
val equal : t -> t -> bool
39-
val check_out : t -> target:Path.t -> unit Fiber.t
40-
end
4190

42-
module Remote : sig
43-
(** handle representing a particular git repository *)
44-
type t
91+
(** [check_out t ~target] materialises the entire tree into [target]
92+
including any submodules. *)
93+
val check_out : t -> target:Path.t -> unit Fiber.t
4594

46-
val default_branch : t -> Object.resolved option Fiber.t
95+
(** For testing only. *)
96+
module Config : sig
97+
val parse : string -> (string * string option * string * string) option
98+
end
4799
end
48100

49-
val remote : t -> url:Loc.t * string -> Remote.t
101+
(** Resolve the revision in the given remote. The [revision] can be any
102+
accepted reference name, branch, tag or Sha1 by Git.
103+
104+
If a reference name is resolved form the remote, the commit is fetched. If
105+
the revision is already present, no network I/O is performed. Returns
106+
[None] if the remote reports "not found". Raises a user error if the
107+
reference is ambigious. *)
50108
val resolve_revision : t -> Remote.t -> revision:string -> Object.resolved option Fiber.t
51-
val content_of_files : t -> File.t list -> string list Fiber.t
52-
val load_or_create : dir:Path.t -> t Fiber.t
53-
val get : t Fiber.t
109+
110+
(** [fetch_object t remote object] ensures that an [object] from the [remote]
111+
is present in the revision store [t]. If the reviison is already present,
112+
no network I/O is performed. Returns [None] if the remote reports "not
113+
found". *)
54114
val fetch_object : t -> Remote.t -> Object.t -> At_rev.t option Fiber.t
115+
116+
(** Fetch the file contents of the repository at the given revision into the
117+
store and return the repository view. *)
55118
val fetch_resolved : t -> Remote.t -> Object.resolved -> At_rev.t Fiber.t

0 commit comments

Comments
 (0)