aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorAleksey Veresov <aleksey@veresov.pro>2021-03-15 17:00:35 +0300
committerAleksey Veresov <aleksey@veresov.pro>2021-03-15 17:00:35 +0300
commit89909343a8b8b7af4ff44afab77a54c28f164cbe (patch)
tree62853fb475e77882bde262072ab0e2734ccc5fb8
parentf46e607f284f2edb41711550990106f47460fc26 (diff)
downloadsuem-89909343a8b8b7af4ff44afab77a54c28f164cbe.tar
suem-89909343a8b8b7af4ff44afab77a54c28f164cbe.tar.xz
suem-89909343a8b8b7af4ff44afab77a54c28f164cbe.zip
Device module started.
-rw-r--r--src/Device.hs12
-rw-r--r--src/Machine.hs2
-rw-r--r--src/Suem.hs34
3 files changed, 27 insertions, 21 deletions
diff --git a/src/Device.hs b/src/Device.hs
index 1d42bb8..50fb3fc 100644
--- a/src/Device.hs
+++ b/src/Device.hs
@@ -1,14 +1,16 @@
-module Machine where
+module Device where
+import Prelude hiding (Word)
import Data.Word (Word32, Word16, Word8)
+import Machine
data DeviceRequest = DeviceGetByte Long
| DeviceGetWord Long
| DeviceGetLong Long
- | DeviceSetByte Long Word8
- | DeviceSetWord Long Word16
- | DeviceSetLong Long Word32
+ | DeviceSetByte Long Byte
+ | DeviceSetWord Long Word
+ | DeviceSetLong Long Long
checkInteruptsFromDevices :: Emulator ()
-checkInteruptsFromDevices = putStrLn "blah-blah"
+checkInteruptsFromDevices = return ()
diff --git a/src/Machine.hs b/src/Machine.hs
index 46ff38d..22d428e 100644
--- a/src/Machine.hs
+++ b/src/Machine.hs
@@ -12,8 +12,8 @@ import Control.Monad
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Reader (MonadReader, ReaderT, ask)
import Control.Monad.Trans (MonadIO)
+import Network.Socket
import Utils
-import Network
-------------------------------------------------------------------------------
diff --git a/src/Suem.hs b/src/Suem.hs
index 2bf6c11..5de87a9 100644
--- a/src/Suem.hs
+++ b/src/Suem.hs
@@ -11,7 +11,7 @@ import Data.IORef
import Data.Foldable
import Control.Monad.Reader (runReaderT)
import Data.IP
-import Network
+import Network.Socket
import Machine
import Commands
import Utils
@@ -398,18 +398,21 @@ data Config = Config Int -- frequence
(Maybe ConfigSocket)
ipString :: String -> Word32
-ipString = sum . map (\(n,o) -> toInteger o * 256 ^ n) . zip [0..]
- . reverse . fromIPv4 . read
+ipString = fromIntegral . sum . map (\(n,o) -> toInteger o * 256 ^ n)
+ . zip [0..] . reverse . fromIPv4 . read
-makeSocket :: ConfigSocket -> Socket
-makeSocket (ConfigUnix a) =
+makeSocket :: Maybe ConfigSocket -> IO (Maybe Socket)
+makeSocket (Just (ConfigUnix a)) = do
sock <- socket AF_UNIX Stream defaultProtocol
Network.Socket.bind sock $ SockAddrUnix a
-makeSocket (ConfigInet a) =
+ return $ Just sock
+makeSocket (Just (ConfigInet a)) = do
sock <- socket AF_INET Stream defaultProtocol
Network.Socket.bind sock $ SockAddrInet
- (ipString $ takeWhile (/= ':') a)
(read $ tail $ dropWhile (/= ':') a)
+ (ipString $ takeWhile (/= ':') a)
+ return $ Just sock
+makeSocket Nothing = return Nothing
makeMachine :: VM.IOVector Byte -> V.Vector Byte
-> Maybe ConfigSocket -> Maybe ConfigSocket
@@ -428,15 +431,16 @@ makeMachine ramData romData s0 s1 s2 s3 s4 s5 s6 s7 = do
fromIntegral 0)
usp <- newIORef 0
ssp <- newIORef sspval
+ ms0 <- makeSocket s0
+ ms1 <- makeSocket s1
+ ms2 <- makeSocket s2
+ ms3 <- makeSocket s3
+ ms4 <- makeSocket s4
+ ms5 <- makeSocket s5
+ ms6 <- makeSocket s6
+ ms7 <- makeSocket s7
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
+ ms0 ms1 ms2 ms3 ms4 ms5 ms6 ms7
where pcval = (fromIntegral $ romData V.! 4) * 256 * 256 * 256 +
(fromIntegral $ romData V.! 5) * 256 * 256 +
(fromIntegral $ romData V.! 6) * 256 +