diff options
Diffstat (limited to 'src/Network')
-rw-r--r-- | src/Network/BitTorrent/Core/Node.hs | 8 | ||||
-rw-r--r-- | src/Network/BitTorrent/Core/PeerAddr.hs | 5 | ||||
-rw-r--r-- | src/Network/BitTorrent/DHT/Message.hs | 4 | ||||
-rw-r--r-- | src/Network/BitTorrent/DHT/Token.hs | 91 |
4 files changed, 104 insertions, 4 deletions
diff --git a/src/Network/BitTorrent/Core/Node.hs b/src/Network/BitTorrent/Core/Node.hs index f6ab7d82..f163a895 100644 --- a/src/Network/BitTorrent/Core/Node.hs +++ b/src/Network/BitTorrent/Core/Node.hs | |||
@@ -39,6 +39,7 @@ import Data.Bits | |||
39 | import Data.ByteString as BS | 39 | import Data.ByteString as BS |
40 | import Data.BEncode as BE | 40 | import Data.BEncode as BE |
41 | import Data.Default | 41 | import Data.Default |
42 | import Data.Hashable | ||
42 | import Data.IP | 43 | import Data.IP |
43 | import Data.List as L | 44 | import Data.List as L |
44 | import Data.Ord | 45 | import Data.Ord |
@@ -126,6 +127,10 @@ instance BEncode a => BEncode (NodeAddr a) where | |||
126 | fromBEncode b = uncurry NodeAddr <$> fromBEncode b | 127 | fromBEncode b = uncurry NodeAddr <$> fromBEncode b |
127 | {-# INLINE fromBEncode #-} | 128 | {-# INLINE fromBEncode #-} |
128 | 129 | ||
130 | instance Hashable a => Hashable (NodeAddr a) where | ||
131 | hashWithSalt s NodeAddr {..} = hashWithSalt s (nodeHost, nodePort) | ||
132 | {-# INLINE hashWithSalt #-} | ||
133 | |||
129 | -- | Example: | 134 | -- | Example: |
130 | -- | 135 | -- |
131 | -- @nodePort \"127.0.0.1:6881\" == 6881@ | 136 | -- @nodePort \"127.0.0.1:6881\" == 6881@ |
@@ -160,7 +165,7 @@ instance Eq a => Ord (NodeInfo a) where | |||
160 | instance Serialize a => Serialize (NodeInfo a) where | 165 | instance Serialize a => Serialize (NodeInfo a) where |
161 | get = NodeInfo <$> get <*> get | 166 | get = NodeInfo <$> get <*> get |
162 | put NodeInfo {..} = put nodeId >> put nodeAddr | 167 | put NodeInfo {..} = put nodeId >> put nodeAddr |
163 | 168 | {- | |
164 | type CompactInfo = ByteString | 169 | type CompactInfo = ByteString |
165 | 170 | ||
166 | data NodeList a = CompactNodeList [NodeInfo a] | 171 | data NodeList a = CompactNodeList [NodeInfo a] |
@@ -176,3 +181,4 @@ encodeCompact = S.runPut . mapM_ put | |||
176 | 181 | ||
177 | --encodePeerList :: [PeerAddr] -> [BEncode] | 182 | --encodePeerList :: [PeerAddr] -> [BEncode] |
178 | --encodePeerList = undefined | 183 | --encodePeerList = undefined |
184 | -} \ No newline at end of file | ||
diff --git a/src/Network/BitTorrent/Core/PeerAddr.hs b/src/Network/BitTorrent/Core/PeerAddr.hs index 261df8d0..9f5c7c5d 100644 --- a/src/Network/BitTorrent/Core/PeerAddr.hs +++ b/src/Network/BitTorrent/Core/PeerAddr.hs | |||
@@ -38,6 +38,7 @@ import Data.BEncode.BDict (BKey) | |||
38 | import Data.ByteString.Char8 as BS8 | 38 | import Data.ByteString.Char8 as BS8 |
39 | import Data.Char | 39 | import Data.Char |
40 | import Data.Default | 40 | import Data.Default |
41 | import Data.Hashable | ||
41 | import Data.HashMap.Strict as HM | 42 | import Data.HashMap.Strict as HM |
42 | import Data.IP | 43 | import Data.IP |
43 | import Data.List as L | 44 | import Data.List as L |
@@ -81,6 +82,10 @@ instance Serialize PortNumber where | |||
81 | put = putWord16be . fromIntegral | 82 | put = putWord16be . fromIntegral |
82 | {-# INLINE put #-} | 83 | {-# INLINE put #-} |
83 | 84 | ||
85 | instance Hashable PortNumber where | ||
86 | hashWithSalt s = hashWithSalt s . fromEnum | ||
87 | {-# INLINE hashWithSalt #-} | ||
88 | |||
84 | {----------------------------------------------------------------------- | 89 | {----------------------------------------------------------------------- |
85 | -- IP addr | 90 | -- IP addr |
86 | -----------------------------------------------------------------------} | 91 | -----------------------------------------------------------------------} |
diff --git a/src/Network/BitTorrent/DHT/Message.hs b/src/Network/BitTorrent/DHT/Message.hs index 49629755..83413752 100644 --- a/src/Network/BitTorrent/DHT/Message.hs +++ b/src/Network/BitTorrent/DHT/Message.hs | |||
@@ -30,7 +30,6 @@ module Network.BitTorrent.DHT.Message | |||
30 | import Control.Applicative | 30 | import Control.Applicative |
31 | import Data.BEncode as BE | 31 | import Data.BEncode as BE |
32 | import Data.BEncode.BDict | 32 | import Data.BEncode.BDict |
33 | import Data.ByteString as BS | ||
34 | import Data.List as L | 33 | import Data.List as L |
35 | import Data.Monoid | 34 | import Data.Monoid |
36 | import Data.Serialize as S | 35 | import Data.Serialize as S |
@@ -40,14 +39,13 @@ import Network.KRPC | |||
40 | 39 | ||
41 | import Data.Torrent.InfoHash | 40 | import Data.Torrent.InfoHash |
42 | import Network.BitTorrent.Core | 41 | import Network.BitTorrent.Core |
42 | import Network.BitTorrent.DHT.Token | ||
43 | import Network.KRPC () | 43 | import Network.KRPC () |
44 | 44 | ||
45 | {----------------------------------------------------------------------- | 45 | {----------------------------------------------------------------------- |
46 | -- envelopes | 46 | -- envelopes |
47 | -----------------------------------------------------------------------} | 47 | -----------------------------------------------------------------------} |
48 | 48 | ||
49 | type Token = ByteString | ||
50 | |||
51 | node_id_key :: BKey | 49 | node_id_key :: BKey |
52 | node_id_key = "id" | 50 | node_id_key = "id" |
53 | 51 | ||
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 #-} | ||
14 | module 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 | |||
24 | import Control.Applicative | ||
25 | import Control.Monad.State | ||
26 | import Data.BEncode (BEncode) | ||
27 | import Data.ByteString as BS | ||
28 | import Data.ByteString.Lazy as BL | ||
29 | import Data.ByteString.Lazy.Builder as BS | ||
30 | import Data.Default | ||
31 | import Data.List as L | ||
32 | import Data.Hashable | ||
33 | import Data.String | ||
34 | import Data.Time | ||
35 | import System.Random | ||
36 | |||
37 | import Network.BitTorrent.Core | ||
38 | |||
39 | |||
40 | type Secret = Int | ||
41 | |||
42 | -- TODO use ShortByteString | ||
43 | newtype Token = Token BS.ByteString | ||
44 | deriving (Show, Eq, BEncode, IsString) | ||
45 | |||
46 | -- | Meaningless token, for testsing purposes only. | ||
47 | instance 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. | ||
52 | makeToken :: Hashable a => NodeAddr a -> Secret -> Token | ||
53 | makeToken n s = Token $ toBS $ hashWithSalt s n | ||
54 | where | ||
55 | toBS = toStrict . toLazyByteString . int64BE . fromIntegral | ||
56 | |||
57 | -- | Constant space token map based on secret. | ||
58 | data TokenMap = TokenMap | ||
59 | { prevSecret :: {-# UNPACK #-} !Secret | ||
60 | , curSecret :: {-# UNPACK #-} !Secret | ||
61 | , generator :: {-# UNPACK #-} !StdGen | ||
62 | } deriving Show | ||
63 | |||
64 | tokens :: Int -> TokenMap | ||
65 | tokens seed = (`evalState` mkStdGen seed) $ | ||
66 | TokenMap <$> state next | ||
67 | <*> state next | ||
68 | <*> get | ||
69 | |||
70 | lookup :: Hashable a => NodeAddr a -> TokenMap -> Token | ||
71 | lookup addr TokenMap {..} = makeToken addr curSecret | ||
72 | |||
73 | -- | If token is not set 'Network.KRPC.ProtocolError' should be sent | ||
74 | -- back. | ||
75 | member :: Hashable a => NodeAddr a -> Token -> TokenMap -> Bool | ||
76 | member 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. | ||
81 | updateInterval :: NominalDiffTime | ||
82 | updateInterval = 5 * 60 | ||
83 | |||
84 | update :: TokenMap -> TokenMap | ||
85 | update 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 | ||