97 lines
2.7 KiB
Haskell
97 lines
2.7 KiB
Haskell
module Day2 where
|
|
|
|
import System.IO
|
|
import ParseLib.Abstract
|
|
import Prelude hiding ((<$), ($>), (<*), (*>), sequence)
|
|
import Data.Maybe
|
|
import Data.List
|
|
import Foreign (toBool)
|
|
|
|
main :: IO ()
|
|
main = do
|
|
handle <- openFile "app/Day2-input.txt" ReadMode
|
|
input <- hGetContents handle
|
|
|
|
let games = map (fst . head . parse parseGame . fst . head . parse lexer) (lines input)
|
|
cubes = map maxColors games
|
|
possible = filter isPossible cubes
|
|
total = sum (map fst possible)
|
|
|
|
putStr "Part 1: "
|
|
print total
|
|
|
|
let power = sum $ map totalPower cubes
|
|
|
|
putStr "Part 2: "
|
|
print power
|
|
|
|
where
|
|
isPossible :: (Int, [Color]) -> Bool
|
|
isPossible (_, cs) =
|
|
fromMaybe (Red 0) (find isRed cs) <= Red 12
|
|
&& fromMaybe (Green 0) (find isGreen cs) <= Green 13
|
|
&& fromMaybe (Blue 0) (find isBlue cs) <= Blue 14
|
|
|
|
totalPower :: (Int, [Color]) -> Int
|
|
totalPower (_, cs) =
|
|
value (fromMaybe (Red 1) (find isRed cs)) *
|
|
value (fromMaybe (Green 1) (find isGreen cs)) *
|
|
value (fromMaybe (Blue 1) (find isBlue cs))
|
|
|
|
data Token = TGame Int
|
|
| TRed Int
|
|
| TBlue Int
|
|
| TGreen Int
|
|
| TSep
|
|
deriving (Show, Eq)
|
|
|
|
isTGame TGame{} = True
|
|
isTGame _ = False
|
|
|
|
isTRed TRed{} = True
|
|
isTRed _ = False
|
|
isTBlue TBlue{} = True
|
|
isTBlue _ = False
|
|
isTGreen TGreen{} = True
|
|
isTGreen _ = False
|
|
lexer :: Parser Char [Token]
|
|
lexer = greedy parseToken
|
|
|
|
parseToken :: Parser Char Token
|
|
parseToken = TGame <$ token "Game " <*> natural <* token ": "
|
|
<|> TRed <$> natural <* token " red" <* greedy (token ", ")
|
|
<|> TBlue <$> natural <* token " blue" <* greedy (token ", ")
|
|
<|> TGreen <$> natural <* token " green" <* greedy (token ", ")
|
|
<|> TSep <$ token "; " <* greedy (token ", ")
|
|
|
|
data Game = Game Int [[Color]] deriving Show
|
|
data Color = Red Int | Green Int | Blue Int deriving (Show, Eq, Ord)
|
|
|
|
value (Red i) = i
|
|
value (Green i) = i
|
|
value (Blue i) = i
|
|
|
|
isRed Red{} = True
|
|
isRed _ = False
|
|
isBlue Blue{} = True
|
|
isBlue _ = False
|
|
isGreen Green{} = True
|
|
isGreen _ = False
|
|
|
|
colors (Game _ cs) = cs
|
|
|
|
|
|
parseGame :: Parser Token Game
|
|
parseGame = (\(TGame g) cs -> Game g cs) <$> satisfy isTGame <*> listOf (many parseColor) (symbol TSep)
|
|
|
|
parseColor :: Parser Token Color
|
|
parseColor = (\(TRed i) -> Red i) <$> satisfy isTRed
|
|
<|> (\(TGreen i) -> Green i) <$> satisfy isTGreen
|
|
<|> (\(TBlue i) -> Blue i) <$> satisfy isTBlue
|
|
|
|
maxColors :: Game -> (Int, [Color])
|
|
maxColors (Game i cs) = (i, [maximum red, maximum green, maximum blue])
|
|
where
|
|
red = mapMaybe (find isRed) cs
|
|
green = mapMaybe (find isGreen) cs
|
|
blue = mapMaybe (find isBlue) cs |