Skip to content

Commit

Permalink
Clean up a bit
Browse files Browse the repository at this point in the history
  • Loading branch information
jaspervdj committed Apr 6, 2012
1 parent 04621ec commit b0f0e4a
Show file tree
Hide file tree
Showing 9 changed files with 77 additions and 27 deletions.
1 change: 1 addition & 0 deletions .ghci
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
:set -isrc
18 changes: 17 additions & 1 deletion README.markdown
Original file line number Diff line number Diff line change
Expand Up @@ -8,4 +8,20 @@ Implementation of Notch's [dcpu-16] CPU in Haskell.
Status
------

- Emulator seems to run Notch's test program
The emulator seems to run Notch's test program.

The current strategy is to simulate 10000 instructions (*not* cycles). A better
strategy would be to stop when PC ends up after the code, but this would not
work for some hacks (e.g. programs that modify themselves).

Building
--------

cabal configure && cabal build

Running
-------

./dist/build/dcpu16-hs/dcpu16-hs examples/notch.bin

You should probably redirect the output to a file.
8 changes: 5 additions & 3 deletions dcpu16-hs.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -19,8 +19,10 @@ Executable dcpu16-hs
Emulator
Instruction
Memory
Util

Build-depends:
base >= 4 && < 5,
ghc-prim >= 0.2 && < 0.3,
mtl >= 2.0 && < 2.1
base >= 4 && < 5,
bytestring >= 0.9 && < 0.10,
ghc-prim >= 0.2 && < 0.3,
mtl >= 2.0 && < 2.1
Binary file added examples/notch.bin
Binary file not shown.
4 changes: 4 additions & 0 deletions examples/notch.hex
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
0000000: 7c01 0030 7de1 1000 0020 7803 1000 c00d
0000010: 7dc1 001a a861 7c01 2000 2161 2000 8463
0000020: 806d 7dc1 000d 9031 7c10 0018 7dc1 001a
0000030: 9037 61c1 7dc1 001a 0000 0000 0000 0000
29 changes: 20 additions & 9 deletions src/Emulator.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,16 +8,19 @@ module Emulator
) where

import Control.Applicative ((<$>))
import Control.Monad (forM, forM_)
import Control.Monad (forM)
import Control.Monad.Reader (ReaderT, ask, runReaderT)
import Control.Monad.ST (ST, runST)
import Control.Monad.Trans (lift)
import Data.Bits (shiftL, shiftR, xor, (.&.), (.|.))
import Data.Word (Word, Word16)
import Text.Printf (printf)

import Data.ByteString (ByteString)
import qualified Data.ByteString as B

import Instruction
import Memory (Address, Memory)
import Util
import qualified Memory as Memory

type EmulatorM s = ReaderT (Memory s) (ST s)
Expand All @@ -28,10 +31,21 @@ runEmulatorM program = runST $ do
Memory.store mem Memory.sp 0xffff
runReaderT program mem

loadProgram :: [Word16] -> EmulatorM s ()
loadProgram ws = do
mem <- ask
forM_ (zip [0 ..] ws) $ \(i, w) -> lift $ Memory.store mem (Memory.ram i) w
-- | Load a program from a bytestring
loadProgram :: ByteString -> EmulatorM s ()
loadProgram bs = loop 0
where
len = B.length bs
loop !i
| i + 1 >= len = return ()
| otherwise = do
let !b1 = fromIntegral $ B.index bs i
!b2 = fromIntegral $ B.index bs (i + 1)
!w16 = (b1 `shiftL` 8) + b2
!addr = fromIntegral $ i `div` 2
mem <- ask
lift $ Memory.store mem (Memory.ram addr) w16
loop (i + 2)

loadNextWord :: EmulatorM s Word16
loadNextWord = do
Expand Down Expand Up @@ -270,6 +284,3 @@ prettifyRam = do
mem <- ask
vals <- mapM (lift . Memory.load mem . Memory.ram) [lo .. up]
return $ prettifyWord16 lo ++ ": " ++ unwords (map prettifyWord16 vals)

prettifyWord16 :: Word16 -> String
prettifyWord16 = printf "%04x"
7 changes: 4 additions & 3 deletions src/Instruction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@ import Data.Bits (shiftR, (.&.))
import Data.Word (Word16)

import Memory
import Util

data BasicInstruction
= Set
Expand Down Expand Up @@ -61,10 +62,10 @@ parseInstruction word = case oooo of
-- Non-basic instructions
0x0 -> case aaaaaa of
0x01 -> NonBasicInstruction Jsr b
_ -> undefined
_ -> error $ "Unknown non-basic opcode: " ++ prettifyWord16 aaaaaa

-- Unknown instruction
_ -> undefined
_ -> error $ "unknown basic opcode: " ++ prettifyWord16 oooo
where
-- Word is of the form bbbbbbaaaaaaoooo
oooo = word .&. 0xf
Expand Down Expand Up @@ -104,6 +105,6 @@ parseOperand word
0x1d -> OO
0x1e -> ORamAtNextWord
0x1f -> ONextWord
_ -> undefined -- Unknown value
_ -> error $ "Unknown operand: " ++ prettifyWord16 word
where
reg = toEnum . fromIntegral
28 changes: 17 additions & 11 deletions src/Main.hs
Original file line number Diff line number Diff line change
@@ -1,18 +1,24 @@
module Main where

import Control.Monad (replicateM_)
import System.Environment (getArgs, getProgName)
import System.Exit (exitFailure)

import qualified Data.ByteString as B

import Emulator

main :: IO ()
main = putStr $ runEmulatorM $ do
loadProgram p
replicateM_ 100000 step
prettify
where
-- Notch's test program
p = [ 0x7c01, 0x0030, 0x7de1, 0x1000, 0x0020, 0x7803, 0x1000, 0xc00d
, 0x7dc1, 0x001a, 0xa861, 0x7c01, 0x2000, 0x2161, 0x2000, 0x8463
, 0x806d, 0x7dc1, 0x000d, 0x9031, 0x7c10, 0x0018, 0x7dc1, 0x001a
, 0x9037, 0x61c1, 0x7dc1, 0x001a, 0x0000, 0x0000, 0x0000, 0x0000
]
main = do
progName <- getProgName
args <- getArgs
case args of
[x] -> do
bytes <- B.readFile x
putStr $ runEmulatorM $ do
loadProgram bytes
replicateM_ 10000 step
prettify
_ -> do
putStr $ "Usage: " ++ progName ++ " <executable>"
exitFailure
9 changes: 9 additions & 0 deletions src/Util.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
module Util
( prettifyWord16
) where

import Data.Word (Word16)
import Text.Printf (printf)

prettifyWord16 :: Word16 -> String
prettifyWord16 = printf "%04x"

0 comments on commit b0f0e4a

Please sign in to comment.