summaryrefslogtreecommitdiff
path: root/src/Network/BitTorrent/DHT.hs
diff options
context:
space:
mode:
authorSam T <pxqr.sta@gmail.com>2013-07-09 00:09:20 +0400
committerSam T <pxqr.sta@gmail.com>2013-07-09 00:09:20 +0400
commit19efaca1db008a58a1c1b65395465550ec0b72b6 (patch)
tree7b99c38e0af6b894d2a84727a1cba6a838e01e02 /src/Network/BitTorrent/DHT.hs
parentf7245e3cc7c5729b401bbbe3438a9f5b9dda211b (diff)
~ Move DHT to single module.
Diffstat (limited to 'src/Network/BitTorrent/DHT.hs')
-rw-r--r--src/Network/BitTorrent/DHT.hs165
1 files changed, 163 insertions, 2 deletions
diff --git a/src/Network/BitTorrent/DHT.hs b/src/Network/BitTorrent/DHT.hs
index 2d2073f0..60f4566a 100644
--- a/src/Network/BitTorrent/DHT.hs
+++ b/src/Network/BitTorrent/DHT.hs
@@ -1,14 +1,175 @@
1{-# LANGUAGE OverloadedStrings #-} 1{-# LANGUAGE OverloadedStrings #-}
2{-# LANGUAGE RecordWildCards #-}
2module Network.BitTorrent.DHT 3module Network.BitTorrent.DHT
3 ( 4 ( dhtServer
4 ) where 5 ) where
5 6
7import Control.Applicative
8import Control.Concurrent.STM
6import Data.ByteString 9import Data.ByteString
10import Data.Serialize as S
11import Data.Function
12import Data.Ord
13import Data.HashMap.Strict as HM
14
7import Network 15import Network
16import Network.Socket
17import Remote.KRPC
8 18
19import Data.BEncode
20import Data.Torrent
9import Data.Kademlia.Routing.Table 21import Data.Kademlia.Routing.Table
10 22
23{-----------------------------------------------------------------------
24 Node
25-----------------------------------------------------------------------}
26
27type NodeId = ByteString
28
29-- WARN is the 'system' random suitable for this?
30-- | Generate random NodeID used for the entire session.
31-- Distribution of ID's should be as uniform as possible.
32--
33genNodeID :: IO NodeId
34genNodeID = undefined -- randomIO
35
36instance Serialize PortNumber where
37 get = fromIntegral <$> getWord16be
38 put = putWord16be . fromIntegral
39
40
41data NodeAddr = NodeAddr {
42 nodeIP :: !HostAddress
43 , nodePort :: !PortNumber
44 } deriving (Show, Eq)
45
46instance Serialize NodeAddr where
47 get = NodeAddr <$> getWord32be <*> get
48 put NodeAddr {..} = do
49 putWord32be nodeIP
50 put nodePort
51
52
53data NodeInfo = NodeInfo {
54 nodeID :: !NodeId
55 , nodeAddr :: !NodeAddr
56 } deriving (Show, Eq)
57
58instance Serialize NodeInfo where
59 get = NodeInfo <$> getByteString 20 <*> get
60 put NodeInfo {..} = put nodeID >> put nodeAddr
61
62type CompactInfo = ByteString
63
64decodeCompact :: CompactInfo -> Either String [NodeInfo]
65decodeCompact = S.runGet (many get)
66
67encodeCompact :: [NodeId] -> CompactInfo
68encodeCompact = S.runPut . mapM_ put
69
70type Distance = NodeId
71
11--type DHT k v = StateT (Table k v) IO 72--type DHT k v = StateT (Table k v) IO
12 73
13--findNode :: NodeID -> DHT k v [NodeInfo] 74--findNode :: NodeID -> DHT k v [NodeInfo]
14--findNode = undefined \ No newline at end of file 75--findNode = undefined
76
77genSecret :: IO Secret
78genSecret = undefined
79
80type Token = Int
81type Secret = Int
82
83token :: NodeAddr -> Secret -> Token
84token = return undefined
85
86defaultToken :: Token
87defaultToken = 0xdeadbeef
88
89{-----------------------------------------------------------------------
90 Routing table
91-----------------------------------------------------------------------}
92
93-- TODO use more compact routing table
94type RoutingTable = HashMap NodeId NodeAddr
95
96type Alpha = Int
97
98kclosest :: Int -> NodeId -> RoutingTable -> [NodeId]
99kclosest = undefined
100
101{-----------------------------------------------------------------------
102 Node session
103-----------------------------------------------------------------------}
104
105data NodeSession = NodeSession {
106 nodeId :: !NodeId
107 , routingTable :: !(TVar RoutingTable)
108 , alpha :: !Alpha
109 }
110
111instance Eq NodeSession where
112 (==) = (==) `on` nodeId
113
114instance Ord NodeSession where
115 compare = comparing nodeId
116
117{-----------------------------------------------------------------------
118 Queries
119-----------------------------------------------------------------------}
120
121instance BEncodable PortNumber where
122
123pingM :: Method NodeId NodeId
124pingM = method "ping" ["id"] ["id"]
125
126findNodeM :: Method (NodeId, NodeId) (NodeId, CompactInfo)
127findNodeM = method "find_node" ["id", "target"] ["id", "nodes"]
128
129-- | Lookup peers by a torrent infohash.
130getPeersM :: Method (NodeId, InfoHash) (NodeId, Token, CompactInfo) -- use Map ByteString BEncode
131getPeersM = method "get_peers" ["id", "info_hash"] ["id", "token", "nodes"]
132
133-- | Used to announce that the peer, controlling the quering node is
134-- downloading a torrent on a port.
135announcePeerM :: Method (NodeId, InfoHash, PortNumber, Token) NodeId
136announcePeerM = method "announce_peer" ["id", "info_hash", "port", "token"] ["id"]
137
138pingC :: NodeSession -> NodeAddr -> IO ()
139pingC NodeSession {..} addr @ NodeAddr {..} = do
140 nid <- call (nodeIP, nodePort) pingM nodeId
141 atomically $ modifyTVar' routingTable $ HM.insert nid addr
142
143--getPeerC :: NodeSession -> NodeAddr -> InfoHash -> IO (Either CompactInfo )
144getPeerC NodeSession {..} addr @ NodeAddr {..} ih = do
145 call (nodeIP, nodePort) getPeersM
146
147type ServerHandler a b = NodeSession -> NodeAddr -> a -> IO b
148
149pingS :: ServerHandler NodeId NodeId
150pingS NodeSession {..} addr nid = do
151 atomically $ modifyTVar' routingTable $ HM.insert nid addr
152 return nodeId
153
154findNodeS :: ServerHandler (NodeId, NodeId) (NodeId, CompactInfo)
155findNodeS NodeSession {..} addr (nid, qnid) = do
156 rt <- atomically $ readTVar routingTable
157 return (nodeId, encodeCompact $ kclosest alpha qnid rt)
158
159getPeersS :: ServerHandler (NodeId, InfoHash) (NodeId, Token, CompactInfo)
160getPeersS NodeSession {..} addr (nid, ih) = do
161
162 return (nodeId, defaultToken, error "compact info")
163
164announcePeerS :: ServerHandler (NodeId, InfoHash, PortNumber, Token) NodeId
165announcePeerS NodeSession {..} addr (nid, ih, port, token) = do
166 let right = (error "checkToken")
167 return nodeId
168
169dhtServer :: PortNumber -> NodeSession -> IO ()
170dhtServer p s = server p
171 [ pingM ==> pingS s undefined
172 , findNodeM ==> findNodeS s undefined
173 , getPeersM ==> getPeersS s undefined
174 , announcePeerM ==> announcePeerS s undefined
175 ] \ No newline at end of file