Skip to content

Commit

Permalink
Merge pull request #3115 from OCamlPro/pinswitchcreate
Browse files Browse the repository at this point in the history
Provide installation and local switch creation with locked opam files
  • Loading branch information
AltGr authored Nov 23, 2017
2 parents 1764fe7 + 2d8dd87 commit 8052069
Show file tree
Hide file tree
Showing 7 changed files with 213 additions and 85 deletions.
5 changes: 4 additions & 1 deletion CHANGES
Original file line number Diff line number Diff line change
Expand Up @@ -16,13 +16,16 @@ are not marked).
* Shorten conflict messages even more
* Added `opam admin add-constraint` to amend a set of reverse dependencies in a
repository
* New format for `depexts:`, easier to understand and more flexible
* New format for `depexts:`, easier to understand and more flexible. Depexts for
the host can now be inferred by opam
* Optimised search criteria for the built-in solver
* Added a `build-id` variable to identify package builds
* Extend hooks (new variable `installed-files`, new session hooks)
* `opam switch create DIR` now installs packages defined in `DIR`
* Added system-related variables `arch`, `os`, `os-distribution`, `os-family`,
`os-version`
* Added support for using `opam.locked` files instead of `opam` ones (`--locked`)
* Opam plugins are now made available across switches

2.0.0~beta4
* Building with OCaml < 4.02.3 is no longer supported
Expand Down
19 changes: 19 additions & 0 deletions src/client/opamArg.ml
Original file line number Diff line number Diff line change
Expand Up @@ -502,6 +502,18 @@ let atom_or_local =
in
parse, print

let atom_or_dir =
let parse str = match fst atom_or_local str with
| `Ok (`Filename _) ->
`Error (Printf.sprintf
"Not a valid package specification or existing directory: %s"
str)
| `Ok (`Atom _ | `Dirname _ as atom_or_dir) -> `Ok (atom_or_dir)
| `Error e -> `Error e
in
let print ppf = snd atom_or_local ppf in
parse, print

let variable_bindings =
let parse str =
try
Expand Down Expand Up @@ -810,6 +822,13 @@ let atom_or_local_list =
description, with explicit directory (e.g. `./foo.opam' or `.')"
atom_or_local

let atom_or_dir_list =
arg_list "PACKAGES"
"List of package names, with an optional version or constraint, e.g `pkg', \
`pkg.1.0' or `pkg>=0.5' ; or directory names containing package \
description, with explicit directory (e.g. `./srcdir' or `.')"
atom_or_dir

let nonempty_atom_list =
nonempty_arg_list "PACKAGES"
"List of package names, with an optional version or constraint, \
Expand Down
6 changes: 6 additions & 0 deletions src/client/opamArg.mli
Original file line number Diff line number Diff line change
Expand Up @@ -63,6 +63,9 @@ val atom_or_local_list:
[ `Atom of atom | `Filename of filename | `Dirname of dirname ] list
Term.t

val atom_or_dir_list:
[ `Atom of atom | `Dirname of dirname ] list Term.t

(** Generic argument list builder *)
val arg_list: string -> string -> 'a Arg.converter -> 'a list Term.t

Expand Down Expand Up @@ -169,6 +172,9 @@ val atom: atom Arg.converter
val atom_or_local:
[ `Atom of atom | `Filename of filename | `Dirname of dirname ] Arg.converter

val atom_or_dir:
[ `Atom of atom | `Dirname of dirname ] Arg.converter

(** [var=value,...] argument *)
val variable_bindings: (OpamVariable.t * string) list Arg.converter

Expand Down
194 changes: 133 additions & 61 deletions src/client/opamAuxCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -88,9 +88,16 @@ let url_with_local_branch = function
| None -> url)
| url -> url

let opams_of_dir d =
let opams_of_dir ?(locked=false) d =
let files = OpamPinned.files_in_source d in
List.fold_left (fun acc (n, f) ->
let f =
let locked_f =
OpamFilename.add_extension (OpamFile.filename f) "locked"
in
if locked && OpamFilename.exists locked_f then OpamFile.make locked_f
else f
in
let name =
let open OpamStd.Option.Op in
n >>+ fun () ->
Expand Down Expand Up @@ -152,7 +159,7 @@ let resolve_locals_pinned st atom_or_local_list =
in
List.rev atoms

let resolve_locals ?(quiet=false) atom_or_local_list =
let resolve_locals ?(quiet=false) ?locked atom_or_local_list =
let target_dir dir =
let d = OpamFilename.Dir.to_string dir in
let backend = OpamUrl.guess_version_control d in
Expand All @@ -163,7 +170,7 @@ let resolve_locals ?(quiet=false) atom_or_local_list =
List.fold_left (fun (to_pin, atoms) -> function
| `Atom a -> to_pin, a :: atoms
| `Dirname d ->
let names_files = opams_of_dir d in
let names_files = opams_of_dir ?locked d in
if names_files = [] && not quiet then
OpamConsole.warning "No package definitions found at %s"
(OpamFilename.Dir.to_string d);
Expand Down Expand Up @@ -205,8 +212,8 @@ let resolve_locals ?(quiet=false) atom_or_local_list =
(OpamUrl.to_string t))
duplicates)

let autopin_aux st ?quiet atom_or_local_list =
let to_pin, atoms = resolve_locals ?quiet atom_or_local_list in
let autopin_aux st ?quiet ?locked atom_or_local_list =
let to_pin, atoms = resolve_locals ?quiet ?locked atom_or_local_list in
if to_pin = [] then
atoms, to_pin, OpamPackage.Set.empty, OpamPackage.Set.empty
else
Expand Down Expand Up @@ -304,9 +311,9 @@ let fix_atom_versions_in_set set atoms =
(OpamPackage.package_of_name_opt set name))
atoms

let simulate_autopin st ?quiet atom_or_local_list =
let simulate_autopin st ?quiet ?locked atom_or_local_list =
let atoms, to_pin, obsolete_pins, already_pinned_set =
autopin_aux st ?quiet atom_or_local_list
autopin_aux st ?quiet ?locked atom_or_local_list
in
if to_pin = [] then st, atoms else
let st =
Expand All @@ -315,15 +322,33 @@ let simulate_autopin st ?quiet atom_or_local_list =
in
let st, pins = simulate_local_pinnings st to_pin in
let pins = OpamPackage.Set.union pins already_pinned_set in
let pin_depends =
OpamPackage.Set.fold (fun nv acc ->
List.fold_left (fun acc (nv,target) ->
OpamPackage.Map.add nv target acc)
acc
(OpamFile.OPAM.pin_depends (OpamSwitchState.opam st nv)))
pins OpamPackage.Map.empty
in
if not (OpamPackage.Map.is_empty pin_depends) then
(OpamConsole.msg "Would pin the following:\n%s"
(OpamStd.Format.itemize (fun (nv, url) ->
Printf.sprintf "%s to %s"
(OpamConsole.colorise `bold (OpamPackage.to_string nv))
(OpamConsole.colorise `underline (OpamUrl.to_string url)))
(OpamPackage.Map.bindings pin_depends));
OpamConsole.note "The following may not reflect the above pinnings \
(package definitions are not available yet)";
OpamConsole.msg "\n");
let atoms = fix_atom_versions_in_set pins atoms in
st, atoms

let autopin st ?(simulate=false) ?quiet atom_or_local_list =
let autopin st ?(simulate=false) ?quiet ?locked atom_or_local_list =
if OpamStateConfig.(!r.dryrun) || OpamClientConfig.(!r.show) then
simulate_autopin st atom_or_local_list
simulate_autopin st ?quiet ?locked atom_or_local_list
else
let atoms, to_pin, obsolete_pins, already_pinned_set =
autopin_aux st ?quiet atom_or_local_list
autopin_aux st ?quiet ?locked atom_or_local_list
in
if to_pin = [] && OpamPackage.Set.is_empty obsolete_pins &&
OpamPackage.Set.is_empty already_pinned_set
Expand Down Expand Up @@ -368,22 +393,15 @@ let autopin st ?(simulate=false) ?quiet atom_or_local_list =
let st =
OpamPackage.Set.fold (fun nv st ->
OpamPinCommand.handle_pin_depends st nv (OpamSwitchState.opam st nv))
already_pinned_set st
(OpamPackage.Set.union pins already_pinned_set) st
in
let pins = OpamPackage.Set.union pins already_pinned_set in
let atoms = fix_atom_versions_in_set pins atoms in
st, atoms

let get_compatible_compiler ?repos rt dir =
let get_compatible_compiler ?repos ?locked rt dir =
let gt = rt.repos_global in
let default_compiler =
OpamFile.Config.default_compiler gt.config
in
if default_compiler = Empty then
(OpamConsole.warning "No compiler selected"; [])
else
let candidates = OpamFormula.to_dnf default_compiler in
let local_files = opams_of_dir dir in
let local_files = opams_of_dir ?locked dir in
let local_opams =
List.fold_left (fun acc (name, f) ->
let opam = OpamFile.OPAM.safe_read f in
Expand All @@ -392,7 +410,7 @@ let get_compatible_compiler ?repos rt dir =
match OpamFile.OPAM.version_opt opam with
| Some v -> OpamPackage.create name v, opam
| None ->
let v = OpamPackage.Version.of_string "dev" in
let v = OpamPackage.Version.of_string "~dev" in
OpamPackage.create name v,
OpamFile.OPAM.with_version v opam
in
Expand All @@ -401,50 +419,104 @@ let get_compatible_compiler ?repos rt dir =
local_files
in
let local_packages = OpamPackage.keys local_opams in
let pin_depends =
OpamPackage.Map.fold (fun _nv opam acc ->
List.fold_left (fun acc (nv,_) -> OpamPackage.Set.add nv acc)
acc (OpamFile.OPAM.pin_depends opam))
local_opams OpamPackage.Set.empty
in
let local_atoms =
OpamSolution.eq_atoms_of_packages local_packages
in
try
let univ =
let virt_st =
OpamSwitchState.load_virtual ?repos_list:repos gt rt
in
let opams =
OpamPackage.Map.union (fun _ x -> x) virt_st.opams local_opams
in
let virt_st =
{ virt_st with
opams;
packages =
OpamPackage.Set.union virt_st.packages local_packages;
available_packages = lazy (
OpamPackage.Map.filter (fun package opam ->
OpamFilter.eval_to_bool ~default:false
(OpamPackageVar.resolve_switch_raw ~package gt
(OpamSwitch.of_dirname dir)
OpamFile.Switch_config.empty)
(OpamFile.OPAM.available opam))
opams
|> OpamPackage.keys);
}
in
OpamSwitchState.universe virt_st
~requested:(OpamPackage.names_of_packages local_packages)
Query
let virt_st =
let virt_st =
OpamSwitchState.load_virtual ?repos_list:repos gt rt
in
let opams =
OpamPackage.Map.union (fun _ x -> x) virt_st.opams local_opams
in
List.find
(fun atoms ->
OpamSolver.atom_coinstallability_check univ
(local_atoms @ atoms))
candidates
with Not_found ->
let available = lazy (
OpamPackage.Map.filter (fun package opam ->
OpamFilter.eval_to_bool ~default:false
(OpamPackageVar.resolve_switch_raw ~package gt
(OpamSwitch.of_dirname dir)
OpamFile.Switch_config.empty)
(OpamFile.OPAM.available opam))
opams
|> OpamPackage.keys
) in
let open OpamPackage.Set.Op in
{ virt_st with
opams =
OpamPackage.Set.fold (fun nv acc ->
OpamPackage.Map.add nv (OpamFile.OPAM.create nv) acc)
pin_depends opams;
packages =
virt_st.packages ++ local_packages ++ pin_depends;
available_packages =
lazy (Lazy.force available ++ pin_depends);
}
in
let univ =
OpamSwitchState.universe virt_st
~requested:(OpamPackage.names_of_packages local_packages)
Query
in
(* Find if there is a single possible dependency having Pkgflag_Compiler *)
let alldeps =
OpamSolver.dependencies
~depopts:false ~build:true ~post:true ~installed:false
univ local_packages
in
let compilers =
OpamPackage.Set.filter (fun nv ->
OpamFile.OPAM.has_flag Pkgflag_Compiler
(OpamSwitchState.opam virt_st nv))
(OpamPackage.Set.of_list alldeps)
in
let compilers =
OpamSolver.installable_subset
{univ with u_base = local_packages; u_installed = local_packages}
compilers
in
try
[OpamSolution.eq_atom_of_package
(OpamPackage.Set.choose_one compilers)]
with
| Not_found ->
OpamConsole.warning
"The default compiler selection: %s\n\
is not compatible with the local packages found at %s.\n\
You can use `--compiler` to select a different compiler."
(OpamFormula.to_string default_compiler)
(OpamFilename.Dir.to_string dir);
if OpamConsole.confirm
"Continue anyway, with no compiler selected ?"
"No possible installation was found including a compiler and the \
selected packages.";
if OpamClientConfig.(!r.show) ||
OpamConsole.confirm
"Create the switch with no specific compiler selected, and attempt to \
continue anyway ?"
then []
else OpamStd.Sys.exit_because `Aborted
| Failure _ ->
(* Find a matching compiler from the default selection *)
let default_compiler =
OpamFile.Config.default_compiler gt.config
in
if default_compiler = Empty then
(OpamConsole.warning "No compiler selected"; [])
else
let candidates = OpamFormula.to_dnf default_compiler in
try
List.find
(fun atoms ->
OpamSolver.atom_coinstallability_check univ
(local_atoms @ atoms))
candidates
with Not_found ->
OpamConsole.warning
"The default compiler selection: %s\n\
is not compatible with the local packages found at %s, and the \
packages don't specify an unambiguous compiler.\n\
You can use `--compiler` to manually select one."
(OpamFormula.to_string default_compiler)
(OpamFilename.Dir.to_string dir);
if OpamConsole.confirm
"Continue anyway, with no specific compiler selected ?"
then []
else OpamStd.Sys.exit_because `Aborted
Loading

0 comments on commit 8052069

Please sign in to comment.