{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_HADDOCK ignore-exports #-}
module Day11 (day11a, day11b, Chart(..), chart) where
import Data.Char (toUpper)
import Data.List (foldl', scanl')
data Step = N | NE | SE | S | SW | NW deriving Read
data Pos = Pos
{ x :: !Int
, y :: !Int
}
data Chart = Chart
{ bounds :: ((Int, Int), (Int, Int))
, maxDistance :: Int
, path :: [((Int, Int), Int)]
}
parse :: String -> [Step]
parse s = read $ '[' : map toUpper s ++ "]"
step :: Pos -> Step -> Pos
step Pos {..} N = Pos (x + 1) (y + 1)
step Pos {..} NE = Pos (x + 1) y
step Pos {..} SE = Pos x (y - 1)
step Pos {..} S = Pos (x - 1) (y - 1)
step Pos {..} SW = Pos (x - 1) y
step Pos {..} NW = Pos x (y + 1)
walk :: Pos -> Int
walk Pos {..} = (abs x + abs y + abs (x - y)) `div` 2
day11a :: String -> Int
day11a = walk . foldl' step (Pos 0 0) . parse
day11b :: String -> Int
day11b = maximum . map walk . scanl' step (Pos 0 0) . parse
chart :: String -> Chart
chart input = Chart {..} where
positions = scanl' step (Pos 0 0) $ parse input
points = [(x - y, x + y) | Pos {..} <- positions]
distances = map walk positions
bounds =
((minimum $ map fst points, minimum $ map snd points),
(maximum $ map fst points, maximum $ map snd points))
maxDistance = maximum distances
path = zip points distances