1
- {-# Language QuasiQuotes, TemplateHaskell, ImportQualifiedPost, LambdaCase, ImplicitParams, BangPatterns , DataKinds #-}
1
+ {-# Language QuasiQuotes, ConstraintKinds, TemplateHaskell, ImportQualifiedPost, LambdaCase, ImplicitParams, DataKinds #-}
2
2
{-|
3
3
Module : Main
4
4
Description : Day 22 solution
8
8
9
9
<https://adventofcode.com/2022/day/22>
10
10
11
+ This solution works by first exploring the input file and assigning a cube
12
+ location to each flattened location. The path is explored in terms of the cube
13
+ coordinates and then is converted back into input file coordinates at the end.
14
+
11
15
>>> :{
12
16
:main + " ...#
13
17
.#..
@@ -40,28 +44,41 @@ import Data.Map qualified as Map
40
44
import Data.Maybe (isJust )
41
45
import Data.Set (Set )
42
46
import Data.Set qualified as Set
47
+ import qualified Advent.AsmProg as cube
43
48
44
49
data D = DL | DR
45
50
46
51
stageTH
47
52
53
+ type HiVal = ? hiVal :: Int
54
+
48
55
-- |
49
56
-- >>> :main
50
57
-- 55267
51
58
main :: IO ()
52
59
main =
53
60
do (rawmap, path) <- [format |2022 22 (( |.|#)*!%n)*%n(%u|@D)*%n|]
61
+
62
+ -- figure out the side-length of the cube we're working with
63
+ -- so that we can handle both examples and regular inputs
54
64
let elts = countBy (`elem` " .#" ) (concat rawmap)
55
- let ? highVal = until (\ x -> 6 * x* x >= elts) (1 + ) 1 - 1
65
+ let ? hiVal = until (\ x -> 6 * x* x >= elts) (1 + ) 1 - 1
66
+
67
+ -- associate cube coordinates with all of the input file coordinates
56
68
let maze = explore (Set. fromList [c | (c, ' .' ) <- coordLines rawmap])
57
- (endLoc, endFacing) = foldl (applyCommand maze) (originLoc, 0 ) path
58
- Just (C y x) = onMaze maze endLoc
59
- endFacing' = fixFacing maze endLoc endFacing
60
- print (1000 * (y + 1 ) + 4 * (x + 1 ) + endFacing')
69
+
70
+ -- figure out the cube coordinate that our path ends on
71
+ let S endLoc endFacing = fixFacing maze (foldl (applyCommand maze) (S originLoc 0 ) path)
72
+
73
+ -- translate the cube coordinates back into flat coordinates
74
+ let C y x = maze Map. ! endLoc
75
+
76
+ -- compute the "password" from the end location
77
+ print (1000 * (y + 1 ) + 4 * (x + 1 ) + endFacing)
61
78
62
79
-- | Given the set of flat path coordinates compute the cube-coordinate
63
80
-- to flat coordinate map.
64
- explore :: ( ? highVal :: Int ) => Set Coord -> Map Loc Coord
81
+ explore :: HiVal => Set Coord -> Map Loc Coord
65
82
explore input = Map. fromList (dfsOn snd step (originLoc, Set. findMin input))
66
83
where
67
84
step (l, c) =
@@ -70,19 +87,24 @@ explore input = Map.fromList (dfsOn snd step (originLoc, Set.findMin input))
70
87
[(locUp l, above c) | above c `Set.member` input] ++
71
88
[(locDown l, below c) | below c `Set.member` input]
72
89
73
- applyCommand :: (? highVal :: Int ) => Map Loc Coord -> (Loc , Facing ) -> Either Int D -> (Loc , Facing )
74
- applyCommand maze (! here, ! dir) = \ case
75
- Left n -> (walkN maze n dir here, dir)
76
- Right t -> (here, turn t dir)
90
+ -- | A location on the cube and a direction
91
+ data S = S ! Loc ! Facing
92
+
93
+ -- | Apply a command to the state of the walker on the cube.
94
+ -- Each move is either forward a certain number or a turn.
95
+ applyCommand :: HiVal => Map Loc Coord -> S -> Either Int D -> S
96
+ applyCommand maze (S here dir) = \ case
97
+ Left n -> S (walkN maze n dir here) dir
98
+ Right t -> S here (turn t dir)
77
99
78
100
-- | Walk a number of steps in the given direction
79
- walkN :: ( ? highVal :: Int ) => Map Loc Coord -> Int -> Facing -> Loc -> Loc
101
+ walkN :: HiVal => Map Loc Coord -> Int -> Facing -> Loc -> Loc
80
102
walkN maze n dir here = last (takeWhile valid (take (n + 1 ) (iterate (move dir) here)))
81
103
where valid = isJust . onMaze maze
82
104
83
105
-- | Find the location in the input file corresponding to this
84
106
-- cube location if one exists.
85
- onMaze :: ( ? highVal :: Int ) => Map Loc Coord -> Loc -> Maybe Coord
107
+ onMaze :: HiVal => Map Loc Coord -> Loc -> Maybe Coord
86
108
onMaze maze loc = msum (map (`Map.lookup` maze) (take 4 (iterate locRotate loc)))
87
109
88
110
-- | Symmetric group S4 corresponds to the symmetries of a cube.
@@ -97,42 +119,45 @@ rotZ = mkPermutation ([2,3,1,0]!!)
97
119
data Loc = Loc { locFace :: S4 , locCoord :: Coord }
98
120
deriving (Show , Ord , Eq )
99
121
122
+ -- | Initial location on the top-left or a face.
100
123
originLoc :: Loc
101
124
originLoc = Loc mempty origin
102
125
103
- locRight , locLeft , locUp , locDown , locRotate :: ( ? highVal :: Int ) => Loc -> Loc
126
+ locRight , locLeft , locUp , locDown , locRotate :: HiVal => Loc -> Loc
104
127
locRight (Loc p (C y x))
105
- | x < ? highVal = Loc p (C y (x + 1 ))
128
+ | x < ? hiVal = Loc p (C y (x + 1 ))
106
129
| otherwise = Loc (p <> invert rotY) (C y 0 )
107
130
108
131
locLeft (Loc p (C y x))
109
132
| 0 < x = Loc p (C y (x - 1 ))
110
- | otherwise = Loc (p <> rotY) (C y ? highVal )
133
+ | otherwise = Loc (p <> rotY) (C y ? hiVal )
111
134
112
135
locDown (Loc p (C y x))
113
- | y < ? highVal = Loc p (C (y + 1 ) x)
136
+ | y < ? hiVal = Loc p (C (y + 1 ) x)
114
137
| otherwise = Loc (p <> rotX) (C 0 x)
115
138
116
139
locUp (Loc p (C y x))
117
140
| 0 < y = Loc p (C (y - 1 ) x)
118
- | otherwise = Loc (p <> invert rotX) (C ? highVal x)
141
+ | otherwise = Loc (p <> invert rotX) (C ? hiVal x)
119
142
120
- locRotate (Loc p (C y x)) = Loc (p <> rotZ) (C x (? highVal - y))
143
+ -- Rotate the representation of the current location 90-degrees
144
+ -- clockwise in order to put it onto a symmetric cube-face.
145
+ locRotate (Loc p (C y x)) = Loc (p <> rotZ) (C x (? hiVal - y))
121
146
122
147
-- | Rotate the facing until we're on the cube face as it
123
148
-- is oriented on the input text.
124
- fixFacing :: ( ? highVal :: Int ) => Map Loc Coord -> Loc -> Facing -> Facing
125
- fixFacing maze loc n
126
- | Map. member loc maze = n
127
- | otherwise = fixFacing maze (locRotate loc) (turn DR n)
149
+ fixFacing :: HiVal => Map Loc Coord -> S -> S
150
+ fixFacing maze ( S loc n)
151
+ | Map. member loc maze = S loc n
152
+ | otherwise = fixFacing maze (S ( locRotate loc) (turn DR n) )
128
153
129
154
type Facing = Int
130
155
131
156
turn :: D -> Facing -> Facing
132
157
turn DL x = (x - 1 ) `mod` 4
133
158
turn DR x = (x + 1 ) `mod` 4
134
159
135
- move :: ( ? highVal :: Int ) => Facing -> Loc -> Loc
160
+ move :: HiVal => Facing -> Loc -> Loc
136
161
move 0 = locRight
137
162
move 1 = locDown
138
163
move 2 = locLeft
0 commit comments