summaryrefslogtreecommitdiff
path: root/2020/19.hs
diff options
context:
space:
mode:
Diffstat (limited to '2020/19.hs')
-rw-r--r--2020/19.hs50
1 files changed, 50 insertions, 0 deletions
diff --git a/2020/19.hs b/2020/19.hs
new file mode 100644
index 0000000..3ae886f
--- /dev/null
+++ b/2020/19.hs
@@ -0,0 +1,50 @@
+module Main where
+
+import qualified Data.Array as A
+import Data.Foldable (toList)
+import Text.Parsec hiding (getInput)
+
+import Input
+import Util
+
+
+data Rule = S Char | D [[Int]]
+ deriving (Show)
+
+parseRule :: String -> (Int, Rule)
+parseRule = either (error . show) id . parse pRule ""
+ where
+ pRule :: Parsec String () (Int, Rule)
+ pRule = (,) <$> pNum <*> (string ": " >> pRhs)
+ pNum = read <$> many1 digit
+ pRhs = S <$> pString <|> D <$> (pConj `sepBy` try (spaces >> char '|'))
+ pString = try $ spaces >> between (char '"') (char '"') (satisfy (/= '"'))
+ pConj = many1 (try (spaces >> pNum))
+
+newtype Gram = Gram (A.Array Int Rule)
+ deriving (Show)
+
+parseGram :: [String] -> Gram
+parseGram l =
+ let parsed = map parseRule l
+ ids = map fst parsed
+ in Gram (A.array (minimum ids, maximum ids) parsed)
+
+matches :: Gram -> [Int] -> String -> Bool
+matches _ [] [] = True
+matches gram@(Gram arr) (r:rs) (c:cs) =
+ case arr A.! r of
+ S c' | c == c' -> matches gram rs cs
+ | otherwise -> False
+ D alts -> any (\alt -> matches gram (alt ++ rs) (c:cs)) alts
+matches _ _ _ = False
+
+update2 :: Gram -> Gram
+update2 (Gram arr) = Gram (arr A.// [(8, D [[42], [42, 8]]), (11, D [[42, 31], [42, 11, 31]])])
+
+main :: IO ()
+main = do
+ [rules, inputs] <- toList . splitOn null <$> getInput 19
+ let gram = parseGram rules
+ print (length (filter (matches gram [0]) inputs))
+ print (length (filter (matches (update2 gram) [0]) inputs))