{-# LANGUAGE LambdaCase #-} module Main where import Data.List import Data.List.Split import Data.List.Utils import qualified Data.Map.Strict as M import Data.Maybe import Helpers import Linear.V2 type DungeonMap = M.Map (V2 Int) Char main :: IO () main = do map <- updateScreenBuffer M.empty (0, 0) <$> readFile "testinput1" putStrLn $ drawMap map let spos = findPos '@' map let epos = findPos 'e' map print $ getNeighbors map spos print $ getNeighborsMap map (getNeighbors map spos) print $ distanceFromTo map '@' 'd' updateScreenBuffer :: DungeonMap -> (Int, Int) -> String -> DungeonMap updateScreenBuffer buf _ [] = buf updateScreenBuffer buf (x, y) (a:as) = updateScreenBuffer bufNew coord as where bufNew = if a /= '\n' then M.insert (V2 x y) a buf else buf coord = if a /= '\n' then (x + 1, y) else (0, y + 1) getNeighbors :: DungeonMap -> V2 Int -> DungeonMap getNeighbors m coord = M.fromList [ (u + coord, M.findWithDefault '#' (u + coord) m) | u <- unitVecs , M.findWithDefault '#' (u + coord) m /= '#' ] getNeighborsMap :: DungeonMap -> DungeonMap -> DungeonMap getNeighborsMap m n = M.unions [getNeighbors m x | (x, _) <- M.toList n] distanceFromTo :: DungeonMap -> Char -> Char -> Int distanceFromTo dmap schar echar = distanceFromTo' dmap (M.singleton spos schar) spos epos 1 where spos = findPos schar dmap epos = findPos echar dmap distanceFromTo' mMap nMap start end n = if M.member end newNMap then n else distanceFromTo' mMap newNMap start end (n + 1) where newNMap = M.union nMap (getNeighborsMap mMap nMap) findPos :: Char -> DungeonMap -> V2 Int findPos c = head . M.keys . M.filter (`elem` [c])