aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorAleksey Veresov <aleksey@veresov.pro>2021-02-14 21:01:33 +0300
committerAleksey Veresov <aleksey@veresov.pro>2021-02-14 21:01:33 +0300
commit0cdd25d921202030745069dbccd16ef856e16750 (patch)
treee67d27b96bda96d118e61547f23a0a44e567a594
parent1ad10fab38c4be9dac68fba9c8249591d883d699 (diff)
downloadsuem-0cdd25d921202030745069dbccd16ef856e16750.tar
suem-0cdd25d921202030745069dbccd16ef856e16750.tar.xz
suem-0cdd25d921202030745069dbccd16ef856e16750.zip
Example commands added.
-rw-r--r--package.yaml1
-rw-r--r--src/Commands.hs30
-rw-r--r--src/Machine.hs38
-rw-r--r--src/Suem.hs84
4 files changed, 101 insertions, 52 deletions
diff --git a/package.yaml b/package.yaml
index 4894b86..73957e0 100644
--- a/package.yaml
+++ b/package.yaml
@@ -13,6 +13,7 @@ dependencies:
- vector
- bytestring
- optparse-applicative
+- lens
library:
source-dirs: src
diff --git a/src/Commands.hs b/src/Commands.hs
new file mode 100644
index 0000000..1413c87
--- /dev/null
+++ b/src/Commands.hs
@@ -0,0 +1,30 @@
+module Commands where
+
+import Control.Lens
+import Machine
+
+doNothing :: Machine -> Machine
+doNothing m = Machine (Registers (pc r + 2) (sr r) (drs r)
+ (ars r) (usp r) (ssp r))
+ (ram m) (rom m)
+ where r = regs m
+
+doUnlink :: Int -> Machine -> Machine
+doUnlink 7 m = let r = regs m in if isSupervisor m
+ then Machine (Registers (pc r + 2) (sr r) (drs r) (ars r)
+ (usp r) (getLong m (fromIntegral $ ssp r) + 4))
+ (ram m) (rom m)
+ else Machine (Registers (pc r + 2) (sr r) (drs r) (ars r)
+ (getLong m (fromIntegral $ usp r) + 4) (ssp r))
+ (ram m) (rom m)
+doUnlink a m = let
+ r = regs m
+ av = getLong m (fromIntegral (ars r !! a))
+ newars = ars r & element (fromIntegral a) .~ av
+ in if isSupervisor m
+ then Machine (Registers (pc r + 2) (sr r) (drs r)
+ newars (usp r) (av + 4))
+ (ram m) (rom m)
+ else Machine (Registers (pc r + 2) (sr r) (drs r)
+ newars (av + 4) (ssp r))
+ (ram m) (rom m)
diff --git a/src/Machine.hs b/src/Machine.hs
new file mode 100644
index 0000000..5e6256f
--- /dev/null
+++ b/src/Machine.hs
@@ -0,0 +1,38 @@
+module Machine where
+
+import qualified Data.Vector.Unboxed as V
+import Data.Word
+import Data.Bits
+
+data Registers = Registers {
+ pc :: Word32,
+ sr :: Word16,
+ drs :: [Word32], -- d0 to d7
+ ars :: [Word32], -- a0 to a6
+ usp :: Word32, -- this is a7 in user mode
+ ssp :: Word32 -- this is a7 in supermode
+}
+
+data Machine = Machine {
+ regs :: Registers,
+ ram :: V.Vector Word8,
+ rom :: V.Vector Word8
+}
+
+isSupervisor :: Machine -> Bool
+isSupervisor m = testBit (sr $ regs m) 2
+
+getByte :: Machine -> Int -> Word8
+getByte m a | a < 0x8 = rom m V.! a
+ | a < 0x7e0000 = if V.length (ram m) >= a then ram m V.! a
+ else 0xff
+ | a < 0x800000 = rom m V.! (a - 0x7e0000)
+ | otherwise = 0xff
+
+getWord :: Machine -> Int -> Word16 -- TODO: only even addresses are allowed
+getWord m a = (fromIntegral $ getByte m a) * 256 +
+ (fromIntegral $ getByte m (a + 1))
+
+getLong :: Machine -> Int -> Word32 -- TODO: only even addresses are allowed
+getLong m a = (fromIntegral $ getWord m a) * 256 * 256 +
+ (fromIntegral $ getWord m (a + 2))
diff --git a/src/Suem.hs b/src/Suem.hs
index 0602196..3ca635b 100644
--- a/src/Suem.hs
+++ b/src/Suem.hs
@@ -4,37 +4,8 @@ import qualified Data.Vector.Unboxed as V
import qualified Data.ByteString as B
import Data.Word
import Data.Bits
-
-
-data Registers = Registers {
- pc :: Word32,
- sr :: Word16,
- drs :: [Word32], -- d0 to d7
- ars :: [Word32], -- a0 to a6
- usp :: Word32, -- this is a7 in user mode
- ssp :: Word32 -- this is a7 in supermode
-}
-
-data Machine = Machine {
- regs :: Registers,
- ram :: V.Vector Word8,
- rom :: V.Vector Word8
-}
-
-getByte :: Machine -> Int -> Word8
-getByte m a | a < 0x8 = rom m V.! a
- | a < 0x7e0000 = if V.length (ram m) >= a then ram m V.! a
- else 0xff
- | a < 0x800000 = rom m V.! (a - 0x7e0000)
- | otherwise = 0xff
-
-getWord :: Machine -> Int -> Word16 -- TODO: only even addresses are allowed
-getWord m a = (fromIntegral $ getByte m a) * 256 +
- (fromIntegral $ getByte m (a + 1))
-
-getLong :: Machine -> Int -> Word32 -- TODO: only even addresses are allowed
-getLong m a = (fromIntegral $ getWord m a) * 256 * 256 +
- (fromIntegral $ getWord m (a + 2))
+import Machine
+import Commands
data ConfigSocket = ConfigInet String | ConfigUnix String
@@ -51,31 +22,40 @@ data Config = Config Int -- frequence
(Maybe ConfigSocket)
(Maybe ConfigSocket)
-doCommand :: Word16 -> Machine -> Machine
-doCommand cmd m = case cmd .&. 0xf000 of
- 0 -> if testBit cmd 7
- then let rega = (shiftR cmd 9) .&. 0x7 in
- m
- else m
- 0x1000 -> m
- 0x2000 -> m
- 0x3000 -> m
- 0x4000 -> m
- 0x5000 -> m
- 0x6000 -> m
- 0x7000 -> m
- 0x8000 -> m
- 0x9000 -> m
- 0xb000 -> m
- 0xc000 -> m
- 0xd000 -> m
- 0xe000 -> m
- _ -> error "Bad command"
+boolToInt :: Bool -> Int
+boolToInt True = 1
+boolToInt False = 0
+
+toBits :: Word16 -> [Int]
+toBits x = map (boolToInt . testBit x) [0..(finiteBitSize x-1)]
+
+fromBits :: [Int] -> Int
+fromBits = foldl (\a b -> 2 * a + b) 0 . reverse
+doCommand :: [Int] -> Machine -> Machine
+--doCommand [0,1,0,0,1,1,1,0, 0,1,1,0,0,0,0,0] = doReset
+doCommand [0,1,0,0,1,1,1,0, 0,1,1,0,0,0,0,1] = doNothing
+--doCommand [0,1,0,0,1,1,1,0, 0,1,1,0,0,0,1,0] = doStop
+--doCommand [0,1,0,0,1,1,1,0, 0,1,1,0,0,0,1,1] = doRTE
+--doCommand [0,1,0,0,1,1,1,0, 0,1,1,0,0,1,0,1] = doRTS
+--doCommand [0,1,0,0,1,1,1,0, 0,1,1,0,0,1,1,0] = doTrapV
+--doCommand [0,1,0,0,1,1,1,0, 0,1,1,0,0,1,1,1] = doRTR
+--doCommand [0,1,0,0,1,0,1,0, 1,1,1,1,1,1,0,0] = doIllegal
+--doCommand [0,1,0,0,1,0,1,0, 1,1,a,b,c,d,e,f] =
+-- doTAS (fromBits [a,b,c]) (fromBits [d,e,f])
+--doCommand [0,1,0,0,1,0,1,0, a,b,c,d,e,f,g,h] =
+-- doTST (fromBits [a,b]) (fromBits [c,d,e]) (fromBits [f,g,h])
+--doCommand [0,1,0,0,1,0,1,0, 0,1,0,0,a,b,c,d] =
+-- doTrap (fromBits [a,b,c,d])
+--doCommand [0,1,0,0,1,0,1,0, 0,1,0,1,0,a,b,c] =
+-- doLink (fromBits [a,b,c])
+doCommand [0,1,0,0,1,0,1,0, 0,1,0,1,1,a,b,c] =
+ doUnlink (fromBits [a,b,c])
+doCommand _ = error "Bad command."
runMachine :: Machine -> IO ()
runMachine m = do
- runMachine $ doCommand (getWord m $ fromIntegral $ pc $ regs m) m
+ runMachine $ doCommand (toBits $ getWord m $ fromIntegral $ pc $ regs m) m
makeMachine :: V.Vector Word8 -> Int -> Machine
makeMachine romData ramSize = Machine rs rd romData