summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Mainline.hs456
-rw-r--r--src/Network/BitTorrent/DHT/Token.hs58
2 files changed, 472 insertions, 42 deletions
diff --git a/Mainline.hs b/Mainline.hs
index d24b3376..12d1540b 100644
--- a/Mainline.hs
+++ b/Mainline.hs
@@ -4,32 +4,51 @@
4{-# LANGUAGE DeriveTraversable #-} 4{-# LANGUAGE DeriveTraversable #-}
5{-# LANGUAGE FlexibleInstances #-} 5{-# LANGUAGE FlexibleInstances #-}
6{-# LANGUAGE GeneralizedNewtypeDeriving #-} 6{-# LANGUAGE GeneralizedNewtypeDeriving #-}
7{-# LANGUAGE PatternSynonyms #-}
8{-# LANGUAGE StandaloneDeriving #-}
7module Mainline where 9module Mainline where
8 10
11import Control.Applicative
9import Control.Arrow 12import Control.Arrow
10import Control.Concurrent.STM 13import Control.Concurrent.STM
11import Crypto.Random 14import Crypto.Random
12import Data.BEncode as BE 15import Data.BEncode as BE
13import Data.BEncode.BDict as BE 16import qualified Data.BEncode.BDict as BE
17 ;import Data.BEncode.BDict (BKey)
18import Data.Bits
19import Data.Bits.ByteString
14import Data.Bool 20import Data.Bool
15import Data.ByteArray 21import qualified Data.ByteArray as BA
16import Data.ByteString (ByteString) 22 ;import Data.ByteArray (ByteArrayAccess)
17import Data.ByteString as B 23import qualified Data.ByteString as B
18import Data.ByteString.Lazy (toStrict) 24 ;import Data.ByteString (ByteString)
25import Data.ByteString.Lazy (toStrict)
19import Data.Data 26import Data.Data
27import Data.Default
28import Data.Hashable
20import Data.IP 29import Data.IP
30import Data.List
21import Data.Maybe 31import Data.Maybe
22import Data.Monoid 32import Data.Monoid
23import qualified Data.Serialize as S 33import qualified Data.Serialize as S
34import Data.Set (Set)
35import Data.Torrent
24import Data.Typeable 36import Data.Typeable
25import Data.Word 37import Data.Word
26import Network.Address (Address, fromSockAddr, sockAddrPort, 38import Network.Address (Address, fromSockAddr, setPort,
27 toSockAddr, withPort) 39 sockAddrPort, toSockAddr)
40import Network.BitTorrent.DHT.ContactInfo as Peers
41import Network.BitTorrent.DHT.Token as Token
42import qualified Network.DHT.Routing as R
43 ;import Network.DHT.Routing (Info, Timestamp, getTimestamp)
28import Network.QueryResponse 44import Network.QueryResponse
29import Network.Socket 45import Network.Socket
30 46
31newtype NodeId = NodeId ByteString 47newtype NodeId = NodeId ByteString
32 deriving (Eq,Ord,Show,ByteArrayAccess, BEncode) 48 deriving (Eq,Ord,Show,ByteArrayAccess, BEncode, Bits)
49
50instance FiniteBits NodeId where
51 finiteBitSize _ = 160
33 52
34data NodeInfo = NodeInfo 53data NodeInfo = NodeInfo
35 { nodeId :: NodeId 54 { nodeId :: NodeId
@@ -37,8 +56,44 @@ data NodeInfo = NodeInfo
37 , nodePort :: PortNumber 56 , nodePort :: PortNumber
38 } 57 }
39 58
59instance Hashable NodeInfo where
60 hashWithSalt s ni = hashWithSalt s (nodeIP ni , nodePort ni)
61 {-# INLINE hashWithSalt #-}
62
63
64
65{-
66
67-- | KRPC 'compact list' compatible encoding: contact information for
68-- nodes is encoded as a 26-byte string. Also known as "Compact node
69-- info" the 20-byte Node ID in network byte order has the compact
70-- IP-address/port info concatenated to the end.
71 get = NodeInfo <$> (NodeId <$> S.getBytes 20 ) <*> S.get <*> S.get
72-}
73
74getNodeInfo4 :: S.Get NodeInfo
75getNodeInfo4 = NodeInfo <$> (NodeId <$> S.getBytes 20)
76 <*> (IPv4 <$> S.get)
77 <*> S.get
78
79putNodeInfo4 :: NodeInfo -> S.Put
80putNodeInfo4 (NodeInfo (NodeId nid) (IPv4 ip) port)
81 = S.putByteString nid >> S.put ip >> S.put port
82putNodeInfo4 _ = return ()
83
84getNodeInfo6 :: S.Get NodeInfo
85getNodeInfo6 = NodeInfo <$> (NodeId <$> S.getBytes 20)
86 <*> (IPv6 <$> S.get)
87 <*> S.get
88
89putNodeInfo6 :: NodeInfo -> S.Put
90putNodeInfo6 (NodeInfo (NodeId nid) (IPv6 ip) port)
91 = S.putByteString nid >> S.put ip >> S.put port
92putNodeInfo6 _ = return ()
93
94
40nodeAddr :: NodeInfo -> SockAddr 95nodeAddr :: NodeInfo -> SockAddr
41nodeAddr (NodeInfo _ ip port) = toSockAddr ip `withPort` port 96nodeAddr (NodeInfo _ ip port) = setPort port $ toSockAddr ip
42 97
43nodeInfo :: NodeId -> SockAddr -> Either String NodeInfo 98nodeInfo :: NodeId -> SockAddr -> Either String NodeInfo
44nodeInfo nid saddr 99nodeInfo nid saddr
@@ -110,7 +165,7 @@ instance BE.BEncode (Message BValue) where
110 165
111encodeMessage (Q origin tid a meth ro) 166encodeMessage (Q origin tid a meth ro)
112 = case a of 167 = case a of
113 BDict args -> encodeQuery tid meth (BDict $ genericArgs origin ro `union` args) 168 BDict args -> encodeQuery tid meth (BDict $ genericArgs origin ro `BE.union` args)
114 _ -> encodeQuery tid meth a -- XXX: Not really a valid query. 169 _ -> encodeQuery tid meth a -- XXX: Not really a valid query.
115encodeMessage (R origin tid v ip) 170encodeMessage (R origin tid v ip)
116 = case v of 171 = case v of
@@ -148,6 +203,60 @@ encodePacket :: Message BValue -> NodeInfo -> (ByteString, SockAddr)
148encodePacket msg ni = ( toStrict $ BE.encode msg 203encodePacket msg ni = ( toStrict $ BE.encode msg
149 , nodeAddr ni ) 204 , nodeAddr ni )
150 205
206classify :: Message BValue -> MessageClass String Method TransactionId
207classify (Q { msgID = tid, qryMethod = meth }) = IsQuery meth tid
208classify (R { msgID = tid }) = IsResponse tid
209
210encodePayload :: BEncode a => TransactionId -> NodeInfo -> NodeInfo -> a -> Message BValue
211encodePayload tid self dest b = R (nodeId self) tid (Right $ BE.toBEncode b) (Just $ nodeAddr dest)
212
213errorPayload :: TransactionId -> NodeInfo -> NodeInfo -> Error -> Message a
214errorPayload tid self dest e = R (nodeId self) tid (Left e) (Just $ nodeAddr dest)
215
216decodePayload :: BEncode a => Message BValue -> Either String a
217decodePayload msg = BE.fromBEncode $ qryPayload msg
218
219type Handler = MethodHandler String TransactionId NodeInfo (Message BValue)
220
221handler :: ( BEncode a
222 , BEncode b
223 ) =>
224 (NodeInfo -> a -> IO b) -> Maybe Handler
225handler f = Just $ MethodHandler decodePayload encodePayload f
226
227
228handlerE :: ( BEncode a
229 , BEncode b
230 ) =>
231 (NodeInfo -> a -> IO (Either Error b)) -> Maybe Handler
232handlerE f = Just $ MethodHandler decodePayload enc f
233 where
234 enc tid self dest (Left e) = errorPayload tid self dest e
235 enc tid self dest (Right b) = encodePayload tid self dest b
236
237type AnnounceSet = Set (InfoHash, PortNumber)
238
239data SwarmsDatabase = SwarmsDatabase
240 { contactInfo :: !( TVar PeerStore ) -- ^ Published by other nodes.
241 , sessionTokens :: !( TVar SessionTokens ) -- ^ Query session IDs.
242 , announceInfo :: !( TVar AnnounceSet ) -- ^ To publish by this node.
243 }
244
245newSwarmsDatabase :: IO SwarmsDatabase
246newSwarmsDatabase = do
247 toks <- nullSessionTokens
248 atomically
249 $ SwarmsDatabase <$> newTVar def
250 <*> newTVar toks
251 <*> newTVar def
252
253type RoutingInfo = Info NodeInfo NodeId
254
255data Routing = Routing
256 { routing4 :: !( TVar (Maybe RoutingInfo) )
257 , routing6 :: !( TVar (Maybe RoutingInfo) )
258 }
259
151newClient :: 260newClient ::
152 SockAddr -> IO (Client String Method TransactionId NodeInfo (Message BValue)) 261 SockAddr -> IO (Client String Method TransactionId NodeInfo (Message BValue))
153newClient addr = do 262newClient addr = do
@@ -156,13 +265,26 @@ newClient addr = do
156 self <- atomically $ newTVar 265 self <- atomically $ newTVar
157 $ NodeInfo nid (fromMaybe (toEnum 0) $ fromSockAddr addr) 266 $ NodeInfo nid (fromMaybe (toEnum 0) $ fromSockAddr addr)
158 (fromMaybe 0 $ sockAddrPort addr) 267 (fromMaybe 0 $ sockAddrPort addr)
159 -- drg <- getSystemDRG 268 routing <- atomically $ Routing <$> newTVar Nothing <*> newTVar Nothing
160 let net = layerTransport parsePacket encodePacket udp 269 swarms <- newSwarmsDatabase
270 let net = onInbound grok $ layerTransport parsePacket encodePacket udp
271 grok _ _ = do
272 -- TODO Update kademlia table.
273 -- TODO Update external ip address and update BEP-42 node id.
274 return ()
161 dispatch tbl = DispatchMethods 275 dispatch tbl = DispatchMethods
162 { classifyInbound = classify 276 { classifyInbound = classify
163 , lookupHandler = handlers 277 , lookupHandler = handlers
164 , tableMethods = tbl 278 , tableMethods = tbl
165 } 279 }
280
281 handlers :: Method -> Maybe Handler
282 handlers ( Method "ping" ) = handler pingH
283 handlers ( Method "find_node" ) = handler $ findNodeH routing
284 handlers ( Method "get_peers" ) = handler $ getPeersH routing swarms
285 handlers ( Method "announce_peer" ) = handlerE $ announceH swarms
286 handlers ( Method meth ) = Just $ defaultHandler meth
287
166 mapT = transactionMethods mapMethods gen 288 mapT = transactionMethods mapMethods gen
167 gen :: Word16 -> (TransactionId, Word16) 289 gen :: Word16 -> (TransactionId, Word16)
168 gen cnt = (TransactionId $ S.encode cnt, cnt+1) 290 gen cnt = (TransactionId $ S.encode cnt, cnt+1)
@@ -176,29 +298,287 @@ newClient addr = do
176 , clientResponseId = return 298 , clientResponseId = return
177 } 299 }
178 300
179classify :: Message BValue -> MessageClass String Method TransactionId 301defaultHandler :: ByteString -> Handler
180classify (Q { msgID = tid, qryMethod = meth }) = IsQuery meth tid 302defaultHandler meth = MethodHandler decodePayload errorPayload returnError
181classify (R { msgID = tid }) = IsResponse tid 303 where
182 304 returnError :: NodeInfo -> BValue -> IO Error
183encodePayload tid self dest b = R (nodeId self) tid (Right $ BE.toBEncode b) (Just $ nodeAddr dest) 305 returnError _ _ = return $ Error MethodUnknown ("Unknown method " <> meth)
184 306
185errorPayload tid self dest e = R (nodeId self) tid (Left e) (Just $ nodeAddr dest) 307
186 308data Ping = Ping deriving Show
187decodePayload :: BEncode a => Message BValue -> Either String a 309
188decodePayload msg = BE.fromBEncode $ qryPayload msg 310-- Pong is the same as Ping.
189 311type Pong = Ping
190handler f = Just $ MethodHandler decodePayload encodePayload f 312pattern Pong = Ping
191 313
192handlers :: Method -> Maybe (MethodHandler String TransactionId NodeInfo (Message BValue)) 314instance BEncode Ping where
193handlers (Method "ping" ) = error "handler pingH" 315 toBEncode Ping = toDict endDict
194handlers (Method "find_node") = error "find_node" 316 fromBEncode _ = pure Ping
195handlers (Method "get_peers") = error "get_peers" 317
196handlers (Method meth ) = Just $ MethodHandler decodePayload errorPayload (defaultH meth) 318data WantIP = Want_IP4 | Want_IP6 | Want_Both
197 319 deriving (Eq, Enum, Ord, Show)
198data Ping = Ping 320
321wantList :: WantIP -> [ByteString]
322wantList Want_IP4 = ["ip4"]
323wantList Want_IP6 = ["ip6"]
324wantList Want_Both = ["ip4","ip6"]
325
326instance BEncode WantIP where
327 toBEncode w = toBEncode $ wantList w
328 fromBEncode bval = do
329 wants <- fromBEncode bval
330 let _ = wants :: [ByteString]
331 case (elem "ip4" wants, elem "ip6" wants) of
332 (True,True) -> Right Want_Both
333 (True,False) -> Right Want_IP4
334 (False,True) -> Right Want_IP6
335 _ -> Left "Unrecognized IP type."
336
337data FindNode = FindNode NodeId (Maybe WantIP)
338
339instance BEncode FindNode where
340 toBEncode (FindNode nid iptyp) = toDict $ target_key .=! nid
341 .: want_key .=? iptyp
342 .: endDict
343 fromBEncode = fromDict $ FindNode <$>! target_key
344 <*>? want_key
345
346data NodeFound = NodeFound
347 { nodes4 :: [NodeInfo]
348 , nodes6 :: [NodeInfo]
349 }
350
351instance BEncode NodeFound where
352 toBEncode (NodeFound ns ns6) = toDict $
353 nodes_key .=?
354 (if Prelude.null ns then Nothing
355 else Just (S.runPut (mapM_ putNodeInfo4 ns)))
356 .: nodes6_key .=?
357 (if Prelude.null ns6 then Nothing
358 else Just (S.runPut (mapM_ putNodeInfo6 ns6)))
359 .: endDict
199 360
200pingH :: NodeInfo -> Ping -> IO Ping 361 fromBEncode bval = NodeFound <$> ns4 <*> ns6
201pingH = error "pingH" 362 where
363 ns4 = fromDict (binary getNodeInfo4 nodes_key) bval
364 ns6 = fromDict (binary getNodeInfo6 nodes6_key) bval
365
366binary :: S.Get a -> BKey -> BE.Get [a]
367binary get k = field (req k) >>= either (fail . format) return .
368 S.runGet (many get)
369 where
370 format str = "fail to deserialize " ++ show k ++ " field: " ++ str
371
372pingH :: NodeInfo -> Ping -> IO Pong
373pingH _ Ping = return Pong
374
375-- | True if the argument is an IPv4-mapped address with prefix ::FFFF:0:0/96
376-- as defined in RFC 4291.
377is4mapped :: IPv6 -> Bool
378is4mapped ip
379 | [0,0,0,0,0,0,0xffff,_] <- fromIPv6 ip
380 = True
381 | otherwise = False
382
383prefer4or6 :: NodeInfo -> Maybe WantIP -> WantIP
384prefer4or6 addr iptyp = fromMaybe unspecified iptyp
385 where
386 unspecified = case nodeIP addr of
387 IPv4 _ -> Want_IP4
388 IPv6 a | is4mapped a -> Want_IP4
389 | otherwise -> Want_IP6
390
391findNodeH :: Routing -> NodeInfo -> FindNode -> IO NodeFound
392findNodeH routing addr (FindNode node iptyp) = do
393 let preferred = prefer4or6 addr iptyp
394 ks <- bool (return []) (go $ routing4 routing) (preferred /= Want_IP6)
395 ks6 <- bool (return []) (go $ routing6 routing) (preferred /= Want_IP4)
396 return $ NodeFound ks ks6
397 where
398 go var = do
399 let myid = error "TODO myid" :: NodeId
400 k = error "TODO k" :: Int
401 nobkts = error "TODO nobkts" :: Int
402 nfo <- atomically $ readTVar var
403 let tbl = maybe (R.nullTable myid nobkts) R.myBuckets nfo
404 return $ R.kclosest nodeId k node tbl
405
406data GetPeers = GetPeers InfoHash (Maybe WantIP)
407
408instance BEncode GetPeers where
409 toBEncode (GetPeers ih iptyp)
410 = toDict $ info_hash_key .=! ih
411 .: want_key .=? iptyp
412 .: endDict
413 fromBEncode = fromDict $ GetPeers <$>! info_hash_key <*>? want_key
414
415
416type PeerList = Either [NodeInfo] [PeerAddr]
417
418data GotPeers = GotPeers
419 { -- | If the queried node has no peers for the infohash, returned
420 -- the K nodes in the queried nodes routing table closest to the
421 -- infohash supplied in the query.
422 peers :: PeerList
423
424 -- | The token value is a required argument for a future
425 -- announce_peer query.
426 , grantedToken :: Token
427 } -- deriving (Show, Eq, Typeable)
428
429nodeIsIPv6 :: NodeInfo -> Bool
430nodeIsIPv6 (NodeInfo _ (IPv6 _) _) = True
431nodeIsIPv6 _ = False
432
433instance BEncode GotPeers where
434 toBEncode GotPeers {..} = toDict $
435 case peers of
436 Left ns
437 | let (ns6,ns4) = partition nodeIsIPv6 ns
438 ->
439 nodes_key .=? (if null ns4 then Nothing
440 else Just $ S.runPut (mapM_ putNodeInfo4 ns4))
441 .: nodes6_key .=? (if null ns6 then Nothing
442 else Just $ S.runPut (mapM_ putNodeInfo4 ns6))
443 .: token_key .=! grantedToken
444 .: endDict
445 Right ps ->
446 token_key .=! grantedToken
447 .: peers_key .=! map S.encode ps -- TODO: Spec says we shouldn't mix ip4/ip6 here.
448 -- (We could filter in MethodHandler.)
449 .: endDict
202 450
203defaultH :: ByteString -> NodeInfo -> BValue -> IO Error 451 fromBEncode = fromDict $ do
204defaultH meth _ _ = return $ Error MethodUnknown ("Unknown method " <> meth) 452 mns4 <- optional (binary getNodeInfo4 nodes_key) -- "nodes"
453 mns6 <- optional (binary getNodeInfo6 nodes6_key) -- "nodes6"
454 let mns = ((++) <$> mns4 <*> mns6)
455 <|> mns4
456 <|> mns6
457 tok <- field (req token_key) -- "token"
458 mps <- optional (field (req peers_key) >>= decodePeers) -- "values"
459 case (Right <$> mps) <|> (Left <$> mns) of
460 Nothing -> fail "get_peers: neihter peers nor nodes key is valid"
461 Just xs -> pure $ GotPeers xs tok
462 where
463 decodePeers = either fail pure . mapM S.decode
464
465getPeersH :: Routing -> SwarmsDatabase -> NodeInfo -> GetPeers -> IO GotPeers
466getPeersH routing (SwarmsDatabase peers toks _) naddr (GetPeers ih iptyp) = do
467 ps <- do
468 tm <- getTimestamp
469 ps <- atomically $ do
470 (ps,store') <- Peers.freshPeers ih tm <$> readTVar peers
471 writeTVar peers store'
472 return ps
473 if null ps
474 then Left <$> error "TODO: getClosest ih"
475 else return (Right ps)
476 tok <- grantToken toks naddr
477 return $ GotPeers ps tok
478
479-- | Announce that the peer, controlling the querying node, is
480-- downloading a torrent on a port.
481data Announce = Announce
482 { -- | If set, the 'port' field should be ignored and the source
483 -- port of the UDP packet should be used as the peer's port
484 -- instead. This is useful for peers behind a NAT that may not
485 -- know their external port, and supporting uTP, they accept
486 -- incoming connections on the same port as the DHT port.
487 impliedPort :: Bool
488
489 -- | infohash of the torrent;
490 , topic :: InfoHash
491
492 -- | some clients announce the friendly name of the torrent here.
493 , announcedName :: Maybe ByteString
494
495 -- | the port /this/ peer is listening;
496 , port :: PortNumber
497
498 -- TODO: optional boolean "seed" key
499
500 -- | received in response to a previous get_peers query.
501 , sessionToken :: Token
502
503 } deriving (Show, Eq, Typeable)
504
505peer_ip_key = "ip"
506peer_id_key = "peer id"
507peer_port_key = "port"
508msg_type_key = "msg_type"
509piece_key = "piece"
510total_size_key = "total_size"
511node_id_key :: BKey
512node_id_key = "id"
513read_only_key :: BKey
514read_only_key = "ro"
515want_key :: BKey
516want_key = "want"
517target_key :: BKey
518target_key = "target"
519nodes_key :: BKey
520nodes_key = "nodes"
521nodes6_key :: BKey
522nodes6_key = "nodes6"
523info_hash_key :: BKey
524info_hash_key = "info_hash"
525peers_key :: BKey
526peers_key = "values"
527token_key :: BKey
528token_key = "token"
529name_key :: BKey
530name_key = "name"
531port_key :: BKey
532port_key = "port"
533implied_port_key :: BKey
534implied_port_key = "implied_port"
535
536instance BEncode Announce where
537 toBEncode Announce {..} = toDict $
538 implied_port_key .=? flagField impliedPort
539 .: info_hash_key .=! topic
540 .: name_key .=? announcedName
541 .: port_key .=! port
542 .: token_key .=! sessionToken
543 .: endDict
544 where
545 flagField flag = if flag then Just (1 :: Int) else Nothing
546
547 fromBEncode = fromDict $ do
548 Announce <$> (boolField <$> optional (field (req implied_port_key)))
549 <*>! info_hash_key
550 <*>? name_key
551 <*>! port_key
552 <*>! token_key
553 where
554 boolField = maybe False (/= (0 :: Int))
555
556
557
558-- | The queried node must verify that the token was previously sent
559-- to the same IP address as the querying node. Then the queried node
560-- should store the IP address of the querying node and the supplied
561-- port number under the infohash in its store of peer contact
562-- information.
563data Announced = Announced
564 deriving (Show, Eq, Typeable)
565
566instance BEncode Announced where
567 toBEncode _ = toBEncode Ping
568 fromBEncode _ = pure Announced
569
570announceH :: SwarmsDatabase -> NodeInfo -> Announce -> IO (Either Error Announced)
571announceH (SwarmsDatabase peers toks _) naddr announcement = do
572 checkToken toks naddr (sessionToken announcement)
573 >>= bool (Left <$> return (Error ProtocolError "invalid parameter: token"))
574 (Right <$> go)
575 where
576 go = do
577 let annPort = if impliedPort announcement
578 then nodePort naddr
579 else port announcement
580 peerAddr = PeerAddr Nothing (nodeIP naddr) annPort
581 atomically
582 $ modifyTVar' peers
583 $ insertPeer (topic announcement) (announcedName announcement) peerAddr
584 return Announced
diff --git a/src/Network/BitTorrent/DHT/Token.hs b/src/Network/BitTorrent/DHT/Token.hs
index e3a6b1f6..08079b75 100644
--- a/src/Network/BitTorrent/DHT/Token.hs
+++ b/src/Network/BitTorrent/DHT/Token.hs
@@ -24,6 +24,10 @@ module Network.BitTorrent.DHT.Token
24 24
25 -- * Session tokens 25 -- * Session tokens
26 , TokenMap 26 , TokenMap
27 , SessionTokens
28 , nullSessionTokens
29 , checkToken
30 , grantToken
27 31
28 -- ** Construction 32 -- ** Construction
29 , Network.BitTorrent.DHT.Token.tokens 33 , Network.BitTorrent.DHT.Token.tokens
@@ -52,7 +56,7 @@ import Data.Hashable
52import Data.String 56import Data.String
53import Data.Time 57import Data.Time
54import System.Random 58import System.Random
55 59import Control.Concurrent.STM
56import Network.Address 60import Network.Address
57 61
58-- TODO use ShortByteString 62-- TODO use ShortByteString
@@ -77,7 +81,7 @@ type Secret = Int
77 81
78-- The BitTorrent implementation uses the SHA1 hash of the IP address 82-- The BitTorrent implementation uses the SHA1 hash of the IP address
79-- concatenated onto a secret, we use hashable instead. 83-- concatenated onto a secret, we use hashable instead.
80makeToken :: Hashable a => NodeAddr a -> Secret -> Token 84makeToken :: Hashable a => a -> Secret -> Token
81makeToken n s = Token $ toBS $ hashWithSalt s n 85makeToken n s = Token $ toBS $ hashWithSalt s n
82 where 86 where
83 toBS = toStrict . toLazyByteString . int64BE . fromIntegral 87 toBS = toStrict . toLazyByteString . int64BE . fromIntegral
@@ -104,7 +108,7 @@ tokens seed = (`evalState` mkStdGen seed) $
104-- 'update's. 108-- 'update's.
105-- 109--
106-- Typically used to handle find_peers query. 110-- Typically used to handle find_peers query.
107lookup :: Hashable a => NodeAddr a -> TokenMap -> Token 111lookup :: Hashable a => a -> TokenMap -> Token
108lookup addr TokenMap {..} = makeToken addr curSecret 112lookup addr TokenMap {..} = makeToken addr curSecret
109 113
110-- | Check if token is valid. 114-- | Check if token is valid.
@@ -112,7 +116,7 @@ lookup addr TokenMap {..} = makeToken addr curSecret
112-- Typically used to handle 'Network.DHT.Mainline.Announce' 116-- Typically used to handle 'Network.DHT.Mainline.Announce'
113-- query. If token is invalid the 'Network.KRPC.ProtocolError' should 117-- query. If token is invalid the 'Network.KRPC.ProtocolError' should
114-- be sent back to the malicious node. 118-- be sent back to the malicious node.
115member :: Hashable a => NodeAddr a -> Token -> TokenMap -> Bool 119member :: Hashable a => a -> Token -> TokenMap -> Bool
116member addr token TokenMap {..} = token `L.elem` valid 120member addr token TokenMap {..} = token `L.elem` valid
117 where valid = makeToken addr <$> [curSecret, prevSecret] 121 where valid = makeToken addr <$> [curSecret, prevSecret]
118 122
@@ -130,3 +134,49 @@ update TokenMap {..} = TokenMap
130 } 134 }
131 where 135 where
132 (newSecret, newGen) = next generator 136 (newSecret, newGen) = next generator
137
138data SessionTokens = SessionTokens
139 { tokenMap :: !TokenMap
140 , lastUpdate :: !UTCTime
141 , maxInterval :: !NominalDiffTime
142 }
143
144nullSessionTokens :: IO SessionTokens
145nullSessionTokens = SessionTokens
146 <$> (tokens <$> randomIO)
147 <*> getCurrentTime
148 <*> pure defaultUpdateInterval
149
150-- TODO invalidate *twice* if needed
151invalidateTokens :: UTCTime -> SessionTokens -> SessionTokens
152invalidateTokens curTime ts @ SessionTokens {..}
153 | curTime `diffUTCTime` lastUpdate > maxInterval = SessionTokens
154 { tokenMap = update tokenMap
155 , lastUpdate = curTime
156 , maxInterval = maxInterval
157 }
158 | otherwise = ts
159
160{-----------------------------------------------------------------------
161-- Tokens
162-----------------------------------------------------------------------}
163
164tryUpdateSecret :: TVar SessionTokens -> IO ()
165tryUpdateSecret toks = do
166 curTime <- getCurrentTime
167 atomically $ modifyTVar' toks (invalidateTokens curTime)
168
169grantToken :: Hashable addr => TVar SessionTokens -> addr -> IO Token
170grantToken sessionTokens addr = do
171 tryUpdateSecret sessionTokens
172 toks <- readTVarIO sessionTokens
173 return $ Network.BitTorrent.DHT.Token.lookup addr $ tokenMap toks
174
175-- | Throws 'HandlerError' if the token is invalid or already
176-- expired. See 'TokenMap' for details.
177checkToken :: Hashable addr => TVar SessionTokens -> addr -> Token -> IO Bool
178checkToken sessionTokens addr questionableToken = do
179 tryUpdateSecret sessionTokens
180 toks <- readTVarIO sessionTokens
181 return $ member addr questionableToken (tokenMap toks)
182