aecf61358f
goal needs to be x, so moved into the list comprehension
95 lines
3.0 KiB
Haskell
95 lines
3.0 KiB
Haskell
{-# LANGUAGE LambdaCase #-}
|
|
module Main where
|
|
|
|
import Data.List
|
|
import Data.List.Split
|
|
import Data.List.Utils
|
|
import Data.Char
|
|
import qualified Data.Map.Strict as M
|
|
import qualified Data.Set as S
|
|
import Data.Maybe
|
|
import Helpers
|
|
import Linear.V2
|
|
import Debug.Trace
|
|
|
|
type DungeonMap = M.Map (V2 Int) Char
|
|
data Distance = Reachable Int | Unreachable deriving (Show, Eq)
|
|
|
|
instance Num Distance where
|
|
Reachable x + Reachable y = Reachable (x+y)
|
|
Unreachable + _ = Unreachable
|
|
_ + Unreachable = Unreachable
|
|
|
|
instance Ord Distance where
|
|
Reachable x <= Reachable y = x<=y
|
|
Unreachable <= _ = False
|
|
_ <= Unreachable = True
|
|
|
|
main :: IO ()
|
|
main = do
|
|
dMap <- updateScreenBuffer M.empty (0, 0) <$> readFile "testinput1"
|
|
putStrLn $ drawMap dMap
|
|
print $ distanceFromTo dMap '@' 'f'
|
|
print $ distanceFromTo dMap '@' 'a'
|
|
print $ distanceFromTo dMap '@' 'A'
|
|
print $ tls1 dMap (S.fromList "abcdef") 'f'
|
|
|
|
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
|
|
, let c = M.findWithDefault '#' (u + coord) m in c `elem` ".@⌂" || isLower c
|
|
]
|
|
|
|
getNeighborsMap :: DungeonMap -> DungeonMap -> DungeonMap
|
|
getNeighborsMap m n = M.unions [getNeighbors m x | (x, _) <- M.toList n]
|
|
|
|
distanceFromTo :: DungeonMap -> Char -> Char -> Distance
|
|
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
|
|
| M.member end newNMap = Reachable n
|
|
| newNMap == nMap = Unreachable
|
|
| otherwise = distanceFromTo' mMap newNMap start end (n + 1)
|
|
where
|
|
newNMap = M.union nMap (getNeighborsMap mMap nMap)
|
|
--todo: maek tail recursive
|
|
|
|
findPos :: Char -> DungeonMap -> V2 Int
|
|
findPos c = head . M.keys . M.filter (`elem` [c])
|
|
|
|
-- tracePath :: DungeonMap -> Char -> String -> Maybe Int
|
|
-- tracePath dMap _ [] = Just 0
|
|
-- tracePath dMap c (x:xs) = case distanceFromTo dMap c x of
|
|
-- Nothing -> Nothing
|
|
-- Just y -> let trace = tracePath dMap c xs in if isJust trace then Just (y + fromJust trace) else Nothing
|
|
tls1 :: DungeonMap -> S.Set Char -> Char -> Distance
|
|
tls1 dMap nodeSet goal
|
|
| S.size nodeSet == 1 = (distanceFromTo dMap '@' (head $ S.toList nodeSet))
|
|
-- ^ S = {c}, different 1 element sets possible?
|
|
| otherwise =
|
|
minimum
|
|
[tls1 dMap sMinusC x + distanceFromTo newDMap x goal | x <- S.toList sMinusC]
|
|
where
|
|
sMinusC = traceShowId (S.delete goal nodeSet)
|
|
newDMap = traceShowId (M.insert door '⌂' dMap)
|
|
door = traceShowId (findPos (toUpper (traceShowId goal)) dMap)
|
|
-- tls2 = undefined
|