diff options
| author | Akshay <[email protected]> | 2020-12-16 11:10:23 +0000 |
|---|---|---|
| committer | Akshay <[email protected]> | 2020-12-16 11:10:23 +0000 |
| commit | 28091a3489732f42bf7419c6fcc6f0a3d1c674fc (patch) | |
| tree | a89b9bddbe37f5f504b5704a1ed36726103ab563 /execs | |
| parent | 8c1193fece01bb80e86d8cc36efcf8820a6ccb46 (diff) | |
add initial day16 solution
Diffstat (limited to 'execs')
| -rw-r--r-- | execs/Day16.hs | 52 |
1 files changed, 52 insertions, 0 deletions
diff --git a/execs/Day16.hs b/execs/Day16.hs new file mode 100644 index 0000000..88752ad --- /dev/null +++ b/execs/Day16.hs | |||
| @@ -0,0 +1,52 @@ | |||
| 1 | module Main where | ||
| 2 | |||
| 3 | import Data.Function (on) | ||
| 4 | import Data.List (sortBy) | ||
| 5 | import Data.List.Split (splitOn) | ||
| 6 | import Data.Map (Map, (!)) | ||
| 7 | import qualified Data.Map as Map | ||
| 8 | import Data.Set (Set, (\\)) | ||
| 9 | import qualified Data.Set as Set | ||
| 10 | import Text.Parsec.Char | ||
| 11 | import Text.ParserCombinators.Parsec | ||
| 12 | import Utils | ||
| 13 | |||
| 14 | type Constraint = ((Int, Int), (Int, Int)) | ||
| 15 | |||
| 16 | parseNumber = read <$> many1 digit | ||
| 17 | parseBound = (,) <$> parseNumber <* char '-' <*> parseNumber | ||
| 18 | parseConstraint = (,) <$> parseBound <* string " or " <*> parseBound | ||
| 19 | parseConstraints = (manyTill anyChar (string ": ") *> parseConstraint) `sepBy` newline | ||
| 20 | parseTicket = parseNumber `sepBy` char ',' | ||
| 21 | parseNears = string "nearby tickets:" *> newline *> parseTicket `sepBy` newline | ||
| 22 | parseMine = string "your ticket:" *> newline *> parseTicket | ||
| 23 | parseInput s = do | ||
| 24 | let (p:q:r:_) = splitOn "\n\n" s | ||
| 25 | (,,) <$> parse parseConstraints "cs" p | ||
| 26 | <*> parse parseMine "mine" q | ||
| 27 | <*> parse parseNears "nears" r | ||
| 28 | |||
| 29 | within (a, b) = flip bet a |+ flip bet b | ||
| 30 | findInvalid cs = filter (\t -> not $ any (`within` t) cs) | ||
| 31 | isValid cs = all (\t -> any (`within` t) cs) | ||
| 32 | |||
| 33 | validFor :: [Constraint] -> [Int] -> Set Int | ||
| 34 | validFor cs items = foldl1 Set.intersection (map vcf items) | ||
| 35 | where vcf i = Set.fromList [idx | (cons, idx) <- zip cs [0..], cons `within` i] | ||
| 36 | |||
| 37 | main :: IO () | ||
| 38 | main = do | ||
| 39 | q <- parseInput <$> readFile "input/16" | ||
| 40 | n <- readFile "input/16" | ||
| 41 | let Right (cs, mine, nears) = q | ||
| 42 | validTickets = filter (isValid cs) nears | ||
| 43 | cols = map (\i -> map (!! i) validTickets) [0..length cs - 1] | ||
| 44 | possibleCons = sortBy (compare `on` (Set.size . snd)) $ zip [0..] $ map (validFor cs) cols | ||
| 45 | corresp = Map.fromList | ||
| 46 | $ map (\(i,v) -> (head $ Set.toList v, i)) | ||
| 47 | $ (head possibleCons:) | ||
| 48 | $ zipWith fn <*> tail | ||
| 49 | $ possibleCons | ||
| 50 | where fn (i, s) (i', s') = (i', s' \\ s) | ||
| 51 | print $ sum $ concatMap (findInvalid cs) nears | ||
| 52 | print $ product $ map ((mine!!) . (corresp!)) [0..5] | ||
