Skip to content

Commit

Permalink
comments
Browse files Browse the repository at this point in the history
  • Loading branch information
glguy committed Dec 7, 2023
1 parent 86e1cfa commit 4608019
Showing 1 changed file with 29 additions and 2 deletions.
31 changes: 29 additions & 2 deletions solutions/src/2023/07.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,9 @@ Maintainer : emertens@gmail.com
<https://adventofcode.com/2023/day/7>
Sort the hands of a poker-like card game and compute the
resulting winnings.
>>> :{
:main +
"32T3K 765
Expand All @@ -21,11 +24,11 @@ QQQJA 483
5905
-}
module Main where
module Main (main) where

import Advent (format, counts)
import Data.List (sortOn, sort, elemIndex, nub)
import Data.Foldable (toList)
import Data.List (sortOn, sort, elemIndex, nub)
import Data.Maybe (fromJust)

-- |
Expand All @@ -39,16 +42,39 @@ main =
print (winnings strength1 input)
print (winnings strength2 input)

-- | Compute the winnings after ordering the given hands by strength
-- and multiplying the bids by position in the ranked list.
winnings :: Ord a => (String -> a) -> [(String, Int)] -> Int
winnings strength input =
sum [bid * rank | rank <- [1..]
| (hand, bid) <- input, then sortOn by strength hand]

-- | Map a hand to a representative of its strength for part 1
--
-- >>> strength1 "2AAAA" < strength1 "33332"
-- True
--
-- >>> strength1 "77788" < strength1 "77888"
-- True
--
-- >>> strength1 "KTJJT" < strength1 "KK677"
-- True
--
-- >>> strength1 "T55J5" < strength1 "QQQJA"
-- True
strength1 :: String -> [Int]
strength1 hand = category hand : map val hand
where
val x = fromJust (x `elemIndex` "23456789TJQKA")

-- | Map a hand to a representative of its strength for part 2.
-- This version treats @J@ as a wildcard of low individual value.
--
-- >>> strength2 "JKKK2" < strength2 "QQQQ2"
-- True
--
-- >>> sortOn strength2 ["T55J5", "KTJJT", "QQQJA"]
-- ["T55J5","QQQJA","KTJJT"]
strength2 :: String -> [Int]
strength2 hand =
maximum
Expand All @@ -59,6 +85,7 @@ strength2 hand =
where
val x = fromJust (x `elemIndex` "J23456789TQKA")

-- | Map a hand to an integer representing its set size.
category :: String -> Int
category hand =
case sort (toList (counts hand)) of
Expand Down

0 comments on commit 4608019

Please sign in to comment.