10.39.3.2 Exported Predicates

The following predicates all take as (optional) argument a list Options which can be used to change the default behavior of the execution. This list may contain zero or more of the following:

data_file(MznDatFile)
where MznDatFile must be a MiniZinc data file. Means that MznDatFile is passed to the MiniZinc-to-FlatZinc translator through the --data option.
parameters(ListOfParDef)
where ListOfParDef is a list of elements of the form Id=Value where Id is a MiniZinc identifier and Value is a MiniZinc value. Means that all elements are written to a temporary file which is passed to the MiniZinc-to-FlatZinc translator through the --data option.
post(Boolean)
where Boolean must be true or false. If true (the default), the constraints of the MiniZinc program are posted directly and a separate call to fzn_post/1 (see FlatZinc Exported Predicates) is not necessary. (Only usable with mzn_load_file/3 and mzn_load_model/3.)
solutions(NumberOfSolutions)
where NumberOfSolutions must be an integer greater than zero or the atom all. Describes the number of solutions to search for, default is 1. (Only usable with mzn_run_file/2 and mzn_run_model/2.)
output(File)
where File must be the name of a writable file. Causes any output written on the current output stream to be directed to File. (Only usable with mzn_run_file/2 and mzn_run_model/2.)
statistics(Boolean)
where Boolean must be true or false (default). If true, the following statistics are written on the current output stream (see the built-in statistics/[0,2] and fd_statistics/[0,2] of library(clpfd) for more detailed information on their meaning):
runtime
Total running time (milliseconds), including parsing the FlatZinc program.
solvetime
Running time (milliseconds) for posting the constraints and performing the search.
solutions
The number of solutions found.
constraints
The number of constraints created.
backtracks
The number of times a contradiction was found by a domain being wiped out, or by a global constraint signalling failure.
prunings
The number of times a domain was pruned.
(Only usable with mzn_run_file/2 and mzn_run_model/2.)
timeout(Time)
where Time must be an integer between (not including) 0 and 2147483647. Stops the computation if it has not finished before Time milliseconds has elapsed. Measuring starts after the call to the MiniZinc-to-FlatZinc translator has finished. (Only usable with mzn_run_file/2 and mzn_run_model/2.)
variables(ListOfVarDef)
where ListOfVarDef is a list of elements of the form Id=Var where Id is a MiniZinc identifier and Var is a Prolog variable. Means that Var is unified with the value of Id after the MiniZinc program is loaded. (Only usable with mzn_load_file/3 and mzn_load_model/3).

The first two predicates can be used to run a MiniZinc program in one go.

mzn_run_file(+MznFile)
mzn_run_file(+MznFile, +Options)
MznFile is a MiniZinc program file and Options is a list of options as described above. (Usable options are data_file/1, parameters/1, solutions/1, and statistics/1.) Runs the MiniZinc program in MznFile and writes the result on the current output stream. This is done by first calling the external MiniZinc-to-FlatZinc translator and parsing the output of that program with fzn_run_stream/[1,2] (see FlatZinc Exported Predicates). Fails if the constraints of the MiniZinc program are inconsistent.

Exceptions:


mzn_run_model(+MznModel)
mzn_run_model(+MznModel, +Options)
MznModel is a MiniZinc program specified by a list of strings as explained below and Options is a list of options as described above. (Usable options are data_file/1, parameters/1, solutions/1, and statistics/1.) Runs the MiniZinc program specified by MznModel and writes the result on the current output stream. This is done by first calling the external MiniZinc-to-FlatZinc translator and parsing the output of that program with fzn_run_stream/[1,2] (see FlatZinc Exported Predicates). The MiniZinc program specification MznModel must be a list of strings (list of character codes) where each element must specify one line of the MiniZinc program. For example, a MiniZinc program for the N Queens problem can be specified as follows:
          NQueens = ["int: n;",
                     "array [1..n] of var 1..n: q;",
                     "constraint forall (i in 1..n, j in i+1..n)",
                         "(q[i] != q[j] /\\",
                          "q[i] + i != q[j] + j /\\",
                          "q[i] - i != q[j] - j);",
                     "solve satisfy;",
                     "output [\"A solution to the \", show(n),",
                     "\" Queens problem: \", show(q), \"\\n\"];"]
     

Note that backslashes and double quotes must be escaped with an additional backslash.

Exceptions:

Consider the following MiniZinc program for solving the N Queens problem located in library('zinc/examples/queen.mzn'):

                                  
queen.mzn
int: n; array [1..n] of var 1..n: q; constraint forall (i in 1..n, j in i+1..n) ( q[i] != q[j] /\ q[i] + i != q[j] + j /\ q[i] - i != q[j] - j ); solve satisfy; output ["A solution to the ", show(n), " Queens problem: ", show(q), "\n"];

Consider now the following goal at the Prolog top level:

     | ?- mzn_run_file(library('zinc/examples/queen'),
                       [data_file(library('zinc/examples/queen4.dat'))]).

Since library('zinc/examples/queen4.dat') contains the single line

     n = 4;

the following is written on the current output stream:

     q = array1d(1..4, [2, 4, 1, 3]);
     ----------

The initialization n = 4 can also be passed using the parameter/1 option. So the following goal is equivalent to the one above:

     | ?- mzn_run_file(library('zinc/examples/queen'), [parameters([n=4])]).

Finally, the following goal finds all solutions to the 4 Queens problem:

     | ?- mzn_run_file(library('zinc/examples/queen'),
                       [parameters([n=4]), solutions(all)]).

Given this goal, the following is written on the current output stream:

     q = array1d(1..4, [2, 4, 1, 3]);
     ----------
     q = array1d(1..4, [3, 1, 4, 2]);
     ----------
     ==========

The next two predicates can be used to construct a FlatZinc state (see FlatZinc Exported Predicates).

mzn_load_file(+MznFile, -FznState)
mzn_load_file(+MznFile, +Options, -FznState)
MznFile is a MiniZinc program file and Options is a list of options as described above. (Usable options are data_file/1, parameters/1, post/1, and variables/1.) Initializes a FlatZinc state FznState with respect to MznFile. May fail if post(true) and the constraints are inconsistent.

Exceptions:


mzn_load_model(+MznModel, -FznState)
mzn_load_model(+MznModel, +Options, -FznState)
MznModel is a MiniZinc program specified by a list of strings as explained for mzn_run_model/[1,2] above and Options is a list of options as described above. (Usable options are data_file/1, parameters/1, post/1, and variables/1.) Initializes a FlatZinc state FznState with respect to MznModel. May fail if post(true) and the constraints are inconsistent.

Exceptions:

The following Prolog goal constructs a FlatZinc state representing the 4 Queens problem:

     | ?- mzn_load_file(library('zinc/examples/queen'),
                        [parameters([n=4])], Queen4State).

See FlatZinc Exported Predicates for more information on FlatZinc states and how they can be queried. A very useful option to mzn_load_file/3 and mzn_load_model/3 is the variables/1 option, which can be used to unify values of MiniZinc identifiers with Prolog variables (this option can be used in place of several calls to fzn_identifier/3). For example, the following goal posts an additional symmetry breaking constraint and labels the variables using a Prolog goal that finds all remaining solutions to the 4 Queens problem:

     | ?- mzn_load_file(library('zinc/examples/queen'),
                        [parameters([n=4]), variables([q=Q])],
                        Queen4State),
          Q = [Q1, Q2|_], Q1 #< Q2,
          findall(_, (labeling([], Q), fzn_output(Queen4State)), _).

Given this goal, the following is written on the current output stream:

     q = array1d(1..4, [2, 4, 1, 3]);
     ----------

The final predicate can be used to translate a MiniZinc file to a FlatZinc by a direct call to the MiniZinc-to-FlatZinc translator.

mzn_to_fzn(+MznFile, +FznFile)
mzn_to_fzn(+MznFile, +Options, +FznFile)
MznFile is a MiniZinc program file and Options is a list of options as described above. (Usable options are data_file/1 and parameters/1.) Calls the external MiniZinc-to-FlatZinc translator which result is written to FznFile.

Exceptions:


Send feedback on this subject.