haskell: 2023 02 b

This commit is contained in:
Maciej Jur 2023-12-02 14:32:05 +01:00
parent a0d8e5cfd2
commit fb082aac07
Signed by: kamov
GPG key ID: 191CBFF5F72ECAFD
3 changed files with 30 additions and 17 deletions

View file

@ -3,7 +3,6 @@ module Main where
import Utils (readInput) import Utils (readInput)
import qualified Day01 import qualified Day01
import qualified Day02 import qualified Day02
import Debug.Trace (traceShowId)
day01 :: IO () day01 :: IO ()
@ -17,7 +16,9 @@ day02 = do
text <- readInput 2 text <- readInput 2
case Day02.parse text of case Day02.parse text of
Left err -> putStrLn err Left err -> putStrLn err
Right xd -> print . Day02.solveA . traceShowId $ xd Right xd -> do
print . Day02.solveA $ xd
print . Day02.solveB $ xd
main :: IO () main :: IO ()
main = do main = do

View file

@ -1,6 +1,6 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE RecordWildCards #-}
module Day02 (Cube(..), Game(..), parse, solveA) where module Day02 (Cube(..), Game(..), parse, solveA, solveB) where
import Data.Void (Void) import Data.Void (Void)
import Data.Text (Text) import Data.Text (Text)
@ -13,8 +13,8 @@ import Text.Megaparsec.Char.Lexer (decimal)
data Cube = R Int | G Int | B Int deriving Show data Cube = R Int | G Int | B Int deriving Show
data Game = Game data Game = Game
{ gameId :: Int { gId :: Int
, gameSets :: [[Cube]] , gSets :: [[Cube]]
} deriving Show } deriving Show
type Parser = Parsec Void Text type Parser = Parsec Void Text
@ -26,14 +26,14 @@ parse = first errorBundlePretty . runParser games ""
cube :: Parser Cube cube :: Parser Cube
cube = do cube = do
_ <- optional space _ <- optional space
number <- decimal count <- decimal
space space
color <- choice color <- choice
[ R <$ string "red" [ R <$ string "red"
, G <$ string "green" , G <$ string "green"
, B <$ string "blue" , B <$ string "blue"
] ]
return . color $ number return $ color count
set :: Parser [Cube] set :: Parser [Cube]
set = space *> cube `sepBy` char ',' set = space *> cube `sepBy` char ','
sets :: Parser [[Cube]] sets :: Parser [[Cube]]
@ -42,9 +42,9 @@ parse = first errorBundlePretty . runParser games ""
game = do game = do
_ <- string "Game" _ <- string "Game"
space space
gameId <- decimal gId <- decimal
_ <- char ':' _ <- char ':'
gameSets <- sets gSets <- sets
_ <- optional newline _ <- optional newline
return $ Game {..} return $ Game {..}
games :: Parser [Game] games :: Parser [Game]
@ -52,7 +52,7 @@ parse = first errorBundlePretty . runParser games ""
solveA :: [Game] -> Int solveA :: [Game] -> Int
solveA = sum . map gameId . filter isValid solveA = sum . map gId . filter isValid
where where
isSetValid :: Cube -> Bool isSetValid :: Cube -> Bool
isSetValid count = case count of isSetValid count = case count of
@ -60,4 +60,15 @@ solveA = sum . map gameId . filter isValid
G g -> g <= 13 G g -> g <= 13
B b -> b <= 14 B b -> b <= 14
isValid :: Game -> Bool isValid :: Game -> Bool
isValid Game {..} = all (all isSetValid) gameSets isValid Game {..} = all (all isSetValid) gSets
solveB :: [Game] -> Int
solveB = sum . map toPower
where
update :: (Int, Int, Int) -> Cube -> (Int, Int, Int)
update (r, g, b) cube = case cube of
R r' -> (max r r', g, b)
G g' -> (r, max g g', b)
B b' -> (r, g, max b b')
toPower :: Game -> Int
toPower Game {..} = (\(r, g, b) -> r * g * b) . foldl update (0, 0, 0) . concat $ gSets

View file

@ -18,10 +18,11 @@ day01 = TestList
day02 :: Test day02 :: Test
day02 = TestList day02 = TestList
[ TestCase $ assertEqual "should return 8" 8 (Day02.solveA inputA) [ TestCase $ assertEqual "should return 8" 8 (Day02.solveA input)
, TestCase $ assertEqual "should return 2286" 2286 (Day02.solveB input)
] ]
where where
inputA = input =
[ Day02.Game 1 [[Day02.B 3, Day02.R 4], [Day02.R 1, Day02.G 2, Day02.B 6], [Day02.G 2]] [ Day02.Game 1 [[Day02.B 3, Day02.R 4], [Day02.R 1, Day02.G 2, Day02.B 6], [Day02.G 2]]
, Day02.Game 2 [[Day02.B 1, Day02.G 2], [Day02.G 3, Day02.B 4, Day02.R 1], [Day02.G 1, Day02.B 1]] , Day02.Game 2 [[Day02.B 1, Day02.G 2], [Day02.G 3, Day02.B 4, Day02.R 1], [Day02.G 1, Day02.B 1]]
, Day02.Game 3 [[Day02.G 8, Day02.B 6, Day02.R 20], [Day02.B 5, Day02.R 4, Day02.G 13], [Day02.G 5, Day02.R 1]] , Day02.Game 3 [[Day02.G 8, Day02.B 6, Day02.R 20], [Day02.B 5, Day02.R 4, Day02.G 13], [Day02.G 5, Day02.R 1]]