summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorTom Smeding <tom@tomsmeding.com>2021-12-13 22:28:40 +0100
committerTom Smeding <tom@tomsmeding.com>2021-12-13 22:46:16 +0100
commit43c9eeb5cfa3007d61883b32f30766e381516560 (patch)
tree965accdf16f57e86d4171b0f6d3839866f12c7a4
parent6c37ffc703834884cb13bae873ba38d8f284d6ef (diff)
12
-rw-r--r--2021/12.hs52
-rw-r--r--2021/12.in24
2 files changed, 76 insertions, 0 deletions
diff --git a/2021/12.hs b/2021/12.hs
new file mode 100644
index 0000000..03b2d77
--- /dev/null
+++ b/2021/12.hs
@@ -0,0 +1,52 @@
+module Main where
+
+import qualified Data.Array as A
+import Data.Bifunctor (bimap)
+import Data.Char
+import Data.List
+import qualified Data.Map.Strict as Map
+import qualified Data.Set as Set
+import Data.Tuple (swap)
+
+import Input
+import Util
+
+
+uniq :: Eq a => [a] -> [a]
+uniq (x : y : xs) | x == y = uniq (y : xs)
+ | otherwise = x : uniq (y : xs)
+uniq l = l
+
+main :: IO ()
+main = do
+ inp <- getInput 12
+ let listpairs = map (toList . splitOn (== '-')) inp
+ pairs = map (\[a,b] -> (a, b)) listpairs
+ nodes = uniq (sort (concat listpairs))
+ nodeids = Map.fromList (zip nodes [0::Int ..])
+ idpairs = map (bimap (nodeids Map.!) (nodeids Map.!)) pairs
+ startid = nodeids Map.! "start"
+ endid = nodeids Map.! "end"
+ collect l = A.listArray (0, length l - 1) l
+ graph = collect
+ [collect [b | (a, b) <- idpairs ++ map swap idpairs
+ , a == node]
+ | node <- [0 .. length nodes - 1]]
+ issmall = collect (map (all isLower) nodes)
+ npathsfrom :: Int -> Set.Set Int -> Bool -> [[Int]]
+ npathsfrom node seen permissive
+ | node == endid = [[endid]]
+ | otherwise =
+ let nexts = A.elems (graph A.! node)
+ allowed n = not (issmall A.! n) || n `Set.notMember` seen
+ doubling n = n /= startid && n /= endid && not (allowed n)
+ nexts_allowed = filter allowed nexts
+ nexts_doubling = filter doubling nexts
+ seen' | issmall A.! node = Set.insert node seen
+ | otherwise = seen
+ in concatMap (\n -> map (node :) (npathsfrom n seen' permissive)) nexts_allowed
+ ++ (if permissive
+ then concatMap (\n -> map (node :) (npathsfrom n seen' False)) nexts_doubling
+ else [])
+ print (length $ npathsfrom startid mempty False)
+ print (length $ npathsfrom startid mempty True)
diff --git a/2021/12.in b/2021/12.in
new file mode 100644
index 0000000..e1a2275
--- /dev/null
+++ b/2021/12.in
@@ -0,0 +1,24 @@
+pf-pk
+ZQ-iz
+iz-NY
+ZQ-end
+pf-gx
+pk-ZQ
+ZQ-dc
+NY-start
+NY-pf
+NY-gx
+ag-ZQ
+pf-start
+start-gx
+BN-ag
+iz-pf
+ag-FD
+pk-NY
+gx-pk
+end-BN
+ag-pf
+iz-pk
+pk-ag
+iz-end
+iz-BN