We start with some imports obviously:
{-# LANGUAGE LambdaCase #-}
import qualified Data.Set as SOnce we have those in place, begin by parsing the input; the input is of the form:
R24, L45, CNN ...
Where C is a letter, NN form a
natural number. First we normalize the input by appending a “,” to
the end. We then use words to split on spaces, now
each element is of the form CNN,. Using
init we can drop the trailing comma, and finally,
call extract to parse C and
NN separately.
parse :: String -> [(Char, Int)]
parse input = map (extract . init) $ words normalized
where normalized = input ++ ","
extract (d:rest) = (d, read rest)Next, we define a list of axes, the +x axis is defined as (1, 0) and so on:
axis :: [(Int, Int)]
axis = [(0, 1), (1, 0), (0, -1), (-1, 0)]And finally, the first bit of interesting computation; given a direction, we apply a move to the right or left. Each face is represented by an integer (0 being North, 1 being East etc.), Turning right adds one; and turing left subtracts one, the modulo makes the computation cyclic:
dir :: Int -> Char -> Int
dir face = \case
'R' -> (face + 1) `mod` 4
'L' -> (face - 1) `mod` 4Now, given a position, and a movement; we can compute the new
position like so; first compute the new face to look at by
turning, next, determine the axis that we would move along. If we
are moving along the +x axis, (dx, dy) is set to (1, 0). Thus the
new position is given by movind l * dx along the
x-axis, and l * dy along the y-axis (which would be
zero if dy is zero).
move (face, x, y) (d, l) = (nf, x + l * dx, y + l * dy)
where nf = dir face d
(dx, dy) = axis !! nfThe problem requires us to compute the Manhattan distance of the destination location; which is given by:
mag (_, x, y) = abs x + abs yThus, the solution to part 1 is given by p1; apply
the move function starting at (0, 0, 0); and applying
all the moves in the input. Finally compute the Manhattan distance
of the destination from the origin.
p1 :: [(Char, Int)] -> Int
p1 n = mag $ foldl' move (0, 0, 0) nIn the second part, we are tasked with finding the first point that we cross over. This requires us to first enumerate all the points we have visited by making each move.
This range function is a helper to enumerate all
points between two integers:
range :: Int -> Int -> [Int]
range a b
| a <= b = [a .. b]
| otherwise = [a, a - 1 .. b]The first point we cross over will then be the first duplicate
element in the list of points we visit, firstDup uses
Data.Set to determine the first duplicate point from
a sequence:
firstDup :: Ord a => [a] -> a
firstDup xs = go S.empty xs
where
go seen (x : xs)
| x `S.member` seen = x
| otherwise = go (S.insert x seen) xsThus, the solution to the second part is given by
p2. First, pts is calculated as all the
final locations after each move. We then run through these
pairwise and calculate all the points in between. Finally, we
determine the magnitude of the first point we visit twice.
p2 :: [(Char, Int)] -> Int
p2 n = mag $ firstDup coords
where
pts = scanl move (0, 0, 0) n
pairs = zip pts (tail pts)
coords =
[ (0, x, y)
| ((_, x1, y1), (_, x2, y2)) <- pairs,
x <- range x1 x2,
y <- range y1 y2,
(x, y) /= (x1, y1)
]Finally the main function is defined like so:
input = "R8, R4, R4, R8"
main = do
let f = parse input
print $ p1 f
print $ p2 f