summaryrefslogtreecommitdiff
path: root/src/Network/BitTorrent/DHT/Token.hs
diff options
context:
space:
mode:
authorSam Truzjan <pxqr.sta@gmail.com>2013-12-27 12:58:17 +0400
committerSam Truzjan <pxqr.sta@gmail.com>2013-12-27 12:58:17 +0400
commit1e22d4d33ad6b7da93f7fd1fd757f10d74d98309 (patch)
tree5a95c01d10ecb44d49af6e698ae42920218eedf9 /src/Network/BitTorrent/DHT/Token.hs
parent12c32c9b6c25c9768b01cca583061f19908d7151 (diff)
Add naive session tokens implementation
Diffstat (limited to 'src/Network/BitTorrent/DHT/Token.hs')
-rw-r--r--src/Network/BitTorrent/DHT/Token.hs91
1 files changed, 91 insertions, 0 deletions
diff --git a/src/Network/BitTorrent/DHT/Token.hs b/src/Network/BitTorrent/DHT/Token.hs
new file mode 100644
index 00000000..6705f932
--- /dev/null
+++ b/src/Network/BitTorrent/DHT/Token.hs
@@ -0,0 +1,91 @@
1-- | The return value for a query for peers includes an opaque value
2-- known as the \"token.\" For a node to announce that its controlling
3-- peer is downloading a torrent, it must present the token received
4-- from the same queried node in a recent query for peers. When a node
5-- attempts to "announce" a torrent, the queried node checks the token
6-- against the querying node's IP address. This is to prevent
7-- malicious hosts from signing up other hosts for torrents. Since the
8-- token is merely returned by the querying node to the same node it
9-- received the token from, the implementation is not defined. Tokens
10-- must be accepted for a reasonable amount of time after they have
11-- been distributed.
12--
13{-# LANGUAGE GeneralizedNewtypeDeriving #-}
14module Network.BitTorrent.DHT.Token
15 ( Token
16 , TokenMap
17 , Network.BitTorrent.DHT.Token.tokens
18 , Network.BitTorrent.DHT.Token.lookup
19 , Network.BitTorrent.DHT.Token.member
20 , Network.BitTorrent.DHT.Token.updateInterval
21 , Network.BitTorrent.DHT.Token.update
22 ) where
23
24import Control.Applicative
25import Control.Monad.State
26import Data.BEncode (BEncode)
27import Data.ByteString as BS
28import Data.ByteString.Lazy as BL
29import Data.ByteString.Lazy.Builder as BS
30import Data.Default
31import Data.List as L
32import Data.Hashable
33import Data.String
34import Data.Time
35import System.Random
36
37import Network.BitTorrent.Core
38
39
40type Secret = Int
41
42-- TODO use ShortByteString
43newtype Token = Token BS.ByteString
44 deriving (Show, Eq, BEncode, IsString)
45
46-- | Meaningless token, for testsing purposes only.
47instance Default Token where
48 def = Token "0xdeadbeef"
49
50-- The BitTorrent implementation uses the SHA1 hash of the IP address
51-- concatenated onto a secret, we use hashable instead.
52makeToken :: Hashable a => NodeAddr a -> Secret -> Token
53makeToken n s = Token $ toBS $ hashWithSalt s n
54 where
55 toBS = toStrict . toLazyByteString . int64BE . fromIntegral
56
57-- | Constant space token map based on secret.
58data TokenMap = TokenMap
59 { prevSecret :: {-# UNPACK #-} !Secret
60 , curSecret :: {-# UNPACK #-} !Secret
61 , generator :: {-# UNPACK #-} !StdGen
62 } deriving Show
63
64tokens :: Int -> TokenMap
65tokens seed = (`evalState` mkStdGen seed) $
66 TokenMap <$> state next
67 <*> state next
68 <*> get
69
70lookup :: Hashable a => NodeAddr a -> TokenMap -> Token
71lookup addr TokenMap {..} = makeToken addr curSecret
72
73-- | If token is not set 'Network.KRPC.ProtocolError' should be sent
74-- back.
75member :: Hashable a => NodeAddr a -> Token -> TokenMap -> Bool
76member addr token TokenMap {..} = token `L.elem` valid
77 where valid = makeToken addr <$> [curSecret, prevSecret]
78
79-- Secret changes every five minutes and tokens up to ten minutes old
80-- are accepted.
81updateInterval :: NominalDiffTime
82updateInterval = 5 * 60
83
84update :: TokenMap -> TokenMap
85update TokenMap {..} = TokenMap
86 { prevSecret = curSecret
87 , curSecret = newSecret
88 , generator = newGen
89 }
90 where
91 (newSecret, newGen) = next generator \ No newline at end of file