summaryrefslogtreecommitdiff
path: root/2019
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
parent1405a7fe6ce05a75bb36bcee3c7d19cc296a6de0 (diff)
Day 11
Diffstat (limited to '2019')
-rw-r--r--2019/11.hs51
-rw-r--r--2019/11.in1
2 files changed, 52 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)
diff --git a/2019/11.in b/2019/11.in
new file mode 100644
index 0000000..b1a2f81
--- /dev/null
+++ b/2019/11.in
@@ -0,0 +1 @@
+3,8,1005,8,332,1106,0,11,0,0,0,104,1,104,0,3,8,102,-1,8,10,101,1,10,10,4,10,108,1,8,10,4,10,101,0,8,28,3,8,102,-1,8,10,1001,10,1,10,4,10,1008,8,1,10,4,10,101,0,8,51,1,1103,5,10,1,1104,9,10,2,1003,0,10,1,5,16,10,3,8,102,-1,8,10,101,1,10,10,4,10,108,0,8,10,4,10,1001,8,0,88,1006,0,2,1006,0,62,2,8,2,10,3,8,1002,8,-1,10,101,1,10,10,4,10,1008,8,1,10,4,10,102,1,8,121,1006,0,91,1006,0,22,1006,0,23,1006,0,1,3,8,102,-1,8,10,1001,10,1,10,4,10,1008,8,1,10,4,10,101,0,8,155,1006,0,97,1,1004,2,10,2,1003,6,10,3,8,1002,8,-1,10,101,1,10,10,4,10,108,0,8,10,4,10,1002,8,1,187,1,104,15,10,2,107,9,10,1006,0,37,1006,0,39,3,8,1002,8,-1,10,1001,10,1,10,4,10,108,0,8,10,4,10,102,1,8,223,2,2,17,10,1,1102,5,10,3,8,1002,8,-1,10,101,1,10,10,4,10,108,0,8,10,4,10,1001,8,0,253,3,8,102,-1,8,10,1001,10,1,10,4,10,1008,8,1,10,4,10,1002,8,1,276,1006,0,84,3,8,102,-1,8,10,101,1,10,10,4,10,1008,8,0,10,4,10,1001,8,0,301,2,1009,9,10,1006,0,10,2,102,15,10,101,1,9,9,1007,9,997,10,1005,10,15,99,109,654,104,0,104,1,21102,1,936995738516,1,21101,0,349,0,1105,1,453,21102,1,825595015976,1,21102,1,360,0,1105,1,453,3,10,104,0,104,1,3,10,104,0,104,0,3,10,104,0,104,1,3,10,104,0,104,1,3,10,104,0,104,0,3,10,104,0,104,1,21102,46375541763,1,1,21101,0,407,0,1105,1,453,21102,1,179339005019,1,21101,0,418,0,1106,0,453,3,10,104,0,104,0,3,10,104,0,104,0,21102,825012036372,1,1,21102,441,1,0,1105,1,453,21101,988648461076,0,1,21101,452,0,0,1105,1,453,99,109,2,22102,1,-1,1,21102,40,1,2,21102,484,1,3,21101,0,474,0,1106,0,517,109,-2,2105,1,0,0,1,0,0,1,109,2,3,10,204,-1,1001,479,480,495,4,0,1001,479,1,479,108,4,479,10,1006,10,511,1102,1,0,479,109,-2,2105,1,0,0,109,4,2102,1,-1,516,1207,-3,0,10,1006,10,534,21101,0,0,-3,21202,-3,1,1,22101,0,-2,2,21102,1,1,3,21102,553,1,0,1106,0,558,109,-4,2106,0,0,109,5,1207,-3,1,10,1006,10,581,2207,-4,-2,10,1006,10,581,22102,1,-4,-4,1105,1,649,21202,-4,1,1,21201,-3,-1,2,21202,-2,2,3,21101,0,600,0,1105,1,558,21201,1,0,-4,21101,0,1,-1,2207,-4,-2,10,1006,10,619,21101,0,0,-1,22202,-2,-1,-2,2107,0,-3,10,1006,10,641,22102,1,-1,1,21102,1,641,0,106,0,516,21202,-2,-1,-2,22201,-4,-2,-4,109,-5,2105,1,0