Cool logic in the face of fire

“Well, look at it logically,” said Hermione, turning to the rest of the group. “I mean, Binky didn't even die today, did he? Lavender just got the news today.”
Lavender wailed loudly.

— Hermione Granger in Prisoner of Azkaban

Again and again Hermione manages to demonstrate her emotional range being that of a robotic teaspoon. Because of that, I think it would be fair to build our very own Hermione (using Prolog), and try and win ourselves “50 points for Gryffindor”!

In Philosopher’s Stone, Harry and Hermione find themselves trapped in a chamber on the way to get the stone. There are a number of flasks on a table together with a piece of paper bearing a riddle:

Danger lies before you, while safety lies behind,
Two of us will help you, whichever you would find,
One among us seven will let you move ahead,
Another will transport the drinker back instead,
Two among our number hold only nettle wine,
Three of us are killers, waiting hidden in line.
Choose, unless you wish to stay here forevermore,
To help you in your choice, we give you these clues four:
First, however slyly the poison tries to hide
You will always find some on nettle wine’s left side;
Second, different are those who stand at either end,
But if you would move onward, neither is your friend;
Third, as you see clearly, all are different size,
Neither dwarf nor giant holds death in their insides;
Fourth, the second left and the second on the right
Are twins once you taste them, though different at first sight

Harry might be the most capable of the lot emotionally, but sadly he did not win the lottery when it comes to brain power. Because of this, it’ll have to be Hermione who solves Snape’s riddle. Here she is:

:- use_module(library(clpfd)).

ahead(1).
back(2).
wine(3).
poison(4).

hermione :-
    Flasks = [First, SecondLeft, _, _, _, SecondRight, Last],
    Sizes = [_, _, Dwarf, _, _, Giant, _],    % Taken from the picture, not mentioned in book.
    Flasks ins 1..4,
    Flasks = Sizes,
    First #\= Last,                           % Different are those who stand at either end,
    First #\= 1,                              % But if you would move onward,
    Last #\= 1,                               % neither is your friend;
    Dwarf #\= 4,                              % Neither dwarf-
    Giant #\= 4,                              % nor giant holds death in their insides; 
    SecondLeft #= SecondRight,                % The second left and the second on the right are twins ..
    labeling([], Flasks),
    count(Flasks, 1, 1),                      % One among us seven will let you move ahead,
    count(Flasks, 2, 1),                      % Another will transport the drinker back instead, 
    count(Flasks, 3, 2),                      % Two among our number hold only nettle wine,
    count(Flasks, 4, 3),                      % Three of us are killers, waiting hidden in line. (actually implied)
    poison_left_of_wine(Flasks),              % However slyly the poison tries to hide, you will always find some on nettle wine’s left side;
    write_names(Flasks), !.

% Predicate for checking if the estimate contains the correct number of each substance
count(L, X, N) :-
    findall(P, (member(P, L), P = X), CP),
    length(CP, N).

% Predicates for checking if there is always poison on "nettle wine's left side"
poison_left_of_wine([_]).
poison_left_of_wine([H|T]) :-
    poison_left_of_wine(T),
    T = [X|_],
    poison_left_of_wine(H, X).
poison_left_of_wine(_, W) :-
    not(wine(W)).
poison_left_of_wine(P, _) :-
    poison(P).

% Predicates for writing out the result
write_names([]).
write_names([H|T]) :-
    (ahead(H), write("Ahead Potion");
    back(H), write("Back Potion");
    wine(H), write("Nettle Wine");
    poison(H), write("Poison")),
    comma(T),
    write_names(T), !.
comma([]) :- !.
comma(_) :- write(", ").

All we have to do is call her:

?- hermione.
Poison, Nettle Wine, Ahead Potion, Poison, Poison, Nettle Wine, Back Potion
true.

Is this fan-fiction?


Source of the picture: Pottermore