OpcodeTest: Pretty print instructions
authorLucian Mogosanu <lucian.mogosanu@gmail.com>
Tue, 23 Dec 2014 17:43:02 +0000 (19:43 +0200)
committerLucian Mogosanu <lucian.mogosanu@gmail.com>
Tue, 23 Dec 2014 17:43:02 +0000 (19:43 +0200)
src/OpcodeTest.hs

index 9815fda..f892b4e 100644 (file)
@@ -1,5 +1,6 @@
 module Main where
 
+import Text.Printf
 import System.IO
 import System.Environment
 import Data.Word
@@ -39,7 +40,7 @@ whatevsSpectrum bs = do
       code = BS.drop 8 bs
   if header /= BS.pack [ 0x5a, 0x38, 0x30, 0x41, 0x53, 0x4d, 0x1a, 0x0a ]
     then fail "Doesn't look like a Z80 file..."
-    else whatevsRAM >>= initRAM 0 code
+    else whatevsRAM >>= initRAM 0 bs -- code
                     >>= \ ram -> return $ Spectrum whatevsCPU { getPC = 0 } ram
 
 initRAM :: Word16 -> BS.ByteString -> RAM -> IO RAM
@@ -48,12 +49,30 @@ initRAM addr code ram
   | otherwise = ramSetByte ram addr (BS.head code)
              >> initRAM (addr + 1) (BS.tail code) ram
 
-parseZ80 :: Int -> ZXS [Instruction]
+parseZ80 :: Word16 -> ZXS [(Word16, [Word8], Instruction)]
 parseZ80 = go []
   where go acc n
-          | n < 0 = fail "parseZ80: Not enough bytes to parse"
-          | n <= 0 = return $ reverse acc
-          | otherwise = decode >>= \ i -> go (i : acc) (n - 1)
+          | n == 0 = return $ reverse acc
+          | otherwise = do
+            pc <- getsCPU getPC
+            i <- decode
+            pc' <- getsCPU getPC
+            ops <- getOpcodesBetween pc pc'
+            let d = pc' - pc
+            go ((pc, ops, i) : acc) (n - d)
+        getOpcodesBetween pc pc'
+          | pc == pc' = return []
+          | otherwise = do
+            b <- getMainMemByte pc
+            rest <- getOpcodesBetween (pc + 1) pc'
+            return $ b : rest
+
+printInstrs :: [(Word16, [Word8], Instruction)] -> IO ()
+printInstrs = mapM_ printInstr
+  where
+  printInstr (n, ops, i) = printf "%04x\t%s\t\t%s\n" n (printOps ops) (show i)
+  printOps :: [Word8] -> String
+  printOps = concatMap $ \ op -> printf "%02x" op
 
 main = do
   args <- getArgs
@@ -61,7 +80,7 @@ main = do
     then print "TODO: print usage"
     else do
       bs <- withFile (head args) ReadMode BS.hGetContents
-      let n = BS.length bs
+      let n = fromIntegral $ BS.length bs
       s <- whatevsSpectrum bs
-      is <- evalZXST (parseZ80 (n - 8)) s
-      print is
+      is <- evalZXST (parseZ80 n) s
+      printInstrs is