aoc/2023/04/app/Main.hs

68 lines
1.6 KiB
Haskell

{-# LANGUAGE OverloadedStrings #-}
module Main where
import Data.Char (isDigit)
import Data.Map (fromList, member, (!))
import qualified Data.Text as T
import qualified Data.Text.IO as TIO
import Data.Attoparsec.Text
type WinningNumbers = [Integer]
type MyNumbers = [Integer]
type Game = (Integer, WinningNumbers, MyNumbers)
type Input = [Game]
main :: IO ()
main = do
input <- parseInput <$> TIO.getContents
putStrLn ("Part 1: " <> show (part1 input))
putStrLn ("Part 2: " <> show (part2 input))
parseInput :: T.Text -> Input
parseInput s = case parseOnly inputParser s of
Right i -> i
Left e -> error e
part1 :: Input -> Int
part1 gs = sum $ map cardValue gs
cardValue :: Game -> Int
cardValue = value . winCount
where
value 0 = 0
value n = 2 ^ (n - 1)
part2 :: Input -> Int
part2 games = walkCards $ zip [0..] $ map winCount games
walkCards :: [(Int, Int)] -> Int
walkCards x = walkCards' (map fst x) 0
where
walkCards' [] acc = acc
walkCards' (id:xs) acc = walkCards' xs (acc + walkCards' (additional id) 1)
additional id = [next | n <- [1..(winCounts ! id)], let next = id + n, next <= lastId]
winCounts = fromList x
lastId = fst $ last x
winCount :: Game -> Int
winCount (_, ws, ms) = length $ filter (`elem` ws) ms
inputParser :: Parser Input
inputParser = sepBy1 gameParser endOfLine <* skipSpace <* endOfInput
gameParser :: Parser Game
gameParser = do
string "Card"
skipSpace
id <- decimal
string ": "
winning <- parseNumberList
string " | "
my <- parseNumberList
return (id, winning, my)
parseNumberList :: Parser [Integer]
parseNumberList = sepBy1 (skipSpace *> decimal) " "