Started on 'Super Chip' support

This commit is contained in:
Dan Piponi 2018-01-24 17:33:26 -08:00
parent bf85fe1933
commit 150993a1d4
4 changed files with 52 additions and 17 deletions

View file

@ -33,6 +33,7 @@ import System.Console.CmdArgs hiding ((+=))
import Keys
import qualified SDL
import Events
--import Debugger
data Args = Args { file :: String, bank :: String, options :: String } deriving (Show, Data, Typeable)
@ -113,7 +114,7 @@ main = do
let initialPC = fromIntegral pclo+(fromIntegral pchi `shift` 8)
liftIO $ putStrLn $ "Starting at address: 0x" ++ showHex initialPC ""
store pc initialPC
-- runDebugger
--runDebugger
loop
SDL.destroyWindow window

View file

@ -366,9 +366,22 @@ pureReadRom addr = do
let bankStateRef = atari ^. bankState
bankState' <- liftIO $ readIORef bankStateRef
let bankedAddress = bankAddress bankState' addr
-- liftIO $ putStrLn $ "readReadRom: Reading from bankAddress 0x" ++ showHex bankedAddress "" ++ " (" ++ show bankState' ++ ")"
byte <- liftIO $ readArray m bankedAddress
return byte
liftIO $ readArray m bankedAddress
{-# INLINE pureWriteRom #-}
-- | pureReadRom sees address in full 6507 range 0x0000-0x1fff
-- You can write to Super Chip "ROM"
pureWriteRom :: Word16 -> Word8 -> MonadAtari ()
pureWriteRom addr v = do
-- liftIO $ putStrLn $ "readReadRom: Reading from address 0x" ++ showHex addr ""
atari <- ask
let m = atari ^. rom
let bankStateRef = atari ^. bankState
bankState' <- liftIO $ readIORef bankStateRef
when (bankWritable bankState' addr) $ do
let bankedAddress = bankAddress bankState' addr
-- liftIO $ putStrLn $ "readReadRom: Reading from bankAddress 0x" ++ showHex bankedAddress "" ++ " (" ++ show bankState' ++ ")"
liftIO $ writeArray m bankedAddress v
{-# INLINE pureReadMemory #-}
-- | pureReadMemory expects an address in range 0x0000-0x1fff
@ -387,7 +400,7 @@ pureReadMemory RAM addr = do
pureWriteMemory :: MemoryType -> Word16 -> Word8 -> MonadAtari ()
pureWriteMemory TIA addr v = writeStella (addr .&. 0x3f) v
pureWriteMemory RIOT addr v = writeStella (0x280+(addr .&. 0x1f)) v
pureWriteMemory ROM _ _ = return ()
pureWriteMemory ROM addr v = pureWriteRom addr v
pureWriteMemory RAM addr v = do
atari <- ask
let m = atari ^. ram
@ -487,7 +500,9 @@ instance Emu6502 MonadAtari where
debugStrLn _ _ = return ()
{- INLINE illegal -}
illegal i = error $ "Illegal opcode 0x" ++ showHex i ""
illegal i = do
dumpState
error $ "Illegal opcode 0x" ++ showHex i ""
{-# INLINABLE dumpMemory #-}
dumpMemory :: MonadAtari ()

View file

@ -10,6 +10,7 @@ module Memory(MemoryType(..),
bankAddress,
memoryType,
bankSwitch,
bankWritable,
BankMode(..)
) where
@ -60,11 +61,13 @@ isROM a = testBit a 12
data BankMode = UnBanked
| ModeF6
| ModeF6SC
| ModeF8
| Mode3F deriving (Show, Data, Typeable)
data BankState = NoBank
| BankF6 !Word16
| BankF6SC !Word16
| BankF8 !Word16
| Bank3F !Word16 deriving Show
@ -107,3 +110,11 @@ bankAddress (BankF8 offset) addr = ((iz addr .&. 0xfff)+iz offset)
bankAddress (BankF6 offset) addr = ((iz addr .&. 0xfff)+iz offset)
bankAddress (Bank3F _) addr | addr > 0x1800 = iz addr
bankAddress (Bank3F offset) addr = ((iz addr .&. 0x7ff)+iz offset)
{-# INLINE bankWritable #-}
-- | bankAddress sees the full 6507 address
-- i.e. it is in range 0x0000-0x1fff
-- though we only expect to see values in range 0x1000-0x1fff
-- as we only reach this function if the 6507 is reading from ROM.
bankWritable :: BankState -> Word16 -> Bool
bankWritable _ _ = False

View file

@ -1,3 +1,8 @@
//
// Convert RAM trace to image
// c++ -std=c++11 -O3 -o trace trace.cpp && ./trace && open trace.bmp
//
#include <iostream>
#include <fstream>
#include <vector>
@ -34,10 +39,10 @@ void savebmp(const char *filename, int height, int width,
outputfile << "BM";
for (int n = 0; n < 6; n++) {
outputfile.put(headers[n] & 0x000000FFU);
outputfile.put((headers[n] & 0x0000FF00U) >> 8);
outputfile.put((headers[n] & 0x00FF0000U) >> 16);
outputfile.put((headers[n] & 0xFF000000U) >> 24);
outputfile.put(headers[n] & 0x000000FFU);
outputfile.put((headers[n] & 0x0000FF00U) >> 8);
outputfile.put((headers[n] & 0x00FF0000U) >> 16);
outputfile.put((headers[n] & 0xFF000000U) >> 24);
}
//
@ -49,10 +54,10 @@ void savebmp(const char *filename, int height, int width,
outputfile.put(0);
for (int n = 7; n < 13; n++) {
outputfile.put(headers[n] & 0x000000FFU);
outputfile.put((headers[n] & 0x0000FF00U) >> 8);
outputfile.put((headers[n] & 0x00FF0000U) >> 16);
outputfile.put((headers[n] & 0xFF000000U) >> 24);
outputfile.put(headers[n] & 0x000000FFU);
outputfile.put((headers[n] & 0x0000FF00U) >> 8);
outputfile.put((headers[n] & 0x00FF0000U) >> 16);
outputfile.put((headers[n] & 0xFF000000U) >> 24);
}
//
@ -98,9 +103,12 @@ int main() {
std::vector<char> trace(size);
std::vector<bool> ram(1024, 0);
cout << "Reading trace..." << endl;
if (file.read(trace.data(), size)) {
const int vscale = 512;
int vsize = (size/2+vscale-1)/vscale;
const int vscale = 1;
int end = size/2;
//end = 10000;
int vsize = (end+vscale-1)/vscale;
// Count of how many times each bit is one per time period
std::vector<int> data(1024*vsize, 0);
@ -108,7 +116,7 @@ int main() {
// Count of number of times bit is written per time period
std::vector<int> activity(1024*vsize, 0);
for (int i = 0; i < size/2; ++i) {
for (int i = 0; i < end; ++i) {
int index = i/vscale;
int row = 1024*index;