Skip to content

Commit

Permalink
Merge pull request #1526 from OCamlPro/fixes
Browse files Browse the repository at this point in the history
Some fixes, and call the solver on 'opam reinstall'
  • Loading branch information
AltGr committed Jul 18, 2014
2 parents e3dc0b2 + 0b1eece commit 9d6784a
Show file tree
Hide file tree
Showing 11 changed files with 94 additions and 40 deletions.
14 changes: 10 additions & 4 deletions CHANGES
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@
source, pin packages that don't exist in a repository, fill a local opam
file from a template, etc.
* Improved the internal solver to handle much larger problems (#1358)
* Use Unix.lockf for more reliable repository locks (#1299)
* Use Unix.lockf for more reliable internal repository locks (#1299)
* Large performance improvements (#1363)
* Upgraded external dependencies to dose 3.2.2, ocamlgraph 1.8.5, cmdliner
0.9.4, cudf 0.7
Expand All @@ -46,12 +46,18 @@
* opam files: added a 'dev-repo' field, and the experimental 'flags' field
(#1217, #1472)
* Generate an opam-admin.top to easily apply scripts on a package repository
(#1454)
(#1454). Provide scripts to ease adding new metadata ('dev-repo', etc.)
* Added 'opam upgrade --fixup' to save the day if your installed package set
gets inconsistent.
* Fixed some return codes
* Added options '--raw', '--depends', '--external' and more fields to 'opam
show'
* Added option to query (recursive) (reverse) dependencies and external
dependencies to 'opam list
* Fixed opam init for some shells
* OPAM search now includes the 'syntax' and 'libs' fields in the search
* 'opam source' command to get the package archive or upstream source easily
* Added an 'install' field in opam files, to separate from build
* Added the 'build', 'test' and 'doc' dependency flags to limit the scope
of some dependencies
* Hundreds of smaller fixes and UI improvements

1.1.2
Expand Down
6 changes: 4 additions & 2 deletions src/client/opamArg.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1527,8 +1527,10 @@ let pin ?(unpin_only=false) () =
let pin_option = pin_option_of_string ~kind:`local path in
`Ok (Client.PIN.pin name ~edit ~action (Some pin_option))
with Not_found ->
`Error (true, Printf.sprintf
"No valid package description found at path %s."
`Error (false, Printf.sprintf
"No valid package description found at path %s.\n\
Please supply at least a package name \
(e.g. `opam pin add NAME PATH')"
path))
| Some `add, [name; target] ->
let name = OpamPackage.Name.of_string name in
Expand Down
52 changes: 29 additions & 23 deletions src/client/opamClient.ml
Original file line number Diff line number Diff line change
Expand Up @@ -560,7 +560,7 @@ module API = struct
See also preprocess_request and check_conflicts *)
let orphans ?changes ?(transitive=false) t =
let all = t.packages ++ t.installed in
let universe = OpamState.universe t Reinstall in
let universe = OpamState.universe t (Reinstall OpamPackage.Set.empty) in
(* Basic definition of orphan packages *)
let orphans = t.installed -- Lazy.force t.available_packages in
(* Restriction to the request-related packages *)
Expand Down Expand Up @@ -1091,10 +1091,14 @@ module API = struct
(* packages which still have local data are OK for install/reinstall *)
let has_no_local_data nv =
not (OpamFilename.exists_dir (OpamPath.packages t.root nv)) in
let orphans =
OpamPackage.Set.filter has_no_local_data
(full_orphans ++ orphan_versions) in
let available = lazy (t.packages -- orphans) in
let full_orphans, full_orphans_with_local_data =
OpamPackage.Set.partition has_no_local_data
full_orphans in
let orphan_versions, orphan_versions_with_local_data =
OpamPackage.Set.partition has_no_local_data
orphan_versions in
let available = lazy (t.packages -- full_orphans -- orphan_versions) in
let orphans = full_orphans ++ orphan_versions in
let conflict_atoms =
List.filter
(fun (name,_ as a) ->
Expand All @@ -1110,7 +1114,12 @@ module API = struct
(OpamMisc.pretty_list
(List.map OpamFormula.string_of_atom conflict_atoms))
else
t, full_orphans, orphan_versions
{t with available_packages = lazy
(Lazy.force t.available_packages ++
full_orphans_with_local_data ++
orphan_versions_with_local_data )},
full_orphans,
orphan_versions

let install_t ?ask atoms add_to_roots deps_only t =
log "INSTALL %a" (slog OpamFormula.string_of_atoms) atoms;
Expand Down Expand Up @@ -1345,26 +1354,22 @@ module API = struct

let atoms = OpamSolution.eq_atoms_of_packages reinstall in

let t, _, _ = check_conflicts t atoms in
let t, full_orphans, orphan_versions = check_conflicts t atoms in

let universe = OpamState.universe t Reinstall in
let depends = (* Do not cast to a set, we need to keep the order *)
OpamSolver.reverse_dependencies
~depopts:true ~installed:true ~build:false universe reinstall in
let to_process =
List.map (fun pkg -> To_recompile pkg) depends in
let requested =
OpamPackage.Name.Set.of_list (List.rev_map fst atoms) in

let request =
preprocess_request t full_orphans orphan_versions
{ wish_install = OpamSolution.eq_atoms_of_packages reinstall;
wish_remove = [];
wish_upgrade = [];
criteria = !OpamGlobals.solver_fixup_preferences; } in

let solution =
OpamSolver.sequential_solution universe ~requested to_process in
let solution = match solution with
| Conflicts cs ->
log "conflict!";
OpamGlobals.msg "%s"
(OpamCudf.string_of_conflict (OpamState.unavailable_reason t) cs);
No_solution
| Success solution ->
OpamSolution.apply ?ask t Reinstall ~requested solution in
OpamSolution.resolve_and_apply ?ask t (Reinstall reinstall) ~requested
request in

OpamSolution.check_solution t solution

let reinstall names =
Expand Down Expand Up @@ -1403,7 +1408,8 @@ module API = struct
with Not_found -> ()
with e ->
OpamGlobals.note
"Pinning command successful, but your packages may be out of sync.";
"Pinning command successful, but your installed packages \
may be out of sync.";
raise e

let get_upstream t name =
Expand Down
2 changes: 1 addition & 1 deletion src/client/opamSolution.ml
Original file line number Diff line number Diff line change
Expand Up @@ -295,7 +295,7 @@ let parallel_apply t action solution =
| Import r
| Switch r -> OpamPackage.Name.Set.union root_installs r
| Upgrade _
| Reinstall -> root_installs
| Reinstall _ -> root_installs
| Depends
| Remove -> OpamPackage.Name.Set.empty in

Expand Down
48 changes: 41 additions & 7 deletions src/core/opamFile.ml
Original file line number Diff line number Diff line change
Expand Up @@ -96,11 +96,11 @@ module Syntax = struct
begin match OpamFormat.assoc_option f.file_contents s_opam_version
(OpamFormat.parse_string @> OpamVersion.of_string) with
| Some opam_version ->
if OpamVersion.compare opam_version OpamVersion.current > 0 then (
if not !OpamGlobals.skip_version_checks &&
OpamVersion.compare opam_version OpamVersion.current > 0 then (
OpamGlobals.error
"Your version of OPAM (%s) is not recent enough to read \
%s. Upgrade OPAM to a more recent version (at least %s) \
to read this file correctly."
"Your version of OPAM (%s) is not recent enough to read %s.\n\
Upgrade to version %s or later to read this file."
(OpamVersion.to_string OpamVersion.current)
(OpamMisc.prettify_path f.file_name)
(OpamVersion.to_string opam_version);
Expand All @@ -118,7 +118,7 @@ module Syntax = struct
let invalids = OpamFormat.invalid_fields f.file_contents fields in
let too_many, invalids = List.partition (fun x -> List.mem x fields) invalids in
if too_many <> [] then
OpamGlobals.warning "duplicated fields in %s: %s"
OpamGlobals.warning "duplicate fields in %s: %s"
f.file_name
(OpamMisc.string_of_list (fun x -> x) too_many);
if !OpamGlobals.strict then (
Expand Down Expand Up @@ -963,6 +963,7 @@ module X = struct
s_bug_reports;
s_flags;
s_dev_repo;
s_install;
]

let to_1_0_fields k v =
Expand Down Expand Up @@ -1160,8 +1161,41 @@ module X = struct
let remove = OpamFormat.assoc_list s s_remove OpamFormat.parse_commands in
let depends = OpamFormat.assoc_default OpamFormula.Empty s s_depends
OpamFormat.parse_ext_formula in
let depopts = OpamFormat.assoc_default OpamFormula.Empty s s_depopts
OpamFormat.parse_opt_formula in
let depopts =
let rec cleanup ~pos acc disjunction =
List.fold_left (fun acc -> function
| OpamFormula.Atom (_, (_,Empty)) as atom -> atom :: acc
| OpamFormula.Atom (name, (flags, cstr)) ->
OpamGlobals.warning
"At %s:\n\
Version constraint (%s) no longer allowed in optional \
dependency (ignored).\n\
Use the 'conflicts' field instead."
(string_of_pos pos)
(OpamFormula.string_of_formula (fun (r,v) ->
OpamFormula.string_of_relop r ^" "^
OpamPackage.Version.to_string v)
cstr);
OpamFormula.Atom (name, (flags, Empty)) :: acc
| f ->
OpamGlobals.warning
"At %s:\n\
Optional dependencies must be a disjunction. Treated as such."
(string_of_pos pos);
cleanup ~pos acc
(OpamFormula.fold_left (fun acc a -> OpamFormula.Atom a::acc) [] f)
)
acc disjunction
in
OpamFormat.assoc_default OpamFormula.Empty s s_depopts @@ fun value ->
let f = OpamFormat.parse_opt_formula value in
if OpamVersion.compare opam_version (OpamVersion.of_string "1.2") >= 0 then
OpamFormula.ors_to_list f
|> cleanup ~pos:(OpamFormat.value_pos value) []
|> List.rev
|> OpamFormula.ors
else f
in
let conflicts = OpamFormat.assoc_default OpamFormula.Empty s s_conflicts
OpamFormat.parse_formula in
let libraries = OpamFormat.assoc_list s s_libraries OpamFormat.parse_libraries in
Expand Down
1 change: 1 addition & 0 deletions src/core/opamGlobals.ml
Original file line number Diff line number Diff line change
Expand Up @@ -56,6 +56,7 @@ let sync_archives = check "SYNCARCHIVES"
let compat_mode_1_0 = check "COMPATMODE_1_0"
let use_external_solver = ref (not (!(check "NOASPCUD") || !(check "USEINTERNALSOLVER")))
let no_self_upgrade = check "NOSELFUPGRADE"
let skip_version_checks = check "SKIPVERSIONCHECKS"

(* Value set when opam calls itself *)
let self_upgrade_bootstrapping_value = "bootstrapping"
Expand Down
1 change: 1 addition & 0 deletions src/core/opamGlobals.mli
Original file line number Diff line number Diff line change
Expand Up @@ -42,6 +42,7 @@ val sync_archives : bool ref
val compat_mode_1_0 : bool ref
val use_external_solver : bool ref
val no_self_upgrade : bool ref
val skip_version_checks : bool ref

(* Value set when opam calls itself *)
val self_upgrade_bootstrapping_value : string
Expand Down
3 changes: 2 additions & 1 deletion src/core/opamRepository.ml
Original file line number Diff line number Diff line change
Expand Up @@ -187,7 +187,8 @@ let check_version repo =
|> OpamFile.Repo.safe_read
|> OpamFile.Repo.opam_version
end in
if OpamVersion.compare repo_version OpamVersion.current > 0 then
if not !OpamGlobals.skip_version_checks &&
OpamVersion.compare repo_version OpamVersion.current > 0 then
OpamGlobals.error_and_exit
"\nThe current version of OPAM cannot read the repository. \
You should upgrade to at least version %s.\n"
Expand Down
2 changes: 1 addition & 1 deletion src/core/opamTypes.mli
Original file line number Diff line number Diff line change
Expand Up @@ -244,7 +244,7 @@ type 'a request = {
type user_action =
| Install of name_set (** The 'root' packages to be installed *)
| Upgrade of package_set (** The subset of packages to upgrade *)
| Reinstall
| Reinstall of package_set
| Depends
| Init of name_set (** The 'root' packages to be installed *)
| Remove
Expand Down
2 changes: 2 additions & 0 deletions src/solver/opamCudf.ml
Original file line number Diff line number Diff line change
Expand Up @@ -713,10 +713,12 @@ let compute_root_causes universe actions requested =
| To_delete p, To_delete _, `Depends -> Use [p]
| To_delete p, To_delete _, `Provides -> Required_by [p]
| To_delete p, To_change _, `Depends -> Use [p]
| To_recompile p, To_change _, `Provides -> Required_by [p]
| _, To_change(None,_), `Depends -> Unknown
| _, To_change _, _ -> Upstream_changes
| To_change _, To_delete _, `Depends -> Conflicts_with
[action_contents cause]
| To_recompile p, To_delete _, `Depends -> Conflicts_with [p]
| _, _, _ -> Unknown
in
let get_causes acc roots =
Expand Down
3 changes: 2 additions & 1 deletion src/solver/opamSolver.ml
Original file line number Diff line number Diff line change
Expand Up @@ -141,7 +141,8 @@ let opam2cudf universe ?(depopts=false) ?build ?test ?doc
(name, None)::OpamFormula.to_conjunction conflicts in
let installed = OpamPackage.Set.mem package universe.u_installed in
let reinstall = match universe.u_action with
| Upgrade reinstall -> OpamPackage.Set.mem package reinstall
| Upgrade reinstall | Reinstall reinstall ->
OpamPackage.Set.mem package reinstall
| _ -> false in
let installed_root = OpamPackage.Set.mem package universe.u_installed_roots in
let pinned_to_current_version =
Expand Down

0 comments on commit 9d6784a

Please sign in to comment.