summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Network/BitTorrent/Core/Node.hs58
-rw-r--r--src/Network/BitTorrent/Core/PeerAddr.hs1
2 files changed, 54 insertions, 5 deletions
diff --git a/src/Network/BitTorrent/Core/Node.hs b/src/Network/BitTorrent/Core/Node.hs
index 0cb95dd2..f6ab7d82 100644
--- a/src/Network/BitTorrent/Core/Node.hs
+++ b/src/Network/BitTorrent/Core/Node.hs
@@ -1,4 +1,21 @@
1-- |
2-- Module : Network.BitTorrent.Core.Node
3-- Copyright : (c) Sam Truzjan 2013
4-- (c) Daniel Gröber 2013
5-- License : BSD3
6-- Maintainer : pxqr.sta@gmail.com
7-- Stability : experimental
8-- Portability : portable
9--
10-- A \"node\" is a client\/server listening on a UDP port
11-- implementing the distributed hash table protocol. The DHT is
12-- composed of nodes and stores the location of peers. BitTorrent
13-- clients include a DHT node, which is used to contact other nodes
14-- in the DHT to get the location of peers to download from using
15-- the BitTorrent protocol.
16--
1{-# LANGUAGE RecordWildCards #-} 17{-# LANGUAGE RecordWildCards #-}
18{-# LANGUAGE FlexibleInstances #-}
2{-# LANGUAGE TemplateHaskell #-} 19{-# LANGUAGE TemplateHaskell #-}
3{-# LANGUAGE GeneralizedNewtypeDeriving #-} 20{-# LANGUAGE GeneralizedNewtypeDeriving #-}
4{-# LANGUAGE DeriveDataTypeable #-} 21{-# LANGUAGE DeriveDataTypeable #-}
@@ -22,23 +39,29 @@ import Data.Bits
22import Data.ByteString as BS 39import Data.ByteString as BS
23import Data.BEncode as BE 40import Data.BEncode as BE
24import Data.Default 41import Data.Default
42import Data.IP
43import Data.List as L
25import Data.Ord 44import Data.Ord
26import Data.Typeable
27import Data.Serialize as S 45import Data.Serialize as S
46import Data.String
47import Data.Typeable
28import Data.Word 48import Data.Word
29import Network 49import Network
30import System.Entropy 50import System.Entropy
31 51
32import Data.Torrent.JSON 52import Data.Torrent.JSON
33import Network.BitTorrent.Core.PeerAddr () 53import Network.BitTorrent.Core.PeerAddr (PeerAddr (..))
34 54
35{----------------------------------------------------------------------- 55{-----------------------------------------------------------------------
36-- Node id 56-- Node id
37-----------------------------------------------------------------------} 57-----------------------------------------------------------------------}
38-- TODO more compact representation ('ShortByteString's?) 58-- TODO more compact representation ('ShortByteString's?)
39 59
40-- | Normally, /this/ node id should we saved between invocations of 60-- | Each node has a globally unique identifier known as the \"node
41-- the client software. 61-- ID.\"
62--
63-- Normally, /this/ node id should we saved between invocations
64-- of the client software.
42newtype NodeId = NodeId ByteString 65newtype NodeId = NodeId ByteString
43 deriving (Show, Eq, Ord, BEncode, FromJSON, ToJSON, Typeable) 66 deriving (Show, Eq, Ord, BEncode, FromJSON, ToJSON, Typeable)
44 67
@@ -55,6 +78,13 @@ instance Serialize NodeId where
55 put (NodeId bs) = putByteString bs 78 put (NodeId bs) = putByteString bs
56 {-# INLINE put #-} 79 {-# INLINE put #-}
57 80
81-- | ASCII encoded.
82instance IsString NodeId where
83 fromString str
84 | L.length str == nodeIdSize = NodeId (fromString str)
85 | otherwise = error "fromString: invalid NodeId length"
86 {-# INLINE fromString #-}
87
58-- | Test if the nth bit is set. 88-- | Test if the nth bit is set.
59testIdBit :: NodeId -> Word -> Bool 89testIdBit :: NodeId -> Word -> Bool
60testIdBit (NodeId bs) i 90testIdBit (NodeId bs) i
@@ -85,7 +115,9 @@ $(deriveJSON omitRecordPrefix ''NodeAddr)
85-- | KRPC compatible encoding. 115-- | KRPC compatible encoding.
86instance Serialize a => Serialize (NodeAddr a) where 116instance Serialize a => Serialize (NodeAddr a) where
87 get = NodeAddr <$> get <*> get 117 get = NodeAddr <$> get <*> get
118 {-# INLINE get #-}
88 put NodeAddr {..} = put nodeHost >> put nodePort 119 put NodeAddr {..} = put nodeHost >> put nodePort
120 {-# INLINE put #-}
89 121
90-- | Torrent file compatible encoding. 122-- | Torrent file compatible encoding.
91instance BEncode a => BEncode (NodeAddr a) where 123instance BEncode a => BEncode (NodeAddr a) where
@@ -94,6 +126,19 @@ instance BEncode a => BEncode (NodeAddr a) where
94 fromBEncode b = uncurry NodeAddr <$> fromBEncode b 126 fromBEncode b = uncurry NodeAddr <$> fromBEncode b
95 {-# INLINE fromBEncode #-} 127 {-# INLINE fromBEncode #-}
96 128
129-- | Example:
130--
131-- @nodePort \"127.0.0.1:6881\" == 6881@
132--
133instance IsString (NodeAddr IPv4) where
134 fromString = fromPeerAddr . fromString
135
136fromPeerAddr :: PeerAddr a -> NodeAddr a
137fromPeerAddr PeerAddr {..} = NodeAddr
138 { nodeHost = peerHost
139 , nodePort = peerPort
140 }
141
97{----------------------------------------------------------------------- 142{-----------------------------------------------------------------------
98-- Node info 143-- Node info
99-----------------------------------------------------------------------} 144-----------------------------------------------------------------------}
@@ -108,7 +153,10 @@ $(deriveJSON omitRecordPrefix ''NodeInfo)
108instance Eq a => Ord (NodeInfo a) where 153instance Eq a => Ord (NodeInfo a) where
109 compare = comparing nodeId 154 compare = comparing nodeId
110 155
111-- | KRPC 'compact list' compatible encoding. 156-- | KRPC 'compact list' compatible encoding: contact information for
157-- nodes is encoded as a 26-byte string. Also known as "Compact node
158-- info" the 20-byte Node ID in network byte order has the compact
159-- IP-address/port info concatenated to the end.
112instance Serialize a => Serialize (NodeInfo a) where 160instance Serialize a => Serialize (NodeInfo a) where
113 get = NodeInfo <$> get <*> get 161 get = NodeInfo <$> get <*> get
114 put NodeInfo {..} = put nodeId >> put nodeAddr 162 put NodeInfo {..} = put nodeId >> put nodeAddr
diff --git a/src/Network/BitTorrent/Core/PeerAddr.hs b/src/Network/BitTorrent/Core/PeerAddr.hs
index 86b88491..63ae04b9 100644
--- a/src/Network/BitTorrent/Core/PeerAddr.hs
+++ b/src/Network/BitTorrent/Core/PeerAddr.hs
@@ -1,4 +1,5 @@
1-- | 1-- |
2-- Module : Network.BitTorrent.Core.PeerAddr
2-- Copyright : (c) Sam Truzjan 2013 3-- Copyright : (c) Sam Truzjan 2013
3-- (c) Daniel Gröber 2013 4-- (c) Daniel Gröber 2013
4-- License : BSD3 5-- License : BSD3