day4: Solve part1

This commit is contained in:
Alexander Kobjolke 2023-12-05 20:36:09 +01:00
parent d360838d47
commit 4261938d95
8 changed files with 228 additions and 152 deletions

View file

@ -1,6 +1,56 @@
module AoC.Y2023.D04 (solve) where
module AoC.Y2023.D04 where
import AoC.Parser
import AoC.Riddle
import Text.Megaparsec (sepBy, (<?>))
import Text.Megaparsec.Char (char, space, string)
import Text.Megaparsec.Char.Lexer qualified as L
type Cards = [Int]
data Game = Game
{ winningCards :: Cards
, playedCards :: Cards
}
deriving stock (Show)
-- | parse list of cards
--
-- >>> parseText pCards "5 6 42 23"
-- Right [5,6,42,23]
pCards :: Parser Cards
pCards = L.decimal `sepBy` ws
-- | parse a game
--
-- >>> parseText pGame "Game 1: 5 6 42 23 | 78 56 42"
pGame :: Parser Game
pGame = do
_ <- string "Card "
_ <- L.decimal :: Parser Int
_ <- string ": "
w <- many $ L.decimal <* ws
_ <- string "|"
h <- L.decimal `sepBy` ws
pure $ Game w h
-- sets <- pCards `sepBy` (char '|' >> ws)
-- case sets of
-- [w, h] -> pure $ Game w h
-- _ -> fail "expected two sets of cards"
pPuzzle :: Parser [Game]
pPuzzle = linewise pGame
solve :: (MonadIO m) => Text -> m (Either Text Solution)
solve _ = pure $ Left "not yet implemented"
solve riddle = case parseText pPuzzle riddle of
Right puzzle ->
let
part1 :: Integer
part1 = 42
part2 :: Integer
part2 = part1
in
pure $ Right [part1, part2]
Left e -> pure $ Left e