summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSam Truzjan <pxqr.sta@gmail.com>2013-12-17 15:48:20 +0400
committerSam Truzjan <pxqr.sta@gmail.com>2013-12-17 15:48:20 +0400
commit26444f9639063547d46d2aac17f555c0c56bba00 (patch)
tree3bf9bf9281cda60549cc4490ffe998a60bad177f
parentea8d3846ca916136eadf2cd72731ec61b7889ddc (diff)
Move Node attributes to the Core modules
We need to share them between Exchange subsystem and DHT.
-rw-r--r--bittorrent.cabal4
-rw-r--r--src/Network/BitTorrent/Core/Node.hs108
2 files changed, 111 insertions, 1 deletions
diff --git a/bittorrent.cabal b/bittorrent.cabal
index faf72c75..947461a9 100644
--- a/bittorrent.cabal
+++ b/bittorrent.cabal
@@ -54,9 +54,11 @@ library
54 Network.BitTorrent.Client.Swarm 54 Network.BitTorrent.Client.Swarm
55 Network.BitTorrent.Core 55 Network.BitTorrent.Core
56 Network.BitTorrent.Core.Fingerprint 56 Network.BitTorrent.Core.Fingerprint
57 Network.BitTorrent.Core.Node
57 Network.BitTorrent.Core.PeerId 58 Network.BitTorrent.Core.PeerId
58 Network.BitTorrent.Core.PeerAddr 59 Network.BitTorrent.Core.PeerAddr
59-- Network.BitTorrent.DHT 60-- Network.BitTorrent.DHT
61-- Network.BitTorrent.DHT.Message
60-- Network.BitTorrent.DHT.Protocol 62-- Network.BitTorrent.DHT.Protocol
61-- Network.BitTorrent.DHT.Session 63-- Network.BitTorrent.DHT.Session
62-- Network.BitTorrent.Exchange 64-- Network.BitTorrent.Exchange
@@ -133,7 +135,7 @@ library
133 135
134 -- Network 136 -- Network
135 , network >= 2.4 137 , network >= 2.4
136-- , krpc >= 0.4 138 , krpc >= 0.4
137 , http-types >= 0.8 139 , http-types >= 0.8
138 , http-conduit >= 1.9 && < 2.0 140 , http-conduit >= 1.9 && < 2.0
139 , wai >= 1.4 && < 2.0 141 , wai >= 1.4 && < 2.0
diff --git a/src/Network/BitTorrent/Core/Node.hs b/src/Network/BitTorrent/Core/Node.hs
new file mode 100644
index 00000000..e93c3586
--- /dev/null
+++ b/src/Network/BitTorrent/Core/Node.hs
@@ -0,0 +1,108 @@
1{-# LANGUAGE RecordWildCards #-}
2{-# LANGUAGE TemplateHaskell #-}
3{-# LANGUAGE GeneralizedNewtypeDeriving #-}
4module Network.BitTorrent.Core.Node
5 ( -- * Node ID
6 NodeId
7 , genNodeId
8
9 -- * Node address
10 , NodeAddr (..)
11
12 -- * Node info
13 , NodeInfo (..)
14 ) where
15
16import Control.Applicative
17import Data.Aeson (ToJSON, FromJSON)
18import Data.Aeson.TH
19import Data.ByteString as BS
20import Data.BEncode as BE
21import Data.Serialize as S
22import Network
23import System.Entropy
24
25import Data.Torrent.JSON
26import Network.BitTorrent.Core.PeerAddr ()
27
28{-----------------------------------------------------------------------
29-- Node id
30-----------------------------------------------------------------------}
31
32-- | Normally, /this/ node id should we saved between invocations of
33-- the client software.
34newtype NodeId = NodeId ByteString
35 deriving (Show, Eq, FromJSON, ToJSON)
36
37nodeIdSize :: Int
38nodeIdSize = 20
39
40instance Serialize NodeId where
41 get = NodeId <$> getByteString nodeIdSize
42 {-# INLINE get #-}
43 put (NodeId bs) = putByteString bs
44 {-# INLINE put #-}
45
46-- TODO WARN is the 'system' random suitable for this?
47-- | Generate random NodeID used for the entire session.
48-- Distribution of ID's should be as uniform as possible.
49--
50genNodeId :: IO NodeId
51genNodeId = NodeId <$> getEntropy nodeIdSize
52
53type Distance = NodeId
54
55{-----------------------------------------------------------------------
56-- Node address
57-----------------------------------------------------------------------}
58
59data NodeAddr a = NodeAddr
60 { nodeHost :: !a
61 , nodePort :: {-# UNPACK #-} !PortNumber
62 } deriving (Show, Eq)
63
64$(deriveJSON omitRecordPrefix ''NodeAddr)
65
66-- | KRPC compatible encoding.
67instance Serialize a => Serialize (NodeAddr a) where
68 get = NodeAddr <$> get <*> get
69 put NodeAddr {..} = put nodeHost >> put nodePort
70
71-- | Torrent file compatible encoding.
72instance BEncode a => BEncode (NodeAddr a) where
73 toBEncode NodeAddr {..} = toBEncode (nodeHost, nodePort)
74 {-# INLINE toBEncode #-}
75 fromBEncode b = uncurry NodeAddr <$> fromBEncode b
76 {-# INLINE fromBEncode #-}
77
78{-----------------------------------------------------------------------
79-- Node info
80-----------------------------------------------------------------------}
81
82data NodeInfo a = NodeInfo
83 { nodeId :: !NodeId
84 , nodeAddr :: !(NodeAddr a)
85 } deriving (Show, Eq)
86
87$(deriveJSON omitRecordPrefix ''NodeInfo)
88
89-- | KRPC 'compact list' compatible encoding.
90instance Serialize a => Serialize (NodeInfo a) where
91 get = NodeInfo <$> get <*> get
92 put NodeInfo {..} = put nodeId >> put nodeAddr
93
94type CompactInfo = ByteString
95
96data NodeList a = CompactNodeList [NodeInfo a]
97
98decodeCompact :: Serialize a => CompactInfo -> [NodeInfo a]
99decodeCompact = either (const []) id . S.runGet (many get)
100
101encodeCompact :: [NodeId] -> CompactInfo
102encodeCompact = S.runPut . mapM_ put
103
104--decodePeerList :: [BEncode] -> [PeerAddr]
105--decodePeerList = undefined
106
107--encodePeerList :: [PeerAddr] -> [BEncode]
108--encodePeerList = undefined