Skip to content

Commit

Permalink
Merge pull request #3351 from OCamlPro/update-mccs
Browse files Browse the repository at this point in the history
Add the newer mccs backends
  • Loading branch information
AltGr authored May 16, 2018
2 parents fa43c9f + 1914082 commit 08c89d5
Show file tree
Hide file tree
Showing 13 changed files with 98 additions and 48 deletions.
2 changes: 1 addition & 1 deletion opam-solver.opam
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@ build: [
]
depends: [
"opam-format" {= "2.0.0~rc2"}
"mccs" {>= "1.1+4"}
"mccs" {>= "1.1+6"}
"dose3" {>= "5"}
"cudf" {>= "0.7"}
"jbuilder" {build & >= "1.0+beta17"}
Expand Down
3 changes: 2 additions & 1 deletion src/client/opamCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -920,7 +920,8 @@ let config =
OpamGlobalState.with_ `Lock_none @@ fun gt ->
OpamSwitchState.with_ `Lock_none gt @@ fun state ->
let module Solver = (val OpamSolverConfig.(Lazy.force !r.solver)) in
print "solver" "%s" Solver.name;
print "solver" "%s"
(OpamCudfSolver.get_name (module Solver));
print "install-criteria" "%s"
(OpamSolverConfig.criteria `Default);
print "upgrade-criteria" "%s"
Expand Down
2 changes: 1 addition & 1 deletion src/core/opamStd.ml
Original file line number Diff line number Diff line change
Expand Up @@ -616,7 +616,7 @@ module OpamSys = struct
let cmd =
List.find Sys.file_exists (List.map (fun d -> Filename.concat d cmd) path)
in
let ic = Unix.open_process_in (cmd^" "^args) in
let ic = Unix.open_process_in (cmd^" "^args^" 2>/dev/null") in
try
let r = f ic in
ignore (Unix.close_process_in ic) ; r
Expand Down
28 changes: 17 additions & 11 deletions src/solver/opamBuiltinMccs.ml.dummy
Original file line number Diff line number Diff line change
Expand Up @@ -10,18 +10,24 @@

open OpamCudfSolverSig

let name = "builtin-dummy-solver"
module S = struct
let name = "builtin-dummy-solver"

let is_present = lazy false
let is_present () = false

let command_name = None
let ext = ref None

let default_criteria = {
crit_default = "";
crit_upgrade = "";
crit_fixup = "";
crit_best_effort_prefix = None;
}
let command_name = None

let call ~criteria:_ ?timeout:_ _cudf =
failwith "This opam was compiled without a solver built in"
let default_criteria = {
crit_default = "";
crit_upgrade = "";
crit_fixup = "";
crit_best_effort_prefix = None;
}

let call ~criteria:_ ?timeout:_ _cudf =
failwith "This opam was compiled without a solver built in"
end

let all_backends = [ (module S: S) ]
34 changes: 27 additions & 7 deletions src/solver/opamBuiltinMccs.ml.real
Original file line number Diff line number Diff line change
Expand Up @@ -10,11 +10,7 @@

open OpamCudfSolverSig

let name = "builtin-"^Mccs.solver_id

let is_present = lazy true

let command_name = None
let name solver_backend = "builtin-"^Mccs.get_solver_id ~solver:solver_backend ()

let default_criteria = {
crit_default = "-removed,\
Expand All @@ -28,11 +24,35 @@ let default_criteria = {
crit_best_effort_prefix = Some "+count[opam-query:,false],";
}

let call ~criteria ?timeout cudf =
let call solver_backend ext ~criteria ?timeout cudf =
let solver = match solver_backend, ext with
| `LP _, Some ext -> `LP ext
| _ -> solver_backend
in
match
Mccs.resolve_cudf ~verbose:OpamCoreConfig.(!r.debug_level >= 2)
Mccs.resolve_cudf
~solver
~verbose:OpamCoreConfig.(!r.debug_level >= 2)
?timeout criteria cudf
with
| None -> raise Common.CudfSolver.Unsat
| Some (preamble, univ) -> Some preamble, univ
| exception Mccs.Timeout -> raise Timeout

let of_backend backend : (module OpamCudfSolverSig.S) =
(module struct
let name = name backend
let ext = ref None
let is_present () =
match backend, !ext with
| `LP "", None -> false
| `LP cmd, None | `LP _, Some cmd ->
OpamSystem.resolve_command cmd <> None
| _ -> true
let command_name = None
let default_criteria = default_criteria
let call = call backend !ext
end)

let all_backends =
List.map of_backend Mccs.supported_backends
2 changes: 1 addition & 1 deletion src/solver/opamBuiltinMccs.mli
Original file line number Diff line number Diff line change
Expand Up @@ -8,4 +8,4 @@
(* *)
(**************************************************************************)

include OpamCudfSolverSig.S
val all_backends: (module OpamCudfSolverSig.S) list
5 changes: 3 additions & 2 deletions src/solver/opamCudf.ml
Original file line number Diff line number Diff line change
Expand Up @@ -521,7 +521,7 @@ let is_pinned = check s_pinned

let default_preamble =
let l = [
(s_source, `String None) ;
(s_source, `String None);
(s_source_number, `String None);
(s_reinstall, `Bool (Some false));
(s_installed_root, `Bool (Some false));
Expand Down Expand Up @@ -594,7 +594,8 @@ let dump_cudf_request ~version_map (_, univ,_ as cudf) criteria =
let filename = Printf.sprintf "%s-%d.cudf" f !solver_calls in
let oc = open_out filename in
let module Solver = (val OpamSolverConfig.(Lazy.force !r.solver)) in
Printf.fprintf oc "# Solver: %s\n" Solver.name;
Printf.fprintf oc "# Solver: %s\n"
(OpamCudfSolver.get_name (module Solver));
Printf.fprintf oc "# Criteria: %s\n" criteria;
Cudf_printer.pp_cudf oc cudf;
OpamPackage.Map.iter (fun (pkg:OpamPackage.t) (vnum: int) ->
Expand Down
46 changes: 33 additions & 13 deletions src/solver/opamCudfSolver.ml
Original file line number Diff line number Diff line change
Expand Up @@ -80,7 +80,9 @@ let call_external_solver command ~criteria ?timeout (_, universe,_ as cudf) =
module External (E: ExternalArg) : S = struct
let name = E.name

let is_present = E.is_present
let ext = ref None

let is_present () = Lazy.force E.is_present

let command_name = Some E.command_name

Expand Down Expand Up @@ -211,20 +213,32 @@ let make_custom_solver name args criteria =
: S)


let default_solver_selection = [
(module OpamBuiltinMccs: S);
(module Aspcud: S);
(module Mccs: S);
(module Aspcud_old: S);
(module Packup: S);
]
let default_solver_selection =
OpamBuiltinMccs.all_backends @ [
(module Aspcud: S);
(module Mccs: S);
(module Aspcud_old: S);
(module Packup: S);
]

let extract_solver_param name =
if OpamStd.String.ends_with ~suffix:")" name then
match OpamStd.String.cut_at name '(' with
| Some (xname, ext2) ->
xname, Some (OpamStd.String.remove_suffix ~suffix:")" ext2)
| None -> name, None
else name, None

let custom_solver cmd = match cmd with
| [ CIdent name, _ ] | [ CString name, _ ] ->
(try
let xname, ext = extract_solver_param name in
List.find (fun (module S: S) ->
(S.name = Filename.basename name || S.command_name = Some name)
&& Lazy.force S.is_present)
let n, _ = extract_solver_param S.name in
(n = xname || n = Filename.basename xname ||
S.command_name = Some name) &&
(if ext <> None then S.ext := ext;
S.is_present ()))
default_solver_selection
with Not_found ->
OpamConsole.error_and_exit `Configuration_error
Expand All @@ -236,7 +250,7 @@ let custom_solver cmd = match cmd with
let corresponding_module =
List.find (fun (module S: S) ->
S.command_name =
Some (Filename.basename name) && Lazy.force S.is_present)
Some (Filename.basename name) && S.is_present ())
default_solver_selection
in
let module S = (val corresponding_module) in
Expand All @@ -255,15 +269,15 @@ let solver_of_string s =

let has_builtin_solver () =
List.exists
(fun (module S: S) -> S.command_name = None && Lazy.force S.is_present)
(fun (module S: S) -> S.command_name = None && S.is_present ())
default_solver_selection

let get_solver ?internal l =
try
List.find
(fun (module S: S) ->
(internal = None || internal = Some (S.command_name = None)) &&
Lazy.force S.is_present)
S.is_present ())
l
with Not_found ->
OpamConsole.error_and_exit `Configuration_error
Expand All @@ -276,3 +290,9 @@ let get_solver ?internal l =
"This opam has been compiled without a built-in solver, so you need \
to install and configure an external one. See \
http://opam.ocaml.org/doc/Install.html#ExternalSolvers for details.")

let get_name (module S: S) =
let name, ext0 = extract_solver_param S.name in
match !S.ext, ext0 with
| Some e, _ | None, Some e -> Printf.sprintf "%s(%s)" name e
| None, None -> name
3 changes: 3 additions & 0 deletions src/solver/opamCudfSolver.mli
Original file line number Diff line number Diff line change
Expand Up @@ -38,3 +38,6 @@ val solver_of_string : string -> (module S)
val get_solver : ?internal:bool -> (module S) list -> (module S)

val has_builtin_solver : unit -> bool

(** Gets the full solver name with params *)
val get_name : (module S) -> string
5 changes: 4 additions & 1 deletion src/solver/opamCudfSolverSig.ml
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,10 @@ module type S = sig

val name: string

val is_present: bool Lazy.t
(** extra configurable solver parameters *)
val ext: string option ref

val is_present: unit -> bool

val command_name: string option
(** None means the solver is built-in *)
Expand Down
3 changes: 2 additions & 1 deletion src/solver/opamSolverConfig.ml
Original file line number Diff line number Diff line change
Expand Up @@ -180,5 +180,6 @@ let criteria kind =

let call_solver ~criteria cudf =
let module S = (val Lazy.force (!r.solver)) in
OpamConsole.log "SOLVER" "Calling solver %s with criteria %s" S.name criteria;
OpamConsole.log "SOLVER" "Calling solver %s with criteria %s"
(OpamCudfSolver.get_name (module S)) criteria;
S.call ~criteria ?timeout:(!r.solver_timeout) cudf
9 changes: 2 additions & 7 deletions src/state/shellscripts/bwrap.sh
Original file line number Diff line number Diff line change
@@ -1,16 +1,11 @@
#!/bin/bash -ue

ROOT="~/.opam"
if [ -v OPAMROOT ]; then
ROOT=$OPAMROOT
fi

if ! command -v bwrap >/dev/null; then
echo "The 'bwrap' command was not found. Install 'bubblewrap' on your system, or" >&2
echo "disable sandboxing in $ROOT/config at your own risk." >&2
echo "disable sandboxing in ${OPAMROOT:-~/.opam}/config at your own risk." >&2
echo "See https://github.com/projectatomic/bubblewrap for bwrap details." >&2
echo "For 'bwrap' use in opam, see the FAQ:" >&2
echo " https://opam.ocaml.org/doc/2.0/FAQ.html#Why-does-opam-require-bwrap." >&2
echo " https://opam.ocaml.org/doc/2.0/FAQ.html#Why-does-opam-require-bwrap" >&2
exit 10
fi

Expand Down
4 changes: 2 additions & 2 deletions src_ext/Makefile.sources
Original file line number Diff line number Diff line change
Expand Up @@ -33,8 +33,8 @@ MD5_dose3 = e7d4b1840383c6732f29a47c08ba5650

$(call PKG_SAME,dose3)

URL_mccs = https://github.com/AltGr/ocaml-mccs/archive/1.1+5.tar.gz
MD5_mccs = 8a569a8f31969805da236471f4c0811d
URL_mccs = https://github.com/AltGr/ocaml-mccs/archive/1.1+6.tar.gz
MD5_mccs = 864333066431caf9ebe3a3e1dc4fb22e

$(call PKG_SAME,mccs)

Expand Down

0 comments on commit 08c89d5

Please sign in to comment.