Add Opcode test
authorLucian Mogosanu <lucian.mogosanu@gmail.com>
Fri, 19 Dec 2014 14:56:14 +0000 (16:56 +0200)
committerLucian Mogosanu <lucian.mogosanu@gmail.com>
Fri, 19 Dec 2014 14:56:14 +0000 (16:56 +0200)
src/OpcodeTest.hs [new file with mode: 0644]

diff --git a/src/OpcodeTest.hs b/src/OpcodeTest.hs
new file mode 100644 (file)
index 0000000..9815fda
--- /dev/null
@@ -0,0 +1,67 @@
+module Main where
+
+import System.IO
+import System.Environment
+import Data.Word
+import qualified Data.ByteString as BS
+
+import Z80.CPU
+import Z80.ISA
+import ZXS.Machine
+import ZXS.RAM
+import ZXS.Decode
+
+whatevsRAM :: IO RAM
+whatevsRAM = newRAM (0x0000, 0xffff)
+
+whatevsCPU :: CPU
+whatevsCPU = CPU
+  { getAF = 0
+  , getBC = 0
+  , getDE = 0
+  , getHL = 0
+  , getAF' = 0
+  , getBC' = 0
+  , getDE' = 0
+  , getHL' = 0
+  , getI = 0
+  , getR = 0
+  , getIX = 0
+  , getIY = 0
+  , getSP = 0
+  , getPC = 0
+  , getPrefixed = Unprefixed
+  }
+
+whatevsSpectrum :: BS.ByteString -> IO Spectrum
+whatevsSpectrum bs = do
+  let header = BS.take 8 bs
+      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
+                    >>= \ ram -> return $ Spectrum whatevsCPU { getPC = 0 } ram
+
+initRAM :: Word16 -> BS.ByteString -> RAM -> IO RAM
+initRAM addr code ram
+  | BS.null code = return ram
+  | otherwise = ramSetByte ram addr (BS.head code)
+             >> initRAM (addr + 1) (BS.tail code) ram
+
+parseZ80 :: Int -> ZXS [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)
+
+main = do
+  args <- getArgs
+  if length args /= 1
+    then print "TODO: print usage"
+    else do
+      bs <- withFile (head args) ReadMode BS.hGetContents
+      let n = BS.length bs
+      s <- whatevsSpectrum bs
+      is <- evalZXST (parseZ80 (n - 8)) s
+      print is