Day 11 Part 2 done

This commit is contained in:
shu 2019-12-12 22:06:32 +01:00
parent bd832427bc
commit c94ec57f9f
2 changed files with 42 additions and 27 deletions

View File

@ -10,7 +10,6 @@ module Intcode
import Control.DeepSeq as DeepSeq import Control.DeepSeq as DeepSeq
import Data.Char import Data.Char
import Data.List as L import Data.List as L
import Debug.Trace
import Data.Maybe import Data.Maybe
import Data.Vector as V hiding import Data.Vector as V hiding
( (++) ( (++)

View File

@ -1,18 +1,19 @@
module Main where module Main where
import Intcode import Data.List
import Data.List.Split import Data.List.Split
import qualified Data.Map.Strict as M import qualified Data.Map.Strict as M
import qualified Data.Vector as V import qualified Data.Vector as V
import Intcode
import Linear.V2 import Linear.V2
import Debug.Trace
data RoboState = data RoboState =
RoboState RoboState
{ hull :: M.Map (V2 Int) Integer { hull :: M.Map (V2 Int) Integer
, position :: V2 Int , position :: V2 Int
, direction :: V2 Int , direction :: V2 Int
} deriving Show }
deriving (Show)
main :: IO () main :: IO ()
main = do main = do
@ -20,35 +21,50 @@ main = do
let program = V.fromList $ concatMap (map read . splitOn ",") (lines content) let program = V.fromList $ concatMap (map read . splitOn ",") (lines content)
let run x = let run x =
runIntcode runIntcode
(TM ( TM
{ tape = tapePreprocess program { tape = tapePreprocess program
, pointer = 0 , pointer = 0
, pointerOffset = 0 , pointerOffset = 0
, output = [] , output = []
, input = Just 0 , input = Just x
, state = Continue , state = Continue
}, RoboState {hull = M.empty, position = V2 0 0, direction = V2 0 1 }) }
print "hue" , RoboState {hull = M.empty, position = V2 0 0, direction = V2 0 1})
print $ length $ hull $ snd $ run 0 print $ length $ hull $ snd $ run 0
-- concat putStrLn $ drawHull $ hull $ snd $ run 1
-- ["Part 1: " ++ show a ++ ", Part 2: " ++ show b | a <- out1, b <- out2]
drawHull :: M.Map (V2 Int) Integer -> String
drawHull m =
intercalate "\n" $
transpose $
map reverse $
chunksOf
60
[ case M.findWithDefault 0 (V2 x y) m of
1 -> '•'
_ -> ' '
| x <- [(-10) .. 49]
, y <- [(-10) .. 49]
]
runIntcode :: (TuringMachine, RoboState) -> (TuringMachine, RoboState) runIntcode :: (TuringMachine, RoboState) -> (TuringMachine, RoboState)
runIntcode (tm,rb) = runIntcode (tm, rb) =
case state tmNew of case state tmNew of
Continue -> runIntcode (tmNew,rb) Continue -> runIntcode (tmNew, rb)
AwaitInput -> runIntcode $ updateState (tmNew,rb) AwaitInput -> runIntcode $ updateState (tmNew, rb)
_ -> (tmNew,rb) _ -> (tmNew, rb)
where where
tmNew = execSteps tm tmNew = execSteps tm
updateState :: (TuringMachine, RoboState) -> (TuringMachine, RoboState) updateState :: (TuringMachine, RoboState) -> (TuringMachine, RoboState)
updateState (tm, rb) = (tmNew, rbNew) updateState (tm, rb) = (tmNew, rbNew)
where hullNew = M.insert (position rb) (output tm !! 1) (hull rb) where
dirNew = if output tm !! 0 == 0 hullNew = M.insert (position rb) (output tm !! 1) (hull rb)
then perp $ direction rb dirNew =
else iterate perp (direction rb) !! 3 if head (output tm) == 0
posNew = (position rb + dirNew) then perp $ direction rb
floorNext = M.findWithDefault 0 posNew (hull rb) else iterate perp (direction rb) !! 3
rbNew = rb{hull = hullNew, position = posNew, direction = dirNew} posNew = position rb + dirNew
tmNew = tm{input = Just floorNext, output = []} floorNext = M.findWithDefault 0 posNew (hull rb)
rbNew = rb {hull = hullNew, position = posNew, direction = dirNew}
tmNew = tm {input = Just floorNext, output = []}