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)