module Main where import qualified Data.Map.Strict as Map import qualified Data.Map.Lazy as LMap import Data.Maybe import qualified Data.Set as Set import Text.Parsec (runParser, sepBy1, string, many1, space, letter, string, digit) import Input type Comp = String data Rule = Rule [(Int, Comp)] (Int, Comp) deriving (Show) parseRule :: String -> Rule parseRule = either (error . show) id . runParser pRule () "" where pRule = Rule <$> (pPair `sepBy1` pComma) <*> (string " => " >> pPair) pPair = (,) <$> (read <$> many1 digit) <*> (space >> many1 letter) pComma = string ", " ceilDiv :: Integral i => i -> i -> i ceilDiv a b = (a + b - 1) `div` b binaryMax :: Integral i => i -> i -> (i -> Bool) -> Maybe i binaryMax low high f | low < high = let mid = low + (high - low) `div` 2 res = f mid in if res then binaryMax mid high f else binaryMax low (mid - 1) f | low == high, f low = Just low | otherwise = Nothing main :: IO () main = do rules <- map parseRule <$> getInput 14 let compounds = Set.toList $ Set.fromList [c | Rule src (_, to) <- rules, c <- to : map snd src] supportGraph = Map.fromListWith (++) [(srccomp, [(num, ncomp, comp)]) -- need 'num' of 'srccomp' for 'ncomp' of 'comp' | Rule src (ncomp, comp) <- rules , (num, srccomp) <- src] let buildNeedOf nfuel = let computeNeed "FUEL" = nfuel computeNeed comp = sum [nreqcomp * ((needOf Map.! c2) `ceilDiv` nprodc2) | (nreqcomp, nprodc2, c2) <- fromMaybe [] (Map.lookup comp supportGraph)] needOf = LMap.fromList [(comp, computeNeed comp) | comp <- compounds] in needOf print (buildNeedOf 1 Map.! "ORE") let lim = 1000000000000 print (fromJust (binaryMax 0 lim (\m -> buildNeedOf m Map.! "ORE" <= lim)))