538fba7063
With some approximation
130 lines
4.5 KiB
Haskell
Executable file
130 lines
4.5 KiB
Haskell
Executable file
#! /usr/bin/env -S"ANSWER=42" nix-shell
|
|
#! nix-shell -p ghcid
|
|
#! nix-shell -p "haskellPackages.ghcWithPackages (p: with p; [pretty-simple linear])"
|
|
#! nix-shell -i "ghcid -c 'ghci' -T main"
|
|
|
|
{-# OPTIONS_GHC -Wall -Wincomplete-uni-patterns #-}
|
|
{-# OPTIONS_GHC -Wno-unused-top-binds -Wno-unused-imports -Wno-type-defaults #-}
|
|
{-# OPTIONS_GHC -Wno-unused-matches #-}
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
{-# LANGUAGE DeriveAnyClass #-}
|
|
|
|
import Debug.Trace (trace, traceShowId, traceShow)
|
|
import Text.Pretty.Simple
|
|
import Control.Monad
|
|
import Linear.V2
|
|
import Data.Monoid
|
|
|
|
exampleData :: [ String ]
|
|
exampleData =
|
|
[ "F10"
|
|
, "N3"
|
|
, "F7"
|
|
, "R90"
|
|
, "F11"
|
|
]
|
|
|
|
|
|
|
|
data Ship = Ship { position :: V2 Double, orientation :: V2 Double }
|
|
deriving (Show, Eq, Ord)
|
|
|
|
-- At first, ship is at (0,0) facing East
|
|
ship0 :: Ship
|
|
ship0 = Ship (pure 0) (V2 1 0)
|
|
|
|
-- At first, ship is at (0,0) facing East
|
|
ship1 :: Ship
|
|
ship1 = Ship (pure 0) (V2 10 1)
|
|
|
|
-- instance Semigroup Ship
|
|
-- where
|
|
-- (<>) s1 s2 = Ship (getSum <$> ((Sum <$> (position s1)) <> (Sum <$> (position s2))))
|
|
-- (getSum <$> ((Sum <$> (orientation s1)) <> (Sum <$> (orientation s2))))
|
|
--
|
|
-- instance Monoid Ship
|
|
-- where
|
|
-- mempty = Ship (pure 0) (pure 0)
|
|
|
|
data Instruction = InsMoveForward !Double
|
|
| InsMoveNorth !Double
|
|
| InsMoveSouth !Double
|
|
| InsMoveEast !Double
|
|
| InsMoveWest !Double
|
|
| InsTurnL !Double
|
|
| InsTurnR !Double
|
|
deriving (Show, Eq, Ord)
|
|
|
|
parseIns :: String -> Instruction
|
|
-- Action N means to move north by the given value.
|
|
parseIns ('N':x) = InsMoveNorth (read x)
|
|
-- Action S means to move south by the given value.
|
|
parseIns ('S':x) = InsMoveSouth (read x)
|
|
-- Action E means to move east by the given value.
|
|
parseIns ('E':x) = InsMoveEast (read x)
|
|
-- Action W means to move west by the given value.
|
|
parseIns ('W':x) = InsMoveWest (read x)
|
|
-- Action L means to turn left the given number of degrees.
|
|
parseIns ('L':x) = InsTurnL (read x)
|
|
-- Action R means to turn right the given number of degrees.
|
|
parseIns ('R':x) = InsTurnR (read x)
|
|
-- Action F means to move forward by the given value in the direction the ship is currently facing.
|
|
parseIns ('F':x) = InsMoveForward (read x)
|
|
parseIns e = trace ("Unknown instruction: "<>show e) undefined
|
|
|
|
|
|
-- 2*PI rad = 360 deg
|
|
-- 1 rad = 180/PI deg
|
|
-- PI/180 rad = 1 deg
|
|
|
|
runIns1 :: Ship -> Instruction -> Ship
|
|
runIns1 s (InsMoveForward n) = s { position = (position s) + (pure n) * (orientation s) }
|
|
runIns1 s (InsMoveNorth n) = s { position = (position s) + (pure n) * V2 0 1 }
|
|
runIns1 s (InsMoveSouth n) = s { position = (position s) + (pure n) * V2 0 (-1) }
|
|
runIns1 s (InsMoveEast n) = s { position = (position s) + (pure n) * V2 1 0 }
|
|
runIns1 s (InsMoveWest n) = s { position = (position s) + (pure n) * V2 (-1) 0 }
|
|
runIns1 s (InsTurnL n) = s { orientation = angle ((unangle (orientation s)) + n * pi / 180) }
|
|
runIns1 s (InsTurnR n) = s { orientation = angle ((unangle (orientation s)) - n * pi / 180) }
|
|
|
|
manhattanV2 :: (Num a) => V2 a -> a
|
|
manhattanV2 (V2 x y) = (abs x) + (abs y)
|
|
|
|
solvePart1 :: [String] -> Double
|
|
solvePart1 = manhattanV2 . position . foldl runIns1 ship0 . map parseIns
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
runIns2 :: Ship -> Instruction -> Ship
|
|
runIns2 s (InsMoveForward n) = s { position = (position s) + (pure n) * (orientation s) }
|
|
runIns2 s (InsMoveNorth n) = s { orientation = (orientation s) + V2 0 n }
|
|
runIns2 s (InsMoveSouth n) = s { orientation = (orientation s) + V2 0 (-n) }
|
|
runIns2 s (InsMoveEast n) = s { orientation = (orientation s) + V2 n 0 }
|
|
runIns2 s (InsMoveWest n) = s { orientation = (orientation s) + V2 (-n) 0 }
|
|
runIns2 s (InsTurnL n) = s { orientation = rotV2By (orientation s) n }
|
|
runIns2 s (InsTurnR n) = s { orientation = rotV2By (orientation s) (-n) }
|
|
|
|
rotV2By :: (Num a, Floating a) => V2 a -> a -> V2 a
|
|
rotV2By (V2 x1 y1) n = V2 x y
|
|
where
|
|
x = cos a * x1 - sin a * y1
|
|
y = sin a * x1 + cos a * y1
|
|
a = n * pi / 180
|
|
|
|
solvePart2 :: [String] -> Double
|
|
solvePart2 = manhattanV2 . position . foldl runIns2 ship1 . map parseIns
|
|
|
|
main :: IO ()
|
|
main = do
|
|
input <- lines <$> readFile "day12/input"
|
|
putStrLn ":: Tests"
|
|
pPrint exampleData
|
|
pPrint $ map parseIns exampleData
|
|
pPrint $ angle (90 * pi / 180)
|
|
putStrLn ":: Day 12 - Part 1"
|
|
pPrint $ solvePart1 exampleData
|
|
pPrint $ solvePart1 input
|
|
putStrLn ":: Day 12 - Part 2"
|
|
pPrint $ solvePart2 exampleData
|
|
pPrint $ solvePart2 input
|