2019-12-18 15:02:42 +01:00
{- # LANGUAGE LambdaCase # -}
module Main where
import Data.List
import Data.List.Split
import Data.List.Utils
2019-12-18 18:30:47 +01:00
import Data.Char
2019-12-18 15:02:42 +01:00
import qualified Data.Map.Strict as M
2019-12-18 18:30:47 +01:00
import qualified Data.Set as S
2019-12-18 15:02:42 +01:00
import Data.Maybe
import Helpers
import Linear.V2
2019-12-18 18:30:47 +01:00
import Debug.Trace
2019-12-18 15:02:42 +01:00
type DungeonMap = M . Map ( V2 Int ) Char
2019-12-18 18:30:47 +01:00
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
2019-12-18 15:02:42 +01:00
main :: IO ()
main = do
2019-12-18 18:30:47 +01:00
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'
2019-12-18 15:02:42 +01:00
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
2019-12-18 18:30:47 +01:00
, let c = M . findWithDefault '#' ( u + coord ) m in c ` elem ` " .@⌂ " || isLower c
2019-12-18 15:02:42 +01:00
]
getNeighborsMap :: DungeonMap -> DungeonMap -> DungeonMap
getNeighborsMap m n = M . unions [ getNeighbors m x | ( x , _ ) <- M . toList n ]
2019-12-18 18:30:47 +01:00
distanceFromTo :: DungeonMap -> Char -> Char -> Distance
distanceFromTo dMap schar echar =
distanceFromTo' dMap ( M . singleton spos schar ) spos epos 1
2019-12-18 15:02:42 +01:00
where
2019-12-18 18:30:47 +01:00
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 )
2019-12-18 15:02:42 +01:00
where
newNMap = M . union nMap ( getNeighborsMap mMap nMap )
2019-12-18 18:30:47 +01:00
--todo: maek tail recursive
2019-12-18 15:02:42 +01:00
findPos :: Char -> DungeonMap -> V2 Int
findPos c = head . M . keys . M . filter ( ` elem ` [ c ] )
2019-12-18 18:30:47 +01:00
-- 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