summaryrefslogtreecommitdiff
path: root/2020/7.hs
blob: 6c6e67365d1649845c8ac15c59fc2381bac1da69 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
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)