6
6
module Day18 (part1 , part1' , part2 , part2' ) where
7
7
8
8
import Common (readEntire )
9
- import Data.List.NonEmpty (NonEmpty ((:|) ))
10
- import Data.List.NonEmpty qualified as NonEmpty (cons , toList )
11
- import Data.Set (Set )
12
- import Data.Set qualified as Set (empty , fromList , insert , member , notMember )
9
+ import Control.Monad (ap , join , liftM2 )
10
+ import Control.Monad.Loops (firstM )
11
+ import Control.Monad.ST (runST )
12
+ import Data.Function (on )
13
+ import Data.Functor (($>) )
14
+ import Data.IntSet qualified as IntSet (empty , fromList , insert , notMember )
15
+ import Data.List (scanl' )
16
+ import Data.Maybe (listToMaybe )
13
17
import Data.Text (Text )
14
18
import Data.Text qualified as T (lines , stripPrefix )
15
19
import Data.Text.Read (Reader )
16
20
import Data.Text.Read qualified as T (decimal )
21
+ import Data.Vector.Unboxed.Mutable qualified as MV (generate , length , read , write )
17
22
18
23
coord :: (Integral a ) => Reader (a , a )
19
24
coord input = do
@@ -28,39 +33,54 @@ part1 = part1' 70 1024
28
33
part1' :: Int -> Int -> Text -> Either String Int
29
34
part1' size n input = do
30
35
coords <- mapM (readEntire coord) . take n $ T. lines input
31
- case go size $ Set. fromList coords of
32
- Just path -> Right $ length path - 1
33
- Nothing -> Left " no solution"
34
-
35
- go :: Int -> Set (Int , Int ) -> Maybe (NonEmpty (Int , Int ))
36
- go size visited = go' visited [(0 , 0 ) :| [] ] []
36
+ maybe (Left " no solution" ) Right $ go (IntSet. fromList $ 0 : map index coords) [((0 , 0 ), 0 )] []
37
37
where
38
- go' visited' (path @ (pos @ ( x, y) :| _) : queue1) queue2
39
- | pos `Set.member` visited' = go' visited' queue1 queue2
40
- | pos == ( size, size) = Just path
41
- | otherwise =
42
- go' ( Set. insert pos visited') queue1 $
43
- [ NonEmpty. cons pos' path
44
- | pos'@ (x', y') <- [(x - 1 , y), (x, y - 1 ), (x, y + 1 ), (x + 1 , y)],
45
- 0 <= x' && x' <= size && 0 <= y' && y' <= size
46
- ]
47
- ++ queue2
48
- go' _ _ [] = Nothing
49
- go' visited' [] queue2 = go' visited' (reverse queue2 ) []
38
+ index ( x, y) = x * (size + 1 ) + y
39
+ go visited (((x, y), t) : queue) queue'
40
+ | x == size && y == size = Just t
41
+ | otherwise = go (foldl' ( flip $ IntSet. insert . index) visited next) queue $ map (,t + 1 ) next ++ queue'
42
+ where
43
+ next =
44
+ [ pos'
45
+ | pos' @ (x', y') <- [(x - 1 , y), (x, y - 1 ), (x, y + 1 ), (x + 1 , y)],
46
+ 0 <= x' && x' <= size && 0 <= y' && y' <= size && index pos' `IntSet.notMember` visited
47
+ ]
48
+ go _ _ [] = Nothing
49
+ go visited [] queue = go visited (reverse queue ) []
50
50
51
51
part2 :: Text -> Either String (Int , Int )
52
52
part2 = part2' 70
53
53
54
54
part2' :: Int -> Text -> Either String (Int , Int )
55
- part2' size input = mapM (readEntire coord) (T. lines input) >>= go' Set. empty
55
+ part2' size input = do
56
+ candidates <-
57
+ reverse
58
+ . filter (uncurry $ IntSet. notMember . index)
59
+ . (zip `ap` scanl' (flip $ IntSet. insert . index) IntSet. empty)
60
+ <$> mapM (readEntire coord) (T. lines input)
61
+ let obstacles0 = maybe IntSet. empty (uncurry $ IntSet. insert . index) $ listToMaybe candidates
62
+ maybe (Left " No solution" ) (Right . fst ) $ runST $ do
63
+ acc <- MV. generate (join (*) $ size + 1 ) id
64
+ let root key = MV. read acc key >>= root' key
65
+ root' key value
66
+ | key == value = pure value
67
+ | otherwise = do
68
+ value' <- root value
69
+ MV. write acc key value' $> value'
70
+ union i j = join $ MV. write acc <$> root i <*> root j
71
+ sequence_
72
+ [ (union `on` index) pos pos'
73
+ | pos@ (x, y) <- join (liftM2 (,)) [0 .. size],
74
+ index pos `IntSet.notMember` obstacles0,
75
+ pos' <- [(x, y + 1 ) | y < size] ++ [(x + 1 , y) | x < size],
76
+ index pos' `IntSet.notMember` obstacles0
77
+ ]
78
+ flip firstM candidates $ \ (pos@ (x, y), obstacles) -> do
79
+ sequence_
80
+ [ (union `on` index) pos pos'
81
+ | pos' <- [(x - 1 , y) | x > 0 ] ++ [(x, y - 1 ) | y > 0 ] ++ [(x, y + 1 ) | y < size] ++ [(x + 1 , y) | x < size],
82
+ index pos' `IntSet.notMember` obstacles
83
+ ]
84
+ (==) <$> root 0 <*> root (MV. length acc - 1 )
56
85
where
57
- go' visited (candidate : rest) =
58
- case go size visited' of
59
- Just path ->
60
- let path' = Set. fromList $ NonEmpty. toList path
61
- (skip, rest') = span (`Set.notMember` path') rest
62
- in go' (visited' <> Set. fromList skip) rest'
63
- Nothing -> Right candidate
64
- where
65
- visited' = Set. insert candidate visited
66
- go' _ _ = Left " no solution"
86
+ index (x, y) = x * (size + 1 ) + y
0 commit comments