Up

module Sigs

: sig

Some useful abstract module types.

#
module type MAP = sig
include Map.S
#
val find : key -> 'a t -> 'a option
end
#
module type CORE_MODEL = sig
#
module Role : sig
#
type t

A role that needs to be filled by a single implementation. If two dependencies require the same role then they will both get the same implementation.

#
val to_string : t -> string
#
val compare : t -> t -> int
end
#
type impl

An impl is something that can fill a Role.t

#
type command

A command is an entry-point provided by an implementation. Using a command may require extra dependencies (for example, a "test" command might depend on a test runner).

#
type command_name = private string

An identifier for a command within a role.

#
type dependency

A dependency indicates that an impl or command requires another role to be filled.

#
type dep_info = {
# dep_role
: Role.t;
# dep_importance
: [
| `essential
| `recommended
| `restricts
]
;
# dep_required_commands
: command_name list;
}
#
type requirements = {
# role
: Role.t;
# command
: command_name option;
}
#
val requires : Role.t -> impl -> dependency list * command_name list

Get an implementation's dependencies.

The dependencies should be ordered with the most important first. The solver will prefer to select the best possible version of an earlier dependency, even if that means selecting a worse version of a later one (restricts_only dependencies are ignored for this).

An implementation or command can also bind to itself. e.g. "test" command that requires its own "run" command. We also return all such required commands.

#
val dep_info : dependency -> dep_info
#
val command_requires : Role.t -> command -> dependency list * command_name list

As requires, but for commands.

#
val get_command : impl -> command_name -> command option
end
#
module type SOLVER_INPUT = sig

This defines what the solver sees (hiding the raw XML, etc).

include CORE_MODEL
#
type role_information = {
# replacement
: Role.t option;(*Another role that conflicts with this one.*)
# impls
: impl list;(*Candidates to fill the role.*)
}

Information provided to the solver about a role.

#
type restriction

A restriction limits which implementations can fill a role.

#
val impl_to_string : impl -> string
#
val command_to_string : command -> string
#
val implementations : Role.t -> role_information

The list of candidates to fill a role.

#
val restrictions : dependency -> restriction list

Restrictions on how the role is filled

#
val meets_restriction : impl -> restriction -> bool
#
val machine_group : impl -> Arch.machine_group option
end
#
module type SELECTIONS = sig
#
type t

Some selections previously produced by a solver. Note: logically, this should include CORE_MODEL, but that causes problems with duplicating RoleMap.

#
type role
#
type impl
#
type command_name
#
type requirements
#
val get_selected : role -> t -> impl option
#
val selected_commands : t -> role -> command_name list
#
val requirements : t -> requirements
#
module RoleMap : MAP with type key = role
end
#
module type SOLVER_RESULT = sig

The result of running the solver. Unlike the plain SELECTIONS type, this type can relate the selections back to the solver inputs, which is useful to provide diagnostics and the GUI.

include SOLVER_INPUT
include SELECTIONS with type impl := impl and type command_name := command_name and type requirements := requirements and type role = Role.t
#
type rejection

The reason why the model rejected an implementation before it got to the solver.

#
val rejects : Role.t -> (impl * rejection) list

Get the candidates which were rejected for a role (and not passed to the solver).

#
val compare_version : impl -> impl -> int

Used to sort the results.

#
val format_version : impl -> string
#
val user_restrictions : Role.t -> restriction option

Get any user-specified restrictions affecting a role. These are used to filter out implementations before they get to the solver.

#
val id_of_impl : impl -> string
#
val format_machine : impl -> string
#
val string_of_restriction : restriction -> string
#
val describe_problem : impl -> rejection -> string
#
val explain : t -> Role.t -> string

Get diagnostics-of-last-resort.

#
val raw_selections : t -> impl RoleMap.t

Get the final assignment of implementations to roles.

#
val dummy_impl : impl
end
end