summaryrefslogtreecommitdiff
path: root/src/Network/Tox/Crypto/Handlers.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Network/Tox/Crypto/Handlers.hs')
-rw-r--r--src/Network/Tox/Crypto/Handlers.hs61
1 files changed, 57 insertions, 4 deletions
diff --git a/src/Network/Tox/Crypto/Handlers.hs b/src/Network/Tox/Crypto/Handlers.hs
index ac3d1ef0..0cb2d4db 100644
--- a/src/Network/Tox/Crypto/Handlers.hs
+++ b/src/Network/Tox/Crypto/Handlers.hs
@@ -19,6 +19,7 @@ import Data.Serialize as S
19import Data.Word 19import Data.Word
20import GHC.Conc (unsafeIOToSTM) 20import GHC.Conc (unsafeIOToSTM)
21import qualified Data.Set as Set 21import qualified Data.Set as Set
22import qualified Data.Array.Unboxed as A
22 23
23-- util, todo: move to another module 24-- util, todo: move to another module
24maybeToEither :: Maybe b -> Either String b 25maybeToEither :: Maybe b -> Either String b
@@ -31,7 +32,7 @@ data NetCryptoSessionStatus = Unaccepted | Accepted | Confirmed
31 32
32type IOHook addr x = addr -> x -> IO (Maybe (x -> x)) 33type IOHook addr x = addr -> x -> IO (Maybe (x -> x))
33type NetCryptoHook = IOHook NetCryptoSession CryptoData 34type NetCryptoHook = IOHook NetCryptoSession CryptoData
34 35type MsgTypeArray = A.UArray Word8 Word16
35 36
36data NetCryptoSession = NCrypto { ncState :: TVar NetCryptoSessionStatus 37data NetCryptoSession = NCrypto { ncState :: TVar NetCryptoSessionStatus
37 , ncTheirBaseNonce :: TVar Nonce24 -- base nonce + packet number 38 , ncTheirBaseNonce :: TVar Nonce24 -- base nonce + packet number
@@ -44,6 +45,12 @@ data NetCryptoSession = NCrypto { ncState :: TVar NetCryptoSessionStatus
44 , ncSockAddr :: SockAddr 45 , ncSockAddr :: SockAddr
45 , ncHooks :: TVar (Map.Map MessageType [NetCryptoHook]) 46 , ncHooks :: TVar (Map.Map MessageType [NetCryptoHook])
46 , ncUnrecognizedHook :: TVar (MessageType -> NetCryptoHook) 47 , ncUnrecognizedHook :: TVar (MessageType -> NetCryptoHook)
48 , ncMessageTypes :: TVar MsgTypeArray -- ^ supported messages, 0 for unsupported,
49 -- otherwise the messageType, some message types
50 -- may not be in ncHooks yet, but they should appear
51 -- here if ncUnrecognizedHook will add them to ncHooks
52 -- on an as-need basis. On 0 entries, this Transport
53 -- will return id in case they are handled by another Transport.
47 , ncAllSessions :: NetCryptoSessions -- ^ may be needed if one net-crypto session 54 , ncAllSessions :: NetCryptoSessions -- ^ may be needed if one net-crypto session
48 -- needs to possibly start another, as is 55 -- needs to possibly start another, as is
49 -- the case in group chats 56 -- the case in group chats
@@ -54,6 +61,7 @@ data NetCryptoSessions = NCSessions { netCryptoSessions :: TVar (Map.Map SockAdd
54 , transportCrypto :: TransportCrypto 61 , transportCrypto :: TransportCrypto
55 , defaultHooks :: Map.Map MessageType [NetCryptoHook] 62 , defaultHooks :: Map.Map MessageType [NetCryptoHook]
56 , defaultUnrecognizedHook :: MessageType -> NetCryptoHook 63 , defaultUnrecognizedHook :: MessageType -> NetCryptoHook
64 , msgTypeArray :: MsgTypeArray
57 } 65 }
58 66
59newSessionsState :: TransportCrypto -> (MessageType -> NetCryptoHook) -> Map.Map MessageType [NetCryptoHook] -> IO NetCryptoSessions 67newSessionsState :: TransportCrypto -> (MessageType -> NetCryptoHook) -> Map.Map MessageType [NetCryptoHook] -> IO NetCryptoSessions
@@ -63,6 +71,7 @@ newSessionsState crypto unrechook hooks = do
63 , transportCrypto = crypto 71 , transportCrypto = crypto
64 , defaultHooks = hooks 72 , defaultHooks = hooks
65 , defaultUnrecognizedHook = unrechook 73 , defaultUnrecognizedHook = unrechook
74 , msgTypeArray = allMsgTypes -- todo make this a parameter
66 } 75 }
67 76
68data HandshakeParams 77data HandshakeParams
@@ -109,6 +118,7 @@ freshCryptoSession sessions
109 ncHooks0 <- atomically $ newTVar (defaultHooks sessions) 118 ncHooks0 <- atomically $ newTVar (defaultHooks sessions)
110 ncUnrecognizedHook0 <- atomically $ newTVar (defaultUnrecognizedHook sessions) 119 ncUnrecognizedHook0 <- atomically $ newTVar (defaultUnrecognizedHook sessions)
111 ncGroups0 <- atomically $ newTVar (Map.empty) 120 ncGroups0 <- atomically $ newTVar (Map.empty)
121 ncMessageTypes0 <- atomically $ newTVar (msgTypeArray sessions)
112 let netCryptoSession = 122 let netCryptoSession =
113 NCrypto { ncState = ncState0 123 NCrypto { ncState = ncState0
114 , ncTheirBaseNonce= ncTheirBaseNonce0 124 , ncTheirBaseNonce= ncTheirBaseNonce0
@@ -123,6 +133,7 @@ freshCryptoSession sessions
123 , ncUnrecognizedHook = ncUnrecognizedHook0 133 , ncUnrecognizedHook = ncUnrecognizedHook0
124 , ncAllSessions = sessions 134 , ncAllSessions = sessions
125 , ncGroups = ncGroups0 135 , ncGroups = ncGroups0
136 , ncMessageTypes = ncMessageTypes0
126 } 137 }
127 atomically $ modifyTVar allsessions (Map.insert addr netCryptoSession) 138 atomically $ modifyTVar allsessions (Map.insert addr netCryptoSession)
128 139
@@ -239,18 +250,24 @@ cryptoNetHandler sessions addr (NetCrypto (CryptoPacket nonce16 encrypted)) = do
239 hookmap <- atomically $ readTVar ncHooks 250 hookmap <- atomically $ readTVar ncHooks
240 -- run hook 251 -- run hook
241 flip fix (cd,hookmap) $ \lookupAgain (cd,hookmap) -> do 252 flip fix (cd,hookmap) $ \lookupAgain (cd,hookmap) -> do
253 msgTyps <- atomically $ readTVar ncMessageTypes
242 let msgTyp = cd ^. messageType 254 let msgTyp = cd ^. messageType
243 case Map.lookup msgTyp hookmap of 255 msgTypMapped16 = msgTypes ! msgId cd
256 msgTypMapped = fromIntegral msgTypMapped16
257 if msgTypMapped16 == 0
258 then return id
259 else
260 case Map.lookup msgTypMapped hookmap of
244 Nothing -> do -- no recognizing hook, run ncUnrecognizedHook0, loopAgain on result 261 Nothing -> do -- no recognizing hook, run ncUnrecognizedHook0, loopAgain on result
245 unrecognize <- atomically $ readTVar (ncUnrecognizedHook session) 262 unrecognize <- atomically $ readTVar (ncUnrecognizedHook session)
246 mbConsume <- unrecognize msgTyp session cd 263 mbConsume <- unrecognize msgTypMapped session cd
247 case mbConsume of 264 case mbConsume of
248 Just f -> do 265 Just f -> do
249 -- ncUnrecognizedHook0 may have updated the hookmap 266 -- ncUnrecognizedHook0 may have updated the hookmap
250 hookmap' <- atomically $ readTVar ncHooks 267 hookmap' <- atomically $ readTVar ncHooks
251 lookupAgain (f cd,hookmap') 268 lookupAgain (f cd,hookmap')
252 Nothing -> return Nothing 269 Nothing -> return Nothing
253 Just hooks -> flip fix (hooks,cd,msgTyp) $ \loop (hooks,cd,typ) -> do 270 Just hooks -> flip fix (hooks,cd,msgTypMapped) $ \loop (hooks,cd,typ) -> do
254 let _ = cd :: CryptoData 271 let _ = cd :: CryptoData
255 case (hooks,cd) of 272 case (hooks,cd) of
256 ([],_) -> return Nothing 273 ([],_) -> return Nothing
@@ -269,6 +286,42 @@ cryptoNetHandler sessions addr (NetCrypto (CryptoPacket nonce16 encrypted)) = do
269 _ -> error "unreachable-last2Bytes" 286 _ -> error "unreachable-last2Bytes"
270 dATA_NUM_THRESHOLD = 21845 -- = 65535 / 3 287 dATA_NUM_THRESHOLD = 21845 -- = 65535 / 3
271 288
289-- | construct a 'MsgTypeArray' for specified types, using their known common positions
290-- in the MessageId space if they have such a thing.
291mkMsgTypes :: [MessageType] -> MsgTypeArray
292mkMsgTypes msgs = let zeros = A.listArray (0,255) (replicate 256 0)
293 in zeros A.// map (\x -> (toIndex x,toWord16 x)) msgs
294 where
295 toIndex (Msg mid) = fromIntegral . fromEnum $ mid
296 toIndex (GrpMsg KnownLossless nam) = 0x63 -- fromEnum MESSAGE_GROUPCHAT
297 toIndex (GrpMsg KnownLossy nam) = 0xC7 -- fromEnum LOSSY_GROUPCHAT
298
299-- | Handle all Tox messages that this code base is aware of.
300allMsgTypes :: MsgTypeArray
301allMsgTypes = A.listArray (minBound,maxBound) (0:knownMsgs)
302 where
303 knownMsgs :: [Word16]
304 knownMsgs =
305 concat [ map (fromIntegral . fromEnum) [ PacketRequest .. KillPacket ]
306 , map (const 0) [ 3 .. 15 ] -- UnspecifiedPacket
307 , map (const 0) [ 16 .. 23 ] -- MessengerLoseless
308 , map (fromIntegral . fromEnum) [ ONLINE .. OFFLINE ]
309 , map (const 0) [ 26 .. 47 ] -- MessengerLoseless
310 , map (fromIntegral . fromEnum) [ NICKNAME .. TYPING ]
311 , map (const 0) [ 52 .. 63 ] -- MessengerLoseless
312 , map (fromIntegral . fromEnum) [ MESSAGE .. ACTION ]
313 , map (const 0) [ 66 .. 68 ] -- MessengerLoseless
314 , map (fromIntegral . fromEnum) [ MSI ]
315 , map (const 0) [ 70 .. 79 ] -- MessengerLoseless
316 , map (fromIntegral . fromEnum) [ FILE_SENDREQUEST .. FILE_DATA ]
317 , map (const 0) [ 83 .. 95 ] -- MessengerLoseless
318 , map (fromIntegral . fromEnum) [ INVITE_GROUPCHAT .. MESSAGE_GROUPCHAT ]
319 , map (const 0) [ 100 .. 191 ] -- MessengerLoseless
320 , map (const 0) [ 192 .. 198 ] -- MessengerLossy
321 , map (fromIntegral . fromEnum) [ LOSSY_GROUPCHAT ]
322 , map (const 0) [ 200 .. 255 ] -- All lossy, exept the last
323 ]
324
272-- | handles nothing 325-- | handles nothing
273defaultCryptoDataHooks :: Map.Map MessageType [NetCryptoHook] 326defaultCryptoDataHooks :: Map.Map MessageType [NetCryptoHook]
274defaultCryptoDataHooks = Map.empty 327defaultCryptoDataHooks = Map.empty