Part 1
This commit is contained in:
parent
3997886348
commit
c15d4ee29d
1 changed files with 36 additions and 26 deletions
|
@ -9,7 +9,7 @@
|
|||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
|
||||
import Debug.Trace (trace)
|
||||
import Debug.Trace (trace, traceShowId, traceShow)
|
||||
import Text.Pretty.Simple
|
||||
import Control.Monad
|
||||
import Linear.V2
|
||||
|
@ -26,7 +26,7 @@ exampleData =
|
|||
|
||||
|
||||
|
||||
data Ship = Ship { position :: V2 Int, orientation :: V2 Double }
|
||||
data Ship = Ship { position :: V2 Double, orientation :: V2 Double }
|
||||
deriving (Show, Eq, Ord)
|
||||
|
||||
-- At first, ship is at (0,0) facing East
|
||||
|
@ -42,43 +42,51 @@ ship0 = Ship (pure 0) (V2 1 0)
|
|||
-- where
|
||||
-- mempty = Ship (pure 0) (pure 0)
|
||||
|
||||
data Instruction = InsMoveForward !Int
|
||||
| InsMoveNorth !Int
|
||||
| InsMoveSouth !Int
|
||||
| InsMoveEast !Int
|
||||
| InsMoveWest !Int
|
||||
| InsTurnL !Int
|
||||
| InsTurnR !Int
|
||||
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 :: Int)
|
||||
parseIns ('N':x) = InsMoveNorth (read x)
|
||||
-- Action S means to move south by the given value.
|
||||
parseIns ('S':x) = InsMoveSouth (read x :: Int)
|
||||
parseIns ('S':x) = InsMoveSouth (read x)
|
||||
-- Action E means to move east by the given value.
|
||||
parseIns ('E':x) = InsMoveEast (read x :: Int)
|
||||
parseIns ('E':x) = InsMoveEast (read x)
|
||||
-- Action W means to move west by the given value.
|
||||
parseIns ('W':x) = InsMoveWest (read x :: Int)
|
||||
parseIns ('W':x) = InsMoveWest (read x)
|
||||
-- Action L means to turn left the given number of degrees.
|
||||
parseIns ('L':x) = InsTurnL (read x :: Int)
|
||||
parseIns ('L':x) = InsTurnL (read x)
|
||||
-- Action R means to turn right the given number of degrees.
|
||||
parseIns ('R':x) = InsTurnR (read x :: Int)
|
||||
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 :: Int)
|
||||
parseIns ('F':x) = InsMoveForward (read x)
|
||||
parseIns e = trace ("Unknown instruction: "<>show e) undefined
|
||||
|
||||
runIns :: Instruction -> Ship -> Ship
|
||||
runIns (InsMoveForward n) s = s { position = (position s) + fmap truncate ((pure $ fromIntegral n) * (orientation s)) }
|
||||
runIns (InsMoveNorth n) s = s { position = (position s) + (pure n) * V2 0 (-1) }
|
||||
runIns (InsMoveSouth n) s = s { position = (position s) + (pure n) * V2 0 1 }
|
||||
runIns (InsMoveEast n) s = s { position = (position s) + (pure n) * V2 1 0 }
|
||||
runIns (InsMoveWest n) s = s { position = (position s) + (pure n) * V2 (-1) 0 }
|
||||
runIns (InsTurnL n) s = s { orientation = (orientation s) + angle (fromIntegral n :: Double) }
|
||||
runIns (InsTurnR n) s = s { orientation = (orientation s) - angle (fromIntegral n :: Double) }
|
||||
|
||||
solvePart1 :: [String] -> Ship
|
||||
solvePart1 = foldr runIns ship0 . map parseIns
|
||||
-- 2*PI rad = 360 deg
|
||||
-- 1 rad = 180/PI deg
|
||||
-- PI/180 rad = 1 deg
|
||||
|
||||
runIns :: Ship -> Instruction -> Ship
|
||||
runIns s (InsMoveForward n) = s { position = (position s) + (pure n) * (orientation s) }
|
||||
runIns s (InsMoveNorth n) = s { position = (position s) + (pure n) * V2 0 1 }
|
||||
runIns s (InsMoveSouth n) = s { position = (position s) + (pure n) * V2 0 (-1) }
|
||||
runIns s (InsMoveEast n) = s { position = (position s) + (pure n) * V2 1 0 }
|
||||
runIns s (InsMoveWest n) = s { position = (position s) + (pure n) * V2 (-1) 0 }
|
||||
runIns s (InsTurnL n) = s { orientation = angle ((unangle (orientation s)) + n * pi / 180) }
|
||||
runIns 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 runIns ship0 . map parseIns
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
|
@ -86,5 +94,7 @@ main = do
|
|||
putStrLn ":: Tests"
|
||||
pPrint exampleData
|
||||
pPrint $ map parseIns exampleData
|
||||
pPrint $ angle (90 * pi / 180)
|
||||
putStrLn ":: Day 12 - Part 1"
|
||||
pPrint $ solvePart1 exampleData
|
||||
pPrint $ solvePart1 input
|
||||
|
|
Loading…
Reference in a new issue