Autumn Challenge 2023: Lion and Unicorn

When Alice entered the forest of forgetfulness, she did not
forget everything, only certain things. She often forgot her
name, and the most likely thing for her to forget was the day
of the week. Now, the lion and the unicorn were frequent
visitors to this forest. These two are strange creatures. The
lion lies on Mondays, Tuesdays, and Wednesdays and tells
the truth on the other days of the week. The unicorn, on the
other hand, lies on Thursdays, Fridays, and Saturdays, but tells
the truth on the other days of the week.

One day Alice met the lion and the unicorn resting under a tree.
They made the following statements:

Lion: Yesterday was one of my lying days.
Unicorn: Yesterday was one of my lying days.

From these statements, Alice, who was a bright girl, was able to
deduce the day of the week. What was it?

3 Likes

It must be Thursday then!

Solution

By elimination:
It can’t be Monday since on Mondays the unicorn tells the truth, so Sunday would have had to be one of its lying days, but it’s not.
It can’t be Tuesday since on Tuesdays the lion lies, so Monday would have to be a day in which it tells the truth, but it’s not. Likewise of Wednesday.
Thursday works out.
It can’t be Friday, since on Fridays the unicorn lies, so Thursday would have to be a day in which it tells the truth, but it’s not. Likewise for Saturday.
It can’t be Sunday, since on Sundays the lion tells the truth, so Saturday would have to be one of its lying days, but it’s not.

Here’s my CLP(FD) approach:

:- use_module(library(clpfd)).

go :-
    problem47(Problem47),
    nl.

% 
% Problem 47
% Lion: Yesterday was one of my lying days.
% Unicorn: Yesterday was one of my lying days too.
%
% Solution: Today is Thursday (day 4)
%
problem47(WeekDay) :-
  writeln("problem47"),
  truth_days(unicorn,Unicorn),
  truth_days(lion,   Lion),

  Today in 1..7, 
  T1 #= Today,  % 
  T2 #= ((Today-1) mod 7),  % About what day is it about?
  
  element(T1,Lion,LionWhen),
  element(T2,Lion,LionWhat),
  says(LionWhen, (LionWhat #= 0)), % Says: I was lying yesterday
    
  element(T1,Unicorn,UnicornWhen),
  element(T2,Unicorn,UnicornWhat),
  says(UnicornWhen, UnicornWhat #= 0), % Says: I was lying yesterday

  label([Today]),
  which_day(Today,WeekDay),
  writeln([today=Today,weekDay=WeekDay]),
  fail,
  
  nl.


% Truthfullness of the lion and the unicorn.
% Start week with Monday (day 1)
truth_days(unicorn,[1, 1, 1, 0, 0, 0, 1]).
truth_days(lion,   [0, 0, 0, 1, 1, 1, 1]).

% What did X say about When?
says(When, What) :-
    When #<==> What.

% Which day is it?
which_day(Day,WeekDay) :-
    Days = [mon,tue,wed,thu,fri,sat,sun],
    nth1(Day,Days,WeekDay).

Output:

problem47
[today=4,weekDay=thu]
false.

Addendum: Here are some more examples of these Smullyan puzzles: http:///hakank.org/swi_prolog/smullyan_lion_and_unicorn.pl
Note that these are a 0 based since it’s a little easier to model some of the problems.

1 Like

Thank you for your solution!

I got the puzzle from a discussion here,
which was about Prolog versus Theorem Proving:

The lion and the unicorn met PROLOG
Bruce D. Ramsey, 1986 - Free Access
The lion and the unicorn met PROLOG | ACM SIGPLAN Notices

1 Like

Also, here is my solution, which is almost the same as @hakank , thanks. My first plan is to solve the puzzle by using disjunctive normal form (DNF) in ZDD with counting solutions which were already implemented. That is a simple minded approach; Enumerate all possible situations as clauses of literals in DNF. (Brute force!) Though I haven’t done it yet through. I would like to do it for warming up for more complicated puzzles in the future.

% ?- unicorn_lion_puzzle(Ans).
%@ Ans = thu ;
%@ false.

unicorn_lion_puzzle(DayOfWeek):-
	between(0,6, I), J is I-1,
	K is J mod 7,
	says(unicorn, a(unicorn, K), I, P),
	says(lion, a(lion, K), I, Q),
	check(P),
	check(Q),
	nth0(I, [mon,tue,wed,thu,fri,sat,sun], DayOfWeek).

%
truth_days(unicorn,[1, 1, 1, 0, 0, 0, 1]).
truth_days(lion,   [0, 0, 0, 1, 1, 1, 1]).
%
says(Who, What, When, Prop):- truth_days(Who, Days),
	 I is (When mod 7),
	 nth0(I, Days, V),
	 (	V = 1 -> Prop = What
	 ;  Prop = -(What)
	 ).
%
check(a(unicorn, K)):-!, truth_days(unicorn, L), nth0(K, L, 0).
check(-a(unicorn, K)):-!, truth_days(unicorn, L), nth0(K, L, 1).
check(a(lion, K)):-!, truth_days(lion, L), nth0(K, L, 0).
check(-a(lion, K)):- truth_days(lion, L), nth0(K, L, 1).

That was fun; here’s my basic solution, just literally writing the problem statement in Prolog:

:- module(unicorn_lion, [main/1]).

dow(monday).
dow(tuesday).
dow(wednesday).
dow(thursday).
dow(friday).
dow(saturday).
dow(sunday).

yesterday(monday   , sunday).
yesterday(tuesday  , monday   ).
yesterday(wednesday, tuesday  ).
yesterday(thursday , wednesday).
yesterday(friday   , thursday ).
yesterday(saturday , friday   ).
yesterday(sunday   , saturday ).

lies(lion, monday).
lies(lion, tuesday).
lies(lion, wednesday).

lies(unicorn, thursday).
lies(unicorn, friday).
lies(unicorn, saturday).

statement(By, Day, Statement) :-
    dow(Day),
    lies(By, Day),
    \+ Statement.
statement(By, Day, Statement) :-
    dow(Day),
    \+ lies(By, Day),
    Statement.

main(Today) :-
    dow(Today),
    yesterday(Today, Yesterday),
    statement(lion, Today, lies(lion, Yesterday)),
    statement(unicorn, Today, lies(unicorn, Yesterday)).
4 Likes

Brute-force & simple:

day_of_week(Day) :-
    % 1 means Monday
    between(1, 7, Day).

yesterday_of_week(1, 7).
yesterday_of_week(Day, Yesterday) :-
    Yesterday is Day - 1,
    day_of_week(Yesterday).

day_names(d(mon, tue, wed, thu, fri, sat, sun)).

day_name(Day, DayName) :-
    day_names(DayNames),
    arg(Day, DayNames, DayName).

truth_animal_day(lion, Day) :-
    between(4, 7, Day).

truth_animal_day(unicorn, 7).
truth_animal_day(unicorn, Day) :-
    between(1, 3, Day).

truth_animal(Animal, Day) :-
    yesterday_of_week(Day, Yesterday),
    (   truth_animal_day(Animal, Day)
        % Was lying yesterday
    ->  \+ truth_animal_day(Animal, Yesterday)
    ;   truth_animal_day(Animal, Yesterday)
    ).

lion_unicorn(Day) :-
    day_of_week(Day),
    truth_animal(lion, Day),
    truth_animal(unicorn, Day).

lion_unicorn_certain(DayName) :-
    bagof(D, lion_unicorn(D), [Day]),
    day_name(Day, DayName).
?- lion_unicorn_certain(DayName).
DayName = thu.

No. Except for inserting an intermediate predicate that ensures the argument you do not want to index is ground, i.e.,

my_lies(X,Y) :- lies(X,Z), Y = Z.

And deciding for the 2nd argument is simple: the first has two different values and the second are all unique.

Thank you for the interesting challenge !

Here is a shorter and simplified version of @jamesnvc with as little abstraction as possible:

lion_lies(monday).
lion_lies(tuesday).
lion_lies(wednesday).

unicorn_lies(thursday).
unicorn_lies(friday).
unicorn_lies(saturday).

yesterday(monday, sunday).
yesterday(tuesday, monday).
yesterday(wednesday, tuesday).
yesterday(thursday, wednesday).
yesterday(friday, thursday).
yesterday(saturday, friday).
yesterday(sunday, saturday).

query(Today) :-
   yesterday(Today, Yesterday),

   (  lion_lies(Today)
   -> \+ lion_lies(Yesterday)
   ;  lion_lies(Yesterday)
   ),

   (  unicorn_lies(Today)
   -> \+ unicorn_lies(Yesterday)
   ;  unicorn_lies(Yesterday)
   ).

It is really about writing down the problem.
Interestingly, I believe this is the most optimized version I could get after trying various reification strategy:

?- time(query(Today)).
% 17 inferences, 0.000 CPU in 0.000 seconds (85% CPU, 945705 Lips)
Today = thursday .
?- time((between(1,1000000,_), query(_), fail; true)).
% 28,000,001 inferences, 1.268 CPU in 1.271 seconds (100% CPU, 22076711 Lips)
true.

This is yet another solution using DNF (Disjunctive Normal Form). Idea is simple: Given the lion-unicorn puzzle in English, translate it to a propositional logic. Then build a DNF of the formula, which is the set of solutions of the puzzle. I don’t know generality of this simple minded approach. In fact, I should doubt its generality because of the possible huge DNF on the way of getting the final one. Solving methods posted by others in this thread should be much better than mine here. Fortunately, as for the lion-unicorn puzzle only small DNF is needed with care with basics of propositional logic, which was obtained with zdd library. Anyway it was a good exercise for me on using the zdd library.

% ?- time(solve_lion_uncorn_puzzle_in_dnf(Ans)).
%@ % 8,188,821 inferences, 0.626 CPU in 0.647 seconds (97% CPU, 13085762 Lips)
%@ Ans = today(thu) ;
%@ % 171 inferences, 0.004 CPU in 0.004 seconds (100% CPU, 47017 Lips)
%@ false.
Prolog codes using zdd library
:-module(lion_unicorn, []).

:- use_module(pac(basic)).
:- use_module(zdd('zdd-array')).
:- use_module(zdd(zdd)).
:- use_module(pac(op)).


solve_lion_uncorn_puzzle_in_dnf(Ans):-
	build_puzzle_prop(Prop),
	( zdd X<< dnf(Prop), zmod:zdd_find(=(today(_)), X, Ans) ).

%
day_of_week([mon, tue, wed, thu, fri, sat, sun]).
%
liar_mode_list(unicorn, [1, 1, 1, 0, 0, 0, 1]).
liar_mode_list(lion,    [0, 0, 0, 1, 1, 1, 1]).
%
today(D):- day_of_week(Ds), member(D, Ds).

% ?- yesterday(Y,T).
yesterday(Y, T):- day_of_week(Ds),
 	between(0, 6, J),
 	between(0, 6, I),
 	I is (J-1) mod 7,
 	nth0(J, Ds, T),
 	nth0(I, Ds, Y).

% ?- liar(W, D).
liar(Who, D):- day_of_week(Ds),
	  liar_mode_list(Who, M),
	  between(0, 6, I),
	  nth0(I, M, 0),
	  nth0(I, Ds, D).

% ?- build_puzzle_prop(_Prop), (zdd X<< dnf(_Prop), sets(X, _S), {length(_S, C0)}, card(X, C), psa(X)).
build_puzzle_prop(Props):-
	prop_group(today, Tod),
	prop_group(day_dependent_truth, Deps),
	prop_group(liar, Liar),
	Props = (*(Deps) * +(Tod) * *(Liar)).

% ?- prop_group(today, T).
prop_group(today, TDs):-!, findall(today(D), today(D), TDs).

% ?- prop_group(yesterday, Y), length(Y, N).
prop_group(yesterday, YDay):-!, findall(yesterday(Y, T), yesterday(Y, T), YDay).

% ?- prop_group(liar, Y), length(Y, N), maplist(writeln, Y).
prop_group(liar, LiarProps):-!,
	findall(X,
		  (	today(D),
			member(Who, [lion, unicorn]),
			(	liar(Who, D), X = liar(Who, D)
			;	\+ liar(Who, D), X = -liar(Who, D)
			)
		  ),
		LiarProps).


% ?- prop_group(day_dependent_truth, _Deps), maplist(writeln, _Deps).
%@ today(tue)->liar(lion,tue)== -liar(lion,mon)
%@ today(tue)->liar(unicorn,tue)== -liar(unicorn,mon)
%@ today(wed)->liar(lion,wed)== -liar(lion,tue)
%@ today(wed)->liar(unicorn,wed)== -liar(unicorn,tue)
%@ today(thu)->liar(lion,thu)== -liar(lion,wed)
%@ today(thu)->liar(unicorn,thu)== -liar(unicorn,wed)
%@ today(fri)->liar(lion,fri)== -liar(lion,thu)
%@ today(fri)->liar(unicorn,fri)== -liar(unicorn,thu)
%@ today(sat)->liar(lion,sat)== -liar(lion,fri)
%@ today(sat)->liar(unicorn,sat)== -liar(unicorn,fri)
%@ today(sun)->liar(lion,sun)== -liar(lion,sat)
%@ today(sun)->liar(unicorn,sun)== -liar(unicorn,sat)
%@ today(mon)->liar(lion,mon)== -liar(lion,sun)
%@ today(mon)->liar(unicorn,mon)== -liar(unicorn,sun)
%@ true.

prop_group(day_dependent_truth, Deps):-
	findall( today(D)->(liar(Who, D) == -liar(Who, Y)),
			(	yesterday(Y, D),
				member(Who, [lion, unicorn])
			),
			Deps).

1 Like

It uses zdd library in Prolog, which takes a lot of steps processing
on reading propositional terms into DNF in zdd.

Here is a fast version of mine without using DNF, which might be close, similar, or identical to what others posted.

% ?- time(( between(0, 6, _D), assertion(lion, _D), assertion(unicorn, _D), day_of_week(_Ds), nth0(_D, _Ds, Ans))).
%@ % 119 inferences, 0.000 CPU in 0.000 seconds (86% CPU, 5950000 Lips)
%@ Ans = thu ;
%@ % 75 inferences, 0.000 CPU in 0.000 seconds (78% CPU, 4166667 Lips)
%@ false.


day_of_week([mon,tue,wed,thu,fri,sat,sun]).
%
mode_list(unicorn,[1, 1, 1, 0, 0, 0, 1]).
mode_list(lion,   [0, 0, 0, 1, 1, 1, 1]).
%
yesterday(Y, T):- between(0, 6, T), Y is (T-1) mod 7.
%
assertion(Who, T):- yesterday(Y, T),
			   (	positive_mode(Who, T), negative_mode(Who, Y)
			   ;	negative_mode(Who, T), positive_mode(Who, Y)
			   ).
%
positive_mode(Who, D):- mode_list(Who, Ds), nth0(D, Ds, 1).
%
negative_mode(Who, D):- mode_list(Who, Ds), nth0(D, Ds, 0).

Of course, compared with the DNF version. Time efficiency is out of my interest, sorry.

EDIT
Although I am not appropriate person for experts to talk to about efficiency, I have found about 4 time efficiency by replacing nth0/3 in my codes with arg/3 (i.e. replacing list with vector).

I am rather wondering if chatGPT is able to solve this kind puzzle,
and even if it is not the case, how it is getting closer to the prologer about this kind of logic puzzle.

Here is a test, yesterday/2 symbolic is faster:

/* SWI-Prolog 9.1.17 */
?- L=[sunday,monday,tuesday,wednesday,thursday,friday,saturday], 
    time((between(1,1000000,_), member(X,L), yesterday(X,Y), fail; true)).
% 15,999,998 inferences, 0.609 CPU in 0.604 seconds
(101% CPU, 26256407 Lips)
L = [sunday, monday, tuesday, wednesday, thursday, friday, saturday].

?- L=[0,1,2,3,4,5,6], time((between(1,1000000,_), member(X,L), 
Y is (X-1) mod 7, fail; true)).
% 15,999,998 inferences, 1.141 CPU in 1.146 seconds
(100% CPU, 14027396 Lips)
L = [0, 1, 2, 3, 4, 5, 6].

Amazing! Was using SWI-Prolog with default settings.

Maybe this doesn’t hold for all Prolog systems?

Edit 11.11.2023
How would a novel CLP(FD) or ZZD library look like, that
can directly work symbolic. It hasn’t been yet invented, or has it?
What would it do to the Lion and Unicorn example? You could

view the Bruce Ramsey solution as a form of spare matrices
in FORTRAN. A predicate is a kind of spare matrice, since it
only “stores” 1 and omits 0, and negation as failure which

flips 1 to 0 and 0 to 1 based on spare matrices. ZDD since it
zero supresses has also some potential. But what can constraints
programming do in the Lion and Unicorn example?

Mostly because you are using dynamic calling. Turned into a proper Prolog program, using -O, I get 0.576 vs 0.572 sec.

Program
t1 :-
    L=[sunday,monday,tuesday,wednesday,thursday,friday,saturday],
    time(t1l(L)).

t1l(L) :-
    (   between(1,1000000,_),
        member(X,L),
        yesterday(X,Y),
        fail
    ;   true
    ).

yesterday(monday, sunday).
yesterday(tuesday, monday).
yesterday(wednesday, tuesday).
yesterday(thursday, wednesday).
yesterday(friday, thursday).
yesterday(saturday, friday).
yesterday(sunday, saturday).

t2 :-
    L=[0,1,2,3,4,5,6],
    time(t2l(L)).

t2l(L) :-
    (   between(1,1000000,_),
        member(X,L),
        _Y is (X-1) mod 7,
        fail
    ;   true
    ).

For the first time in my life, I put -O option for running swipl via ediprolog mode, though I havn’t read manual yet on the option. It seems -O options so good to put on also for those who are not so interested in efficiency that I will run swipl with the option as default from now on. Thanks.

%% without -O option.

% ?- time(t1).
%@ % 23,000,001 inferences, 0.914 CPU in 0.915 seconds (100% CPU, 25164390 Lips)
%@ % 23,000,155 inferences, 0.914 CPU in 0.915 seconds (100% CPU, 25162164 Lips)

% ?- time(t2).
%@ % 23,000,000 inferences, 1.338 CPU in 1.339 seconds (100% CPU, 17195619 Lips)
%@ % 23,000,154 inferences, 1.338 CPU in 1.339 seconds (100% CPU, 17194654 Lips)


%% with -O option.

% ?- time(t1).
%@ % 15,999,999 inferences, 0.838 CPU in 0.839 seconds (100% CPU, 19100736 Lips)
%@ % 16,000,145 inferences, 0.838 CPU in 0.839 seconds (100% CPU, 19099086 Lips)

% ?- time(t2).
%@ % 8,999,999 inferences, 0.875 CPU in 0.875 seconds (100% CPU, 10291053 Lips)
%@ % 9,000,145 inferences, 0.875 CPU in 0.875 seconds (100% CPU, 10290196 Lips)
```

Fun problem, only Google’s Bard got it right in one shot, while ChatGPT, Claude 2, Hugging Chat, Pi needed quite a few steps to solve it, usually only after telling them that the answer is Thursday.

In any case, here is also my solution, as it would be written in plain Prolog to be explainable to a (smart) 8 years old.

what_day_is(Today):-
  yesterday(Today,Yesterday),
  check(lion,Today,Yesterday),
  check(unicorn,Today,Yesterday).
  
check(X,Today,Yesterday):-truthful(X,Today),lying(X,Yesterday).
check(X,Today,Yesterday):-lying(X,Today),truthful(X,Yesterday).

lying(lion,'Monday'). 
lying(lion,'Tuesday').
lying(lion,'Wednesday').

lying(unicorn,'Thursday'). 
lying(unicorn,'Friday').
lying(unicorn,'Saturday').

truthful(X,Day):-day(Day),not(lying(X,Day)).

day(D):-tomorrow(D,_).

tomorrow('Monday','Tuesday').
tomorrow('Tuesday','Wednesday').
tomorrow('Wednesday','Thursday').
tomorrow('Thursday','Friday').
tomorrow('Friday','Saturday').
tomorrow('Saturday','Sunday').
tomorrow('Sunday','Monday').

yesterday(Today,Yesterday):-tomorrow(Yesterday,Today).
1 Like

Thank you for information. Google’s Bard sounds getting closer to human than I thought. Natural language understanding technology on dialogue is the most important key, I guess.

Your objective in this thread is to discuss on extracting prolog program from given logic puzzle like lion-unicorn, and in fact you have found a good prolog codes. Correct ?
Then, Congratulation !

In contrast, my approach was, as I posted, first, convert the logic puzzle into a DNF, then scan for the target fact today(_) in the DNF by calling. I took DNF converter as the universal prolog program in a sense, and zdd_find(=(today(_), X, Answer, _) is to scan the final answer buried in created DNF, where actual scan code I used is below, which is universal to use. Thus no need to extract prolog codes depending on the input puzzle. This simple but universal method was possible due to DNF viewed as created data base for answers. It looks like rather a merit of DNF.

zdd_find(F, X, Y, S):- X>1,
	cofact(X, t(A, L, R), S),
	(	call(F, A),	Y = A
	;	zdd_find(F, L, Y, S)    % find left branch
	;	zdd_find(F, R, Y, S)	% find right branch
	).

I should have noticed earlier that this thread is much serious than simple-minded persons might think. It should be time for him to drop. Anyway your exotic formula was useful for me to review DNF/CNF converter of mine. Thanks.

Just information. I just remember that I wrote codes on ZDD over GF(2) (two element Galois field.) I spent time and efforts for it, but unfortunately I found it is broken. It needs some time to be repaired. In fact, I don’t remember well my purpose of the codes.

(Nothing of Importance)