Home > OS >  Dobble Cards Prolog
Dobble Cards Prolog

Time:09-07

I'm learning about list operations in Prolog. I thought computing a Dobble card set would be a fun exercise.

The card game Dobble (aka Spot It!) has 55 cards. There are 57 symbols. Each card has 8 different symbols. Any two cards have exactly one symbol in common.

I am using lists and numbers to represent the cards and symbols in Prolog. I wrote the predicates isCard\1 and oneMatch\2 to define what cards look like, and that two cards have exactly one symbol in common. I'm stuck at putting it together in isDobble\1. Prolog seems to calculate forever, and throws stack overflow errors. Your advice is greatly appreciated!!

My goal is to query "isDobble(X)." and magically :) receive a valid Dobble card set.


isCard(C) :-                            % Card C has the right amount of allowed symbols if..
  length(C, 8),                         % card C has 8 symbols, and
  sublist(C, Sym),                      % symbols are a subset of allowed symbols, and
  findall(S, between(1, 57, S), Sym).   % allowed symbols range from 1 to 57.

oneMatch(A,B) :-                        % Card A and B have exactly one matching Symbol if..
  permutation(A, [AHead|ATail]),        % card A can be permutated, and
  permutation(B, [BHead|BTail]),        % card B can be permutated, such that
  AHead = BHead,                        % the first symbol of card A and B match, while
  ATail \= BTail.                       % any other symbol of card A and B do not match.

isDobble(D) :-                          % It's a Dobble card set D if..
  length(D, 55),                        % the number of cards is 55, and
  permutation(D, [DHead|DTail]),        % any card of the set
  maplist(oneMatch(DHead), DTail),      % matches exactly one symbol of any other card, and
  maplist(isCard, D).                   % any card has the right amount of allowed symbols.

isDobble(X).                            % Show me a Dobble card set X!

CodePudding user response:

Suppose you would have more than 2^225 of elementary computations free. Or say 2^2^225. Would this really solve the problem? Before going into any further detail and wasting one solar system after the other, I looked at a tiny part of your program, a :

isCard(C) :-
  length(C, 8),
  sublist(C, Sym), false,
  findall(S, between(1, 57, S), Sym).

?- isCard(C).
   loops.

This already does not terminate. To see this, take (using that definition for sublist/2):

?- length(C,8), sublist(C,Sym). 
   C = [_A,_B,_C,_D,_E,_F,_G,_H], Sym = [_A,_B,_C,_D,_E,_F,_G,_H]
;  C = [_A,_B,_C,_D,_E,_F,_G,_H], Sym = [_A,_B,_C,_D,_E,_F,_G,_H,_I]
;  C = [_A,_B,_C,_D,_E,_F,_G,_H], Sym = [_A,_B,_C,_D,_E,_F,_G,_H,_I,_J]
;  C = [_A,_B,_C,_D,_E,_F,_G,_H], Sym = [_A,_B,_C,_D,_E,_F,_G,_H,_I,_J,_K]
;  C = [_A,_B,_C,_D,_E,_F,_G,_H], Sym = [_A,_B,_C,_D,_E,_F,_G,_H,_I,_J,_K,_L]
;  C = [_A,_B,_C,_D,_E,_F,_G,_H], Sym = [_A,_B,_C,_D,_E,_F,_G,_H,_I,_J,_K,_L,_M]
;  ... .

By exchanging the last two goals you could solve this somewhat. That is, you would have a terminating program, but one with a lot of solutions.

With clpz/clpfd you can collapse that large search space into a single answer:

:- use_module(library(clpz)).

isCard2(C) :-
   length(C, 8),
   C ins 1..57,
   chain(#<, C).

?- isCard2(C).
   C=[_A,_B,_C,_D,_E,_F,_G,_H],
   clpz:(_A#=<_B  -1), clpz:(_B#=<_C  -1), clpz:(_C#=<_D  -1),
   clpz:(_D#=<_E  -1), clpz:(_E#=<_F  -1), clpz:(_F#=<_G  -1),
   clpz:(_G#=<_H  -1),
   clpz:(_A in 1..50),
   clpz:(_B in 2..51),
   clpz:(_C in 3..52),
   clpz:(_D in 4..53),
   clpz:(_E in 5..54),
   clpz:(_F in 6..55),
   clpz:(_G in 7..56),
   clpz:(_H in 8..57).

That is, with a single answer, you can represent all solutions compactly.

CodePudding user response:

Prolog seems to calculate forever

Indeed!

From ?- help(permutation). in SWI Prolog:

Note that a list of length N has N! permutations, and unbounded permutation generation becomes prohibitively expensive, even for rather short lists (10! = 3,628,800).

length(D, 55)
permutation(D, [DHead|DTail])

Has 55! loops to work through, which is

12696403353658275925965100847566516959580321051449436762275840000000000000

approximately 2243. Thomas Pornin's answer about breaking encryption estimates:

the total mass of the Solar system, if converted in its entirety to energy [...] implies a hard limit of about 6.32×1068 elementary computations, which is about 2^225.2

and that's 18 doublings less than you need; if you could perfectly efficiently use twenty entire Suns on a perfectly efficient computer, you would still need more energy because backtracking and list unification are not an elementary computations, and you have two more permutations still to do.

My goal is to query "isDobble(X)." and magically :) receive a valid Dobble card set.

But then if your goal is magic, you may need some darker arts to cut through such a large search space; e.g. clpfd, but I suspect it would help more to understand this math of the finite projective planes behind Dobble, links to this explanation and then code one and walk through it generating the cards. That links to Python - Spot it! Cards and What are the mathematical/computational principles behind this game? as well as @brebs' link to Spot it algorithm - js from their comment.

CodePudding user response:

Can get part of the way (22 cards instead of 55), using clpBNR:

:- use_module(library(clpBNR)).
% Provide roughly 3.5GB RAM
:- set_prolog_flag(stack_limit, 3_647_483_648).

cards(Cards) :-
    % Should be 55
    length(Cards, 22),
    cards_(Cards, [], 1),
    enumerate(Cards).

cards_([], _, _).
cards_([Card|T], Upto, CardNum) :-
    length(Card, 8),
    % Seems efficient to order the numbers in each card
    ascending_distinct_bnr(Card),
    Card::integer(1, 57),
    count_matches(Upto, Card),
    CardNum1 is CardNum   1,
    cards_(T, [Card|Upto], CardNum1).

% Match the new card with 1 symbol on the other cards
count_matches([], _).
count_matches([H|T], Card) :-
    count_matches_lists_bnr(H, Card, 1),
    count_matches(T, Card).

count_matches_lists_bnr([], _, 0).
count_matches_lists_bnr([H|T], L, Matches) :-
    [Matches, Matches0]::integer(0, _),
    count_matches_bnr(L, H, MatchesL),
    {Matches == Matches0   MatchesL},
    count_matches_lists_bnr(T, L, Matches0).

count_matches_bnr([], _, 0).
count_matches_bnr([H|T], E, Matches) :-
    [Matches, Matches0]::integer(0, _),
    % (H == E) is Boolean, 1 (true) or 0
    {Matches == Matches0   (H == E)},
    count_matches_bnr(T, E, Matches0).

ascending_distinct_bnr([H|T]) :-
    [H|T]::integer,
    ascending_distinct_bnr_(T, H).

ascending_distinct_bnr_([], _).
ascending_distinct_bnr_([H|T], Prev) :-
    {H > Prev},
    ascending_distinct_bnr_(T, H).

Result in swi-prolog:

?- time(cards(C)).
% 23,849,152 inferences, 1.718 CPU in 1.723 seconds (100% CPU, 13881998 Lips)
C = [[1,2,3,4,5,6,7,8],[1,9,10,11,12,13,14,15],[1,16,17,18,19,20,21,22],[1,23,24,25,26,27,28,29],[1,30,31,32,33,34,35,36],[1,37,38,39,40,41,42,43],[1,44,45,46,47,48,49,50],[1,51,52,53,54,55,56,57],[2,9,16,23,30,37,44,51],[2,10,17,24,31,38,45,52],[2,11,18,25,32,39,46,53],[2,12,19,26,33,40,47,54],[2,13,20,27,34,41,48,55],[2,14,21,28,35,42,49,56],[2,15,22,29,36,43,50,57],[3,9,17,25,33,41,49,57],[3,10,16,26,32,42,50,55],[3,11,19,23,31,43,48,56],[3,12,20,28,36,37,45,53],[3,13,18,29,35,38,44,54],[3,14,22,24,34,39,47,51],[3,15,21,27,30,40,46,52]] ;

This could of course be converted to use clpfd.

I added CardNum for future usage.

  • Related