Skip to content

Commit

Permalink
faster
Browse files Browse the repository at this point in the history
  • Loading branch information
glguy committed Dec 19, 2023
1 parent 9d81895 commit 14e4194
Showing 1 changed file with 20 additions and 6 deletions.
26 changes: 20 additions & 6 deletions solutions/src/2023/17.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,11 @@ Maintainer : emertens@gmail.com
<https://adventofcode.com/2023/day/17>
Shortest-path graph search where the graph states are the triple of
a location, direction, and distance traveled in that direction.
a location, direction.
Distance traveled doesn't need to be stored because all of the distances
that can be traveled from a starting location are added to the work
queue at the same time for each starting point.
>>> :{
:main +
Expand Down Expand Up @@ -48,7 +52,7 @@ a location, direction, and distance traveled in that direction.
module Main where

import Advent (getInputArray, arrIx)
import Advent.Coord (east, south, turnLeft, turnRight, scaleCoord, Coord)
import Advent.Coord (east, south, turnLeft, turnRight, Coord)
import Advent.Search (astarN, AStep(..))
import Data.Array.Unboxed (amap, bounds, UArray)
import Data.Char (digitToInt)
Expand Down Expand Up @@ -79,10 +83,20 @@ data S = S !Coord !Coord -- ^ location, direction
step :: Int -> Int -> UArray Coord Int -> S -> [AStep S]
step lo hi input (S here dir) =
[ AStep {
astepNext = S (scaleCoord n dir' + here) dir',
astepNext = S here' dir',
astepCost = cost,
astepHeuristic = 0}
| dir' <- [turnLeft dir, turnRight dir]
, n <- [lo .. hi]
, cost <- sum <$> traverse (arrIx input) [here + scaleCoord d dir' | d <- [1..n] ]
| dir' <- [turnLeft dir, turnRight dir]
, (here', cost) <- take (hi - lo + 1) (drop (lo - 1) (costs input dir' here))
]

-- lazy lists of the locations and costs to get there in order of distance
-- starting at 1 away
costs :: UArray Coord Int -> Coord -> Coord -> [(Coord, Int)]
costs input v = go 0
where
go acc l =
do let l' = l + v
c <- arrIx input l'
let acc' = acc + c
(l', acc') : go acc' l'

0 comments on commit 14e4194

Please sign in to comment.