summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Crypto/Tox.hs4
-rw-r--r--src/Network/Kademlia.hs2
-rw-r--r--src/Network/Tox.hs9
-rw-r--r--src/Network/Tox/Crypto/Handlers.hs19
-rw-r--r--src/Network/Tox/NodeId.hs11
-rw-r--r--src/Network/Tox/Onion/Handlers.hs33
6 files changed, 60 insertions, 18 deletions
diff --git a/src/Crypto/Tox.hs b/src/Crypto/Tox.hs
index 71aa99c4..0a7f07c3 100644
--- a/src/Crypto/Tox.hs
+++ b/src/Crypto/Tox.hs
@@ -218,7 +218,7 @@ decryptSymmetric (SymmetricKey symmkey) (Nonce24 n24) (Encrypted bs) = do
218 let (ds, symm') = Symmetric.decrypt bs'' symm 218 let (ds, symm') = Symmetric.decrypt bs'' symm
219 auth = Symmetric.finalize symm' 219 auth = Symmetric.finalize symm'
220 if BA.convert auth /= mac 220 if BA.convert auth /= mac
221 then Left "symmetricDecipher: Auth fail." 221 then Left "Symmetric decryption failed. Incorrect key material?"
222 else return $ Plain ds 222 else return $ Plain ds
223 223
224encryptSymmetric :: SymmetricKey -> Nonce24 -> Plain s x -> Encrypted x 224encryptSymmetric :: SymmetricKey -> Nonce24 -> Plain s x -> Encrypted x
@@ -237,7 +237,7 @@ data State = State Poly1305.State XSalsa.State
237decrypt :: State -> Encrypted a -> Either String (Plain s a) 237decrypt :: State -> Encrypted a -> Either String (Plain s a)
238decrypt (State hash crypt) ciphertext 238decrypt (State hash crypt) ciphertext
239 | (a == mac) = Right (Plain m) 239 | (a == mac) = Right (Plain m)
240 | otherwise = Left "decipherAndAuth: auth fail" 240 | otherwise = Left "Asymmetric decryption failed. Incorrect key material?"
241 where 241 where
242 (mac, c) = authAndBytes ciphertext 242 (mac, c) = authAndBytes ciphertext
243 m = fst . XSalsa.combine crypt $ c 243 m = fst . XSalsa.combine crypt $ c
diff --git a/src/Network/Kademlia.hs b/src/Network/Kademlia.hs
index 8956df2c..0ab26e80 100644
--- a/src/Network/Kademlia.hs
+++ b/src/Network/Kademlia.hs
@@ -26,8 +26,6 @@ import Data.IP
26import Data.Monoid 26import Data.Monoid
27import Data.Serialize (Serialize) 27import Data.Serialize (Serialize)
28import Data.Time.Clock.POSIX (POSIXTime) 28import Data.Time.Clock.POSIX (POSIXTime)
29import qualified Data.Wrapper.PSQInt as Int
30 ;import Data.Wrapper.PSQInt (pattern (:->))
31import Network.Address (bucketRange,genBucketSample) 29import Network.Address (bucketRange,genBucketSample)
32import Network.Kademlia.Search 30import Network.Kademlia.Search
33import System.Entropy 31import System.Entropy
diff --git a/src/Network/Tox.hs b/src/Network/Tox.hs
index 5bd23da8..3c3bce49 100644
--- a/src/Network/Tox.hs
+++ b/src/Network/Tox.hs
@@ -19,7 +19,7 @@ import Debug.Trace
19import Control.Exception hiding (Handler) 19import Control.Exception hiding (Handler)
20import Control.Applicative 20import Control.Applicative
21import Control.Arrow 21import Control.Arrow
22import Control.Concurrent (MVar) 22import Control.Concurrent (MVar,killThread)
23import Control.Concurrent.STM 23import Control.Concurrent.STM
24import Control.Monad 24import Control.Monad
25import Control.Monad.Fix 25import Control.Monad.Fix
@@ -485,18 +485,19 @@ forkTox tox = do
485 quit <- forkListener "toxCrypto" (toxCrypto tox) 485 quit <- forkListener "toxCrypto" (toxCrypto tox)
486 forkPollForRefresh (DHT.refresher4 $ toxRouting tox) 486 forkPollForRefresh (DHT.refresher4 $ toxRouting tox)
487 forkPollForRefresh (DHT.refresher6 $ toxRouting tox) 487 forkPollForRefresh (DHT.refresher6 $ toxRouting tox)
488 return ( quit 488 keygc <- Onion.forkAnnouncedKeysGC (toxAnnouncedKeys tox)
489 return ( killThread keygc >> quit
489 , bootstrap (DHT.refresher4 $ toxRouting tox) 490 , bootstrap (DHT.refresher4 $ toxRouting tox)
490 , bootstrap (DHT.refresher6 $ toxRouting tox) 491 , bootstrap (DHT.refresher6 $ toxRouting tox)
491 ) 492 )
492 493
493-- TODO: Don't export this. 494-- TODO: Don't export this. The exported interface is 'toxAnnounceToLan'.
494announceToLan :: Socket -> NodeId -> IO () 495announceToLan :: Socket -> NodeId -> IO ()
495announceToLan sock nid = do 496announceToLan sock nid = do
496 addrs <- broadcastAddrs 497 addrs <- broadcastAddrs
497 forM_ addrs $ \addr -> do 498 forM_ addrs $ \addr -> do
498 (broadcast_info:_) <- getAddrInfo (Just defaultHints { addrFlags = [AI_NUMERICHOST], addrSocketType = Datagram }) 499 (broadcast_info:_) <- getAddrInfo (Just defaultHints { addrFlags = [AI_NUMERICHOST], addrSocketType = Datagram })
499 (Just addr) -- TODO: Detect broadcast address. 500 (Just addr)
500 (Just "33445") 501 (Just "33445")
501 let broadcast = addrAddress broadcast_info 502 let broadcast = addrAddress broadcast_info
502 bs = S.runPut $ DHT.putMessage (DHT.DHTLanDiscovery nid) 503 bs = S.runPut $ DHT.putMessage (DHT.DHTLanDiscovery nid)
diff --git a/src/Network/Tox/Crypto/Handlers.hs b/src/Network/Tox/Crypto/Handlers.hs
index 5316acc8..e22388a3 100644
--- a/src/Network/Tox/Crypto/Handlers.hs
+++ b/src/Network/Tox/Crypto/Handlers.hs
@@ -2,6 +2,7 @@
2{-# LANGUAGE TupleSections #-} 2{-# LANGUAGE TupleSections #-}
3{-# LANGUAGE TypeOperators #-} 3{-# LANGUAGE TypeOperators #-}
4{-# LANGUAGE DeriveFunctor #-} 4{-# LANGUAGE DeriveFunctor #-}
5{-# LANGUAGE CPP #-}
5module Network.Tox.Crypto.Handlers where 6module Network.Tox.Crypto.Handlers where
6 7
7import Network.Tox.NodeId 8import Network.Tox.NodeId
@@ -40,8 +41,12 @@ import System.IO.Temp
40import System.Environment 41import System.Environment
41import System.Directory 42import System.Directory
42import System.Random -- for ping fuzz 43import System.Random -- for ping fuzz
44#ifdef THREAD_DEBUG
45import Control.Concurrent.Lifted.Instrument
46#else
43import Control.Concurrent 47import Control.Concurrent
44import GHC.Conc (labelThread) 48import GHC.Conc (labelThread)
49#endif
45import PingMachine 50import PingMachine
46import qualified Data.IntMap.Strict as IntMap 51import qualified Data.IntMap.Strict as IntMap
47import Control.Concurrent.Supply 52import Control.Concurrent.Supply
@@ -719,8 +724,8 @@ updateCryptoSession sessions addr newsession timestamp hp session handshake = do
719 dmsg (" ncTheirDHTKey=" ++ show (ncTheirDHTKey session) 724 dmsg (" ncTheirDHTKey=" ++ show (ncTheirDHTKey session)
720 ++ bool "{/=}" "{==}" (ncTheirDHTKey session == HaveDHTKey (hpCookieRemoteDhtkey hp)) 725 ++ bool "{/=}" "{==}" (ncTheirDHTKey session == HaveDHTKey (hpCookieRemoteDhtkey hp))
721 ++ "hpCookieRemoteDhtkey=" ++ show (hpCookieRemoteDhtkey hp)) 726 ++ "hpCookieRemoteDhtkey=" ++ show (hpCookieRemoteDhtkey hp))
722 if ( -- Just ncTheirBaseNonce0 /= hpTheirBaseNonce hp -- XXX: Do we really want to compare base nonce here? 727 if ( toMaybe ncTheirBaseNonce0 /= hpTheirBaseNonce hp
723 -- || 728 ||
724 ncTheirDHTKey session /= HaveDHTKey (hpCookieRemoteDhtkey hp) 729 ncTheirDHTKey session /= HaveDHTKey (hpCookieRemoteDhtkey hp)
725 ) 730 )
726 then freshCryptoSession sessions addr newsession timestamp hp 731 then freshCryptoSession sessions addr newsession timestamp hp
@@ -1042,10 +1047,16 @@ sendCrypto crypto session updateLocal cm = do
1042 PQ.OGEncodeFail -> return (Left "Failed to encode outgoing packet") 1047 PQ.OGEncodeFail -> return (Left "Failed to encode outgoing packet")
1043 1048
1044sendOnline :: TransportCrypto -> NetCryptoSession -> IO (Either String ()) 1049sendOnline :: TransportCrypto -> NetCryptoSession -> IO (Either String ())
1045sendOnline crypto session = sendCrypto crypto session (return ()) (OneByte ONLINE) 1050sendOnline crypto session = do
1051 let cm=OneByte ONLINE
1052 addMsgToLastN False (cm ^. messageType) session (Out cm)
1053 sendCrypto crypto session (return ()) (OneByte ONLINE)
1046 1054
1047sendOffline :: TransportCrypto -> NetCryptoSession -> IO (Either String ()) 1055sendOffline :: TransportCrypto -> NetCryptoSession -> IO (Either String ())
1048sendOffline crypto session = sendCrypto crypto session (return ()) (OneByte OFFLINE) 1056sendOffline crypto session = do
1057 let cm=OneByte OFFLINE
1058 addMsgToLastN False (cm ^. messageType) session (Out cm)
1059 sendCrypto crypto session (return ()) (OneByte OFFLINE)
1049 1060
1050 1061
1051sendKill :: TransportCrypto -> NetCryptoSession -> IO (Either String ()) 1062sendKill :: TransportCrypto -> NetCryptoSession -> IO (Either String ())
diff --git a/src/Network/Tox/NodeId.hs b/src/Network/Tox/NodeId.hs
index 74239710..dab1b14a 100644
--- a/src/Network/Tox/NodeId.hs
+++ b/src/Network/Tox/NodeId.hs
@@ -555,8 +555,14 @@ parseNoSpamJID jid = do
555 _ -> Left "Hostname should be 43 base64 digits followed by .tox." 555 _ -> Left "Hostname should be 43 base64 digits followed by .tox."
556 pub <- id2key <$> readEither base64 556 pub <- id2key <$> readEither base64
557 let ustr = Text.unpack u 557 let ustr = Text.unpack u
558 '$' : b64digits <- Right ustr -- TODO: support 0x prefix also. 558 case ustr of
559 NoSpam nospam (Just x) <- readEither $ map (\case; '?' -> '0'; c -> c) ustr 559 '$' : b64digits -> solveBase64NoSpamID b64digits pub
560 '0' : 'x' : hexdigits -> do nospam <- readEither ('0':'x':hexdigits)
561 return $ NoSpamId nospam pub
562
563solveBase64NoSpamID :: String -> PublicKey -> Either String NoSpamId
564solveBase64NoSpamID b64digits pub = do
565 NoSpam nospam (Just x) <- readEither $ '$' : map (\case; '?' -> '0'; c -> c) b64digits
560 let nlo = fromIntegral (0x0FFFF .&. nospam) :: Word16 566 let nlo = fromIntegral (0x0FFFF .&. nospam) :: Word16
561 nhi = fromIntegral (0x0FFFF .&. (nospam `shiftR` 16)) :: Word16 567 nhi = fromIntegral (0x0FFFF .&. (nospam `shiftR` 16)) :: Word16
562 sum = x `xor` nlo `xor` nhi `xor` xorsum pub 568 sum = x `xor` nlo `xor` nhi `xor` xorsum pub
@@ -583,7 +589,6 @@ parseNoSpamJID jid = do
583 let bitpos = q * 6 + p * 2 589 let bitpos = q * 6 + p * 2
584 ac' = ac `xor` shiftR (fromIntegral b `shiftL` 48) bitpos 590 ac' = ac `xor` shiftR (fromIntegral b `shiftL` 48) bitpos
585 solve ns ac' 591 solve ns ac'
586
587 n64' <- solve ns n64 592 n64' <- solve ns n64
588 let nospam' = fromIntegral (n64' `shiftR` 32) 593 let nospam' = fromIntegral (n64' `shiftR` 32)
589 cksum' = fromIntegral (n64' `shiftR` 16) 594 cksum' = fromIntegral (n64' `shiftR` 16)
diff --git a/src/Network/Tox/Onion/Handlers.hs b/src/Network/Tox/Onion/Handlers.hs
index 99ef3c69..263d60bd 100644
--- a/src/Network/Tox/Onion/Handlers.hs
+++ b/src/Network/Tox/Onion/Handlers.hs
@@ -11,7 +11,7 @@ import Network.QueryResponse as QR hiding (Client)
11import qualified Network.QueryResponse as QR (Client) 11import qualified Network.QueryResponse as QR (Client)
12import Crypto.Tox 12import Crypto.Tox
13import qualified Data.Wrapper.PSQ as PSQ 13import qualified Data.Wrapper.PSQ as PSQ
14 ;import Data.Wrapper.PSQ (PSQ) 14 ;import Data.Wrapper.PSQ (PSQ,pattern (:->))
15#ifdef CRYPTONITE_BACKPORT 15#ifdef CRYPTONITE_BACKPORT
16import Crypto.Error.Types (CryptoFailable (..), 16import Crypto.Error.Types (CryptoFailable (..),
17 throwCryptoError) 17 throwCryptoError)
@@ -35,6 +35,12 @@ import Network.BitTorrent.DHT.Token as Token
35 35
36import Control.Exception hiding (Handler) 36import Control.Exception hiding (Handler)
37import Control.Monad 37import Control.Monad
38#ifdef THREAD_DEBUG
39import Control.Concurrent.Lifted.Instrument
40#else
41import Control.Concurrent
42import GHC.Conc (labelThread)
43#endif
38import Control.Concurrent.STM 44import Control.Concurrent.STM
39import Data.Time.Clock.POSIX (POSIXTime, getPOSIXTime) 45import Data.Time.Clock.POSIX (POSIXTime, getPOSIXTime)
40import Network.Socket 46import Network.Socket
@@ -159,7 +165,7 @@ toOnionDestination (AnnouncedRoute ni rpath) = OnionToOwner ni rpath
159-- structure. 165-- structure.
160-- 166--
161data AnnouncedKeys = AnnouncedKeys 167data AnnouncedKeys = AnnouncedKeys
162 { keyByAge :: !(PSQ NodeId (Down POSIXTime{-Time at which they announced to you-})) -- TODO: timeout of 300 seconds 168 { keyByAge :: !(PSQ NodeId (POSIXTime{-Time at which they announced to you-}))
163 , keyAssoc :: !(MinMaxPSQ' NodeId NodeDistance (Int{-count of route usage-},AnnouncedRoute)) 169 , keyAssoc :: !(MinMaxPSQ' NodeId NodeDistance (Int{-count of route usage-},AnnouncedRoute))
164 -- ^ PSQ using NodeId(user/public key) as Key 170 -- ^ PSQ using NodeId(user/public key) as Key
165 -- and using 'NodeDistance' as priority. 171 -- and using 'NodeDistance' as priority.
@@ -172,12 +178,33 @@ data AnnouncedKeys = AnnouncedKeys
172 178
173insertKey :: POSIXTime -> NodeId -> AnnouncedRoute -> NodeDistance -> AnnouncedKeys -> AnnouncedKeys 179insertKey :: POSIXTime -> NodeId -> AnnouncedRoute -> NodeDistance -> AnnouncedKeys -> AnnouncedKeys
174insertKey tm pub toxpath d keydb = AnnouncedKeys 180insertKey tm pub toxpath d keydb = AnnouncedKeys
175 { keyByAge = PSQ.insert pub (Down tm) (keyByAge keydb) 181 { keyByAge = PSQ.insert pub tm (keyByAge keydb)
176 , keyAssoc = case MinMaxPSQ.lookup' pub (keyAssoc keydb) of 182 , keyAssoc = case MinMaxPSQ.lookup' pub (keyAssoc keydb) of
177 Just (_,(cnt,_)) -> MinMaxPSQ.insert' pub (cnt,toxpath) d (keyAssoc keydb) 183 Just (_,(cnt,_)) -> MinMaxPSQ.insert' pub (cnt,toxpath) d (keyAssoc keydb)
178 Nothing -> MinMaxPSQ.insert' pub (0 ,toxpath) d (keyAssoc keydb) 184 Nothing -> MinMaxPSQ.insert' pub (0 ,toxpath) d (keyAssoc keydb)
179 } 185 }
180 186
187-- | Forks a thread to garbage-collect old key announcements. Keys may be
188-- discarded after 5 minutes.
189forkAnnouncedKeysGC :: TVar AnnouncedKeys -> IO ThreadId
190forkAnnouncedKeysGC db = forkIO $ do
191 myThreadId >>= flip labelThread "gc:toxids"
192 fix $ \loop -> do
193 cutoff <- getPOSIXTime
194 threadDelay 300000000 -- 300 seconds
195 join $ atomically $ do
196 fix $ \gc -> do
197 keys <- readTVar db
198 case PSQ.minView (keyByAge keys) of
199 Nothing -> return loop
200 Just (pub :-> tm,kba')
201 | tm > cutoff -> return loop
202 | otherwise -> do writeTVar db keys
203 { keyByAge = kba'
204 , keyAssoc = MinMaxPSQ.delete pub (keyAssoc keys)
205 }
206 gc
207
181areq :: Message -> Either String AnnounceRequest 208areq :: Message -> Either String AnnounceRequest
182areq (OnionAnnounce asymm) = Right $ fst $ runIdentity $ asymmData asymm 209areq (OnionAnnounce asymm) = Right $ fst $ runIdentity $ asymmData asymm
183areq _ = Left "Unexpected non-announce OnionMessage" 210areq _ = Left "Unexpected non-announce OnionMessage"