Skip to content

Commit

Permalink
Merge pull request #1529 from OCamlPro/fixed-heuristic-rt
Browse files Browse the repository at this point in the history
Adds opam-rt+heuristic to travis, and fix it
  • Loading branch information
AltGr committed Jul 18, 2014
2 parents 9d6784a + 87c0c58 commit 229c902
Show file tree
Hide file tree
Showing 10 changed files with 79 additions and 26 deletions.
4 changes: 2 additions & 2 deletions .travis-ci.sh
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ export OCAMLRUNPARAM=b

if [ "$OPAM_TEST" = "1" ]; then
# Compile OPAM using the system libraries (install them using OPAM)
sudo apt-get install opam aspcud
sudo apt-get install opam $EXTERNAL_SOLVER
opam init
eval `opam config env`
opam install ocamlfind lwt cohttp ssl cmdliner ocamlgraph dose cudf re
Expand All @@ -38,7 +38,7 @@ if [ "$OPAM_TEST" = "1" ]; then
tar xvfz master.tar.gz
cd opam-rt-master
make
make KINDS="local git" run
OPAMEXTERNALSOLVER=$EXTERNAL_SOLVER make KINDS="local git" run
else
# Compile OPAM from sources and run the basic tests
./configure
Expand Down
3 changes: 2 additions & 1 deletion .travis.yml
Original file line number Diff line number Diff line change
@@ -1,7 +1,8 @@
language: c
script: bash -ex .travis-ci.sh
env:
- OCAML_VERSION=4.01.0 OPAM_TEST=1
- OCAML_VERSION=4.01.0 OPAM_TEST=1 EXTERNAL_SOLVER=
- OCAML_VERSION=4.01.0 OPAM_TEST=1 EXTERNAL_SOLVER=aspcud
- OCAML_VERSION=4.01.0 OPAM_TEST=0
- OCAML_VERSION=4.00.1 OPAM_TEST=0
- OCAML_VERSION=3.12.1 OPAM_TEST=0
32 changes: 23 additions & 9 deletions src/client/opamClient.ml
Original file line number Diff line number Diff line change
Expand Up @@ -619,7 +619,7 @@ module API = struct
let add_wish_install =
List.rev_append eqnames
(OpamSolution.atoms_of_packages
(t.installed_roots %% (Lazy.force t.available_packages))) in
(t.installed_roots %% Lazy.force t.available_packages)) in
let wish_install = List.rev_append add_wish_install wish_install in
let wish_upgrade = List.rev_append neqnames wish_upgrade in
(* Remove orphans *)
Expand All @@ -628,8 +628,7 @@ module API = struct
OpamSolution.eq_atoms_of_packages orphan_versions @
wish_remove in
let available =
OpamPackage.Set.Op.(
Lazy.force t.available_packages -- orphan_versions -- full_orphans) in
Lazy.force t.available_packages -- orphan_versions -- full_orphans in
let still_available atom =
OpamPackage.Set.exists
(fun p -> OpamFormula.check atom p)
Expand Down Expand Up @@ -666,9 +665,13 @@ module API = struct
in
if OpamPackage.Set.is_empty to_update then t else (
OpamGlobals.header_msg "Synchronising pinned packages";
let updated = OpamState.update_dev_packages t to_update in
if OpamPackage.Set.is_empty updated then t
else OpamState.load_state "reload-dev-package-updated"
try
let updated = OpamState.update_dev_packages t to_update in
if OpamPackage.Set.is_empty updated then t
else OpamState.load_state "reload-dev-package-updated"
with e ->
OpamMisc.fatal e;
t
)

let compute_upgrade_t atoms t =
Expand All @@ -682,6 +685,7 @@ module API = struct
requested,
action,
OpamSolution.resolve t action ~requested
~orphans:(full_orphans ++ orphan_versions)
(preprocess_request t full_orphans orphan_versions
{ wish_install = [];
wish_remove = [];
Expand Down Expand Up @@ -730,6 +734,7 @@ module API = struct
requested,
action,
OpamSolution.resolve t action ~requested
~orphans:(full_orphans ++ orphan_versions)
(preprocess_request t full_orphans orphan_versions
{ wish_install = OpamSolution.eq_atoms_of_packages installed_roots;
wish_remove = [];
Expand Down Expand Up @@ -776,11 +781,12 @@ module API = struct
or install aspcud or another solver on your system.\n";
OpamGlobals.exit 1)
else
let t, _full_orphans, _orphan_versions = orphans ~transitive:true t in
let t, full_orphans, orphan_versions = orphans ~transitive:true t in
let requested = OpamPackage.Name.Set.empty in
let action = Upgrade OpamPackage.Set.empty in
let solution =
OpamSolution.resolve_and_apply ~ask:true t action ~requested
~orphans:(full_orphans ++ orphan_versions)
{ wish_install = [];
wish_remove = [];
wish_upgrade = [];
Expand Down Expand Up @@ -1071,6 +1077,7 @@ module API = struct
let solution =
OpamSolution.resolve_and_apply ~ask:false t (Init compiler_names)
~requested:compiler_names
~orphans:OpamPackage.Set.empty
{ wish_install = [];
wish_remove = [];
wish_upgrade = compiler_packages;
Expand Down Expand Up @@ -1196,7 +1203,11 @@ module API = struct
if add_to_roots = Some false || deps_only then
Install OpamPackage.Name.Set.empty
else Install names in
let solution = OpamSolution.resolve t action ~requested:names request in
let solution =
OpamSolution.resolve t action
~requested:names
~orphans:(full_orphans ++ orphan_versions)
request in
let solution = match solution with
| Conflicts cs ->
log "conflict!";
Expand Down Expand Up @@ -1313,7 +1324,9 @@ module API = struct
(OpamSolver.dependencies
~depopts:true ~installed:true universe to_remove))
else to_remove in
let solution = OpamSolution.resolve_and_apply ?ask t Remove ~requested
let solution =
OpamSolution.resolve_and_apply ?ask t Remove ~requested
~orphans:(full_orphans ++ orphan_versions)
{ wish_install = OpamSolution.eq_atoms_of_packages to_keep;
wish_remove = OpamSolution.atoms_of_packages to_remove;
wish_upgrade = [];
Expand Down Expand Up @@ -1368,6 +1381,7 @@ module API = struct

let solution =
OpamSolution.resolve_and_apply ?ask t (Reinstall reinstall) ~requested
~orphans:(full_orphans ++ orphan_versions)
request in

OpamSolution.check_solution t solution
Expand Down
13 changes: 9 additions & 4 deletions src/client/opamSolution.ml
Original file line number Diff line number Diff line change
Expand Up @@ -468,6 +468,10 @@ let parallel_apply t action solution =
| `Successful () ->
finalize ();
OK (actions_list solution.to_process)
| `Exception (OpamGlobals.Exit _ | Sys.Break as e) ->
OpamGlobals.error "Aborting";
finalize ();
raise e
| `Exception e ->
OpamGlobals.error "Actions cancelled because of %s" (Printexc.to_string e);
finalize ();
Expand Down Expand Up @@ -617,11 +621,12 @@ let apply ?ask t action ~requested solution =
Aborted
)

let resolve ?(verbose=true) t action ~requested request =
OpamSolver.resolve ~verbose (OpamState.universe t action) ~requested request
let resolve ?(verbose=true) t action ~requested ~orphans request =
OpamSolver.resolve ~verbose (OpamState.universe t action)
~requested ~orphans request

let resolve_and_apply ?ask t action ~requested request =
match resolve t action ~requested request with
let resolve_and_apply ?ask t action ~requested ~orphans request =
match resolve t action ~requested ~orphans request with
| Conflicts cs ->
log "conflict!";
OpamGlobals.msg "%s"
Expand Down
4 changes: 3 additions & 1 deletion src/client/opamSolution.mli
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,8 @@ val resolve:
?verbose:bool ->
OpamState.state ->
user_action ->
requested:OpamPackage.Name.Set.t ->
requested:name_set ->
orphans:package_set ->
atom request ->
(OpamSolver.solution, OpamCudf.conflict) result

Expand All @@ -46,6 +47,7 @@ val resolve_and_apply:
OpamState.state ->
user_action ->
requested:OpamPackage.Name.Set.t ->
orphans:package_set ->
atom request ->
solver_result

Expand Down
4 changes: 3 additions & 1 deletion src/client/opamSwitchCommand.ml
Original file line number Diff line number Diff line change
Expand Up @@ -216,7 +216,8 @@ let install_packages ~packages switch compiler =
match bad_packages with
| [] ->
let solution = OpamSolution.resolve_and_apply ~ask:false t (Switch roots)
~requested:roots
~requested:roots
~orphans:OpamPackage.Set.empty
{ wish_install = [];
wish_remove = [];
wish_upgrade = to_install;
Expand Down Expand Up @@ -372,6 +373,7 @@ let import_t importfile t =

OpamSolution.resolve_and_apply t (Import roots)
~requested:(OpamPackage.names_of_packages imported)
~orphans:OpamPackage.Set.empty
{ wish_install = to_import;
wish_remove = [];
wish_upgrade = [];
Expand Down
4 changes: 3 additions & 1 deletion src/scripts/opam_mk_repo.ml
Original file line number Diff line number Diff line change
Expand Up @@ -110,7 +110,9 @@ let resolve_deps index names =
} in
let request = { wish_install = atoms; wish_remove = []; wish_upgrade = [];
criteria = !OpamGlobals.solver_preferences; } in
match OpamSolver.resolve ~verbose:true universe ~requested request with
match OpamSolver.resolve ~verbose:true universe ~requested
~orphans:OpamPackage.Set.empty request
with
| Success solution ->
OpamSolver.ActionGraph.fold_vertex (fun act acc -> match act with
| To_change (_, p) -> OpamPackage.Set.add p acc
Expand Down
11 changes: 5 additions & 6 deletions src/solver/opamSolver.ml
Original file line number Diff line number Diff line change
Expand Up @@ -277,19 +277,18 @@ let cycle_conflict univ cycles =
(fun a -> Action.to_string (map_action OpamCudf.cudf2opam a)))
cycles)

let resolve ?(verbose=true) universe ~requested request =
let resolve ?(verbose=true) universe ~requested ~orphans request =
log "resolve request=%a" (slog string_of_request) request;
let version_map =
cudf_versions_map universe (universe.u_available ++ universe.u_installed) in
let simple_universe =
load_cudf_universe universe ~version_map universe.u_available in
load_cudf_universe universe ~version_map
(universe.u_available ++ universe.u_installed -- orphans) in
let request = cleanup_request universe request in
let cudf_request = map_request (atom2cudf universe version_map) request in
let orphan_packages =
universe.u_installed -- universe.u_available -- universe.u_pinned in
let add_orphan_packages u =
load_cudf_universe universe ~version_map
(orphan_packages ++
(orphans ++
(OpamPackage.Set.of_list
(List.map OpamCudf.cudf2opam (Cudf.get_packages u)))) in
let resolve u req =
Expand All @@ -306,7 +305,7 @@ let resolve ?(verbose=true) universe ~requested request =
| Conflicts _ as c -> c
| Success actions ->
let all_packages =
universe.u_available ++ orphan_packages in
universe.u_available ++ orphans in
let simple_universe =
load_cudf_universe universe ~depopts:true ~build:false
~version_map all_packages in
Expand Down
2 changes: 1 addition & 1 deletion src/solver/opamSolver.mli
Original file line number Diff line number Diff line change
Expand Up @@ -64,7 +64,7 @@ val load_cudf_universe:
consistency of the initial description. *)
val resolve :
?verbose:bool ->
universe -> requested:OpamPackage.Name.Set.t -> atom request
universe -> requested:name_set -> orphans:package_set -> atom request
-> (solution, OpamCudf.conflict) result

(** Keep only the packages that are installable. *)
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,28 @@
From b93f8b64c86ded96b31b49b983beabfd8d7280f2 Mon Sep 17 00:00:00 2001
From: Louis Gesbert <louis.gesbert@ocamlpro.com>
Date: Fri, 18 Jul 2014 15:50:24 +0200
Subject: [PATCH] Removed hard failure cases, in favor of finer diagnostics

---
algo/depsolver.ml | 5 -----
1 file changed, 5 deletions(-)

diff --git a/algo/depsolver.ml b/algo/depsolver.ml
index f93fb86..a812ede 100644
--- a/algo/depsolver.ml
+++ b/algo/depsolver.ml
@@ -37,11 +37,6 @@ let reason map universe =
let globalid = Cudf.universe_size universe in
List.filter_map (function
|Diagnostic_int.Dependency(i,vl,il) when i = globalid -> None
- |Diagnostic_int.Missing(i,vl) when i = globalid ->
- fatal "the package encoding global constraints can't be missing"
- |Diagnostic_int.Conflict(i,j,vpkg) when i = globalid || j = globalid ->
- fatal "the package encoding global constraints can't be in conflict"
-
|Diagnostic_int.Dependency(i,vl,il) -> Some (
Diagnostic.Dependency(from_sat (map#inttovar i),vl,List.map (fun i -> from_sat (map#inttovar i)) il)
)
--
2.0.1

0 comments on commit 229c902

Please sign in to comment.