--- /dev/null
+-- Writeup at https://work.njae.me.uk/2021/12/09/advent-of-code-2021-day-8/
+
+
+import Data.Text ()
+import qualified Data.Text.IO as TIO
+
+import Data.Attoparsec.Text
+-- import Control.Applicative
+
+import Data.Tuple
+-- import Data.List
+import Data.Char
+import qualified Data.Map.Strict as M
+import Data.Map.Strict ((!))
+import qualified Data.Set as S
+import Data.Set ((\\))
+
+data Path = Path String [String] (S.Set String)
+ deriving (Eq, Ord, Show)
+
+type PathSet = S.Set Path
+type Graph = M.Map String (S.Set String)
+
+
+
+main :: IO ()
+main =
+ do text <- TIO.readFile "data/advent12.txt"
+ let edges = successfulParse text
+ print edges
+ let graph = mkGraph edges
+ print graph
+ print $ part1 graph
+ -- print $ part1 displays
+ -- print $ part2 displays
+
+mkGraph :: [(String, String)] -> Graph
+mkGraph edges = foldr mkEdge pass1 $ map swap edges
+ where pass1 = foldr mkEdge M.empty edges
+ mkEdge (here, there) g = M.insertWith (S.union) here (S.singleton there) g
+
+part1 graph = S.size $ allPaths graph (S.singleton (Path "start" [] S.empty)) S.empty
+
+allPaths :: Graph -> PathSet -> PathSet -> PathSet
+allPaths graph agenda results
+ | S.null agenda = results
+ | otherwise = allPaths graph agenda'' results'
+ where (current, agenda') = S.deleteFindMin agenda
+ newPaths = extendPath graph current
+ agenda'' = S.union agenda' newPaths
+ results' = S.union results $ recordResult current
+
+extendPath :: Graph -> Path -> PathSet
+extendPath graph (Path current trail visited)
+ | current == "end" = S.empty
+ | otherwise = S.map newPath visitable
+ where neighbours = graph ! current
+ visited' = if isSmall current then S.insert current visited else visited
+ trail' = (current:trail)
+ visitable = neighbours \\ visited
+ newPath next = Path next trail' visited'
+
+recordResult :: Path -> PathSet
+recordResult path@(Path current _trail _visited)
+ | current == "end" = S.singleton path -- (Path current trail visited)
+ | otherwise = S.empty
+
+
+isSmall :: String -> Bool
+isSmall = all isLower
+isBig = not . isSmall
+
+-- Parse the input file
+
+graphP = edgeP `sepBy` endOfLine
+edgeP = (,) <$> (many1 letter <* "-") <*> many1 letter
+
+-- successfulParse :: Text -> (Integer, [Maybe Integer])
+successfulParse input =
+ case parseOnly graphP input of
+ Left _err -> [] -- TIO.putStr $ T.pack $ parseErrorPretty err
+ Right graph -> graph