Skip to content

Commit

Permalink
pkg: add binary package repo (#11020)
Browse files Browse the repository at this point in the history
Adds a repo of binary packages to dune so that dev tools can be quickly
installed without the need to download and compile their entire
dependency cone on supported platforms. Currently ocamlfind and ocamllsp
are included in the repo.

Signed-off-by: Stephen Sherratt <[email protected]>
  • Loading branch information
gridbugs authored Oct 22, 2024
1 parent bd29b15 commit dbd8448
Show file tree
Hide file tree
Showing 8 changed files with 24 additions and 2 deletions.
2 changes: 1 addition & 1 deletion bin/lock_dev_tool.ml
Original file line number Diff line number Diff line change
Expand Up @@ -78,7 +78,7 @@ let solve ~dev_tool ~local_packages =
let lock_dir = Lock_dir.dev_tool_lock_dir_path dev_tool in
Memo.of_reproducible_fiber
@@ Lock.solve
workspace
(Workspace.add_repo workspace Dune_pkg.Pkg_workspace.Repository.binary_packages)
~local_packages
~project_sources:Dune_pkg.Pin_stanza.DB.empty
~solver_env_from_current_system
Expand Down
2 changes: 1 addition & 1 deletion bin/pkg/pkg_common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,7 @@ let repositories_of_lock_dir workspace ~lock_dir_path =
match Workspace.find_lock_dir workspace lock_dir_path with
| Some lock_dir -> lock_dir.repositories
| None ->
List.map Workspace.default_repositories ~f:(fun repo ->
List.map workspace.repos ~f:(fun repo ->
let name = Dune_pkg.Pkg_workspace.Repository.name repo in
let loc = Loc.none in
loc, name)
Expand Down
8 changes: 8 additions & 0 deletions src/dune_pkg/opam_repo.ml
Original file line number Diff line number Diff line change
Expand Up @@ -47,6 +47,14 @@ type t =
; serializable : Serializable.t option
}

let to_dyn { source; loc; serializable } =
Dyn.record
[ "source", Source_backend.to_dyn source
; "loc", Loc.to_dyn loc
; "serializable", Dyn.option Serializable.to_dyn serializable
]
;;

let equal { source; serializable; loc } t =
Source_backend.equal source t.source
&& Option.equal Serializable.equal serializable t.serializable
Expand Down
1 change: 1 addition & 0 deletions src/dune_pkg/opam_repo.mli
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@ module Serializable : sig
val to_dyn : t -> Dyn.t
end

val to_dyn : t -> Dyn.t
val equal : t -> t -> bool

(** [of_opam_repo_dir_path opam_repo_dir] creates a repo represented by a local
Expand Down
9 changes: 9 additions & 0 deletions src/dune_pkg/workspace.ml
Original file line number Diff line number Diff line change
Expand Up @@ -52,6 +52,15 @@ module Repository = struct
}
;;

let binary_packages =
{ name = "binary-packages"
; source =
( Loc.none
, OpamUrl.of_string "git+https://github.com/ocaml-dune/ocaml-binary-packages.git"
)
}
;;

let decode =
let open Decoder in
fields
Expand Down
1 change: 1 addition & 0 deletions src/dune_pkg/workspace.mli
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@ module Repository : sig
val equal : t -> t -> bool
val upstream : t
val overlay : t
val binary_packages : t
val decode : t Decoder.t

module Name : sig
Expand Down
2 changes: 2 additions & 0 deletions src/dune_rules/workspace.ml
Original file line number Diff line number Diff line change
Expand Up @@ -682,6 +682,8 @@ let find_lock_dir t path =
List.find t.lock_dirs ~f:(fun lock_dir -> Path.Source.equal lock_dir.path path)
;;

let add_repo t repo = { t with repos = repo :: t.repos }

include Dune_lang.Versioned_file.Make (struct
type t = unit
end)
Expand Down
1 change: 1 addition & 0 deletions src/dune_rules/workspace.mli
Original file line number Diff line number Diff line change
Expand Up @@ -124,6 +124,7 @@ val equal : t -> t -> bool
val to_dyn : t -> Dyn.t
val hash : t -> int
val find_lock_dir : t -> Path.Source.t -> Lock_dir.t option
val add_repo : t -> Dune_pkg.Pkg_workspace.Repository.t -> t
val default_repositories : Dune_pkg.Pkg_workspace.Repository.t list

module Clflags : sig
Expand Down

0 comments on commit dbd8448

Please sign in to comment.