summaryrefslogtreecommitdiff
path: root/dht/src/Network/BitTorrent/DHT/Token.hs
diff options
context:
space:
mode:
Diffstat (limited to 'dht/src/Network/BitTorrent/DHT/Token.hs')
-rw-r--r--dht/src/Network/BitTorrent/DHT/Token.hs201
1 files changed, 201 insertions, 0 deletions
diff --git a/dht/src/Network/BitTorrent/DHT/Token.hs b/dht/src/Network/BitTorrent/DHT/Token.hs
new file mode 100644
index 00000000..171cc8be
--- /dev/null
+++ b/dht/src/Network/BitTorrent/DHT/Token.hs
@@ -0,0 +1,201 @@
1-- |
2-- Copyright : (c) Sam Truzjan 2013
3-- License : BSD3
4-- Maintainer : pxqr.sta@gmail.com
5-- Stability : experimental
6-- Portability : portable
7--
8-- The return value for a query for peers includes an opaque value
9-- known as the 'Token'. For a node to announce that its controlling
10-- peer is downloading a torrent, it must present the token received
11-- from the same queried node in a recent query for peers. When a node
12-- attempts to \"announce\" a torrent, the queried node checks the
13-- token against the querying node's 'IP' address. This is to prevent
14-- malicious hosts from signing up other hosts for torrents. Since the
15-- token is merely returned by the querying node to the same node it
16-- received the token from, the implementation is not defined. Tokens
17-- must be accepted for a reasonable amount of time after they have
18-- been distributed.
19--
20{-# LANGUAGE GeneralizedNewtypeDeriving, CPP #-}
21module Network.BitTorrent.DHT.Token
22 ( -- * Token
23 Token
24 , maxInterval
25 , toPaddedByteString
26 , fromPaddedByteString
27
28 -- * Session tokens
29 , TokenMap
30 , SessionTokens
31 , nullSessionTokens
32 , checkToken
33 , grantToken
34
35 -- ** Construction
36 , Network.BitTorrent.DHT.Token.tokens
37
38 -- ** Query
39 , Network.BitTorrent.DHT.Token.lookup
40 , Network.BitTorrent.DHT.Token.member
41
42 -- ** Modification
43 , Network.BitTorrent.DHT.Token.defaultUpdateInterval
44 , Network.BitTorrent.DHT.Token.update
45 ) where
46
47import Control.Arrow
48import Control.Monad.State
49#ifdef VERSION_bencoding
50import Data.BEncode (BEncode)
51#endif
52import Data.ByteString as BS
53import Data.ByteString.Char8 as B8
54import Data.ByteString.Lazy as BL
55import Data.ByteString.Lazy.Builder as BS
56import qualified Data.ByteString.Base16 as Base16
57import Data.Default
58import Data.List as L
59import Data.Hashable
60import Data.String
61import Data.Time
62import System.Random
63import Control.Concurrent.STM
64
65-- TODO use ShortByteString
66
67-- | An opaque value.
68newtype Token = Token BS.ByteString
69 deriving ( Eq, IsString
70#ifdef VERSION_bencoding
71 , BEncode
72#endif
73 )
74
75instance Show Token where
76 show (Token bs) = B8.unpack $ Base16.encode bs
77
78instance Read Token where
79 readsPrec i s = pure $ (Token *** B8.unpack) $ Base16.decode (B8.pack s)
80
81-- | Meaningless token, for testing purposes only.
82instance Default Token where
83 def = makeToken (0::Int) 0
84
85-- | Prepend token with 0x20 bytes to fill the available width.
86--
87-- If n > 8, then this will also guarantee a nonzero token, which is useful for
88-- Tox ping-id values for announce responses.
89toPaddedByteString :: Int -> Token -> BS.ByteString
90toPaddedByteString n (Token bs) = BS.append (BS.replicate (n - BS.length bs) 0x20) bs
91
92fromPaddedByteString :: Int -> BS.ByteString -> Token
93fromPaddedByteString n bs = Token $ BS.drop (n - len) bs
94 where
95 len = BS.length tok where Token tok = def
96
97-- | The secret value used as salt.
98type Secret = Int
99
100-- The BitTorrent implementation uses the SHA1 hash of the IP address
101-- concatenated onto a secret, we use hashable instead.
102makeToken :: Hashable a => a -> Secret -> Token
103makeToken n s = Token $ toBS $ hashWithSalt s n
104 where
105 toBS = toStrict . toLazyByteString . int64BE . fromIntegral
106{-# INLINE makeToken #-}
107
108-- | Constant space 'Node' to 'Token' map based on the secret value.
109data TokenMap = TokenMap
110 { prevSecret :: {-# UNPACK #-} !Secret
111 , curSecret :: {-# UNPACK #-} !Secret
112 , generator :: {-# UNPACK #-} !StdGen
113 } deriving Show
114
115-- | A new token map based on the specified seed value. Returned token
116-- map should be periodicatically 'update'd.
117--
118-- Normally, the seed value should vary between invocations of the
119-- client software.
120tokens :: Int -> TokenMap
121tokens seed = (`evalState` mkStdGen seed) $
122 TokenMap <$> state next
123 <*> state next
124 <*> get
125
126-- | Get token for the given node. A token becomes invalid after 2
127-- 'update's.
128--
129-- Typically used to handle find_peers query.
130lookup :: Hashable a => a -> TokenMap -> Token
131lookup addr TokenMap {..} = makeToken addr curSecret
132
133-- | Check if token is valid.
134--
135-- Typically used to handle 'Network.DHT.Mainline.Announce'
136-- query. If token is invalid the 'Network.KRPC.ProtocolError' should
137-- be sent back to the malicious node.
138member :: Hashable a => a -> Token -> TokenMap -> Bool
139member addr token TokenMap {..} = token `L.elem` valid
140 where valid = makeToken addr <$> [curSecret, prevSecret]
141
142-- | Secret changes every five minutes and tokens up to ten minutes old
143-- are accepted.
144defaultUpdateInterval :: NominalDiffTime
145defaultUpdateInterval = 5 * 60
146
147-- | Update current tokens.
148update :: TokenMap -> TokenMap
149update TokenMap {..} = TokenMap
150 { prevSecret = curSecret
151 , curSecret = newSecret
152 , generator = newGen
153 }
154 where
155 (newSecret, newGen) = next generator
156
157data SessionTokens = SessionTokens
158 { tokenMap :: !TokenMap
159 , lastUpdate :: !UTCTime
160 , maxInterval :: !NominalDiffTime
161 }
162
163nullSessionTokens :: IO SessionTokens
164nullSessionTokens = SessionTokens
165 <$> (tokens <$> randomIO)
166 <*> getCurrentTime
167 <*> pure defaultUpdateInterval
168
169-- TODO invalidate *twice* if needed
170invalidateTokens :: UTCTime -> SessionTokens -> SessionTokens
171invalidateTokens curTime ts @ SessionTokens {..}
172 | curTime `diffUTCTime` lastUpdate > maxInterval = SessionTokens
173 { tokenMap = update tokenMap
174 , lastUpdate = curTime
175 , maxInterval = maxInterval
176 }
177 | otherwise = ts
178
179{-----------------------------------------------------------------------
180-- Tokens
181-----------------------------------------------------------------------}
182
183tryUpdateSecret :: TVar SessionTokens -> IO ()
184tryUpdateSecret toks = do
185 curTime <- getCurrentTime
186 atomically $ modifyTVar' toks (invalidateTokens curTime)
187
188grantToken :: Hashable addr => TVar SessionTokens -> addr -> IO Token
189grantToken sessionTokens addr = do
190 tryUpdateSecret sessionTokens
191 toks <- readTVarIO sessionTokens
192 return $ Network.BitTorrent.DHT.Token.lookup addr $ tokenMap toks
193
194-- | Throws 'HandlerError' if the token is invalid or already
195-- expired. See 'TokenMap' for details.
196checkToken :: Hashable addr => TVar SessionTokens -> addr -> Token -> IO Bool
197checkToken sessionTokens addr questionableToken = do
198 tryUpdateSecret sessionTokens
199 toks <- readTVarIO sessionTokens
200 return $ member addr questionableToken (tokenMap toks)
201