summaryrefslogtreecommitdiff
path: root/2019/11.hs
diff options
context:
space:
mode:
authorTom Smeding <tom.smeding@gmail.com>2019-12-11 14:45:54 +0100
committerTom Smeding <tom.smeding@gmail.com>2019-12-11 14:46:29 +0100
commitf5737de23a443b4a6ca47e98a0688f668a96d72e (patch)
tree0eab00127ba5f67318eea9b98cea7ae5a10a96dd /2019/11.hs
parent1405a7fe6ce05a75bb36bcee3c7d19cc296a6de0 (diff)
Day 11
Diffstat (limited to '2019/11.hs')
-rw-r--r--2019/11.hs51
1 files changed, 51 insertions, 0 deletions
diff --git a/2019/11.hs b/2019/11.hs
new file mode 100644
index 0000000..9fd158c
--- /dev/null
+++ b/2019/11.hs
@@ -0,0 +1,51 @@
+module Main where
+
+import Control.Monad
+import qualified Data.Map.Strict as Map
+import Data.Maybe
+
+import Input
+import IntCode
+
+
+type Pos = (Int, Int)
+newtype Dir = Dir Pos deriving (Show)
+data State = State Pos Dir deriving (Show)
+
+moveForward :: State -> State
+moveForward (State (x, y) dir@(Dir (dx, dy))) = State (x + dx, y + dy) dir
+
+turn :: Integer -> State -> State
+turn 0 (State pos (Dir (dx, dy))) = State pos (Dir (-dy, dx))
+turn 1 (State pos (Dir (dx, dy))) = State pos (Dir (dy, -dx))
+turn _ _ = undefined
+
+main :: IO ()
+main = do
+ prog <- parse . head <$> getInput 11
+
+ let looper mcont [clr, dir] bd state@(State pos _) =
+ let state'@(State pos' _) = moveForward (turn dir state)
+ bd' = Map.insert pos clr bd
+ inp = fromMaybe 0 (Map.lookup pos' bd)
+ in case mcont of
+ Just cont -> case runContinue cont [inp] of
+ Left (cont', out) -> looper (Just cont') out bd' state'
+ Right (_, out) -> looper Nothing out bd' state'
+ Nothing -> bd'
+ looper _ _ _ _ = undefined
+
+ initState = (State (0, 0) (Dir (0, 1)))
+ paint start = case runInterruptible prog [start] of
+ Left (cont, out) -> looper (Just cont) out Map.empty initState
+ Right (_, out) -> looper Nothing out Map.empty initState
+
+ let printBD bd =
+ let (minx, maxx) = let xvals = map fst (Map.keys bd) in (minimum (0:xvals), maximum (0:xvals))
+ (miny, maxy) = let yvals = map snd (Map.keys bd) in (minimum (0:yvals), maximum (0:yvals))
+ in forM_ [maxy,maxy-1..miny] $ \y ->
+ putStrLn [".#" !! fromIntegral (fromMaybe 0 (Map.lookup (x, y) bd))
+ | x <- [minx..maxx]]
+
+ print (Map.size (paint 0))
+ printBD (paint 1)