vasily
vasily

Reputation: 2920

Simplifying constraints in CLP puzzle

At the local games evening, four lads were competing in the Scrabble and chess competitions. Liam beat Mark in chess, James came third and the 16 year old won. Liam came second in Scrabble, the 15 year old won, James beat the 18 year old and the 19 year old came third. Kevin is 3 years younger than Mark. The person who came last in chess, came third in Scrabble and only one lad got the same position in both games.

I feel that my solution is more clunky than needs to be:

:- use_module(library(clpfd)).

check(AJ, AK, AL, AM, CJ, CK, CL, CM, SJ, SK, SL, SM) :-
    AJ in 15..16 \/ 18..19,
    AK in 15..16 \/ 18..19,
    AL in 15..16 \/ 18..19,
    AK in 15..16 \/ 18..19,
    all_different([AJ, AK, AL, AM]),
    CJ in 1..4, CK in 1..4, CL in 1..4, CM in 1..4,
    SJ in 1..4, SK in 1..4, SL in 1..4, SM in 1..4,
    all_different([CJ, CK, CL, CM]),
    all_different([SJ, SK, SL, SM]),
    CL #< CM,
    CJ #= 3,
  ( AJ #= 16, CJ #= 1 ;
    AK #= 16, CK #= 1 ;
    AL #= 16, CL #= 1 ;
    AM #= 16, CM #= 1 ),
    SL #= 2,
  ( AJ #= 15, SJ #= 1 ;
    AK #= 15, SK #= 1 ;
    AL #= 15, SL #= 1 ;
    AM #= 15, SM #= 1 ),
    AK #= AM - 3,
  ( CJ #= 4, SJ #= 3 ;
    CK #= 4, SK #= 3 ;
    CL #= 5, SL #= 3 ;
    CM #= 4, SM #= 3 ),
  ( CJ #=  SJ, CK #\= SK, CL #\= SL, CM #\= SM ;
    CJ #\= SJ, CK #=  SK, CL #\= SL, CM #\= SM ;
    CJ #\= SJ, CK #\= SK, CL #=  SL, CM #\= SM ;
    CJ #\= SJ, CK #\= SK, CL #\= SL, CM #=  SM ).

Is there a better way to express the constraints?


Improved version after suggestions:

:- use_module(library(clpfd)).

check(AJ, AK, AL, AM, CJ, CK, CL, CM, SJ, SK, SL, SM) :-
    permutation([AJ, AK, AL, AM], [15, 16, 18, 19]),
    permutation([CJ, CK, CL, CM], [1, 2, 3, 4]),
    permutation([SJ, SK, SL, SM], [1, 2, 3, 4]),
    CL #< CM,
    CJ #= 3,
  ( AJ #= 16, CJ #= 1 ;
    AK #= 16, CK #= 1 ;
    AL #= 16, CL #= 1 ;
    AM #= 16, CM #= 1 ),
    SL #= 2,
  ( AJ #= 15, SJ #= 1 ;
    AK #= 15, SK #= 1 ;
    AL #= 15, SL #= 1 ;
    AM #= 15, SM #= 1 ),
    AK #= AM - 3,
  ( CJ #= 4, SJ #= 3 ;
    CK #= 4, SK #= 3 ;
    CL #= 5, SL #= 3 ;
    CM #= 4, SM #= 3 ),
  ( CJ #=  SJ, CK #\= SK, CL #\= SL, CM #\= SM ;
    CJ #\= SJ, CK #=  SK, CL #\= SL, CM #\= SM ;
    CJ #\= SJ, CK #\= SK, CL #=  SL, CM #\= SM ;
    CJ #\= SJ, CK #\= SK, CL #\= SL, CM #=  SM ).

Upvotes: 1

Views: 210

Answers (1)

hakank
hakank

Reputation: 6854

Here's a SWI-Prolog version, using the global constraint element/3 to access/lookup indices/values from the different lists. (One can see this model as an exercise in element/3 :-).)

:- use_module(library(clpfd)).

go :-
        % At the local games evening, four lads were competing in the Scrabble and 
        % chess competitions.
        N = 4,
        length(Lads,N),
        Lads = [James,Kevin,Liam,Mark],
        Lads = [1,2,3,4],
        Lads ins 1..N,
        LadsS = ['James','Kevin','Liam','Mark'],
        
        length(Chess,N),
        Chess ins 1..N,
        
        length(Scrabble,N),
        Scrabble ins 1..N,

        length(Ages,N),
        Ages ins 15..16 \/ 18..19,

        all_different(Chess),
        all_different(Scrabble),
        all_different(Ages),

        element(Ages15,Ages,15),
        element(Ages16,Ages,16),
        element(Ages18,Ages,18),
        element(Ages19,Ages,19),
        
        % Liam beat Mark in chess, James came third and the 16 year old won.
        element(Liam,Chess,ChessLiam),
        element(Mark,Chess,ChessMark),
        ChessLiam #< ChessMark,
        element(James,Chess,3),
        element(Ages16,Chess,1),

        % Liam came second in Scrabble, the 15 year old won; James beat the 18 year old 
        % and the 19 year old came third.
        element(Liam,Scrabble,2),
        element(Ages15,Scrabble,1),

        element(Ages18,Scrabble,ScrabbleAges18),
        element(James,Scrabble,ScrabbleJames),
        ScrabbleJames #< ScrabbleAges18,
        element(Ages19,Scrabble,3),

        % Kevin is 3 years younger than Mark.
        element(Kevin,Ages,AgesKevin),
        element(Mark,Ages,AgesMark),  
        AgesKevin + 3 #= AgesMark,
        
        % The person who came last in chess, came third in Scrabble and only one lad
        % got the same position in both games.
        element(ChessPlace4,Chess,4),
        element(ChessPlace4,Scrabble,3),

        sums(Chess,Scrabble,0,Sums),
        Sums #= 1,
        
        % Can you determine the ages of the lads and the positions in the two games?

        flatten([Chess,Scrabble,Ages,Sums],Vars),
        label(Vars),
        
        writeln(chess=Chess),
        writeln(scrabble=Scrabble),
        writeln(ages=Ages),
        sol(LadsS,Ages,Scrabble,Chess),
        nl,
        
        fail,
        nl.
go.


sums([],[],Total,Total).
sums([C|Chess],[S|Scrabble],Total0,Total) :-
        B in 0..1,
        C #= S #<==> B #= 1,
        Total1 #= Total0 + B,         
        sums(Chess,Scrabble,Total1,Total).

sol([L|Lads],[A|Ages],[S|Scrabble],[C|Chess]) :-
        format("~w (~d) Scrabble: ~d Chess: ~d~n",[L,A,S,C]),
        sol(Lads,Ages,Scrabble,Chess).

(The full program is available here: http://hakank.org/swi_prolog/scrabble_contest.pl )

Upvotes: 2

Related Questions