summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Data/Torrent.hs18
-rw-r--r--src/Data/Tox/Onion.hs1
-rw-r--r--src/Network/BitTorrent/MainlineDHT.hs2
-rw-r--r--src/Network/Kademlia/Search.hs62
-rw-r--r--src/Network/Tox/Crypto/Transport.hs28
-rw-r--r--src/Network/Tox/DHT/Handlers.hs5
-rw-r--r--src/Network/Tox/Onion/Handlers.hs2
-rw-r--r--src/Network/Tox/TCP.hs8
8 files changed, 63 insertions, 63 deletions
diff --git a/src/Data/Torrent.hs b/src/Data/Torrent.hs
index 69461488..32c709be 100644
--- a/src/Data/Torrent.hs
+++ b/src/Data/Torrent.hs
@@ -42,7 +42,7 @@ module Data.Torrent
42 , FileOffset 42 , FileOffset
43 , FileSize 43 , FileSize
44 , FileInfo (..) 44 , FileInfo (..)
45#ifdef VERSION_lens 45#ifdef USE_lens
46 , fileLength 46 , fileLength
47 , filePath 47 , filePath
48 , fileMD5Sum 48 , fileMD5Sum
@@ -50,7 +50,7 @@ module Data.Torrent
50 50
51 -- ** Layout info 51 -- ** Layout info
52 , LayoutInfo (..) 52 , LayoutInfo (..)
53#ifdef VERSION_lens 53#ifdef USE_lens
54 , singleFile 54 , singleFile
55 , multiFile 55 , multiFile
56 , rootDirName 56 , rootDirName
@@ -90,7 +90,7 @@ module Data.Torrent
90 -- ** Piece control 90 -- ** Piece control
91 , HashList (..) 91 , HashList (..)
92 , PieceInfo (..) 92 , PieceInfo (..)
93#ifdef VERSION_lens 93#ifdef USE_lens
94 , pieceLength 94 , pieceLength
95 , pieceHashes 95 , pieceHashes
96#endif 96#endif
@@ -102,7 +102,7 @@ module Data.Torrent
102 102
103 -- * Info dictionary 103 -- * Info dictionary
104 , InfoDict (..) 104 , InfoDict (..)
105#ifdef VERSION_lens 105#ifdef USE_lens
106 , infohash 106 , infohash
107 , layoutInfo 107 , layoutInfo
108 , pieceInfo 108 , pieceInfo
@@ -115,7 +115,7 @@ module Data.Torrent
115 -- * Torrent file 115 -- * Torrent file
116 , Torrent(..) 116 , Torrent(..)
117 117
118#ifdef VERSION_lens 118#ifdef USE_lens
119 -- ** Lenses 119 -- ** Lenses
120 , announce 120 , announce
121 , announceList 121 , announceList
@@ -378,7 +378,7 @@ data FileInfo a = FileInfo {
378 , Functor, Foldable 378 , Functor, Foldable
379 ) 379 )
380 380
381#ifdef VERSION_lens 381#ifdef USE_lens
382makeLensesFor 382makeLensesFor
383 [ ("fiLength", "fileLength") 383 [ ("fiLength", "fileLength")
384 , ("fiMD5Sum", "fileMD5Sum") 384 , ("fiMD5Sum", "fileMD5Sum")
@@ -467,7 +467,7 @@ data LayoutInfo
467 , liDirName :: !BS.ByteString 467 , liDirName :: !BS.ByteString
468 } deriving (Show, Read, Eq, Typeable) 468 } deriving (Show, Read, Eq, Typeable)
469 469
470#ifdef VERSION_lens 470#ifdef USE_lens
471makeLensesFor 471makeLensesFor
472 [ ("liFile" , "singleFile" ) 472 [ ("liFile" , "singleFile" )
473 , ("liFiles" , "multiFile" ) 473 , ("liFiles" , "multiFile" )
@@ -695,7 +695,7 @@ data PieceInfo = PieceInfo
695 -- ^ Concatenation of all 20-byte SHA1 hash values. 695 -- ^ Concatenation of all 20-byte SHA1 hash values.
696 } deriving (Show, Read, Eq, Typeable) 696 } deriving (Show, Read, Eq, Typeable)
697 697
698#ifdef VERSION_lens 698#ifdef USE_lens
699-- | Number of bytes in each piece. 699-- | Number of bytes in each piece.
700makeLensesFor [("piPieceLength", "pieceLength")] ''PieceInfo 700makeLensesFor [("piPieceLength", "pieceLength")] ''PieceInfo
701 701
@@ -902,7 +902,7 @@ data Torrent = Torrent
902 -- encrypted SHA-1 hash of the info dictionary). 902 -- encrypted SHA-1 hash of the info dictionary).
903 } deriving (Show, Eq, Typeable) 903 } deriving (Show, Eq, Typeable)
904 904
905#ifdef VERSION_lens 905#ifdef USE_lens
906makeLensesFor 906makeLensesFor
907 [ ("tAnnounce" , "announce" ) 907 [ ("tAnnounce" , "announce" )
908 , ("tAnnounceList", "announceList") 908 , ("tAnnounceList", "announceList")
diff --git a/src/Data/Tox/Onion.hs b/src/Data/Tox/Onion.hs
index 85a9d21e..bd802c75 100644
--- a/src/Data/Tox/Onion.hs
+++ b/src/Data/Tox/Onion.hs
@@ -704,6 +704,7 @@ data DataToRoute = DataToRoute
704 { dataFromKey :: PublicKey -- Real public key of sender 704 { dataFromKey :: PublicKey -- Real public key of sender
705 , dataToRoute :: Encrypted OnionData -- (Word8,ByteString) -- DHTPK 0x9c 705 , dataToRoute :: Encrypted OnionData -- (Word8,ByteString) -- DHTPK 0x9c
706 } 706 }
707 deriving Show
707 708
708instance Sized DataToRoute where 709instance Sized DataToRoute where
709 size = ConstSize 32 <> contramap dataToRoute size 710 size = ConstSize 32 <> contramap dataToRoute size
diff --git a/src/Network/BitTorrent/MainlineDHT.hs b/src/Network/BitTorrent/MainlineDHT.hs
index a29657af..6f47e38f 100644
--- a/src/Network/BitTorrent/MainlineDHT.hs
+++ b/src/Network/BitTorrent/MainlineDHT.hs
@@ -1076,6 +1076,8 @@ mainlineSearch qry = Search
1076 { searchSpace = mainlineSpace 1076 { searchSpace = mainlineSpace
1077 , searchNodeAddress = nodeIP &&& nodePort 1077 , searchNodeAddress = nodeIP &&& nodePort
1078 , searchQuery = qry 1078 , searchQuery = qry
1079 , searchAlpha = 8
1080 , searchK = 16
1079 } 1081 }
1080 1082
1081nodeSearch :: MainlineClient -> Search NodeId (IP, PortNumber) () NodeInfo NodeInfo 1083nodeSearch :: MainlineClient -> Search NodeId (IP, PortNumber) () NodeInfo NodeInfo
diff --git a/src/Network/Kademlia/Search.hs b/src/Network/Kademlia/Search.hs
index d3aaae28..e87a8618 100644
--- a/src/Network/Kademlia/Search.hs
+++ b/src/Network/Kademlia/Search.hs
@@ -32,36 +32,38 @@ data Search nid addr tok ni r = Search
32 { searchSpace :: KademliaSpace nid ni 32 { searchSpace :: KademliaSpace nid ni
33 , searchNodeAddress :: ni -> addr 33 , searchNodeAddress :: ni -> addr
34 , searchQuery :: nid -> ni -> IO (Maybe ([ni], [r], Maybe tok)) 34 , searchQuery :: nid -> ni -> IO (Maybe ([ni], [r], Maybe tok))
35 , searchAlpha :: Int -- α = 8
36 -- | 'searchK' should be larger than 'searchAlpha'. How much larger depends on
37 -- how fast the queries are. For Tox's much slower onion-routed queries, we
38 -- need to ensure that closer non-responding queries don't completely push out
39 -- farther away queries.
40 --
41 -- For BitTorrent, setting them both 8 was not an issue, but that is no longer
42 -- supported because now the number of remembered informants is now the
43 -- difference between these two numbers. So, if searchK = 16 and searchAlpha =
44 -- 4, then the number of remembered query responses is 12.
45 , searchK :: Int -- K = 16
35 } 46 }
36 47
37data SearchState nid addr tok ni r = SearchState 48data SearchState nid addr tok ni r = SearchState
38 {-
39 { searchParams :: Search nid addr ni r
40
41 , searchTarget :: nid
42 -- | This action will be performed at least once on each search result.
43 -- It may be invoked multiple times since different nodes may report the
44 -- same result. If the action returns 'False', the search will be
45 -- aborted, otherwise it will continue until it is decided that we've
46 -- asked the closest K nodes to the target.
47 , searchResult :: r -> STM Bool
48
49 -}
50
51 { -- | The number of pending queries. Incremented before any query is sent 49 { -- | The number of pending queries. Incremented before any query is sent
52 -- and decremented when we get a reply. 50 -- and decremented when we get a reply.
53 searchPendingCount :: TVar Int 51 searchPendingCount :: TVar Int
54 -- | Nodes scheduled to be queried. 52 -- | Nodes scheduled to be queried (roughly at most K).
55 , searchQueued :: TVar (MinMaxPSQ ni nid) 53 , searchQueued :: TVar (MinMaxPSQ ni nid)
56 -- | The nearest (K - α) nodes that issued a reply. 54 -- | The nearest (K - α) nodes that issued a reply.
55 --
56 -- α is the maximum number of simultaneous queries.
57 , searchInformant :: TVar (MinMaxPSQ' ni nid (Maybe tok)) 57 , searchInformant :: TVar (MinMaxPSQ' ni nid (Maybe tok))
58 -- | This tracks already-queried addresses so we avoid bothering them 58 -- | This tracks already-queried addresses so we avoid bothering them
59 -- again. XXX: We could probably keep only the pending queries in this 59 -- again. XXX: We could probably keep only the pending queries in this
60 -- set. It also can be a bounded 'MinMaxPSQ', although searchAlpha 60 -- set. It also can be a bounded 'MinMaxPSQ', although searchAlpha
61 -- should limit the number of outstanding queries. 61 -- should limit the number of outstanding queries.
62 , searchVisited :: TVar (Set addr) 62 , searchVisited :: TVar (Set addr)
63 , searchSpec :: Search nid addr tok ni r
63 } 64 }
64 65
66
65newSearch :: ( Ord addr 67newSearch :: ( Ord addr
66 , PSQKey nid 68 , PSQKey nid
67 , PSQKey ni 69 , PSQKey ni
@@ -77,7 +79,7 @@ newSearch :: ( Ord addr
77 -> nid 79 -> nid
78 -> [ni] -- Initial nodes to query. 80 -> [ni] -- Initial nodes to query.
79 -> STM (SearchState nid addr tok ni r) 81 -> STM (SearchState nid addr tok ni r)
80newSearch (Search space nAddr qry) target ns = do 82newSearch s@(Search space nAddr qry _ _) target ns = do
81 c <- newTVar 0 83 c <- newTVar 0
82 q <- newTVar $ MM.fromList 84 q <- newTVar $ MM.fromList
83 $ map (\n -> n :-> kademliaXor space target (kademliaLocation space n)) 85 $ map (\n -> n :-> kademliaXor space target (kademliaLocation space n))
@@ -85,7 +87,7 @@ newSearch (Search space nAddr qry) target ns = do
85 i <- newTVar MM.empty 87 i <- newTVar MM.empty
86 v <- newTVar Set.empty 88 v <- newTVar Set.empty
87 return -- (Search space nAddr qry) , r , target 89 return -- (Search space nAddr qry) , r , target
88 ( SearchState c q i v ) 90 ( SearchState c q i v s )
89 91
90-- | Discard a value from a key-priority-value tuple. This is useful for 92-- | Discard a value from a key-priority-value tuple. This is useful for
91-- swaping items from a "MinMaxPSQ'" to a "MinMaxPSQ". 93-- swaping items from a "MinMaxPSQ'" to a "MinMaxPSQ".
@@ -110,21 +112,6 @@ reset nearestNodes qsearch target st = do
110 writeTVar (searchPendingCount st) 0 112 writeTVar (searchPendingCount st) 0
111 return st 113 return st
112 114
113searchAlpha :: Int
114searchAlpha = 8
115
116-- | 'searchK' should be larger than 'searchAlpha'. How much larger depends on
117-- how fast the queries are. For Tox's much slower onion-routed queries, we
118-- need to ensure that closer non-responding queries don't completely push out
119-- farther away queries.
120--
121-- For BitTorrent, setting them both 8 was not an issue, but that is no longer
122-- supported because now the number of remembered informants is now the
123-- difference between these two numbers. So, if searchK = 16 and searchAlpha =
124-- 4, then the number of remembered query responses is 12.
125searchK :: Int
126searchK = 16
127
128sendQuery :: forall addr nid tok ni r. 115sendQuery :: forall addr nid tok ni r.
129 ( Ord addr 116 ( Ord addr
130 , PSQKey nid 117 , PSQKey nid
@@ -159,8 +146,11 @@ sendQuery Search{..} searchTarget searchResult sch@SearchState{..} (ni :-> d) =
159 | otherwise = MM.insertTake k n ( kademliaXor searchSpace searchTarget 146 | otherwise = MM.insertTake k n ( kademliaXor searchSpace searchTarget
160 $ kademliaLocation searchSpace n ) 147 $ kademliaLocation searchSpace n )
161 q 148 q
149
162 qsize0 <- MM.size <$> readTVar searchQueued 150 qsize0 <- MM.size <$> readTVar searchQueued
163 let qsize = if qsize0 < searchK then searchK else qsize0 151 let qsize = if qsize0 < searchK then searchK else qsize0 -- Allow searchQueued to grow
152 -- only when there's fewer than
153 -- K elements.
164 modifyTVar searchQueued $ \q -> foldr (insertFoundNode qsize) q ns 154 modifyTVar searchQueued $ \q -> foldr (insertFoundNode qsize) q ns
165 modifyTVar searchInformant $ MM.insertTake' (searchK - searchAlpha) ni tok d 155 modifyTVar searchInformant $ MM.insertTake' (searchK - searchAlpha) ni tok d
166 flip fix rs $ \loop -> \case 156 flip fix rs $ \loop -> \case
@@ -174,13 +164,13 @@ sendQuery Search{..} searchTarget searchResult sch@SearchState{..} (ni :-> d) =
174searchIsFinished :: ( PSQKey nid 164searchIsFinished :: ( PSQKey nid
175 , PSQKey ni 165 , PSQKey ni
176 ) => SearchState nid addr tok ni r -> STM Bool 166 ) => SearchState nid addr tok ni r -> STM Bool
177searchIsFinished SearchState{ ..} = do 167searchIsFinished SearchState{..} = do
178 q <- readTVar searchQueued 168 q <- readTVar searchQueued
179 cnt <- readTVar searchPendingCount 169 cnt <- readTVar searchPendingCount
180 informants <- readTVar searchInformant 170 informants <- readTVar searchInformant
181 return $ cnt == 0 171 return $ cnt == 0
182 && ( MM.null q 172 && ( MM.null q
183 || ( MM.size informants >= (searchK - searchAlpha) 173 || ( MM.size informants >= (searchK searchSpec - searchAlpha searchSpec)
184 && ( PSQ.prio (fromJust $ MM.findMax informants) 174 && ( PSQ.prio (fromJust $ MM.findMax informants)
185 <= PSQ.prio (fromJust $ MM.findMin q)))) 175 <= PSQ.prio (fromJust $ MM.findMin q))))
186 176
@@ -197,7 +187,7 @@ search ::
197 , Show nid 187 , Show nid
198 ) => Search nid addr tok ni r -> R.BucketList ni -> nid -> (r -> STM Bool) -> IO (SearchState nid addr tok ni r) 188 ) => Search nid addr tok ni r -> R.BucketList ni -> nid -> (r -> STM Bool) -> IO (SearchState nid addr tok ni r)
199search sch buckets target result = do 189search sch buckets target result = do
200 let ns = R.kclosest (searchSpace sch) searchK target buckets 190 let ns = R.kclosest (searchSpace sch) (searchK sch) target buckets
201 st <- atomically $ newSearch sch target ns 191 st <- atomically $ newSearch sch target ns
202 forkIO $ searchLoop sch target result st 192 forkIO $ searchLoop sch target result st
203 return st 193 return st
@@ -218,7 +208,7 @@ searchLoop sch@Search{..} target result s@SearchState{..} = do
218 found <- MM.minView <$> readTVar searchQueued 208 found <- MM.minView <$> readTVar searchQueued
219 case found of 209 case found of
220 Just (ni :-> d, q) 210 Just (ni :-> d, q)
221 | -- If there's fewer than /k/ informants and there's any 211 | -- If there's fewer than /k - α/ informants and there's any
222 -- node we haven't yet got a response from. 212 -- node we haven't yet got a response from.
223 (MM.size informants < searchK - searchAlpha) && (cnt > 0 || not (MM.null q)) 213 (MM.size informants < searchK - searchAlpha) && (cnt > 0 || not (MM.null q))
224 -- Or there's no informants yet at all. 214 -- Or there's no informants yet at all.
diff --git a/src/Network/Tox/Crypto/Transport.hs b/src/Network/Tox/Crypto/Transport.hs
index 2c13e168..a18b550d 100644
--- a/src/Network/Tox/Crypto/Transport.hs
+++ b/src/Network/Tox/Crypto/Transport.hs
@@ -44,7 +44,7 @@ module Network.Tox.Crypto.Transport
44 , HasMessage(..) 44 , HasMessage(..)
45 , HasMessageType(..) 45 , HasMessageType(..)
46 -- lenses 46 -- lenses
47#ifdef VERSION_lens 47#ifdef USE_lens
48 , groupNumber, groupNumberToJoin, peerNumber, messageNumber 48 , groupNumber, groupNumberToJoin, peerNumber, messageNumber
49 , messageName, messageData, name, title, message, messageType 49 , messageName, messageData, name, title, message, messageType
50#endif 50#endif
@@ -288,7 +288,7 @@ putCryptoMessage seqno (Pkt t :=> Identity x) = do
288 putPacket seqno x 288 putPacket seqno x
289 289
290 290
291#ifdef VERSION_lens 291#ifdef USE_lens
292erCompat :: String -> a 292erCompat :: String -> a
293erCompat lens = error $ "Use of '" ++ lens ++ "' lens on incompatible CryptoMessage type" 293erCompat lens = error $ "Use of '" ++ lens ++ "' lens on incompatible CryptoMessage type"
294#endif 294#endif
@@ -336,7 +336,7 @@ instance HasGroupChatID CryptoMessage where
336 setGroupChatID _ _= error "setGroupChatID on non-groupchat message." 336 setGroupChatID _ _= error "setGroupChatID on non-groupchat message."
337-} 337-}
338 338
339#ifdef VERSION_lens 339#ifdef USE_lens
340groupChatID :: (Functor f, HasGroupChatID x) => (GroupChatId -> f GroupChatId) -> (x -> f x) 340groupChatID :: (Functor f, HasGroupChatID x) => (GroupChatId -> f GroupChatId) -> (x -> f x)
341groupChatID = lens getGroupChatID setGroupChatID 341groupChatID = lens getGroupChatID setGroupChatID
342#endif 342#endif
@@ -370,7 +370,7 @@ instance HasGroupNumber CryptoMessage where
370 setGroupNumber _ _ = error "setGroupNumber on CryptoMessage without group number field." 370 setGroupNumber _ _ = error "setGroupNumber on CryptoMessage without group number field."
371-} 371-}
372 372
373#ifdef VERSION_lens 373#ifdef USE_lens
374groupNumber :: (Functor f, HasGroupNumber x) => (Word16 -> f Word16) -> (x -> f x) 374groupNumber :: (Functor f, HasGroupNumber x) => (Word16 -> f Word16) -> (x -> f x)
375groupNumber = lens getGroupNumber setGroupNumber 375groupNumber = lens getGroupNumber setGroupNumber
376#endif 376#endif
@@ -394,7 +394,7 @@ instance HasGroupNumberToJoin CryptoMessage where
394 setGroupNumberToJoin _ _ = error "setGroupNumberToJoin on CryptoMessage without group number (to join) field." 394 setGroupNumberToJoin _ _ = error "setGroupNumberToJoin on CryptoMessage without group number (to join) field."
395-} 395-}
396 396
397#ifdef VERSION_lens 397#ifdef USE_lens
398groupNumberToJoin :: (Functor f, HasGroupNumberToJoin x) => (GroupNumber -> f GroupNumber) -> (x -> f x) 398groupNumberToJoin :: (Functor f, HasGroupNumberToJoin x) => (GroupNumber -> f GroupNumber) -> (x -> f x)
399groupNumberToJoin = lens getGroupNumberToJoin setGroupNumberToJoin 399groupNumberToJoin = lens getGroupNumberToJoin setGroupNumberToJoin
400#endif 400#endif
@@ -418,7 +418,7 @@ instance HasPeerNumber CryptoMessage where
418 setPeerNumber _ _ = error "setPeerNumber on CryptoMessage without peer number field." 418 setPeerNumber _ _ = error "setPeerNumber on CryptoMessage without peer number field."
419-} 419-}
420 420
421#ifdef VERSION_lens 421#ifdef USE_lens
422peerNumber :: (Functor f, HasPeerNumber x) => (Word16 -> f Word16) -> (x -> f x) 422peerNumber :: (Functor f, HasPeerNumber x) => (Word16 -> f Word16) -> (x -> f x)
423peerNumber = lens getPeerNumber setPeerNumber 423peerNumber = lens getPeerNumber setPeerNumber
424#endif 424#endif
@@ -442,7 +442,7 @@ instance HasMessageNumber CryptoMessage where
442 setMessageNumber _ _ = error "setMessageNumber on CryptoMessage without message number field." 442 setMessageNumber _ _ = error "setMessageNumber on CryptoMessage without message number field."
443-} 443-}
444 444
445#ifdef VERSION_lens 445#ifdef USE_lens
446messageNumber :: (Functor f, HasMessageNumber x) => (Word32 -> f Word32) -> (x -> f x) 446messageNumber :: (Functor f, HasMessageNumber x) => (Word32 -> f Word32) -> (x -> f x)
447messageNumber = lens getMessageNumber setMessageNumber 447messageNumber = lens getMessageNumber setMessageNumber
448#endif 448#endif
@@ -468,7 +468,7 @@ instance HasMessageName CryptoMessage where
468 setMessageName _ _ = error "setMessageName on CryptoMessage without message name field." 468 setMessageName _ _ = error "setMessageName on CryptoMessage without message name field."
469-} 469-}
470 470
471#ifdef VERSION_lens 471#ifdef USE_lens
472messageName :: (Functor f, HasMessageName x) => (MessageName -> f MessageName) -> (x -> f x) 472messageName :: (Functor f, HasMessageName x) => (MessageName -> f MessageName) -> (x -> f x)
473messageName = lens getMessageName setMessageName 473messageName = lens getMessageName setMessageName
474#endif 474#endif
@@ -514,7 +514,7 @@ instance AsWord64 MessageType where
514 fromWord64 x | x < 1024, x .|. 0x0200 == 0x0200 = GrpMsg (toEnum8 ((x - 512) `div` 256)) (toEnum8 x) 514 fromWord64 x | x < 1024, x .|. 0x0200 == 0x0200 = GrpMsg (toEnum8 ((x - 512) `div` 256)) (toEnum8 x)
515 fromWord64 x = error "Not clear how to convert Word64 to MessageType" 515 fromWord64 x = error "Not clear how to convert Word64 to MessageType"
516 516
517#ifdef VERSION_lens 517#ifdef USE_lens
518word16 :: (Functor f, AsWord16 x) => (Word16 -> f Word16) -> (x -> f x) 518word16 :: (Functor f, AsWord16 x) => (Word16 -> f Word16) -> (x -> f x)
519word16 = lens toWord16 (\_ x -> fromWord16 x) 519word16 = lens toWord16 (\_ x -> fromWord16 x)
520#endif 520#endif
@@ -559,7 +559,7 @@ instance HasMessageType CryptoData where
559 setMessageType cd@(CryptoData { bufferData=bd }) typ = cd { bufferData=setMessageType bd typ } 559 setMessageType cd@(CryptoData { bufferData=bd }) typ = cd { bufferData=setMessageType bd typ }
560-} 560-}
561 561
562#ifdef VERSION_lens 562#ifdef USE_lens
563-- | This lens should always succeed on CryptoMessage 563-- | This lens should always succeed on CryptoMessage
564messageType :: (Functor f, HasMessageType x) => (MessageType -> f MessageType) -> (x -> f x) 564messageType :: (Functor f, HasMessageType x) => (MessageType -> f MessageType) -> (x -> f x)
565messageType = lens getMessageType setMessageType 565messageType = lens getMessageType setMessageType
@@ -589,7 +589,7 @@ instance HasMessageData CryptoMessage where
589 setMessageData _ _ = error "setMessageData on CryptoMessage without message data field." 589 setMessageData _ _ = error "setMessageData on CryptoMessage without message data field."
590-} 590-}
591 591
592#ifdef VERSION_lens 592#ifdef USE_lens
593messageData :: (Functor f, HasMessageData x) => (MessageData -> f MessageData) -> (x -> f x) 593messageData :: (Functor f, HasMessageData x) => (MessageData -> f MessageData) -> (x -> f x)
594messageData = lens getMessageData setMessageData 594messageData = lens getMessageData setMessageData
595#endif 595#endif
@@ -621,7 +621,7 @@ instance HasTitle CryptoMessage where
621 setTitle _ _ = error "setTitle on CryptoMessage without title field." 621 setTitle _ _ = error "setTitle on CryptoMessage without title field."
622-} 622-}
623 623
624#ifdef VERSION_lens 624#ifdef USE_lens
625title :: (Functor f, HasTitle x) => (Text -> f Text) -> (x -> f x) 625title :: (Functor f, HasTitle x) => (Text -> f Text) -> (x -> f x)
626title = lens getTitle setTitle 626title = lens getTitle setTitle
627#endif 627#endif
@@ -653,7 +653,7 @@ instance HasMessage CryptoMessage where
653 setMessage _ _ = error "setMessage on CryptoMessage without message field." 653 setMessage _ _ = error "setMessage on CryptoMessage without message field."
654-} 654-}
655 655
656#ifdef VERSION_lens 656#ifdef USE_lens
657message :: (Functor f, HasMessage x) => (Text -> f Text) -> (x -> f x) 657message :: (Functor f, HasMessage x) => (Text -> f Text) -> (x -> f x)
658message = lens getMessage setMessage 658message = lens getMessage setMessage
659#endif 659#endif
@@ -675,7 +675,7 @@ instance HasName CryptoMessage where
675 setName _ _ = error "setName on CryptoMessage without name field." 675 setName _ _ = error "setName on CryptoMessage without name field."
676-} 676-}
677 677
678#ifdef VERSION_lens 678#ifdef USE_lens
679name :: (Functor f, HasTitle x) => (Text -> f Text) -> (x -> f x) 679name :: (Functor f, HasTitle x) => (Text -> f Text) -> (x -> f x)
680name = lens getTitle setTitle 680name = lens getTitle setTitle
681#endif 681#endif
diff --git a/src/Network/Tox/DHT/Handlers.hs b/src/Network/Tox/DHT/Handlers.hs
index 2fbac5d3..afdf2cc3 100644
--- a/src/Network/Tox/DHT/Handlers.hs
+++ b/src/Network/Tox/DHT/Handlers.hs
@@ -195,6 +195,8 @@ newRouting addr crypto update4 update6 = do
195 { searchSpace = toxSpace 195 { searchSpace = toxSpace
196 , searchNodeAddress = nodeIP &&& nodePort 196 , searchNodeAddress = nodeIP &&& nodePort
197 , searchQuery = \_ _ -> return Nothing 197 , searchQuery = \_ _ -> return Nothing
198 , searchAlpha = 1
199 , searchK = 2
198 } 200 }
199 tbl4 <- newTVar $ R.nullTable (comparing nodeId) (\s -> hashWithSalt s . nodeId) tentative_info4 R.defaultBucketCount 201 tbl4 <- newTVar $ R.nullTable (comparing nodeId) (\s -> hashWithSalt s . nodeId) tentative_info4 R.defaultBucketCount
200 tbl6 <- newTVar $ R.nullTable (comparing nodeId) (\s -> hashWithSalt s . nodeId) tentative_info6 R.defaultBucketCount 202 tbl6 <- newTVar $ R.nullTable (comparing nodeId) (\s -> hashWithSalt s . nodeId) tentative_info6 R.defaultBucketCount
@@ -524,4 +526,7 @@ nodeSearch client cbvar = Search
524 { searchSpace = toxSpace 526 { searchSpace = toxSpace
525 , searchNodeAddress = nodeIP &&& nodePort 527 , searchNodeAddress = nodeIP &&& nodePort
526 , searchQuery = getNodes client cbvar 528 , searchQuery = getNodes client cbvar
529 , searchAlpha = 8
530 , searchK = 16
531
527 } 532 }
diff --git a/src/Network/Tox/Onion/Handlers.hs b/src/Network/Tox/Onion/Handlers.hs
index a16508cd..52cc298d 100644
--- a/src/Network/Tox/Onion/Handlers.hs
+++ b/src/Network/Tox/Onion/Handlers.hs
@@ -219,6 +219,8 @@ toxidSearch getTimeout crypto client = Search
219 { searchSpace = toxSpace 219 { searchSpace = toxSpace
220 , searchNodeAddress = nodeIP &&& nodePort 220 , searchNodeAddress = nodeIP &&& nodePort
221 , searchQuery = getRendezvous getTimeout crypto client 221 , searchQuery = getRendezvous getTimeout crypto client
222 , searchAlpha = 3
223 , searchK = 6
222 } 224 }
223 225
224announceSerializer :: (TransactionId -> OnionDestination r -> STM (OnionDestination r, Int)) 226announceSerializer :: (TransactionId -> OnionDestination r -> STM (OnionDestination r, Int))
diff --git a/src/Network/Tox/TCP.hs b/src/Network/Tox/TCP.hs
index 1111d3b8..a7881c24 100644
--- a/src/Network/Tox/TCP.hs
+++ b/src/Network/Tox/TCP.hs
@@ -191,15 +191,15 @@ getUDPNodes' tcp seeking dst0 = do
191 n24 <- transportNewNonce (tcpCrypto tcp) 191 n24 <- transportNewNonce (tcpCrypto tcp)
192 return (b,c,n24) 192 return (b,c,n24)
193 let (dst,gateway') = if UDP.nodeId dst0 == nodeId gateway 193 let (dst,gateway') = if UDP.nodeId dst0 == nodeId gateway
194 then ( dst0 { UDP.nodeIP = fromJust $ fromSockAddr localhost4 } 194 then ( dst0 { UDP.nodeIP = fromJust $ Network.Address.fromSockAddr localhost4 }
195 , gateway { udpNodeInfo = (udpNodeInfo gateway) 195 , gateway { udpNodeInfo = (udpNodeInfo gateway)
196 { UDP.nodeIP = fromJust $ fromSockAddr localhost4 }}) 196 { UDP.nodeIP = fromJust $ Network.Address.fromSockAddr localhost4 }})
197 else (dst0,gateway) 197 else (dst0,gateway)
198 wrap2 <- lookupNonceFunction (tcpCrypto tcp) b (UDP.id2key $ UDP.nodeId dst) 198 wrap2 <- lookupNonceFunction (tcpCrypto tcp) b (UDP.id2key $ UDP.nodeId dst)
199 wrap1 <- lookupNonceFunction (tcpCrypto tcp) c (UDP.id2key $ nodeId gateway) 199 wrap1 <- lookupNonceFunction (tcpCrypto tcp) c (UDP.id2key $ nodeId gateway)
200 wrap0 <- lookupNonceFunction (tcpCrypto tcp) (transportSecret $ tcpCrypto tcp) (UDP.id2key $ UDP.nodeId dst) 200 wrap0 <- lookupNonceFunction (tcpCrypto tcp) (transportSecret $ tcpCrypto tcp) (UDP.id2key $ UDP.nodeId dst)
201 let meth = MethodSerializer -- MethodSerializer Nonce8 NodeInfo RelayPacket meth AnnounceRequest (Either String AnnounceResponse) 201 let meth = MethodSerializer -- MethodSerializer Nonce8 NodeInfo RelayPacket meth AnnounceRequest (Either String AnnounceResponse)
202 { methodTimeout = \tid addr -> return (addr,8000000) -- 8 second timeout 202 { methodTimeout = \tid addr -> return (addr,12000000) -- 12 second timeout
203 , method = () -- meth 203 , method = () -- meth
204 , wrapQuery = \n8 src gateway x -> 204 , wrapQuery = \n8 src gateway x ->
205 OnionPacket n24 $ Addressed (UDP.nodeAddr dst) 205 OnionPacket n24 $ Addressed (UDP.nodeAddr dst)
@@ -274,7 +274,7 @@ newClient crypto store load = do
274 , tableMethods = transactionMethods' store load (contramap (\(Nonce8 w64) -> w64) w64MapMethods) 274 , tableMethods = transactionMethods' store load (contramap (\(Nonce8 w64) -> w64) w64MapMethods)
275 $ first (either error Nonce8 . decode) . randomBytesGenerate 8 275 $ first (either error Nonce8 . decode) . randomBytesGenerate 8
276 } 276 }
277 , clientErrorReporter = logErrors 277 , clientErrorReporter = logErrors { reportTimeout = reportTimeout ignoreErrors }
278 , clientPending = map_var 278 , clientPending = map_var
279 , clientAddress = \_ -> return $ NodeInfo 279 , clientAddress = \_ -> return $ NodeInfo
280 { udpNodeInfo = either error id $ UDP.nodeInfo (UDP.key2id $ transportPublic crypto) (SockAddrInet 0 0) 280 { udpNodeInfo = either error id $ UDP.nodeInfo (UDP.key2id $ transportPublic crypto) (SockAddrInet 0 0)