diff options
Diffstat (limited to 'src')
-rw-r--r-- | src/Network/Tox/Crypto/Handlers.hs | 97 | ||||
-rw-r--r-- | src/Network/Tox/Crypto/Transport.hs | 19 |
2 files changed, 78 insertions, 38 deletions
diff --git a/src/Network/Tox/Crypto/Handlers.hs b/src/Network/Tox/Crypto/Handlers.hs index 0cb2d4db..d6f2de7e 100644 --- a/src/Network/Tox/Crypto/Handlers.hs +++ b/src/Network/Tox/Crypto/Handlers.hs | |||
@@ -13,6 +13,7 @@ import Control.Applicative | |||
13 | import Control.Monad | 13 | import Control.Monad |
14 | import Data.Time.Clock.POSIX | 14 | import Data.Time.Clock.POSIX |
15 | import qualified Data.ByteString as B | 15 | import qualified Data.ByteString as B |
16 | import Data.ByteString (ByteString) | ||
16 | import Control.Lens | 17 | import Control.Lens |
17 | import Data.Function | 18 | import Data.Function |
18 | import Data.Serialize as S | 19 | import Data.Serialize as S |
@@ -34,6 +35,21 @@ type IOHook addr x = addr -> x -> IO (Maybe (x -> x)) | |||
34 | type NetCryptoHook = IOHook NetCryptoSession CryptoData | 35 | type NetCryptoHook = IOHook NetCryptoSession CryptoData |
35 | type MsgTypeArray = A.UArray Word8 Word16 | 36 | type MsgTypeArray = A.UArray Word8 Word16 |
36 | 37 | ||
38 | |||
39 | -- | Information, that may be made visible in multiple sessions, as well | ||
40 | -- as displayed in some way to the user via mutiple views. | ||
41 | data SessionView = SessionView | ||
42 | { svNick :: TVar ByteString | ||
43 | , svStatus :: TVar UserStatus | ||
44 | , svStatusMsg :: TVar ByteString | ||
45 | , svGroups :: TVar (Map.Map GroupChatId (Set.Set SockAddr)) | ||
46 | , svCacheDir :: FilePath -- ^ directory path used if the session has to use the disk for cache | ||
47 | -- clean up only if space is needed | ||
48 | , svTmpDir :: FilePath -- Once off storage goes here, should clean up quickly | ||
49 | , svConfigDir :: FilePath -- profile related storage, etc, never clean up | ||
50 | } | ||
51 | |||
52 | |||
37 | data NetCryptoSession = NCrypto { ncState :: TVar NetCryptoSessionStatus | 53 | data NetCryptoSession = NCrypto { ncState :: TVar NetCryptoSessionStatus |
38 | , ncTheirBaseNonce :: TVar Nonce24 -- base nonce + packet number | 54 | , ncTheirBaseNonce :: TVar Nonce24 -- base nonce + packet number |
39 | , ncMyPacketNonce :: TVar Nonce24 -- base nonce + packet number | 55 | , ncMyPacketNonce :: TVar Nonce24 -- base nonce + packet number |
@@ -54,23 +70,29 @@ data NetCryptoSession = NCrypto { ncState :: TVar NetCryptoSessionStatus | |||
54 | , ncAllSessions :: NetCryptoSessions -- ^ may be needed if one net-crypto session | 70 | , ncAllSessions :: NetCryptoSessions -- ^ may be needed if one net-crypto session |
55 | -- needs to possibly start another, as is | 71 | -- needs to possibly start another, as is |
56 | -- the case in group chats | 72 | -- the case in group chats |
57 | , ncGroups :: TVar (Map.Map GroupChatId (Set.Set SockAddr)) | 73 | , ncView :: TVar SessionView |
58 | } | 74 | } |
59 | 75 | ||
60 | data NetCryptoSessions = NCSessions { netCryptoSessions :: TVar (Map.Map SockAddr NetCryptoSession) | 76 | data NetCryptoSessions = NCSessions { netCryptoSessions :: TVar (Map.Map SockAddr NetCryptoSession) |
61 | , transportCrypto :: TransportCrypto | 77 | , transportCrypto :: TransportCrypto |
62 | , defaultHooks :: Map.Map MessageType [NetCryptoHook] | 78 | , defaultHooks :: Map.Map MessageType [NetCryptoHook] |
63 | , defaultUnrecognizedHook :: MessageType -> NetCryptoHook | 79 | , defaultUnrecognizedHook :: MessageType -> NetCryptoHook |
80 | , sessionView :: SessionView | ||
64 | , msgTypeArray :: MsgTypeArray | 81 | , msgTypeArray :: MsgTypeArray |
65 | } | 82 | } |
66 | 83 | ||
67 | newSessionsState :: TransportCrypto -> (MessageType -> NetCryptoHook) -> Map.Map MessageType [NetCryptoHook] -> IO NetCryptoSessions | 84 | newSessionsState :: TransportCrypto -> (MessageType -> NetCryptoHook) -> Map.Map MessageType [NetCryptoHook] -> IO NetCryptoSessions |
68 | newSessionsState crypto unrechook hooks = do | 85 | newSessionsState crypto unrechook hooks = do |
69 | x <- atomically $ newTVar Map.empty | 86 | x <- atomically $ newTVar Map.empty |
87 | nick <- atomically $ newTVar B.empty | ||
88 | status <- atomically $ newTVar Online | ||
89 | statusmsg <- atomically $ newTVar B.empty | ||
90 | grps <- atomically $ newTVar Map.empty | ||
70 | return NCSessions { netCryptoSessions = x | 91 | return NCSessions { netCryptoSessions = x |
71 | , transportCrypto = crypto | 92 | , transportCrypto = crypto |
72 | , defaultHooks = hooks | 93 | , defaultHooks = hooks |
73 | , defaultUnrecognizedHook = unrechook | 94 | , defaultUnrecognizedHook = unrechook |
95 | , sessionView = SessionView { svNick = nick, svStatus = status, svStatusMsg = statusmsg, svGroups = grps } | ||
74 | , msgTypeArray = allMsgTypes -- todo make this a parameter | 96 | , msgTypeArray = allMsgTypes -- todo make this a parameter |
75 | } | 97 | } |
76 | 98 | ||
@@ -117,8 +139,8 @@ freshCryptoSession sessions | |||
117 | newsession <- generateSecretKey | 139 | newsession <- generateSecretKey |
118 | ncHooks0 <- atomically $ newTVar (defaultHooks sessions) | 140 | ncHooks0 <- atomically $ newTVar (defaultHooks sessions) |
119 | ncUnrecognizedHook0 <- atomically $ newTVar (defaultUnrecognizedHook sessions) | 141 | ncUnrecognizedHook0 <- atomically $ newTVar (defaultUnrecognizedHook sessions) |
120 | ncGroups0 <- atomically $ newTVar (Map.empty) | ||
121 | ncMessageTypes0 <- atomically $ newTVar (msgTypeArray sessions) | 142 | ncMessageTypes0 <- atomically $ newTVar (msgTypeArray sessions) |
143 | ncView0 <- atomically $ newTVar (sessionView sessions) | ||
122 | let netCryptoSession = | 144 | let netCryptoSession = |
123 | NCrypto { ncState = ncState0 | 145 | NCrypto { ncState = ncState0 |
124 | , ncTheirBaseNonce= ncTheirBaseNonce0 | 146 | , ncTheirBaseNonce= ncTheirBaseNonce0 |
@@ -132,8 +154,8 @@ freshCryptoSession sessions | |||
132 | , ncHooks = ncHooks0 | 154 | , ncHooks = ncHooks0 |
133 | , ncUnrecognizedHook = ncUnrecognizedHook0 | 155 | , ncUnrecognizedHook = ncUnrecognizedHook0 |
134 | , ncAllSessions = sessions | 156 | , ncAllSessions = sessions |
135 | , ncGroups = ncGroups0 | ||
136 | , ncMessageTypes = ncMessageTypes0 | 157 | , ncMessageTypes = ncMessageTypes0 |
158 | , ncView = ncView0 | ||
137 | } | 159 | } |
138 | atomically $ modifyTVar allsessions (Map.insert addr netCryptoSession) | 160 | atomically $ modifyTVar allsessions (Map.insert addr netCryptoSession) |
139 | 161 | ||
@@ -247,38 +269,7 @@ cryptoNetHandler sessions addr (NetCrypto (CryptoPacket nonce16 encrypted)) = do | |||
247 | writeTVar ncTheirBaseNonce y | 269 | writeTVar ncTheirBaseNonce y |
248 | -- then set session confirmed, | 270 | -- then set session confirmed, |
249 | atomically $ writeTVar ncState Confirmed | 271 | atomically $ writeTVar ncState Confirmed |
250 | hookmap <- atomically $ readTVar ncHooks | 272 | runCryptoHook session cd |
251 | -- run hook | ||
252 | flip fix (cd,hookmap) $ \lookupAgain (cd,hookmap) -> do | ||
253 | msgTyps <- atomically $ readTVar ncMessageTypes | ||
254 | let msgTyp = cd ^. messageType | ||
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 | ||
261 | Nothing -> do -- no recognizing hook, run ncUnrecognizedHook0, loopAgain on result | ||
262 | unrecognize <- atomically $ readTVar (ncUnrecognizedHook session) | ||
263 | mbConsume <- unrecognize msgTypMapped session cd | ||
264 | case mbConsume of | ||
265 | Just f -> do | ||
266 | -- ncUnrecognizedHook0 may have updated the hookmap | ||
267 | hookmap' <- atomically $ readTVar ncHooks | ||
268 | lookupAgain (f cd,hookmap') | ||
269 | Nothing -> return Nothing | ||
270 | Just hooks -> flip fix (hooks,cd,msgTypMapped) $ \loop (hooks,cd,typ) -> do | ||
271 | let _ = cd :: CryptoData | ||
272 | case (hooks,cd) of | ||
273 | ([],_) -> return Nothing | ||
274 | (hook:more,cd) -> do | ||
275 | r <- hook session cd :: IO (Maybe (CryptoData -> CryptoData)) | ||
276 | case r of | ||
277 | Just f -> let newcd = f cd | ||
278 | newtyp = newcd ^. messageType | ||
279 | in if newtyp == typ then loop (more,newcd,newtyp) | ||
280 | else lookupAgain (newcd,hookmap) | ||
281 | Nothing -> return Nothing -- message consumed | ||
282 | where | 273 | where |
283 | last2Bytes :: Nonce24 -> Word | 274 | last2Bytes :: Nonce24 -> Word |
284 | last2Bytes (Nonce24 bs) = case S.decode (B.drop 22 bs) of | 275 | last2Bytes (Nonce24 bs) = case S.decode (B.drop 22 bs) of |
@@ -286,6 +277,42 @@ cryptoNetHandler sessions addr (NetCrypto (CryptoPacket nonce16 encrypted)) = do | |||
286 | _ -> error "unreachable-last2Bytes" | 277 | _ -> error "unreachable-last2Bytes" |
287 | dATA_NUM_THRESHOLD = 21845 -- = 65535 / 3 | 278 | dATA_NUM_THRESHOLD = 21845 -- = 65535 / 3 |
288 | 279 | ||
280 | runCryptoHook :: NetCryptoSession -> CryptoData -> IO (Maybe (x -> x)) | ||
281 | runCryptoHook session@(NCrypto {ncState, ncHooks,ncSessionSecret,ncTheirSessionPublic,ncTheirBaseNonce,ncMessageTypes}) | ||
282 | cd@(CryptoData {bufferStart, bufferEnd, bufferData=cm}) = do | ||
283 | hookmap <- atomically $ readTVar ncHooks | ||
284 | -- run hook | ||
285 | flip fix (cd,hookmap) $ \lookupAgain (cd,hookmap) -> do | ||
286 | msgTypes <- atomically $ readTVar ncMessageTypes | ||
287 | let msgTyp = cd ^. messageType | ||
288 | msgTypMapped16 = msgTypes A.! fromEnum8 (msgID cm) | ||
289 | msgTypMapped = fromWord16 $ msgTypMapped16 | ||
290 | if msgTypMapped16 == 0 | ||
291 | then return $ Just id | ||
292 | else | ||
293 | case Map.lookup msgTypMapped hookmap of | ||
294 | Nothing -> do -- no recognizing hook, run ncUnrecognizedHook0, loopAgain on result | ||
295 | unrecognize <- atomically $ readTVar (ncUnrecognizedHook session) | ||
296 | mbConsume <- unrecognize msgTypMapped session cd | ||
297 | case mbConsume of | ||
298 | Just f -> do | ||
299 | -- ncUnrecognizedHook0 may have updated the hookmap | ||
300 | hookmap' <- atomically $ readTVar ncHooks | ||
301 | lookupAgain (f cd,hookmap') | ||
302 | Nothing -> return Nothing | ||
303 | Just hooks -> flip fix (hooks,cd,msgTypMapped) $ \loop (hooks,cd,typ) -> do | ||
304 | let _ = cd :: CryptoData | ||
305 | case (hooks,cd) of | ||
306 | ([],_) -> return Nothing | ||
307 | (hook:more,cd) -> do | ||
308 | r <- hook session cd :: IO (Maybe (CryptoData -> CryptoData)) | ||
309 | case r of | ||
310 | Just f -> let newcd = f cd | ||
311 | newtyp = newcd ^. messageType | ||
312 | in if newtyp == typ then loop (more,newcd,newtyp) | ||
313 | else lookupAgain (newcd,hookmap) | ||
314 | Nothing -> return Nothing -- message consumed | ||
315 | |||
289 | -- | construct a 'MsgTypeArray' for specified types, using their known common positions | 316 | -- | construct a 'MsgTypeArray' for specified types, using their known common positions |
290 | -- in the MessageId space if they have such a thing. | 317 | -- in the MessageId space if they have such a thing. |
291 | mkMsgTypes :: [MessageType] -> MsgTypeArray | 318 | mkMsgTypes :: [MessageType] -> MsgTypeArray |
diff --git a/src/Network/Tox/Crypto/Transport.hs b/src/Network/Tox/Crypto/Transport.hs index 35b4904e..21100c86 100644 --- a/src/Network/Tox/Crypto/Transport.hs +++ b/src/Network/Tox/Crypto/Transport.hs | |||
@@ -48,6 +48,9 @@ module Network.Tox.Crypto.Transport | |||
48 | , isIndirectGrpChat | 48 | , isIndirectGrpChat |
49 | , LossyOrLossless(..) | 49 | , LossyOrLossless(..) |
50 | , lossyness | 50 | , lossyness |
51 | , fromEnum8 | ||
52 | , fromEnum16 | ||
53 | , toEnum8 | ||
51 | ) where | 54 | ) where |
52 | 55 | ||
53 | import Crypto.Tox | 56 | import Crypto.Tox |
@@ -61,6 +64,7 @@ import Data.ByteString as B | |||
61 | import Data.Maybe | 64 | import Data.Maybe |
62 | import Data.Monoid | 65 | import Data.Monoid |
63 | import Data.Word | 66 | import Data.Word |
67 | import Data.Bits | ||
64 | import Crypto.Hash | 68 | import Crypto.Hash |
65 | import Control.Lens | 69 | import Control.Lens |
66 | import Data.Text as T | 70 | import Data.Text as T |
@@ -418,14 +422,23 @@ class AsWord16 a where | |||
418 | 422 | ||
419 | toEnum8 ::Enum a => Word8 -> a | 423 | toEnum8 ::Enum a => Word8 -> a |
420 | toEnum8 = toEnum . fromIntegral | 424 | toEnum8 = toEnum . fromIntegral |
425 | fromEnum8 :: Enum a => a -> Word8 | ||
426 | fromEnum8 = fromIntegral . fromEnum | ||
427 | |||
421 | fromEnum16 :: Enum a => a -> Word16 | 428 | fromEnum16 :: Enum a => a -> Word16 |
422 | fromEnum16 = fromIntegral . fromEnum | 429 | fromEnum16 = fromIntegral . fromEnum |
423 | 430 | ||
431 | |||
432 | -- MessageType, for our client keep it inside 16 bits | ||
433 | -- but we should extend it to 32 or even 64 on the wire. | ||
434 | -- Bits: 000000glxxxxxxxx, x = message id or extension specific, l = if extended, lossy/lossless, g = if extended, nongroup/group | ||
435 | -- (at least one bit set in high byte means extended, if none but the g flag and possibly l flag, assume default grp extension) | ||
424 | instance AsWord16 MessageType where | 436 | instance AsWord16 MessageType where |
425 | toWord16 (Msg msgID) = fromIntegral (fromIntegral (fromEnum16 msgID) :: Word8) | 437 | toWord16 (Msg msgID) = fromIntegral (fromIntegral (fromEnum16 msgID) :: Word8) |
426 | toWord16 (GrpMsg lsy msgName) = 256 * (fromEnum16 lsy + 1) + fromIntegral (fromIntegral (fromEnum msgName) :: Word8) | 438 | toWord16 (GrpMsg lsy msgName) = 512 + 256 * (fromEnum16 lsy) + fromIntegral (fromIntegral (fromEnum msgName) :: Word8) |
427 | fromWord16 x | x < 256 = Msg (toEnum $ fromIntegral x) | 439 | fromWord16 x | x < 256 = Msg (toEnum $ fromIntegral x) |
428 | fromWord16 x = GrpMsg (toEnum8 ((fromIntegral (x `div` 256)) - 1)) (toEnum8 (fromIntegral x :: Word8)) | 440 | fromWord16 x | x < 1024, x .|. 0x0200 == 0x0200 = GrpMsg (toEnum8 (fromIntegral ((x - 512) `div` 256))) (toEnum8 (fromIntegral x :: Word8)) |
441 | fromWord16 x = error "Not clear how to convert Word16 to MessageType" | ||
429 | 442 | ||
430 | word16 :: (Functor f, AsWord16 x) => (Word16 -> f Word16) -> (x -> f x) | 443 | word16 :: (Functor f, AsWord16 x) => (Word16 -> f Word16) -> (x -> f x) |
431 | word16 = lens toWord16 (\_ x -> fromWord16 x) | 444 | word16 = lens toWord16 (\_ x -> fromWord16 x) |