module Main where import Data.List.Split import qualified Data.Map.Strict as M import qualified Data.Vector as V import Helpers import Intcode import Linear.V2 data GameState = GameState { board :: M.Map (V2 Int) Integer } deriving (Show) main :: IO () main = do content <- readFile "input" let program = V.fromList $ concatMap (map read . splitOn ",") (lines content) let run x y = runIntcode ( TM { tape = tapePreprocess program (0, y) , pointer = 0 , pointerOffset = 0 , output = [] , input = Just x , state = Continue } , GameState {board = M.empty}) print $ countBlocks $ run 0 1 putStrLn $ drawBoard $ run 0 1 runIntcode :: (TuringMachine, GameState) -> (TuringMachine, GameState) runIntcode (tm, gb) = case state tmNew of Continue -> runIntcode (tmNew, gb) AwaitInput -> runIntcode (tmNew, gb) _ -> (tmNew, gb) where tmNew = execSteps tm parseBoard :: [Integer] -> M.Map (V2 Int) Integer parseBoard xs = foldr pttrans M.empty $ chunksOf 3 xs where pttrans (x:y:n:xs) board = M.insert (V2 (fromIntegral x) (fromIntegral y)) n board countBlocks :: (TuringMachine, GameState) -> Int countBlocks = length . M.filter (== 2) . parseBoard . reverse . output . fst drawBoard :: (TuringMachine, GameState) -> String drawBoard = drawMap (M.fromList [(1, '∥'), (2, '⌂'), (3, '—'), (4, '•')]) . parseBoard . reverse . output . fst