Skip to content

Instantly share code, notes, and snippets.

@mjgpy3
Created December 8, 2020 12:48
Show Gist options
  • Save mjgpy3/cf7dd14219c9323ddf863db84556be51 to your computer and use it in GitHub Desktop.
Save mjgpy3/cf7dd14219c9323ddf863db84556be51 to your computer and use it in GitHub Desktop.
aoc-2020-day7
{-# LANGUAGE OverloadedStrings #-}
module Main where
import qualified Data.Map.Strict as M
import qualified Data.Set as S
import Data.List (foldl')
import qualified Data.Text as T
import qualified Data.Text.IO as TIO
import Data.Bifunctor
parseLine :: T.Text -> (T.Text, [(Int, T.Text)])
parseLine raw =
case T.splitOn " contain " $ T.dropEnd 1 $ T.replace "bag" "" $ T.replace "bags" "" raw of
[bigger, smallerRaw] | smallerRaw == "no other " -> (T.strip bigger, [])
[bigger, smallerRaw] ->
(
T.strip bigger,
map parseBagsWithCount $ T.splitOn ", " smallerRaw
)
where
parseBagsWithCount =
bimap (read . T.unpack) T.strip . T.breakOn " "
-- I anticipate needing a graph the other way for part 2
toGraphs = go M.empty M.empty
where
go contains containedBy [] = (contains, containedBy)
go contains containedBy ((bigger, smaller):rest) =
go (M.insert bigger smaller contains) (insertContainedBy bigger containedBy smaller) rest
insertContainedBy = foldl' . consInsert
consInsert bigger g (_, smaller) | M.member smaller g = M.adjust (bigger :) smaller g
consInsert bigger g (_, smaller) = M.insert smaller [bigger] g
canContainShinyGold g = go S.empty ["shiny gold"]
where
go seen [] = seen
go seen (current:rest) =
case M.lookup current g of
Nothing -> go seen rest
Just ns ->
let
next = filter (`S.notMember` seen) ns
in
go (S.union seen (S.fromList next)) (next ++ rest)
main = do
text <- T.splitOn "\n" . T.strip <$> TIO.readFile "./d7.txt"
print $ S.size $ canContainShinyGold $ snd $ toGraphs $ map parseLine text
{-# LANGUAGE OverloadedStrings #-}
module Main where
import qualified Data.Map.Strict as M
import Data.List (foldl')
import qualified Data.Text as T
import qualified Data.Text.IO as TIO
import Data.Bifunctor
parseLine :: T.Text -> (T.Text, [(Int, T.Text)])
parseLine raw =
case T.splitOn " contain " $ T.dropEnd 1 $ T.replace "bag" "" $ T.replace "bags" "" raw of
[bigger, smallerRaw] | smallerRaw == "no other " -> (T.strip bigger, [])
[bigger, smallerRaw] ->
(
T.strip bigger,
map parseBagsWithCount $ T.splitOn ", " smallerRaw
)
where
parseBagsWithCount =
bimap (read . T.unpack) T.strip . T.breakOn " "
toGraphs = go M.empty M.empty
where
go contains containedBy [] = (contains, containedBy)
go contains containedBy ((bigger, smaller):rest) =
go (M.insert bigger smaller contains) (insertContainedBy bigger containedBy smaller) rest
insertContainedBy = foldl' . consInsert
consInsert bigger g (_, smaller) | M.member smaller g = M.adjust (bigger :) smaller g
consInsert bigger g (_, smaller) = M.insert smaller [bigger] g
neededBags bags g =
sum [amount + amount*(neededBags (M.findWithDefault [] bag g) g) | (amount, bag) <- bags]
solve g = neededBags (g M.! "shiny gold") g
main = do
text <- T.splitOn "\n" . T.strip <$> TIO.readFile "./d7.txt"
print $ solve $ fst $ toGraphs $ map parseLine text
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment