day7.2
This commit is contained in:
parent
d8d4346d39
commit
ed05bffe65
1 changed files with 50 additions and 34 deletions
60
day7.pl
60
day7.pl
|
@ -1,6 +1,6 @@
|
||||||
:- use_module(library(dcg/basics)).
|
% 0 for the joker. the other clauses are just the hand shapes
|
||||||
:- use_module(library(pio)).
|
% sorry about all the cuts
|
||||||
|
sorted_hand([0|Rest], H) :- sorted_hand(Rest, H0), promote(H0, H), !.
|
||||||
sorted_hand([X,X,X,X,X], five) :- !.
|
sorted_hand([X,X,X,X,X], five) :- !.
|
||||||
sorted_hand([X,X,X,X|_], four) :- !.
|
sorted_hand([X,X,X,X|_], four) :- !.
|
||||||
sorted_hand([X,X,X,Y,Y], full_house) :- !.
|
sorted_hand([X,X,X,Y,Y], full_house) :- !.
|
||||||
|
@ -9,11 +9,15 @@ sorted_hand([X,X,X|_], three) :- !.
|
||||||
sorted_hand([X,X|Rest], two_pairs) :- sorted_hand(Rest, pair), !.
|
sorted_hand([X,X|Rest], two_pairs) :- sorted_hand(Rest, pair), !.
|
||||||
sorted_hand([X,X|_], pair) :- !.
|
sorted_hand([X,X|_], pair) :- !.
|
||||||
sorted_hand([_|Rest], H) :- sorted_hand(Rest, H), !.
|
sorted_hand([_|Rest], H) :- sorted_hand(Rest, H), !.
|
||||||
sorted_hand(_, junk).
|
sorted_hand([], junk).
|
||||||
|
|
||||||
hand(Cards, H) :-
|
promote(junk, pair).
|
||||||
msort(Cards, S),
|
promote(pair, three).
|
||||||
sorted_hand(S, H).
|
promote(two_pairs, full_house).
|
||||||
|
promote(three, four).
|
||||||
|
promote(four, five).
|
||||||
|
|
||||||
|
hand(Cards, H) :- msort(Cards, S), sorted_hand(S, H).
|
||||||
|
|
||||||
rank(junk, 0).
|
rank(junk, 0).
|
||||||
rank(pair, 1).
|
rank(pair, 1).
|
||||||
|
@ -27,29 +31,21 @@ 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_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_hand(X, C1-_, C2-_) :- compare_rank(=, C1, C2), compare(X, C1, C2).
|
compare_rank(X0, C1, C2),
|
||||||
|
(X0 = (=) -> compare(X, C1, C2) ; X = X0).
|
||||||
|
|
||||||
|
|
||||||
|
total(Xs, R) :- total(1, Xs, R).
|
||||||
|
|
||||||
total(_, [], 0).
|
total(_, [], 0).
|
||||||
total(I, [_-X|Xs], R) :-
|
total(I, [_-X|Xs], R) :-
|
||||||
I1 is I + 1,
|
I1 is I + 1,
|
||||||
total(I1, Xs, R0),
|
total(I1, Xs, R0),
|
||||||
R is R0 + (I * X).
|
R is R0 + (I * X).
|
||||||
|
|
||||||
total(Xs, R) :- total(1, Xs, R).
|
|
||||||
|
|
||||||
|
:- use_module(library(dcg/basics)).
|
||||||
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)}.
|
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]}.
|
cards(Cs) --> card(A), card(B), card(C), card(D), card(E), {Cs = [A,B,C,D,E]}.
|
||||||
|
@ -59,13 +55,33 @@ line(Cs-B) --> cards(Cs), spaces, bid(B).
|
||||||
lines([]) --> "\n" ; [].
|
lines([]) --> "\n" ; [].
|
||||||
lines([L|Ls]) --> line(L), "\n", lines(Ls).
|
lines([L|Ls]) --> line(L), "\n", lines(Ls).
|
||||||
|
|
||||||
|
value('T', 10).
|
||||||
|
value('J', 11).
|
||||||
|
value('Q', 12).
|
||||||
|
value('K', 13).
|
||||||
|
value('A', 14).
|
||||||
|
value(C, N) :- char_code(C, N0), N is N0 - 0x30, N >= 0, N =< 9.
|
||||||
|
|
||||||
|
|
||||||
part1(File) :-
|
part1(File) :-
|
||||||
phrase_from_file(lines(Ls), File),
|
phrase_from_file(lines(Ls), File),
|
||||||
% length(Ls, N), writeln(N),
|
|
||||||
predsort(compare_hand, Ls, Sorted),
|
predsort(compare_hand, Ls, Sorted),
|
||||||
total(Sorted, R),
|
total(Sorted, R),
|
||||||
writeln(R), !.
|
writeln(R), !.
|
||||||
|
|
||||||
|
|
||||||
|
joker(11, 0).
|
||||||
|
joker(X, X) :- X \= 11.
|
||||||
|
part1_to_part2(Xs-B, Ys-B) :- maplist(joker, Xs, Ys).
|
||||||
|
|
||||||
|
with_hand(Xs-B, H-Xs-B) :- hand(Xs, H).
|
||||||
|
|
||||||
|
part2(File) :-
|
||||||
|
phrase_from_file(lines(Ls0), File),
|
||||||
|
maplist(part1_to_part2, Ls0, Ls),
|
||||||
|
predsort(compare_hand, Ls, Sorted),
|
||||||
|
total(Sorted, R),
|
||||||
|
writeln(R), !.
|
||||||
|
|
||||||
% vim: set ft=prolog :
|
% vim: set ft=prolog :
|
||||||
|
% vim what the fuck is "gringo"
|
||||||
|
|
Loading…
Reference in a new issue