Commit c5c3cfb3 by Stuart Kurtz

Day 15

parent e9431c54
module Main where
import Control.Monad
import Data.Array
import qualified Data.Map as M
import Data.Map (Map)
type Position = (Int,Int)
type ChitonMap = Array Position Int
readMap :: String -> ChitonMap
readMap s = arr where
ps = do
(rx,row) <- enumerate . lines $ s
(cx,col) <- enumerate row
pure $ ((rx,cx),read @Int [col])
enumerate = zip @Int [0..]
maxX = maximum . (map (fst . fst)) $ ps
maxY = maximum . (map (snd . fst)) $ ps
arr = array ((0,0),(maxX,maxY)) ps
showMap :: ChitonMap -> String
showMap cm = unlines [ [head . show $ (cm ! (x,y)) | y <- [0..maxY]] | x <- [0..maxX]] where
((0,0),(maxX,maxY)) = bounds cm
neighbors :: Array Position a -> Position -> [Position]
neighbors cm (x,y) = do
p <- [(x-1,y),(x,y-1),(x,y+1),(x+1,y)]
guard . inRange (bounds cm) $ p
pure p
search :: ChitonMap -> Position -> Position -> (Int,[Position])
search cm start end = iter (M.singleton start (0,[start])) where
iter :: Map Position (Int,[Position]) -> (Int,[Position])
iter costmap
| costmap == newCostmap = costmap M.! end -- this gives a reversed path
| otherwise = iter newCostmap
where
newCostmap = M.unionWith min costmap newpaths
newpaths = M.unionsWith min $ do
(pos,(cost,path)) <- M.assocs costmap
n <- neighbors cm pos
pure $ M.singleton n (cost + cm ! n, n : path)
maxPoint :: Array Position a -> Position
maxPoint = snd . bounds
main :: IO ()
main = pure ()
main = do
cm <- readMap <$> readFile "data/chitons.txt"
let (cost,_) = search cm (0,0) (maxPoint cm)
print cost
module Main where
import Control.Monad
import Data.Array
import qualified Data.Map as M
import Data.Map (Map)
type Position = (Int,Int)
type ChitonMap = Array Position Int
readMap :: String -> ChitonMap
readMap s = arr where
ps = do
(rx,row) <- enumerate . lines $ s
(cx,col) <- enumerate row
pure $ ((rx,cx),read @Int [col])
enumerate = zip @Int [1..]
maxX = maximum . (map (fst . fst)) $ ps
maxY = maximum . (map (snd . fst)) $ ps
arr = array ((1,1),(maxX,maxY)) ps
extendMap :: ChitonMap -> ChitonMap
extendMap cm = result where
result = array newbounds [(p,valueAt p) | p <- range newbounds]
((1,1),(xMax,yMax)) = bounds cm
newbounds = ((1,1),(5*xMax,5*yMax))
valueAt (x,y)
| x > xMax = shift $ valueAt (x-xMax,y)
| y > yMax = shift $ valueAt (x,y-yMax)
| otherwise = cm ! (x,y)
shift 9 = 1
shift v = v+1
showMap :: ChitonMap -> String
showMap cm = unlines [ [head . show $ (cm ! (x,y)) | y <- [1..maxY]] | x <- [1..maxX]] where
((1,1),(maxX,maxY)) = bounds cm
neighbors :: Array Position a -> Position -> [Position]
neighbors cm (x,y) = do
p <- [(x-1,y),(x,y-1),(x,y+1),(x+1,y)]
guard . inRange (bounds cm) $ p
pure p
search :: ChitonMap -> Position -> Position -> Int
search cm start end = iter 0 (M.singleton start (0,0)) where
iter :: Int -> Map Position (Int,Int) -> Int
iter step costmap
| M.null newpaths = fst (costmap M.! end)-- this gives a reversed path
| otherwise = iter (step+1) newCostmap
where
newCostmap :: Map Position (Int,Int)
newCostmap = M.unionWith min costmap newpaths
newpaths = M.unionsWith min $ do
(pos,(cost,s)) <- M.assocs costmap
guard $ s == step
n <- neighbors cm pos
pure $ M.singleton n (cost + cm ! n, step+1)
maxPoint :: Array Position a -> Position
maxPoint = snd . bounds
main :: IO ()
main = pure ()
main = do
cm <- extendMap . readMap <$> readFile "data/chitons.txt"
let (mn,mx) = bounds cm
print $ search cm mn mx
1163751742
1381373672
2136511328
3694931569
7463417111
1319128137
1359912421
3125421639
1293138521
2311944581
\ No newline at end of file
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or sign in to comment