{-# Language QuasiQuotes, TemplateHaskell #-}
module Main where
import Advent (format, partialSums, stageTH)
import Advent.Coord (Coord(..), north, east, south, west)
data D = Dn | Dne | Dnw | Dse | Dsw | Ds deriving Int -> D -> ShowS
[D] -> ShowS
D -> String
(Int -> D -> ShowS) -> (D -> String) -> ([D] -> ShowS) -> Show D
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> D -> ShowS
showsPrec :: Int -> D -> ShowS
$cshow :: D -> String
show :: D -> String
$cshowList :: [D] -> ShowS
showList :: [D] -> ShowS
Show
stageTH
main :: IO ()
IO ()
main =
do [D]
input <- [format|2017 11 @D&,%n|]
let distances :: [Int]
distances = (Coord -> Int) -> [Coord] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Coord -> Int
distance ([Coord] -> [Coord]
forall a. Num a => [a] -> [a]
partialSums ((D -> Coord) -> [D] -> [Coord]
forall a b. (a -> b) -> [a] -> [b]
map D -> Coord
translate [D]
input))
Int -> IO ()
forall a. Show a => a -> IO ()
print ([Int] -> Int
forall a. HasCallStack => [a] -> a
last [Int]
distances)
Int -> IO ()
forall a. Show a => a -> IO ()
print ([Int] -> Int
forall a. Ord a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum [Int]
distances)
distance :: Coord -> Int
distance :: Coord -> Int
distance (C Int
y Int
x) = [Int] -> Int
forall a. Ord a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ((Int -> Int) -> [Int] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Int
forall a. Num a => a -> a
abs [Int
x,Int
y,Int
xInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
y])
translate :: D -> Coord
translate :: D -> Coord
translate D
Dne = Coord
north Coord -> Coord -> Coord
forall a. Num a => a -> a -> a
+ Coord
east
translate D
Dn = Coord
north
translate D
Dnw = Coord
west
translate D
Dsw = Coord
south Coord -> Coord -> Coord
forall a. Num a => a -> a -> a
+ Coord
west
translate D
Ds = Coord
south
translate D
Dse = Coord
east