9 import qualified Data.Map.Strict as M
10 import Data.Map.Strict ((!))
11 import Control.Lens -- hiding ((<|), (|>), (:>), (:<), indices)
13 import Control.Monad.State.Strict
14 import Control.Monad.Reader
15 import Control.Monad.Writer
16 import Control.Monad.RWS.Strict
20 import Data.Binary.Get
21 import qualified Data.ByteString.Lazy as BL
24 data SynacorState = SynacorState
25 { _ssMachines :: [Machine]
26 , _ssInputs :: [String]
27 , _ssOutputs :: [String]
30 , _ssState :: [ExecutionState]
32 , _ssDumpFile :: String
34 makeLenses ''SynacorState
36 instance Show SynacorState
41 , (show (length (state ^. ssMachines)) ++ " machines")
42 , "inputs " ++ (intercalate ":" $ state ^. ssInputs)
43 , "outputs " ++ (intercalate ":" $ fmap (take 20) $ state ^. ssOutputs)
44 , "conts " ++ (show $ state ^. ssContinue)
45 , "unsaved " ++ (show $ state ^. ssUnsaved)
46 , "states " ++ (show $ state ^. ssState)
47 , "tracing " ++ (show $ state ^. ssTracing)
48 , "dumping to " ++ (state ^. ssDumpFile)
53 do -- mem <- getMemory
54 -- print $ [(n, showHex (mem ! n) "") | n <- [0..5] ]
55 -- machineInput <- readFile "adventure_input.txt"
56 -- let mInp = wordify machineInput
57 -- let machine = makeMachine mem
58 -- let (exState, _machine, output) = runMachine mInp machine
60 -- putStrLn $ showOutput output
63 let state1 = runWithoutInput state0
64 let newOutput = head $ state1 ^. ssOutputs
66 -- let state1 = runOneInput state "take tablet"
71 stateF <- adventureHarness state1
73 -- print $ stateF ^. ssInputs
74 -- print $ stateF ^. ssOutputs
75 -- print $ stateF ^. ssState
76 -- let machs = stateF ^. ssMachines
77 -- let machPairs = zipWith (==) machs $ tail machs
80 emptyState :: IO SynacorState
83 let machine = makeMachine mem
85 { _ssMachines = [machine]
90 , _ssState = [Runnable]
94 -- [machine] [] [] True False [Runnable]
96 adventureHarness :: SynacorState -> IO SynacorState
97 adventureHarness state =
98 do command <- prompt "> "
99 state' <- handleCommand command state
100 let traceAndOutput = head $ state' ^. ssOutputs
101 let (newOutput, tracing) = spliceOut traceAndOutput
103 when (state' ^. ssTracing)
104 (appendFile (state' ^. ssDumpFile) $ unlines tracing)
105 if (state' ^. ssContinue)
106 then (adventureHarness state')
110 spliceOut :: String -> (String, [String])
111 spliceOut s = doingOut s "" []
112 where doingOut s out traces
113 | null s = (reverse out, reverse traces)
114 | ">> " `isPrefixOf` s = doingTrace (drop 3 s) out traces ""
115 | otherwise = doingOut (tail s) (head s : out) traces
116 doingTrace s out traces tr
117 | "<<" `isPrefixOf` s = doingOut (drop 2 s) out (reverse tr : traces)
118 | otherwise = doingTrace (tail s) out traces (head s : tr)
121 handleCommand :: String -> SynacorState -> IO SynacorState
122 handleCommand ":quit" state = return $ state & ssContinue .~ False
123 handleCommand ":save" state =
124 do filename <- prompt "Save as? "
125 let inputs = unlines $ tail $ reverse $ state ^. ssInputs
126 writeFile filename inputs
127 return $ state & ssUnsaved .~ True
128 handleCommand ":load" state =
129 do filename <- prompt "From? "
130 machineInput <- readFile filename
131 let inputs = lines machineInput
132 initialState <- emptyState
133 let nonComments = filter (\i -> head i /= '#') inputs
134 let state = foldl' runOneInput initialState ("" : nonComments)
135 return $ state & ssUnsaved .~ False
136 handleCommand ":undo" state =
137 return $ state & ssMachines %~ tail
143 handleCommand ":recap" state =
144 do let inputs = take 3 $ state ^. ssInputs
145 let outputs = "" : (tail $ take 3 $ state ^. ssOutputs)
146 let inOuts = reverse $ zip inputs outputs
147 forM_ inOuts (\(i, o) ->
148 do putStrLn ("#> " ++ i)
152 handleCommand ":trace" state =
153 do filename <- prompt "Dump to? "
154 return $ state & ssTracing .~ True & ssDumpFile .~ filename
155 handleCommand ":untrace" state =
156 return $ state & ssTracing .~ False & ssDumpFile .~ ""
157 handleCommand ":poke8" state =
158 do let machines = state ^. ssMachines
159 let machine = head machines
160 let machine' = machine & registers . ix 7 .~ 25734
161 & memory . ix 5489 .~ 21
162 & memory . ix 5490 .~ 21
163 & memory . ix 5495 .~ 7
164 -- let machine' = machine & memory . ix 5451 .~ 7
165 return $ state & ssMachines .~ (machine' : (tail machines))
166 handleCommand command state = return $ runOneInput state command
169 runWithoutInput :: SynacorState -> SynacorState
170 runWithoutInput state = state & ssMachines %~ (machine' :)
171 -- & ssInputs %~ (input :)
172 & ssOutputs %~ ((showOutput output) :)
175 & ssState %~ (exState :)
176 where machine = head $ state ^. ssMachines
177 (exState, machine', output) = runMachine [] (machine & inputIndex .~ 0)
179 runOneInput :: SynacorState -> String -> SynacorState
180 runOneInput state ":poke8" = state & ssMachines .~ ssMAchinesNew
181 where machine0 = head $ state ^. ssMachines
182 machine = machine0 & registers . ix 7 .~ 25734
183 & memory . ix 5489 .~ 21
184 & memory . ix 5490 .~ 21
185 & memory . ix 5495 .~ 7
186 ssMAchinesNew = machine : (tail $ state ^. ssMachines)
188 runOneInput state input = state & ssMachines %~ (machine' :)
189 & ssInputs %~ (input :)
190 & ssOutputs %~ ((showOutput output) :)
193 & ssState %~ (exState :)
194 where machine0 = head $ state ^. ssMachines
195 machine = if (state ^. ssTracing)
196 then machine0 & tracing .~ True
197 else machine0 & tracing .~ False
198 inputW = wordify (input ++ "\n")
199 (exState, machine', output) = runMachine inputW (machine & inputIndex .~ 0)
200 -- output' = trace ("runone " ++ (show (machine == machine')) ++ " " ++ (show exState) ++ " " ++ (showOutput output)) output
203 prompt :: String -> IO String
209 wordify :: String -> [Word16]
210 wordify cs = fmap (fromIntegral . ord) cs
212 showOutput :: [Word16] -> String
213 showOutput output = fmap (chr . fromInteger . fromIntegral) output
215 getMemory :: IO Memory
217 input <- BL.readFile "challenge.bin"
218 let cells = runGet getCells input
219 return $ M.fromList $ zip [0..] cells
221 getCells :: Get [Word16]
226 else do cell <- getWord16le