1%----------------------------------------------------------------------
2% BEGIN LICENSE BLOCK
3% Version: CMPL 1.1
4%
5% The contents of this file are subject to the Cisco-style Mozilla Public
6% License Version 1.1 (the "License"); you may not use this file except
7% in compliance with the License.  You may obtain a copy of the License
8% at www.eclipse-clp.org/license.
9% 
10% Software distributed under the License is distributed on an "AS IS"
11% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied.  See
12% the License for the specific language governing rights and limitations
13% under the License. 
14% 
15% The Original Code is  The Zinc Modelling interface for ECLiPSe
16% The Initial Developer of the Original Code is  Joachim Schimpf
17% with support from Cisco Systems and NICTA Victoria.
18% Portions created by the Initial Developer are
19% Copyright (C) 2007 Cisco Systems, Inc.  All Rights Reserved.
20% 
21% Contributor(s): Joachim Schimpf
22% 
23% END LICENSE BLOCK
24%----------------------------------------------------------------------
25
26:- module(minizinc).
27
28:- comment(date, "$Date: 2012/10/23 00:38:15 $").
29:- comment(categories, ["Interfacing","Constraints"]).
30:- comment(summary, "Utilities for using MiniZinc with ECLiPSe").
31:- comment(author, "Joachim Schimpf, supported by Cisco Systems and NICTA Victoria").
32:- comment(copyright, "Cisco Systems Inc, licensed under CMPL").
33:- comment(see_also, [
34	flatzinc:struct(zn_options),
35	library(flatzinc),
36	library(fzn_ic),
37	library(fzn_fd),
38	library(fzn_eplex)
39    ]).
40:- comment(status, prototype).
41:- comment(desc, html("
42<H3>
43Overview
44</H3>
45<P>
46This module allows to run MiniZinc models with ECLiPSe.
47MiniZinc models can be either read from a file or stream,
48or they can be embedded as strings into ECLiPSe code.
49The implementation relies on an external MiniZinc-to-FlatZinc converter,
50e.g. mzn2fzn, and on the FlatZinc interpreter lib(flatzinc).
51Mappings to different ECLiPSe solvers are possible via the solver
52mapping libraries fzn_ic, fzn_fd, fzn_eplex, etc.
53</P>
54
55<H3>
56Running MiniZinc Models without using this Library
57</H3>
58<P>
59You can run a MiniZinc model by first converting it to FlatZinc yourself,
60and then using the lib(flatzinc) library. This can be done either via
61an intermediate .fzn file, or by piping the resulting FlatZinc model
62into the ECLiPSe-FlatZinc interpreter using e.g.
63<PRE>
64% mzn2fzn --output-to-stdout model.mzn | eclipse -e \"flatzinc:fzn_run(fzn_ic)\"
65</PRE>
66This should work as long as the mzn2fzn command is in your PATH.
67Note that mzn2fzn is currently not included with ECLiPSe but comes
68with the Melbourne MiniZinc distribution.  You must also make sure that
69the correct specialised global constraint definitions are used,
70by including e.g. lib/fzn_ic in mzn2fzn's search path via its -I option.
71For more details see lib(flatzinc).
72</P>
73
74<H3>
75Running MiniZinc Models using this Library
76</H3>
77<P>
78This library allows you to do everything from within ECLiPSe and let ECLiPSe
79invoke the MiniZinc to FlatZinc translator (mzn2fzn) internally with the
80correct arguments.  The model can be contained in a file:
81<PRE>
82?- mzn_run(\"model.mzn\", fzn_ic).
83</PRE>
84or, if a data instance file is used
85<PRE>
86?- mzn_run(\"model.mzn\", \"instance.dzn\", fzn_ic).
87</PRE>
88Since MiniZinc models are typically small, they can also be embedded as
89a string into ECLiPSe code. For example:
90<PRE>
91    queens8 :-
92	mzn_run_string(\"
93		int: n = 8;
94		array [1..n] of var 1..n: q;
95		constraint
96		    forall (i in 1..n, j in i+1..n) (
97			q[i]     != q[j]     /\\\\
98			q[i] + i != q[j] + j /\\\\
99			q[i] - i != q[j] - j
100		    );
101		solve satisfy;
102	    \", fzn_ic).
103</PRE>
104Note that, because of the rules for escaping characters within
105ECLiPSe strings, the backslashes had to be doubled!
106</P>
107
108<H3>
109Installation
110</H3>
111<P>
112This version is intended to to work with Minizinc 1.1 or later!
113<P>
114In order to be found by lib(minizinc), the Melbourne Minizinc-to-Flatzinc
115converter mzn2fzn must be installed in a directory called <CODE>minizinc-&lt;version&gt;</CODE>
116in one of the following locations (where we write &lt;ECLIPSEDIR&gt; for
117the ECLiPSe installation directory, and &lt;ECLIPSEARCH&gt; for
118the name for the machine architecture, e.g. i386_nt for Windows, i386_linux
119for Linux):
120<OL>
121<LI>Directory specified by <CODE>$ECLIPSEMZN</CODE> environment variable</LI>
122<LI>The user's home directory, as indicated by $HOME or $HOMEPATH</LI>
123<LI><CODE>&lt;location of lib(minizinc)&gt;/&lt;ECLIPSEARCH&gt;</CODE></LI>
124<LI><CODE>&lt;ECLIPSEDIR&gt;/lib_public/&lt;ECLIPSEARCH&gt;</CODE></LI>
125<LI><CODE>&lt;ECLIPSEDIR&gt;/lib/&lt;ECLIPSEARCH&gt;</CODE></LI>
126<LI><CODE>&lt;ECLIPSEDIR&gt;</CODE></LI>
127<LI>Parent of <CODE>&lt;ECLIPSEDIR&gt;</CODE> (e.g. \"C:/Program Files\" on Windows)</LI>
128<LI>Directory specified by <CODE>$PROGRAMFILES</CODE> environment variable</LI>
129</OL>
130<P>
131You can also set the environment variable ECLIPSEMZN (on Windows alternatively
132the registry entry HKLM/SOFTWARE/IC-Parc/Eclipse/<version>/ECLIPSEMZN)
133to the Minizinc installation directory (or to its parent).
134
135
136<H3>
137Combining a MiniZinc model with Search or I/O in ECLiPSe
138</H3>
139<P>
140There are several reasons why one might want to embed a MiniZinc model
141into an ECLiPSe program:
142<UL>
143<LI>Passing parameters from the ECLiPSe program to the MiniZinc model</LI>
144<LI>Getting the model solutions back into ECLiPSe</LI>
145<LI>Programming custom search in ECLiPSe</LI>
146<LI>Doing custom output beyond what the Zinc output annotations can do</LI>
147</UL>
148</P><P>
149To pass a parameter into a MiniZinc model, a generic MiniZinc model must
150be provided, together with a parameter map.
151This map is an ECLiPSe list that corresponds to a MiniZinc (actually
152FlatZinc) instance file:
153<PRE>
154queens(N) :-
155	mzn_run_string(\"
156		int: n;
157		array [1..n] of var 1..n: q;
158		constraint
159		    forall (i in 1..n, j in i+1..n) (
160			q[i]     != q[j]     /\\\\
161			q[i] + i != q[j] + j /\\\\
162			q[i] - i != q[j] - j
163		    );
164		solve satisfy;
165	    \",
166	    [n=N],	% parameter map: ZincId=EclipseValue
167	    fzn_ic).
168</PRE>
169Alternatively, the generic model can be kept separately in a MiniZinc file:
170<PRE>
171queens(N) :-
172	mzn_run(\"n_queens.mzn\", [n=N], fzn_ic).
173</PRE>
174<P>
175With the above exmples, search and output are still completely specified
176in MiniZinc.
177</P><P>
178To add your own search routine and/or output, use mzn_load_string/5 or
179mzn_load/5. This has the effect of only loading the MiniZinc model
180(i.e. setting up the constraints), but then returning to ECLiPSe without
181executing any MiniZinc solve or output primitives.  The rest of the work
182can then be done in ECLiPSe:
183</P>
184<PRE>
185queens(N, Q) :-
186	mzn_load(\"n_queens.mzn\", fzn_ic, [n=N], [q=Q], FznState),
187	labeling(Q),
188	fzn_output(FznState).
189</PRE>
190The [q=Q] mapping gives access to the ECLiPSe array Q corresponding to
191the MiniZinc array q. This is a normal ECLiPSe array of lib(ic) domain
192variables, and can be used for doing search, or outputting the results.
193In the example however, we have fallen back onto the FlatZinc output
194routine to display the results after search has finished.
195</P><P>
196Note that even if you do your own search in ECLiPSe, your MiniZinc model
197must contain a solve item to be syntactically correct (and to specify
198the objective, if any).
199</P>
200
201<H3>
202Options
203</H3>
204Instead of just the name of the solver mapping (<CODE>fzn_ic</CODE> in
205our examples), a <CODE>zn_options{}</CODE> structure can be given to
206customize the behaviour further, e.g.
207<PRE>
208	mzn_run(File, zn_options{solver:fzn_eplex,var_names:on}.
209</PRE>
210<DL>
211<DT>solver (default: fzn_ic)</DT><DD>
212    Determines which ECLiPSe solvers are used.  The name is the
213    name of a library implementing the mapping, e.g. fzn_ic,
214    fzn_fd or fzn_eplex.
215</DD>
216<DT>solutions (default: 1)</DT><DD>
217    The maximum number of solutions computed. Only effective if using
218    builtin search and not optimizing. (0 or all = all solutions)
219</DD>
220<DT>setup_prio (default: 0)</DT><DD>
221    The priority under which the constraint setup will be executed
222    (see call_priority/2 and get_priority/1). Possible values are
223    the ECLiPSe priorities 1 to 12, or 0 (the default) which stands
224    for the current priority of the calling code.  A sensible value
225    for this option is 2, which means that the setup code is executed
226    under high priority (still allowing debug/visualisation goals).
227    The effect of such a setting is that no propagation occurs until
228    all constraints are fully set up, possibly leading to time savings.
229</DD>
230<DT>parser (default: fast)</DT><DD>
231    Whether to use a 'strict' or 'fast' parser for FlatZinc input.
232</DD>
233<DT>var_names (default: off)</DT><DD>
234    Use lib(var_name) to label ECLiPSe variables with their Zinc names.
235    This is useful for debugging.
236</DD>
237<DT>fzn_tmp (default: file)</DT><DD>
238    Use a 'pipe' or intermediate 'file' for FlatZinc.
239</DD>
240</DL>
241
242<H3>
243Mapping between MiniZinc/FlatZinc Data and ECLiPSe Data
244</H3>
245<P>
246When using ECLiPSe with a Mini/FlatZinc model, one needs to be aware of
247the mapping from MiniZinc to FlatZinc (e.g. flattening of arrays),
248and the representation of FlatZinc data in ECLiPSe.
249</P><P>
250Note that the ECLiPSe-side representation depends in part on the chosen
251solver mapping. The following table shows the mapping used with fzn_ic
252(which employs the lib(ic) and lib(ic_sets) solver libraries):
253<PRE>
254	FlatZinc Type/Syntax		ECLiPSe Type/Syntax
255	-----------------------------------------------------------
256	string				string
257	e.g.	\"abc\"			\"abc\"
258
259	bool (false/true)		integer (0/1)
260	e.g.	false			0
261
262	int				integer
263	e.g.	33			33
264
265	float				float or breal
266	e.g.	3.4			3.399__3.401
267
268	set of int			ordered list of integer
269	e.g.	{1,5,4}			[1,4,5]
270		1..3			[1,2,3]
271
272	array[1..N] of T		structure with functor []/N
273	e.g.	[23,54,0]		[](23,54,0)
274
275	var bool			lib(ic) integer variable
276
277	var int				lib(ic) integer variable
278
279	var float			lib(ic) continuous variable
280
281	var set of int			lib(ic_sets) set variable
282</PRE>
283</P>
284")).
285
286
287% The location of this file, when loaded.
288% Used to find the ECLiPSe/Solver specific globals.mzn file
289:- local variable(here).
290?- getcwd(Cwd), setval(here, Cwd).
291
292% Location of MiniZinc installation (with bin and lib subdirectories)
293% We try a couple of locations heuristically
294:- local
295	variable(minizinc_dir, ''),
296	variable(mzn2fzn_exe, "mzn2fzn"),
297	initialization((
298	    get_flag(installation_directory, EclDir),
299	    get_flag(hostarch, Arch),
300	    getval(here, Here),
301	    findall(Dir2, (
302		    ( Dir1 = "$ECLIPSEMZN/"
303		    ; Dir1 = "$HOME/"
304		    ; Dir1 = "$HOMEPATH/"
305		    ; concat_string([Here,Arch,/], Dir1)
306		    ; concat_string([EclDir,"/lib_public/",Arch,/], Dir1)
307		    ; concat_string([EclDir,"/lib/",Arch,/], Dir1)
308		    ; concat_string([EclDir,"/"], Dir1)
309		    ; concat_string([EclDir,"/../"], Dir1)
310		    ; Dir1 = "$PROGRAMFILES/"
311		    ),
312		    canonical_path_name(Dir1, Dir2)
313		), Dirs),
314	    (
315                (
316		    canonical_path_name("$ECLIPSEMZN/", MznDir)
317                ;
318                    member(Dir, Dirs),
319                    exists(Dir),
320                    read_directory(Dir, "", SubDirs0, _),
321                    sort(0, >=, SubDirs0, SubDirs),	% attempt to prefer newer ones
322                    member(Sub, SubDirs),
323                    member(Prefix, ["minizinc-","MiniZinc "]),
324                    substring(Sub, Prefix, 1),
325                    concat_string([Dir,Sub,/], MznDir)
326                ),
327                ( ( substring(MznDir, "minizinc-0", _)
328                  ; substring(MznDir, "minizinc-1.0", _)) -> % require 1.1 at least
329                    printf(warning_output, "Ignoring old version %w%n", [MznDir]),
330                    fail
331                ;
332                    true
333                ),
334		( concat_string([MznDir,"bin/private/mzn2fzn"], Mzn2Fzn)
335		; concat_string([MznDir,"bin/actual/mzn2fzn"], Mzn2Fzn)
336		; concat_string([MznDir,"bin/private/mzn2fzn-actual"], Mzn2Fzn)
337		),
338		existing_file(Mzn2Fzn, ["",".exe"], [readable], _Mzn2FznExe)
339	    ->
340		setval(minizinc_dir, MznDir),
341		setval(mzn2fzn_exe, Mzn2Fzn),
342		os_file_name(MznDir, MznDirOS),
343		printf(log_output, "Using minizinc installation at %w%n", [MznDirOS])
344	    ;
345		printf(log_output, "No usable minizinc installation found in either of:%n", []),
346		( foreach(Dir,Dirs) do writeln(log_output, Dir) ),
347		printf(log_output, "Will rely on PATH instead%n", [])
348	    )
349	)).
350
351% Global counter for generating temp file name
352:- local variable(tmpcnt, 1).
353
354:- lib(lists).
355:- use_module(flatzinc).
356:- reexport struct(_) from flatzinc.
357
358
359% redefined the of/2 expansion to avoid warnings for "array/set of ..."
360:- export macro((of)/2, tr_of/2, []).
361tr_of(OfTerm, Expanded) :-
362	OfTerm =..[of,_,B],
363	atom(B),
364	\+ fzn_simple_type(B),
365	expand_macros(OfTerm, Expanded)@eclipse_language.
366
367
368%----------------------------------------------------------------------
369% Top level predicates
370%----------------------------------------------------------------------
371
372:- export mzn_run/2.
373:- comment(mzn_run/2, [
374    summary:"Run a MiniZinc model from a given file",
375    amode:(mzn_run(+,++) is det),
376    args:["File":"File name (extension defaults to .mzn)",
377	"SolverOrOptions":"Name of solver mapping module, or zn_options-structure"],
378    see_also:[fzn_run/2, mzn_run/3, mzn_run_string/2, struct(zn_options)],
379    desc:html("<P>
380	Reads a MiniZinc model from a file, and interprets it using
381	the solver mapping defined in SolverOrOptions.  At the end of
382	solving, results are printed to the output stream, timing and
383	progress messages are printed to the log_output stream, warnings
384	to the warning_output stream, and error messages the error stream.
385	This predicate always succeeds.
386    </P>"),
387    eg:"
388    ?- mzn_run(\"mymodel.mzn\", fzn_ic).
389    Found a solution with cost 10
390    Found no solution with cost 7.0 .. 9.0
391    end = 10
392    b1 = 1
393    b2 = 0
394    b3 = 1
395    b4 = 0
396    Objective value = 10
397    Total time 0.031s cpu (0.016 setup + 0.000 search)
398
399    ?- mzn_run(queens8, zn_options{solver:fzn_ic,solutions:3}).
400    Starting search
401    q = [1,5,8,6,3,7,2,4]
402    Total time 0.016s cpu (0.016 setup + 0.000 search)
403    q = [1,6,8,3,7,4,2,5]
404    Total time 0.016s cpu (0.016 setup + 0.000 search)
405    q = [1,7,4,6,8,2,5,3]
406    Total time 0.016s cpu (0.016 setup + 0.000 search)
407"]).
408mzn_run(ModelFile, SolverOrOptions) :-
409	mzn_run(ModelFile, [], SolverOrOptions).
410
411
412:- export mzn_run/3.
413:- comment(mzn_run/3, [
414    summary:"Run a MiniZinc model from a given model and instance file",
415    amode:(mzn_run(+,+,++) is det),
416    args:["ModelFile":"File name (extension defaults to .mzn)",
417	"InstFileOrParMap":"Instance file name (extension defaults to .dzn, then .mzn), or list of Id=Term correspondences",
418	"SolverOrOptions":"Name of solver mapping module, or zn_options-structure"],
419    see_also:[mzn_run/2, mzn_run_string/2, struct(zn_options)],
420    desc:html("<P>
421	Reads a MiniZinc model (given a model file and an instance
422	file) and interprets it using the solver mapping defined in
423	SolverOrOptions.  At the end of solving, results are printed
424	to the output stream, timing and progress messages are printed
425	to the log_output stream, warnings to the warning_output
426	stream, and error messages the error stream.  This predicate
427	always succeeds.
428    </P>"),
429    eg:"
430    ?- mzn_run(\"mymodel.mzn\", \"myinstance.mzn\", fzn_ic).
431    Found a solution with cost 10
432    Found no solution with cost 7.0 .. 9.0
433    end = 10
434    b1 = 1
435    b2 = 0
436    b3 = 1
437    b4 = 0
438    Objective value = 10
439    Total time 0.031s cpu (0.016 setup + 0.000 search)
440
441    ?- mzn_run(\"queens.mzn\", [n=8], fzn_ic).
442    Starting search
443    q = [1,5,8,6,3,7,2,4]
444    Total time 0.015s cpu (0.000 setup + 0.000 search)
445"]).
446mzn_run(ModelFile0, ParMapOrFile, SolverOrOptions) :-
447	zn_options(SolverOrOptions, Options),
448	( is_list(ParMapOrFile) ->
449	    pars_to_instancefile(ParMapOrFile, MznInstFile, Options),
450	    mzn2fzn(ModelFile0, MznInstFile, Options, FznStream, PidOrFile),
451	    delete_file(MznInstFile)
452	;
453	    mzn2fzn(ModelFile0, ParMapOrFile, Options, FznStream, PidOrFile)
454	),
455%        Options = zn_options{output:SolOut},
456%        exec([solns2out,'msq.ozn'], [SolOut], _Pid),
457	fzn_run_stream(FznStream, Options),
458%        close(SolOut),
459	mzn2fzn_cleanup(PidOrFile).
460
461
462:- export mzn_run_string/2.
463:- comment(mzn_run_string/2, [
464    summary:"Run a MiniZinc model given as a string or list",
465    amode:(mzn_run_string(++,++) is det),
466    args:["MznModel":"String, Atom or List of constants",
467	"SolverOrOptions":"Name of solver mapping module, or zn_options-structure"],
468    see_also:[mzn_run/2, mzn_run/3, struct(zn_options)],
469    desc:html("<P>
470	Solves the MiniZinc model MznModel, given in the simplest form
471	as a string in MiniZInc syntax.  The problem is solved using
472	a mapping to a concrete ECLiPSe solver, as specified in the
473	SolverOrOptions argument.  Search and output are done according
474	to the model's solve and output items.
475    </P><P>
476	Note that, because of the rules for escaping characters within
477	ECLiPSe strings, any backslashes in the MiniZinc source have
478	to be doubled, and double quotes must be escaped with a backslash!
479    </P><P>
480	Obviously, one would like to pass parameters into a model.  The
481	model can therefore  be given as a list of strings in MiniZinc
482	syntax, interleaved with ECLiPSe ground terms that serve as 
483	parameter instantiations.  The actual MiniZinc model then
484	consists of the concatenation of all these parts.
485    </P>"),
486    eg:"
487    ?- mzn_run_string(\"
488		int: n = 8;
489		array [1..n] of var 1..n: q;
490		constraint
491		    forall (i in 1..n, j in i+1..n) (
492			q[i]     != q[j]     /\\\\
493			q[i] + i != q[j] + j /\\\\
494			q[i] - i != q[j] - j
495		    );
496		solve satisfy;
497	    \", fzn_ic).
498
499    Starting search
500    q = [1,5,8,6,3,7,2,4]
501    Total time 0.020s cpu (0.020 setup+ 0.000 search)
502    Yes (0.02s cpu, solution 1, maybe more)
503
504
505    ?- N=8, mzn_run_string([\"
506		int: n = \",
507	    N, \";
508		array [1..n] of var 1..n: q;
509		constraint
510		    forall (i in 1..n, j in i+1..n) (
511			q[i]     != q[j]     /\\\\
512			q[i] + i != q[j] + j /\\\\
513			q[i] - i != q[j] - j
514		    );
515		solve satisfy;
516	    \"], fzn_ic).
517
518    Starting search
519    q = [1,5,8,6,3,7,2,4]
520    Total time 0.020s cpu (0.020 setup+ 0.000 search)
521    N = 8
522    Yes (0.02s cpu, solution 1, maybe more)
523</PRE>
524"]).
525
526mzn_run_string(MznModel, SolverOrOptions) :-
527	mzn_run_string(MznModel, SolverOrOptions, []).
528
529mzn_run_string(MznModel, SolverOrOptions, ParMap) :-
530	(
531	    mzn_load_string(MznModel, SolverOrOptions, ParMap, [], State),
532	    fzn_search(State),
533	    fzn_output(State),
534	    writeln(----------),
535	    fzn_last(State),
536	    !
537	;
538	    writeln(==========)
539	).
540
541
542:- export mzn_load_string/5.
543:- comment(mzn_load_string/5, [
544    summary:"Load a MiniZinc model given as a string or list",
545    amode:(mzn_load_string(++,++,++,+,-) is semidet),
546    args:["MznModel":"String, Atom or List of constants",
547	"SolverOrOptions":"Name of solver mapping module, or zn_options-structure",
548	"ParMap":"List of FznId=ECLiPSeGroundTerm correspondences",
549	"VarMap":"List of FznId=ECLiPSeVarTerm correspondences",
550	"FznState":"FlatZinc state descriptor"],
551    fail_if:"Fails if the constraint setup fails",
552    see_also:[mzn_run/2, mzn_run/3, mzn_run_string/2, struct(zn_options)],
553    desc:html("<P>
554	Loads the MiniZinc model MznModel, given in the simplest form
555	as a string in MiniZinc syntax.  The problem is set up using
556	a mapping to a concrete ECLiPSe solver, as specified in the
557	SolverOrOptions argument.  Neither search nor output are done.
558    </P><P>
559	Note that, because of the rules for escaping characters within
560	ECLiPSe strings, any backslashes in the MiniZinc source have
561	to be doubled, and double quotes must be escaped with a backslash!
562    </P><P>
563	To pass parameters into the model, a ParMap can be given, consisting
564	of a list of FznId=ECLiPSeGroundTerm correspondences.  Here, FznId
565	is an atom (the FlatZinc parameter identifier within the model),
566	and ECLiPSeGroundTerm is the corresponding ECLiPSe constant.
567    </P><P>
568    	To access the ECLiPSe variables corresponding to the model's
569	variables, VarMap can be given, consisting of a list of
570	FznId=ECLiPSeTerm correspondences.  Here, FznId is an atom
571	(the FlatZinc variable identifier within the model), and
572	ECLiPSeTerm is the corresponding ECLiPSe constant, variable
573	or array.
574    </P><P>
575    	The mzn_load_string/5 predicate returns a FlatZinc solver
576	state which can be used to lookup further information about
577	the model (fzn_var_lookup/3, fzn_obj_lookup/2), to perform
578	the standard search (fzn_search/1), or to perform the model's
579	output actions (fzn_output/1).
580    </P>"),
581    eg:"
582    ?- mzn_load_string(\"
583		int: n;
584		array [1..n] of var 1..n: q;
585		constraint
586		    forall (i in 1..n, j in i+1..n) (
587			q[i]     != q[j]     /\\\\
588			q[i] + i != q[j] + j /\\\\
589			q[i] - i != q[j] - j
590		    );
591		solve satisfy;
592	    \",
593	    fzn_ic,
594	    [n=8],
595	    [q=Q],
596	    FznState).
597
598    Q = [](_2492{1..8}, _2512{1..8}, _2532{1..8}, _2552{1..8}, ...]
599    FznState = state(...)
600    There are 84 delayed goals.
601    Yes (0.02s cpu)
602
603
604    ?- mzn_load_string(\"...\", fzn_ic, [n=8], [q=Q], FznState),
605       ic:labeling(Q).
606
607    Q = [](1, 5, 8, 6, 3, 7, 2, 4)
608    FznState = state(...)
609    Yes (0.03s cpu, solution 1, maybe more)
610
611
612    ?- mzn_load_string(\"...\", fzn_ic, [n=8], [q=Q], FznState),
613       ic:labeling(Q),
614       fzn_output(FznState).
615
616    % output from fzn_output:
617    q = [1,5,8,6,3,7,2,4];
618    % Total time 0.030s cpu (0.020 setup)
619
620    % output from ECLiPSe toplevel:
621    Q = [](1, 5, 8, 6, 3, 7, 2, 4)
622    FznState = state(...)
623    Yes (0.03s cpu, solution 1, maybe more)
624</PRE>
625"]).
626mzn_load_string(MznModel, SolverOrOptions, ParMap, VarMap, State) :-
627	zn_options(SolverOrOptions, Options),
628	model_to_modelfile(MznModel, MznFile),
629	pars_to_instancefile(ParMap, MznInstFile, Options),
630	mzn2fzn(MznFile, MznInstFile, Options, FznStream, PidOrFile),
631	fzn_init(Options, State),
632	( block(fzn_load_stream(FznStream, State), Tag,
633		(mzn_load_cleanup(PidOrFile, MznInstFile),
634		delete_file(MznFile),
635		exit_block(Tag)))
636	->
637	    mzn_load_cleanup(PidOrFile, MznInstFile),
638	    delete_file(MznFile)
639	;
640	    mzn_load_cleanup(PidOrFile, MznInstFile),
641	    delete_file(MznFile),
642	    fail
643	),
644	fzn_ids_to_ecl_vars(VarMap, State).
645
646
647:- export mzn_load/5.
648:- comment(mzn_load/5, [
649    summary:"Load a MiniZinc model from a file",
650    amode:(mzn_load(++,++,++,+,-) is semidet),
651    args:["ModelFile":"File name (extension defaults to .mzn)",
652	"SolverOrOptions":"Name of solver mapping module, or zn_options-structure",
653	"ParMap":"List of FznId=ECLiPSeGroundTerm correspondences",
654	"VarMap":"List of FznId=ECLiPSeVarTerm correspondences",
655	"FznState":"FlatZinc state descriptor"],
656    fail_if:"Fails if the constraint setup fails",
657    see_also:[mzn_run/2, mzn_run/3, mzn_load_string/5, struct(zn_options)],
658    desc:html("<P>
659	Loads a MiniZinc from ModelFile.  The problem is set up using
660	a mapping to a concrete ECLiPSe solver, as specified in the
661	SolverOrOptions argument.  Neither search nor output are done.
662    </P><P>
663	To pass parameters into the model, a ParMap can be given, consisting
664	of a list of FznId=ECLiPSeGroundTerm correspondences.  Here, FznId
665	is an atom (the FlatZinc parameter identifier within the model),
666	and ECLiPSeGroundTerm is the corresponding ECLiPSe constant.
667    </P><P>
668    	To access the ECLiPSe variables corresponding to the model's
669	variables, VarMap can be given, consisting of a list of
670	FznId=ECLiPSeTerm correspondences.  Here, FznId is an atom
671	(the FlatZinc variable identifier within the model), and
672	ECLiPSeTerm is the corresponding ECLiPSe constant, variable
673	or array.
674    </P><P>
675    	The mzn_load/5 predicate returns a FlatZinc solver
676	state which can be used to lookup further information about
677	the model (fzn_var_lookup/3, fzn_obj_lookup/2), to perform
678	the standard search (fzn_search/1), or to perform the model's
679	output actions (fzn_output/1).
680    </P>"),
681    eg:"
682    ?- mzn_load(\"queens\", fzn_ic, [n=8], [q=Q], FznState).
683
684    Q = [](_2492{1..8}, _2512{1..8}, _2532{1..8}, _2552{1..8}, ...]
685    FznState = state(...)
686    There are 84 delayed goals.
687    Yes (0.02s cpu)
688
689
690    ?- mzn_load(\"queens\", fzn_ic, [n=8], [q=Q], FznState),
691       ic:labeling(Q).
692
693    Q = [](1, 5, 8, 6, 3, 7, 2, 4)
694    FznState = state(...)
695    Yes (0.03s cpu, solution 1, maybe more)
696
697
698    ?- mzn_load(\"queens\", fzn_ic, [n=8], [q=Q], FznState),
699       ic:labeling(Q),
700       fzn_output(FznState).
701
702    % output from fzn_output:
703    q = [1,5,8,6,3,7,2,4];
704    % Total time 0.030s cpu (0.020 setup)
705
706    % output from ECLiPSe toplevel:
707    Q = [](1, 5, 8, 6, 3, 7, 2, 4)
708    FznState = state(...)
709    Yes (0.03s cpu, solution 1, maybe more)
710</PRE>
711"]).
712mzn_load(MznFile, SolverOrOptions, ParMap, VarMap, State) :-
713	zn_options(SolverOrOptions, Options),
714	pars_to_instancefile(ParMap, MznInstFile, Options),
715	mzn2fzn(MznFile, MznInstFile, Options, FznStream, PidOrFile),
716	fzn_init(Options, State),
717	( block(fzn_load_stream(FznStream, State), Tag,
718		(mzn_load_cleanup(PidOrFile, MznInstFile), exit_block(Tag)))
719	->
720	    mzn_load_cleanup(PidOrFile, MznInstFile)
721	;
722	    mzn_load_cleanup(PidOrFile, MznInstFile),
723	    fail
724	),
725	fzn_ids_to_ecl_vars(VarMap, State).
726
727
728    model_to_modelfile(MznModel, MznFile) :-
729	make_tmpfile(mod, MznFile),
730	open(MznFile, write, MznStream),
731	(
732	    ( MznModel = [_|_] ->
733		% Crude way to insert ECLiPSe parameters into MiniZinc source
734		( foreach(Part,MznModel), param(MznStream) do
735		    fzn_write(MznStream, Part)
736		)
737	    ;
738		(string(MznModel);atom(MznModel)),
739		write(MznStream, MznModel)
740	    )
741	->
742	    close(MznStream)
743	;
744	    close(MznStream),
745	    delete_file(MznFile),
746	    fzn_error("Malformed Model", [MznModel])
747	).
748
749
750    pars_to_instancefile([], _MznInstFile, _Options) ?- !.
751    pars_to_instancefile(ParMap, MznInstFile, zn_options{solver:Solver}) :-
752	% Check the ParMap
753	ground(ParMap),
754	is_list(ParMap),
755	( foreach(TyId=_Value,ParMap) do
756	    ( TyId = (Ty:Id) ->
757	    	atom(Id),
758		fzn_type(Ty)
759	    ;
760		atom(TyId)
761	    )
762	),
763	!,
764	make_tmpfile(inst, MznInstFile),
765	open(MznInstFile, write, Stream),
766	writeln(Stream, "% Generated instance file"),
767	( foreach(TyId=Value,ParMap), param(Stream,Solver) do
768	    ( TyId = (Ty:Id) ->
769		printf(Stream, "%w = ", [Id]),
770		fzn_write(Stream, Value, Ty, Solver)
771	    ;
772		printf(Stream, "%w = ", [TyId]),
773		fzn_write(Stream, Value)
774	    ),
775	    writeln(Stream, ";")
776	),
777	close(Stream).
778    pars_to_instancefile(ParMap, _MznInstFile, _Options) :-
779	fzn_error("Illegal ParMap: %w", [ParMap]).
780
781    % 
782    fzn_type(no_macro_expansion(array(_) of T)) ?- !,
783	fzn_simple_type(T).
784    fzn_type(no_macro_expansion(set of T)) ?- !,
785	fzn_scalar_type(T).
786    fzn_type(T) :-
787	fzn_simple_type(T).
788
789    fzn_scalar_type(bool).
790    fzn_scalar_type(int).
791
792    fzn_simple_type(bool).
793    fzn_simple_type(int).
794    fzn_simple_type(float).
795
796
797    mzn2fzn_cleanup(PidOrFile) :-
798	( number(PidOrFile) ->
799	    ( wait(PidOrFile, _Status) -> true ; true )
800	;
801	    delete_file(PidOrFile)
802	).
803
804    make_tmpfile(What, File) :-
805	getval(tmpcnt, I),
806	incval(tmpcnt),
807	get_flag(tmp_dir, Dir),
808	get_flag(pid, Pid),
809	get_flag(unix_time, Time),
810	concat_string([Dir,ecl_,What,I,"_",Time,"_",Pid,".mzn"], File).
811
812
813    delete_file(File) :-
814	( nonvar(File), exists(File) -> delete(File) ; true ).
815
816    fzn_ids_to_ecl_vars(VarMap, State) :-
817	( foreach(Id=EclVar,VarMap), param(State) do
818	    ( fzn_var_lookup(State, Id, EclVar) ->
819	    	true
820	    ;
821		fzn_error("No such id in the model: %w", [Id])
822	    )
823	).
824
825    mzn_load_cleanup(PidOrFile, MznFile) :-
826	mzn2fzn_cleanup(PidOrFile),
827	delete_file(MznFile).
828
829
830%----------------------------------------------------------------------
831% Invoke the MiniZinc->FlatZinc converter
832% ModelFile should be file name with or without .mzn extension.
833% DataFile can be a variable, or like ModelFile.
834% Pipe FlatZinc output into FznStream, or produce intermediate .fzn file,
835% depending on the flag UseFznFile.
836% If output is piped, PidOrFile is process id to be waited for.
837% If output is via file, PidOrFile is .fzn file to be deleted.
838%----------------------------------------------------------------------
839
840mzn2fzn(ModelFile0, DataFile0, zn_options{solver:Solver,fzn_tmp:OutFlag}, FznStream, PidOrFile) :-
841	( existing_file(ModelFile0, ["",".mzn"], [readable], ModelFile) ->
842	    os_file_name(ModelFile, ModelFileOS)
843	;
844	    fzn_error("No such file: %w", [ModelFile0])
845	),
846	( (atom(DataFile0);string(DataFile0)) ->
847	    ( existing_file(DataFile0, ["",".dzn",".mzn"], [readable], DataFile) ->
848		os_file_name(DataFile, DataFileOS),
849		Params0 = ["--data",DataFileOS,ModelFileOS]
850	    ;
851		fzn_error("No such file: %w", [DataFile0])
852	    )
853	;
854	    Params0 = [ModelFileOS]
855	),
856	getval(here, EclZincLib),
857	concat_string([EclZincLib,Solver], EclZincSolverSpecificLib),
858	os_file_name(EclZincSolverSpecificLib, EclZincSolverSpecificLibOS),
859	getval(minizinc_dir, MznDir),
860	getval(mzn2fzn_exe, Mzn2Fzn),
861	( MznDir == '' ->
862	    % Hope the exectuable knows its stdlib-dir
863	    Params = ["-I",EclZincSolverSpecificLibOS|Params0]
864	;
865	    % Assume we are calling the mzn2fzn-actual exectuable
866	    % without any environment variable setting
867	    concat_string([MznDir, "lib/minizinc"], ZincDefaultLib),
868	    os_file_name(ZincDefaultLib, ZincDefaultLibOS),
869	    Params = ["-I",EclZincSolverSpecificLibOS,
870		      "--stdlib-dir",ZincDefaultLibOS|Params0]
871	),
872	( OutFlag==file ->
873	    % use intermediate fzn file, and echo any stderr on error
874	    ( var(PidOrFile) ->
875		pathname(ModelFile, Path, Base, _Mzn),
876		concat_string([Path,Base,".fzn"], PidOrFile)
877	    ;
878		true
879	    ),
880	    os_file_name(PidOrFile, FznFileOS),
881%	    writeln(exec([Mzn2Fzn,"--output-to-file",FznFileOS|Params], [null,null,Err], Pid)),
882	    exec([Mzn2Fzn,"--output-to-file",FznFileOS|Params], [null,null,Err], Pid),
883	    read_stream(Err, Message),
884	    write(error, Message),
885	    wait(Pid, Status),
886	    ( Message \== "" ->
887		fzn_error("mzn2fzn unsuccessful", [])
888	    ; Status \== 0 ->
889		fzn_error("mzn2fzn exited with status %16r", [Status])
890	    ;
891		true
892	    ),
893	    open(PidOrFile, read, FznStream)
894	;
895	    % pipe the fzn - we can't easily handle the error output
896	    % without running the risk of blocking
897%	    writeln(exec([Mzn2Fzn,"--output-to-stdout"|Params], [null,FznStream], PidOrFile)),
898	    exec([Mzn2Fzn,"--output-to-stdout"|Params], [null,FznStream], PidOrFile)
899	).
900
901    read_stream(Stream, String) :-
902	( read_string(Stream, end_of_file, _, String) ->
903	    close(Stream)
904	;
905	    close(Stream),
906	    String = ""
907	).
908
909
910:- export mzn2fzn/4.
911:- comment(mzn2fzn/4, [
912    summary:"Convert a MiniZinc model into a FlatZinc model",
913    amode:(mzn2fzn(+,+,++,?) is det),
914    args:["ModelFile":"File name (extension defaults to .mzn)",
915	"InstFileOrParMap":"Instance file name (extension defaults to .dzn, then .mzn), or list of Id=Term correspondences",
916	"SolverOrOptions":"Name of solver mapping module, or zn_options-structure",
917	"FznFile":"Name of generated FlatZinc file (will be generated if variable)"],
918    see_also:[mzn_run/3, flatzinc:fzn_run/2, struct(zn_options)],
919    desc:html("<P>
920	Converts a MiniZinc model (given a model file and an instance
921	file or parameter map) into a FlatZinc model, by invoking the
922	external mzn2fzn converter with the appropriate arguments.
923	If no output file name is specified (FznFile uninstantiated),
924	the name of the output file is the same as the input file, with
925	the extension changed to .fzn.  The options should specify the
926	solver that is intended to be used on the FlatZinc model (so that
927	the correct version of globals.mzn is used), and the fzn_tmp
928	option should be set to 'file' (the default).
929    </P>"),
930    eg:"
931    ?- mzn2fzn(mymodel, [], zn_options{solver:fzn_ic,fzn_tmp:file}, FznFile).
932    FznFile = \"mymodel.fzn\"
933    Yes (0.00s cpu)
934"]).
935
936mzn2fzn(MznFile, ParMapOrFile, SolverOrOptions, FznFile) :-
937	zn_options(SolverOrOptions, Options),
938	Options = zn_options{fzn_tmp:OutFlag},
939	( OutFlag == file ->
940	    ( is_list(ParMapOrFile) ->
941		pars_to_instancefile(ParMapOrFile, MznInstFile, Options),
942		mzn2fzn(MznFile, MznInstFile, Options, FznStream, FznFile),
943		delete_file(MznInstFile)
944	    ;
945		mzn2fzn(MznFile, ParMapOrFile, Options, FznStream, FznFile)
946	    ),
947	    close(FznStream)
948	;
949	    fzn_error("Unsupported option fzn_tmp:%w", [OutFlag])
950	).
951
952