Skip to content

Commit

Permalink
Try implementing part 2
Browse files Browse the repository at this point in the history
  • Loading branch information
fwcd committed Dec 8, 2023
1 parent 03ce265 commit ccf53ab
Showing 1 changed file with 16 additions and 17 deletions.
33 changes: 16 additions & 17 deletions day07/src/day07.pl
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
:- use_module(library(dcg/basics)).
:- use_module(library(sort)).

% +-----------+
% | Utilities |
Expand Down Expand Up @@ -86,23 +85,23 @@
select(C, Cs, Rest),
select(C, Rest, Rest2).

high_card(Cs, C) :-
card_values(Cs, Ns),
maximum(Ns, N),
card_value(C, N).
% TODO: Abstract over the two card_value functions, can we do partial predicates?

hand_type(Cs, 7) :- five_of_a_kind(Cs), !.
hand_type(Cs, 6) :- four_of_a_kind(Cs, _, _), !.
hand_type(Cs, 5) :- full_house(Cs, _, _), !.
hand_type(Cs, 4) :- three_of_a_kind(Cs, _, _), !.
hand_type(Cs, 3) :- two_pair(Cs, _, _, _), !.
hand_type(Cs, 2) :- one_pair(Cs, _, _), !.
hand_type(Cs, 1) :- high_card(Cs, _), !.
high_card(CV, Cs, C) :-
maplist(CV, Cs, Ns),
maximum(Ns, N),
call(CV, C, N).

% TODO: Abstract over the two card_value functions, can we do partial predicates?
hand_type( _, Cs, 7) :- five_of_a_kind(Cs), !.
hand_type( _, Cs, 6) :- four_of_a_kind(Cs, _, _), !.
hand_type( _, Cs, 5) :- full_house(Cs, _, _), !.
hand_type( _, Cs, 4) :- three_of_a_kind(Cs, _, _), !.
hand_type( _, Cs, 3) :- two_pair(Cs, _, _, _), !.
hand_type( _, Cs, 2) :- one_pair(Cs, _, _), !.
hand_type(CV, Cs, 1) :- high_card(CV, Cs, _), !.

hand_value1(Cs, [T|Ns]) :-
hand_type(Cs, T),
hand_type(card_value1, Cs, T),
maplist(card_value1, Cs, Ns).

compare_hands1(Delta, hand(Cs1, _), hand(Cs2, _)) :-
Expand All @@ -121,12 +120,12 @@

hand_value2_candidate(Cs, [T|Ns]) :-
instantiate_jokers(Cs, Cs2),
hand_type(Cs2, T),
hand_type(card_value2, Cs2, T),
maplist(card_value2, Cs2, Ns).

hand_value2(Cs, MaxV) :-
findall(V, hand_value2_candidate(Cs, V), Vs),
maximum(Vs, MaxV).
% Use `order_by` from `library(solution_sequences)`: https://stackoverflow.com/a/42593823/19890279
findall(V, order_by([desc(V)], hand_value2_candidate(Cs, V)), [MaxV|_]).

compare_hands2(Delta, hand(Cs1, _), hand(Cs2, _)) :-
hand_value2(Cs1, V1),
Expand Down

0 comments on commit ccf53ab

Please sign in to comment.