91 lines
3.2 KiB
Haskell
91 lines
3.2 KiB
Haskell
|
#! /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)
|
||
|
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 Int, 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)
|
||
|
|
||
|
-- 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 !Int
|
||
|
| InsMoveNorth !Int
|
||
|
| InsMoveSouth !Int
|
||
|
| InsMoveEast !Int
|
||
|
| InsMoveWest !Int
|
||
|
| InsTurnL !Int
|
||
|
| InsTurnR !Int
|
||
|
deriving (Show, Eq, Ord)
|
||
|
|
||
|
parseIns :: String -> Instruction
|
||
|
-- Action N means to move north by the given value.
|
||
|
parseIns ('N':x) = InsMoveNorth (read x :: Int)
|
||
|
-- Action S means to move south by the given value.
|
||
|
parseIns ('S':x) = InsMoveSouth (read x :: Int)
|
||
|
-- Action E means to move east by the given value.
|
||
|
parseIns ('E':x) = InsMoveEast (read x :: Int)
|
||
|
-- Action W means to move west by the given value.
|
||
|
parseIns ('W':x) = InsMoveWest (read x :: Int)
|
||
|
-- Action L means to turn left the given number of degrees.
|
||
|
parseIns ('L':x) = InsTurnL (read x :: Int)
|
||
|
-- Action R means to turn right the given number of degrees.
|
||
|
parseIns ('R':x) = InsTurnR (read x :: Int)
|
||
|
-- 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 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
|
||
|
|
||
|
main :: IO ()
|
||
|
main = do
|
||
|
input <- lines <$> readFile "day12/input"
|
||
|
putStrLn ":: Tests"
|
||
|
pPrint exampleData
|
||
|
pPrint $ map parseIns exampleData
|
||
|
putStrLn ":: Day 12 - Part 1"
|
||
|
pPrint $ solvePart1 exampleData
|