From f46e607f284f2edb41711550990106f47460fc26 Mon Sep 17 00:00:00 2001 From: Aleksey Veresov Date: Mon, 15 Mar 2021 16:43:32 +0300 Subject: . --- src/Device.hs | 14 ++++++++++++++ src/Machine.hs | 11 ++++++++++- src/Suem.hs | 38 +++++++++++++++++++++++++++++++++++--- 3 files changed, 59 insertions(+), 4 deletions(-) create mode 100644 src/Device.hs (limited to 'src') diff --git a/src/Device.hs b/src/Device.hs new file mode 100644 index 0000000..1d42bb8 --- /dev/null +++ b/src/Device.hs @@ -0,0 +1,14 @@ +module Machine where + +import Data.Word (Word32, Word16, Word8) + + +data DeviceRequest = DeviceGetByte Long + | DeviceGetWord Long + | DeviceGetLong Long + | DeviceSetByte Long Word8 + | DeviceSetWord Long Word16 + | DeviceSetLong Long Word32 + +checkInteruptsFromDevices :: Emulator () +checkInteruptsFromDevices = putStrLn "blah-blah" diff --git a/src/Machine.hs b/src/Machine.hs index 06860bf..46ff38d 100644 --- a/src/Machine.hs +++ b/src/Machine.hs @@ -13,6 +13,7 @@ import Control.Monad.IO.Class (liftIO) import Control.Monad.Reader (MonadReader, ReaderT, ask) import Control.Monad.Trans (MonadIO) import Utils +import Network ------------------------------------------------------------------------------- @@ -30,7 +31,15 @@ data Machine = Machine { usp :: IORef Long, -- this is a7 in user mode ssp :: IORef Long, -- this is a7 in supermode ram :: VM.IOVector Byte, - rom :: V.Vector Byte + rom :: V.Vector Byte, + s0 :: Maybe Socket, + s1 :: Maybe Socket, + s2 :: Maybe Socket, + s3 :: Maybe Socket, + s4 :: Maybe Socket, + s5 :: Maybe Socket, + s6 :: Maybe Socket, + s7 :: Maybe Socket } -- Emulator is a monad which contains Machine and allows easy change of it. diff --git a/src/Suem.hs b/src/Suem.hs index e279d42..2bf6c11 100644 --- a/src/Suem.hs +++ b/src/Suem.hs @@ -10,9 +10,12 @@ import Data.Word import Data.IORef import Data.Foldable import Control.Monad.Reader (runReaderT) +import Data.IP +import Network import Machine import Commands import Utils +import Device ------------------------------------------------------------------------------ @@ -374,6 +377,7 @@ runMachine = forM_ [0..] $ \_ -> do pc <- with pc $ \pc -> readIORef pc cmd <- getWord $ fromIntegral pc doCommand cmd + checkInteruptsFromDevices ------------------------------------------------------------------------------ @@ -393,8 +397,27 @@ data Config = Config Int -- frequence (Maybe ConfigSocket) (Maybe ConfigSocket) -makeMachine :: VM.IOVector Byte -> V.Vector Byte -> IO Machine -makeMachine ramData romData = do +ipString :: String -> Word32 +ipString = sum . map (\(n,o) -> toInteger o * 256 ^ n) . zip [0..] + . reverse . fromIPv4 . read + +makeSocket :: ConfigSocket -> Socket +makeSocket (ConfigUnix a) = + sock <- socket AF_UNIX Stream defaultProtocol + Network.Socket.bind sock $ SockAddrUnix a +makeSocket (ConfigInet a) = + sock <- socket AF_INET Stream defaultProtocol + Network.Socket.bind sock $ SockAddrInet + (ipString $ takeWhile (/= ':') a) + (read $ tail $ dropWhile (/= ':') a) + +makeMachine :: VM.IOVector Byte -> V.Vector Byte + -> Maybe ConfigSocket -> Maybe ConfigSocket + -> Maybe ConfigSocket -> Maybe ConfigSocket + -> Maybe ConfigSocket -> Maybe ConfigSocket + -> Maybe ConfigSocket -> Maybe ConfigSocket + -> IO Machine +makeMachine ramData romData s0 s1 s2 s3 s4 s5 s6 s7 = do pc <- newIORef pcval sr <- newIORef 0x2700 drs <- newIORef (fromIntegral 0, fromIntegral 0, fromIntegral 0, @@ -406,6 +429,14 @@ makeMachine ramData romData = do usp <- newIORef 0 ssp <- newIORef sspval return $ Machine pc sr drs ars usp ssp ramData romData + $ maybe Nothing (Just . makeSocket) s0 + $ maybe Nothing (Just . makeSocket) s1 + $ maybe Nothing (Just . makeSocket) s2 + $ maybe Nothing (Just . makeSocket) s3 + $ maybe Nothing (Just . makeSocket) s4 + $ maybe Nothing (Just . makeSocket) s5 + $ maybe Nothing (Just . makeSocket) s6 + $ maybe Nothing (Just . makeSocket) s7 where pcval = (fromIntegral $ romData V.! 4) * 256 * 256 * 256 + (fromIntegral $ romData V.! 5) * 256 * 256 + (fromIntegral $ romData V.! 6) * 256 + @@ -419,8 +450,9 @@ runEmulator :: Emulator a -> Machine -> IO a runEmulator (Emulator reader) m = runReaderT reader m suem :: Config -> IO () -suem (Config _ ramSize romPath _ _ _ _ _ _ _ _) = do +suem (Config _ ramSize romPath s0 s1 s2 s3 s4 s5 s6 s7) = do romData <- B.readFile romPath ram <- VM.replicate ramSize 0 m <- makeMachine ram (V.fromList $ B.unpack $ romData) + s0 s1 s2 s3 s4 s5 s6 s7 runEmulator runMachine m -- cgit v1.2.3