diff options
Diffstat (limited to 'src/Network/Tox/Crypto/Handlers.hs')
-rw-r--r-- | src/Network/Tox/Crypto/Handlers.hs | 73 |
1 files changed, 69 insertions, 4 deletions
diff --git a/src/Network/Tox/Crypto/Handlers.hs b/src/Network/Tox/Crypto/Handlers.hs index edfcb260..6a79da1b 100644 --- a/src/Network/Tox/Crypto/Handlers.hs +++ b/src/Network/Tox/Crypto/Handlers.hs | |||
@@ -1,5 +1,6 @@ | |||
1 | {-# LANGUAGE NamedFieldPuns #-} | 1 | {-# LANGUAGE NamedFieldPuns #-} |
2 | {-# LANGUAGE TupleSections #-} | 2 | {-# LANGUAGE TupleSections #-} |
3 | {-# LANGUAGE TypeOperators #-} | ||
3 | module Network.Tox.Crypto.Handlers where | 4 | module Network.Tox.Crypto.Handlers where |
4 | 5 | ||
5 | import Network.Tox.NodeId | 6 | import Network.Tox.NodeId |
@@ -22,6 +23,7 @@ import qualified Data.PacketQueue as PQ | |||
22 | ;import Data.PacketQueue (PacketQueue) | 23 | ;import Data.PacketQueue (PacketQueue) |
23 | import Data.Serialize as S | 24 | import Data.Serialize as S |
24 | import Data.Word | 25 | import Data.Word |
26 | import qualified Data.Word64Map as W64 | ||
25 | import GHC.Conc (unsafeIOToSTM) | 27 | import GHC.Conc (unsafeIOToSTM) |
26 | import qualified Data.Set as Set | 28 | import qualified Data.Set as Set |
27 | import qualified Data.Array.Unboxed as A | 29 | import qualified Data.Array.Unboxed as A |
@@ -32,6 +34,7 @@ import System.Environment | |||
32 | import System.Directory | 34 | import System.Directory |
33 | import Control.Concurrent | 35 | import Control.Concurrent |
34 | import GHC.Conc (labelThread) | 36 | import GHC.Conc (labelThread) |
37 | import System.IO.Unsafe(unsafeDupablePerformIO {- unsafeIOToSTM -}) | ||
35 | 38 | ||
36 | -- util, todo: move to another module | 39 | -- util, todo: move to another module |
37 | maybeToEither :: Maybe b -> Either String b | 40 | maybeToEither :: Maybe b -> Either String b |
@@ -45,7 +48,10 @@ data NetCryptoSessionStatus = Unaccepted | Accepted | Confirmed | |||
45 | type IOHook addr x = addr -> x -> IO (Maybe (x -> x)) | 48 | type IOHook addr x = addr -> x -> IO (Maybe (x -> x)) |
46 | type NetCryptoHook = IOHook NetCryptoSession CryptoData | 49 | type NetCryptoHook = IOHook NetCryptoSession CryptoData |
47 | type MsgTypeArray = A.UArray Word8 Word16 | 50 | type MsgTypeArray = A.UArray Word8 Word16 |
48 | 51 | type MsgOutMap = W64.Word64Map Word8 | |
52 | -- type MsgOutMap = A.UArray Word64 Word8 -- if above is too slow, switch to this, but use reasonable bounds | ||
53 | msgOutMapLookup :: Word64 -> MsgOutMap -> Maybe Word8 | ||
54 | msgOutMapLookup = W64.lookup | ||
49 | 55 | ||
50 | -- | Information, that may be made visible in multiple sessions, as well | 56 | -- | Information, that may be made visible in multiple sessions, as well |
51 | -- as displayed in some way to the user via mutiple views. | 57 | -- as displayed in some way to the user via mutiple views. |
@@ -86,7 +92,7 @@ data NetCryptoSession = NCrypto { ncState :: TVar NetCryptoSessionStatu | |||
86 | -- may not be in ncHooks yet, but they should appear | 92 | -- may not be in ncHooks yet, but they should appear |
87 | -- here if ncUnrecognizedHook will add them to ncHooks | 93 | -- here if ncUnrecognizedHook will add them to ncHooks |
88 | -- on an as-need basis. | 94 | -- on an as-need basis. |
89 | , ncOutgoingTypeArray :: TVar MsgTypeArray | 95 | , ncOutgoingIdMap :: TVar MsgOutMap |
90 | , ncAllSessions :: NetCryptoSessions -- ^ may be needed if one net-crypto session | 96 | , ncAllSessions :: NetCryptoSessions -- ^ may be needed if one net-crypto session |
91 | -- needs to possibly start another, as is | 97 | -- needs to possibly start another, as is |
92 | -- the case in group chats | 98 | -- the case in group chats |
@@ -94,6 +100,7 @@ data NetCryptoSession = NCrypto { ncState :: TVar NetCryptoSessionStatu | |||
94 | , ncPacketQueue :: PacketQueue CryptoData | 100 | , ncPacketQueue :: PacketQueue CryptoData |
95 | , ncBufferStart :: TVar Word32 | 101 | , ncBufferStart :: TVar Word32 |
96 | , ncDequeueThread :: Maybe ThreadId | 102 | , ncDequeueThread :: Maybe ThreadId |
103 | , ncOutgoingQueue :: PQ.PacketOutQueue (State,Nonce24,TVar MsgOutMap) CryptoMessage (CryptoPacket Encrypted) CryptoData | ||
97 | } | 104 | } |
98 | 105 | ||
99 | data NetCryptoSessions = NCSessions { netCryptoSessions :: TVar (Map.Map SockAddr NetCryptoSession) | 106 | data NetCryptoSessions = NCSessions { netCryptoSessions :: TVar (Map.Map SockAddr NetCryptoSession) |
@@ -104,6 +111,7 @@ data NetCryptoSessions = NCSessions { netCryptoSessions :: TVar (Map.Map SockAdd | |||
104 | , sessionView :: SessionView | 111 | , sessionView :: SessionView |
105 | , msgTypeArray :: MsgTypeArray | 112 | , msgTypeArray :: MsgTypeArray |
106 | , inboundQueueCapacity :: Word32 | 113 | , inboundQueueCapacity :: Word32 |
114 | , outboundQueueCapacity :: Word32 | ||
107 | , nextSessionId :: TVar SessionID | 115 | , nextSessionId :: TVar SessionID |
108 | } | 116 | } |
109 | 117 | ||
@@ -168,6 +176,7 @@ newSessionsState crypto unrechook hooks = do | |||
168 | } | 176 | } |
169 | , msgTypeArray = allMsgTypes -- todo make this a parameter | 177 | , msgTypeArray = allMsgTypes -- todo make this a parameter |
170 | , inboundQueueCapacity = 200 | 178 | , inboundQueueCapacity = 200 |
179 | , outboundQueueCapacity = 400 | ||
171 | , nextSessionId = nextSessionId0 | 180 | , nextSessionId = nextSessionId0 |
172 | } | 181 | } |
173 | 182 | ||
@@ -208,6 +217,53 @@ newHandShakeData crypto basenonce (HParam {hpOtherCookie,hpMySecretKey,hpCookieR | |||
208 | , otherCookie = freshCookie' | 217 | , otherCookie = freshCookie' |
209 | }) freshCookie | 218 | }) freshCookie |
210 | 219 | ||
220 | type XMessage = CryptoMessage -- todo | ||
221 | |||
222 | ncToWire :: STM (State,Nonce24,TVar MsgOutMap) | ||
223 | -> Word32{- packet number we expect to recieve -} | ||
224 | -> Word32{- buffer_end -} | ||
225 | -> Word32{- packet number -} | ||
226 | -> XMessage | ||
227 | -> STM (Maybe (CryptoPacket Encrypted,Word32{-next packet no-})) | ||
228 | ncToWire getState seqno bufend pktno msg = do | ||
229 | let typ = getMessageType msg | ||
230 | typ64 = toWord64 typ | ||
231 | let lsness msg = | ||
232 | case typ of | ||
233 | Msg mid -> lossyness mid | ||
234 | GrpMsg KnownLossy _ -> Lossy | ||
235 | GrpMsg KnownLossless _ -> Lossless | ||
236 | (state,n24,msgOutMapVar) <- getState | ||
237 | msgOutMap <- readTVar msgOutMapVar | ||
238 | case msgOutMapLookup typ64 msgOutMap of | ||
239 | Just outid -> do | ||
240 | let setMessageId (OneByte _) mid = OneByte (toEnum8 mid) | ||
241 | setMessageId (TwoByte _ x) mid = TwoByte (toEnum8 mid) x | ||
242 | setMessageId (UpToN _ x) mid = UpToN (toEnum8 mid) x | ||
243 | msg' = setMessageId msg outid | ||
244 | in case lsness msg of | ||
245 | UnknownLossyness -> return Nothing | ||
246 | Lossy -> let cd = | ||
247 | CryptoData | ||
248 | { bufferStart = seqno | ||
249 | , bufferEnd = bufend | ||
250 | , bufferData = msg' | ||
251 | } | ||
252 | plain = encodePlain cd | ||
253 | encrypted = encrypt state plain | ||
254 | pkt = CryptoPacket { pktNonce = nonce24ToWord16 n24, pktData = encrypted } | ||
255 | in return (Just (pkt, pktno)) | ||
256 | Lossless -> let cd = | ||
257 | CryptoData | ||
258 | { bufferStart = seqno | ||
259 | , bufferEnd = pktno | ||
260 | , bufferData = msg' | ||
261 | } | ||
262 | plain = encodePlain cd | ||
263 | encrypted = encrypt state plain | ||
264 | pkt = CryptoPacket { pktNonce = nonce24ToWord16 n24, pktData = encrypted } | ||
265 | in return (Just (pkt, pktno+1)) | ||
266 | |||
211 | -- | called when we recieve a crypto handshake with valid cookie | 267 | -- | called when we recieve a crypto handshake with valid cookie |
212 | -- TODO set priority on contact addr to 0 if it is older than ForgetPeriod, | 268 | -- TODO set priority on contact addr to 0 if it is older than ForgetPeriod, |
213 | -- then increment it regardless. (Keep addr in MinMaxPSQ in Roster.Contact) | 269 | -- then increment it regardless. (Keep addr in MinMaxPSQ in Roster.Contact) |
@@ -250,10 +306,18 @@ freshCryptoSession sessions | |||
250 | ncHooks0 <- atomically $ newTVar (defaultHooks sessions) | 306 | ncHooks0 <- atomically $ newTVar (defaultHooks sessions) |
251 | ncUnrecognizedHook0 <- atomically $ newTVar (defaultUnrecognizedHook sessions) | 307 | ncUnrecognizedHook0 <- atomically $ newTVar (defaultUnrecognizedHook sessions) |
252 | ncIncomingTypeArray0 <- atomically $ newTVar (msgTypeArray sessions) | 308 | ncIncomingTypeArray0 <- atomically $ newTVar (msgTypeArray sessions) |
253 | ncOutgoingTypeArray0 <- atomically $ newTVar allMsgTypes | 309 | ncOutgoingIdMap0 <- atomically $ newTVar W64.empty |
254 | ncView0 <- atomically $ newTVar (sessionView sessions) | 310 | ncView0 <- atomically $ newTVar (sessionView sessions) |
255 | pktq <- atomically $ PQ.new (inboundQueueCapacity sessions) 0 | 311 | pktq <- atomically $ PQ.new (inboundQueueCapacity sessions) 0 |
256 | bufstart <- atomically $ newTVar 0 | 312 | bufstart <- atomically $ newTVar 0 |
313 | let toWireIO = do | ||
314 | f <- lookupNonceFunction crypto newsession theirSessionKey | ||
315 | atomically $ do | ||
316 | n24 <- readTVar ncMyPacketNonce0 | ||
317 | let n24plus1 = unsafeDupablePerformIO (incrementNonce24 n24) | ||
318 | writeTVar ncMyPacketNonce0 n24plus1 | ||
319 | return (return (f n24, n24, ncOutgoingIdMap0)) | ||
320 | pktoq <- atomically $ PQ.newOutGoing pktq ncToWire toWireIO 0 (outboundQueueCapacity sessions) 0 | ||
257 | let netCryptoSession0 = | 321 | let netCryptoSession0 = |
258 | NCrypto { ncState = ncState0 | 322 | NCrypto { ncState = ncState0 |
259 | , ncSessionId = sessionId | 323 | , ncSessionId = sessionId |
@@ -270,11 +334,12 @@ freshCryptoSession sessions | |||
270 | , ncUnrecognizedHook = ncUnrecognizedHook0 | 334 | , ncUnrecognizedHook = ncUnrecognizedHook0 |
271 | , ncAllSessions = sessions | 335 | , ncAllSessions = sessions |
272 | , ncIncomingTypeArray = ncIncomingTypeArray0 | 336 | , ncIncomingTypeArray = ncIncomingTypeArray0 |
273 | , ncOutgoingTypeArray = ncOutgoingTypeArray0 | 337 | , ncOutgoingIdMap = ncOutgoingIdMap0 |
274 | , ncView = ncView0 | 338 | , ncView = ncView0 |
275 | , ncPacketQueue = pktq | 339 | , ncPacketQueue = pktq |
276 | , ncBufferStart = bufstart | 340 | , ncBufferStart = bufstart |
277 | , ncDequeueThread = Nothing -- error "you want the NetCrypto-Dequeue thread id, but is it started?" | 341 | , ncDequeueThread = Nothing -- error "you want the NetCrypto-Dequeue thread id, but is it started?" |
342 | , ncOutgoingQueue = pktoq | ||
278 | } | 343 | } |
279 | threadid <- forkIO $ do | 344 | threadid <- forkIO $ do |
280 | tid <- myThreadId | 345 | tid <- myThreadId |