Finish Day 2 - Part 1
parent
56ceceaa49
commit
29c5ea7841
|
@ -11,6 +11,8 @@
|
|||
"factorise",
|
||||
"foldl",
|
||||
"HLINT",
|
||||
"mempty",
|
||||
"Prec",
|
||||
"unrecognised"
|
||||
]
|
||||
}
|
||||
}
|
||||
|
|
|
@ -1,25 +1,78 @@
|
|||
-- https://adventofcode.com/2023/day/2
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
-- imports
|
||||
import Data.Bifunctor (Bifunctor (bimap, second))
|
||||
import Data.Char (isSpace)
|
||||
import Data.List (foldl', sort, (!!))
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
import qualified Data.Text.IO as T
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
entries <- lines <$> readFile "src/advent_of_code/2023/input2"
|
||||
print "Advent of Code 2023 - Day 2"
|
||||
|
||||
print ("Part 1: " <> show (solveP1 entries))
|
||||
print ("Part 2: " <> show (solveP2 entries))
|
||||
entries <- T.lines <$> T.readFile "src/advent_of_code/2023/input2"
|
||||
putStrLn "Advent of Code 2023 - Day 2"
|
||||
-- print entries
|
||||
putStrLn ("Part 1: " <> show (solveP1 entries))
|
||||
-- putStrLn ("Part 2: " <> show (solveP2 entries))
|
||||
|
||||
--
|
||||
-- Part 1
|
||||
--
|
||||
|
||||
solveP1 :: [String] -> [String]
|
||||
solveP1 = id
|
||||
data Colour
|
||||
= Red
|
||||
| Green
|
||||
| Blue
|
||||
deriving (Show, Read, Ord, Eq)
|
||||
|
||||
data Cube c n
|
||||
= Cube c n
|
||||
deriving (Show, Read, Ord, Eq)
|
||||
|
||||
cubeLessThanLimit :: (Cube Colour Int, Cube Colour Int, Cube Colour Int) -> Cube Colour Int -> Bool
|
||||
cubeLessThanLimit (Cube Red n, _, _) (Cube Red v) = v <= n
|
||||
cubeLessThanLimit (_, Cube Green n, _) (Cube Green v) = v <= n
|
||||
cubeLessThanLimit (_, _, Cube Blue n) (Cube Blue v) = v <= n
|
||||
|
||||
lessThanP1 :: Cube Colour Int -> Bool
|
||||
lessThanP1 = cubeLessThanLimit p1Limit
|
||||
|
||||
p1Limit :: (Cube Colour Int, Cube Colour Int, Cube Colour Int)
|
||||
p1Limit = (Cube Red 12, Cube Green 13, Cube Blue 14)
|
||||
|
||||
solveP1 :: [Text] -> Int
|
||||
solveP1 = sum . map fst . filter snd . map (second (all (== True) . concatMap (map lessThanP1)) . parseInput)
|
||||
|
||||
--
|
||||
-- Part 2
|
||||
--
|
||||
|
||||
solveP2 :: [String] -> [String]
|
||||
solveP2 = id
|
||||
|
||||
--
|
||||
-- Parsing
|
||||
--
|
||||
|
||||
parseInput :: Text -> (Int, [[Cube Colour Int]])
|
||||
parseInput = bimap (read . T.unpack . T.drop 5) (map (map stringToCube . T.splitOn ", ") . T.splitOn "; " . T.drop 2) . T.breakOn ": "
|
||||
|
||||
stringToCube :: Text -> Cube Colour Int
|
||||
stringToCube str = read $ "Cube " <> colour' <> " " <> n'
|
||||
where
|
||||
(n, colour) = second (T.drop 1) . T.break isSpace $ str
|
||||
colour' = T.unpack (T.toTitle colour)
|
||||
n' = T.unpack n
|
||||
|
||||
--
|
||||
-- Examples
|
||||
--
|
||||
|
||||
example1 :: [Text]
|
||||
example1 =
|
||||
[ "Game 1: 3 blue, 4 red; 1 red, 2 green, 6 blue; 2 green"
|
||||
, "Game 2: 1 blue, 2 green; 3 green, 4 blue, 1 red; 1 green, 1 blue"
|
||||
, "Game 3: 8 green, 6 blue, 20 red; 5 blue, 4 red, 13 green; 5 green, 1 red"
|
||||
, "Game 4: 1 green, 3 red, 6 blue; 3 green, 6 red; 3 green, 15 blue, 14 red"
|
||||
, "Game 5: 6 red, 1 blue, 3 green; 2 blue, 1 red, 2 green"
|
||||
]
|
||||
|
|
Loading…
Reference in New Issue