This commit is contained in:
rhiannon morris 2023-12-07 19:00:36 +01:00
parent 6b8818376b
commit d8d4346d39
1 changed files with 71 additions and 0 deletions

71
day7.pl Normal file
View File

@ -0,0 +1,71 @@
:- use_module(library(dcg/basics)).
:- use_module(library(pio)).
sorted_hand([X,X,X,X,X], five) :- !.
sorted_hand([X,X,X,X|_], four) :- !.
sorted_hand([X,X,X,Y,Y], full_house) :- !.
sorted_hand([X,X,Y,Y,Y], full_house) :- !.
sorted_hand([X,X,X|_], three) :- !.
sorted_hand([X,X|Rest], two_pairs) :- sorted_hand(Rest, pair), !.
sorted_hand([X,X|_], pair) :- !.
sorted_hand([_|Rest], H) :- sorted_hand(Rest, H), !.
sorted_hand(_, junk).
hand(Cards, H) :-
msort(Cards, S),
sorted_hand(S, H).
rank(junk, 0).
rank(pair, 1).
rank(two_pairs, 2).
rank(three, 3).
rank(full_house, 4).
rank(four, 5). % lol
rank(five, 6).
hand_rank(C, R) :- hand(C, H), rank(H, R).
compare_rank(X, C1, C2) :- hand_rank(C1, R1), hand_rank(C2, R2), compare(X, R1, R2).
compare_hand(X, C1-_, C2-_) :- compare_rank(X, C1, C2), X \= (=).
compare_hand(X, C1-_, C2-_) :- compare_rank(=, C1, C2), compare(X, C1, C2).
total(_, [], 0).
total(I, [_-X|Xs], R) :-
I1 is I + 1,
total(I1, Xs, R0),
R is R0 + (I * X).
total(Xs, R) :- total(1, Xs, R).
value(C, N) :-
char_code(C, N0),
char_code('0', Z),
N is N0 - Z,
N >= 0, N =< 9.
value('T', 10).
value('J', 11).
value('Q', 12).
value('K', 13).
value('A', 14).
card(V) --> [X], {char_code(C, X), value(C, V)}.
cards(Cs) --> card(A), card(B), card(C), card(D), card(E), {Cs = [A,B,C,D,E]}.
bid(N) --> digits(Ds), {number_chars(N, Ds)}.
spaces --> " ", (spaces ; []).
line(Cs-B) --> cards(Cs), spaces, bid(B).
lines([]) --> "\n" ; [].
lines([L|Ls]) --> line(L), "\n", lines(Ls).
part1(File) :-
phrase_from_file(lines(Ls), File),
% length(Ls, N), writeln(N),
predsort(compare_hand, Ls, Sorted),
total(Sorted, R),
writeln(R), !.
% vim: set ft=prolog :