module Main where import qualified Data.Map.Lazy as LMap import Text.Parsec hiding (getInput) import Input type Clr = String data Rule = Rule Clr [(Int, Clr)] deriving (Show) parseRule :: String -> Rule parseRule s = case parse pRule "" s of Right r -> r ; Left e -> error (show e) where pRule :: Parsec String () Rule pRule = do clr <- pClr symbols ["bags", "contain"] cont <- choice [symbols ["no", "other", "bags"] >> char '.' >> return [] ,pContent `sepBy1` char ','] return (Rule clr cont) pContent :: Parsec String () (Int, Clr) pContent = do n <- pNumber clr <- pClr choice [symbol "bag" <|> symbol "bags"] return (n, clr) pClr :: Parsec String () Clr pClr = concat <$> sequence [pWord, return " ", pWord] pNumber :: Parsec String () Int pNumber = try (spaces >> (read <$> many1 digit)) <* notFollowedBy letter pWord :: Parsec String () String pWord = try $ spaces >> many1 letter symbol :: String -> Parsec String () () symbol sym = try $ spaces >> string sym >> notFollowedBy letter symbols :: [String] -> Parsec String () () symbols = sequence_ . map symbol main :: IO () main = do input <- map parseRule <$> getInput 7 let canContainSG = LMap.fromList [(clr, "shiny gold" `elem` map snd cont || any (canContainSG LMap.!) (map snd cont)) | Rule clr cont <- input] cumulSize = LMap.fromList [(clr, 1 + sum (map (uncurry (*) . fmap (cumulSize LMap.!)) cont)) | Rule clr cont <- input] :: LMap.Map Clr Int print (sum . map fromEnum $ LMap.elems canContainSG) print (cumulSize LMap.! "shiny gold" - 1)