aboutsummaryrefslogtreecommitdiff
path: root/2020/12a.hs
diff options
context:
space:
mode:
authorAria <me@aria.rip>2023-01-02 21:58:56 +0000
committerAria <me@aria.rip>2023-01-02 21:58:56 +0000
commit5eb58ad076f2cd435b11b140820da224b60b73d5 (patch)
tree2a67939595fbf993ff04f69b9cd3f0aa20827d96 /2020/12a.hs
initial commit
Diffstat (limited to '2020/12a.hs')
-rw-r--r--2020/12a.hs62
1 files changed, 62 insertions, 0 deletions
diff --git a/2020/12a.hs b/2020/12a.hs
new file mode 100644
index 0000000..a147884
--- /dev/null
+++ b/2020/12a.hs
@@ -0,0 +1,62 @@
+module Day12A where
+
+import System.Environment (getArgs)
+
+data Instruction = North Int | East Int |
+ South Int | West Int |
+ TLeft Int | TRight Int |
+ Forward Int
+ deriving (Eq, Show, Ord);
+
+-- ((x, y), direction)
+type State = ((Int, Int), Int);
+
+initialState :: State;
+initialState = ((0, 0), 90);
+
+directionToDisplacement :: Int -> (Int, Int)
+directionToDisplacement 0 = (0, 1)
+directionToDisplacement 90 = (1, 0)
+directionToDisplacement 180 = (0, -1)
+directionToDisplacement 270 = (-1, 0)
+directionToDisplacement _ = error "Invalid direction"
+
+readInstructions :: String -> [Instruction]
+readInstructions = map readInstruction . lines
+ where readInstruction ('N':xs) = North $ read xs
+ readInstruction ('S':xs) = South $ read xs
+ readInstruction ('E':xs) = East $ read xs
+ readInstruction ('W':xs) = West $ read xs
+ readInstruction ('L':xs) = TLeft $ read xs
+ readInstruction ('R':xs) = TRight $ read xs
+ readInstruction ('F':xs) = Forward $ read xs
+ readInstruction _ = error "Invalid instruction"
+
+doInstruction :: Instruction -> State -> State
+doInstruction (North r) ((x, y), d) = ((x, y + r), d)
+doInstruction (South r) ((x, y), d) = ((x, y - r), d)
+doInstruction (East r) ((x, y), d) = ((x + r, y), d)
+doInstruction (West r) ((x, y), d) = ((x - r, y), d)
+doInstruction (TLeft r) ((x, y), d) = ((x, y), (d - r) `mod` 360)
+doInstruction (TRight r) ((x, y), d) = ((x, y), (d + r) `mod` 360)
+doInstruction (Forward r) ((x, y), d) = ((x + (x' * r), y + (y' * r)), d)
+ where (x', y') = directionToDisplacement d
+
+instructionsFromFile :: String -> IO [Instruction]
+instructionsFromFile s = do
+ contents <- readFile s;
+ return $ readInstructions contents;
+
+main :: IO ()
+main = do
+ args <- getArgs;
+ is <- instructionsFromFile (head args);
+
+ let final = foldl (flip doInstruction) initialState is;
+ putStrLn $ "Final State: " ++ show final;
+
+ let ((x, y), _) = final;
+ let dist = abs x + abs y;
+ putStrLn $ "Distance: " ++ show dist;
+
+ return ();