[Haskell-cafe] Learn Prolog...

Andrew Cheadle amc4 at doc.ic.ac.uk
Mon Sep 3 02:46:17 EDT 2007


It's fairly correct and up-to-date although I note that the constraint 
example 'send more money' given is stated as 'Prolog' when it really 
uses ECLiPSe Prolog constraint syntax (alldifferent/1, labelling/1 and 
'#' integer constraints):

If you're really interested in constraint based languages then have a 
look at ECLiPSe (yes shameless plug and I'm biased ;-):

http://www.eclipse-clp.org

and in particular the language tutorial:

http://www.eclipse-clp.org/doc/tutorial/index.html

ECLiPSe is robust and mature enough for industrial application 
development, most notably by Cisco and CrossCore Optimization.

Incidentally, we've often seen a lot of traffic on here about Sudoku 
solvers and I've always wanted to post the ECLiPSe solution
(neat when you consider the length of the sudoku/2 predicate ;-) :

% ECLiPSe sample code - Sudoku problem
%
%    This is a puzzle, originating from Japan, where you have a
%    9x9 grid, consisting of 9 3x3 sub-grids. The challenge is
%    to fill the grid with numbers from 1 to 9 such that every row,
%    every column, and every 3x3 sub-grid contains the digits 1 to 9.
%    Some of these numbers are given, which is the way different
%    instances of the problem are made. The solution is usually unique.
%
%    Compile this file with ECLiPSe and call e.g.
%    :- solve(1).
%
% Author: Joachim Schimpf, IC-Parc
%

:- lib(ic).
:- import alldifferent/1 from ic_global.

solve(ProblemName) :-
    problem(ProblemName, Board),
    print_board(Board),
    sudoku(3, Board),
    print_board(Board).


sudoku(N, Board) :-
    N2 is N*N,
    dim(Board, [N2,N2]),
    Board[1..N2,1..N2] :: 1..N2,
    ( for(I,1,N2), param(Board,N2) do
        Row is Board[I,1..N2],
        alldifferent(Row),
        Col is Board[1..N2,I],
        alldifferent(Col)
    ),
    ( multifor([I,J],1,N2,N), param(Board,N) do
        ( multifor([K,L],0,N-1), param(Board,I,J), foreach(X,SubSquare) do
        X is Board[I+K,J+L]
        ),
        alldifferent(SubSquare)
    ),
    term_variables(Board, Vars),
    labeling(Vars).


print_board(Board) :-
    dim(Board, [N,N]),
    ( for(I,1,N), param(Board,N) do
        ( for(J,1,N), param(Board,I) do
            X is Board[I,J],
        ( var(X) -> write("  _") ; printf(" %2d", [X]) )
        ), nl
    ), nl.


%----------------------------------------------------------------------
% Sample data
%----------------------------------------------------------------------

problem(1, [](
    [](_, _, 2, _, _, 5, _, 7, 9),
    [](1, _, 5, _, _, 3, _, _, _),
    [](_, _, _, _, _, _, 6, _, _),
    [](_, 1, _, 4, _, _, 9, _, _),
    [](_, 9, _, _, _, _, _, 8, _),
    [](_, _, 4, _, _, 9, _, 1, _),
    [](_, _, 9, _, _, _, _, _, _),
    [](_, _, _, 1, _, _, 3, _, 6),
    [](6, 8, _, 3, _, _, 4, _, _))).

Cheers

Andy

Peter Verswyvelen wrote:
> Jerzy Karczmarczuk  wrote
> > Perhaps somebody can say more about constraint languages which replaced
>
> Yes please! Of example, how correct is 
> http://en.wikipedia.org/wiki/Constraint_programming?
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
-- 
*********************************************************************
*  Andrew Cheadle                    email:  a.cheadle at doc.ic.ac.uk *
*  Department of Computing           http://www.doc.ic.ac.uk/~amc4/ *
*  Imperial College London                                          *
*********************************************************************



More information about the Haskell-Cafe mailing list