summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--bittorrent.cabal5
-rw-r--r--src/Data/Torrent/Bitfield.hs1
-rw-r--r--src/Network/BitTorrent/Exchange/Bus.hs3
-rw-r--r--src/Network/BitTorrent/Exchange/Extension.hs70
-rw-r--r--src/Network/BitTorrent/Exchange/Message.hs136
-rw-r--r--src/Network/BitTorrent/Exchange/Status.hs13
6 files changed, 126 insertions, 102 deletions
diff --git a/bittorrent.cabal b/bittorrent.cabal
index 51da7d4f..acb28fa7 100644
--- a/bittorrent.cabal
+++ b/bittorrent.cabal
@@ -59,9 +59,10 @@ library
59-- , Network.BitTorrent.DHT.Protocol 59-- , Network.BitTorrent.DHT.Protocol
60-- , Network.BitTorrent.DHT.Session 60-- , Network.BitTorrent.DHT.Session
61-- , Network.BitTorrent.Exchange 61-- , Network.BitTorrent.Exchange
62-- , Network.BitTorrent.Exchange.Message 62 , Network.BitTorrent.Exchange.Assembler
63 , Network.BitTorrent.Exchange.Message
63-- , Network.BitTorrent.Exchange.Session 64-- , Network.BitTorrent.Exchange.Session
64-- , Network.BitTorrent.Exchange.Status 65-- , Network.BitTorrent.Exchange.Status
65-- , Network.BitTorrent.Exchange.Wire 66-- , Network.BitTorrent.Exchange.Wire
66-- , Network.BitTorrent.Extension 67-- , Network.BitTorrent.Extension
67-- , Network.BitTorrent.Tracker 68-- , Network.BitTorrent.Tracker
diff --git a/src/Data/Torrent/Bitfield.hs b/src/Data/Torrent/Bitfield.hs
index a87a7ccf..c7ef0998 100644
--- a/src/Data/Torrent/Bitfield.hs
+++ b/src/Data/Torrent/Bitfield.hs
@@ -190,6 +190,7 @@ isSubsetOf a b = bfSet a `S.isSubsetOf` bfSet b
190-- download. 190-- download.
191type Frequency = Int 191type Frequency = Int
192 192
193-- TODO rename to availability
193-- | How many times each piece index occur in the given bitfield set. 194-- | How many times each piece index occur in the given bitfield set.
194frequencies :: [Bitfield] -> Vector Frequency 195frequencies :: [Bitfield] -> Vector Frequency
195frequencies [] = V.fromList [] 196frequencies [] = V.fromList []
diff --git a/src/Network/BitTorrent/Exchange/Bus.hs b/src/Network/BitTorrent/Exchange/Bus.hs
index 4800c4a0..7de91180 100644
--- a/src/Network/BitTorrent/Exchange/Bus.hs
+++ b/src/Network/BitTorrent/Exchange/Bus.hs
@@ -34,6 +34,9 @@ flushPending = {-# SCC flushPending #-} do
34 P2P monad 34 P2P monad
35-----------------------------------------------------------------------} 35-----------------------------------------------------------------------}
36 36
37filterMeaninless :: P2P Message Message
38filterMeaninless = undefined
39
37-- | 40-- |
38-- Exceptions: 41-- Exceptions:
39-- 42--
diff --git a/src/Network/BitTorrent/Exchange/Extension.hs b/src/Network/BitTorrent/Exchange/Extension.hs
deleted file mode 100644
index e81cdb87..00000000
--- a/src/Network/BitTorrent/Exchange/Extension.hs
+++ /dev/null
@@ -1,70 +0,0 @@
1-- |
2-- Copyright : (c) Sam Truzjan 2013
3-- License : BSD3
4-- Maintainer : pxqr.sta@gmail.com
5-- Stability : experimental
6-- Portability : portable
7--
8-- This module provides peer capabilities detection.
9--
10-- See <http://www.bittorrent.org/beps/bep_0004.html> for more
11-- information.
12--
13module Network.BitTorrent.Exchange.Extension
14 ( -- * Capabilities
15 Caps
16
17 -- * Extensions
18 , Extension(..)
19 ) where
20
21import Data.Bits
22import Data.Default
23import Data.Monoid
24import Data.Word
25import Text.PrettyPrint
26import Text.PrettyPrint.Class
27
28class (Enum a, Bounded a) => Capability a where
29 capMask :: a -> Word64
30 capRequires :: a -> Word64
31
32newtype Caps a = Caps Word64
33
34instance (Pretty a, Capability a) => Pretty (Caps a) where
35 pretty = hcat . punctuate ", " . map pretty . toList
36
37instance Default (Caps a) where
38 def = Caps 0
39 {-# INLINE def #-}
40
41instance Monoid (Caps a) where
42 mempty = Caps (-1)
43 {-# INLINE mempty #-}
44
45 mappend (Caps a) (Caps b) = Caps (a .&. b)
46 {-# INLINE mappend #-}
47
48allowed :: Capability a => a -> Caps a -> Bool
49allowed = member
50fromList :: Capability a => [a] -> Caps a
51fromList = Caps . foldr (.&.) 0 . map capMask
52
53toList :: Capability a => Caps a -> [a]
54toList (Caps rb) = filter (testMask rb . capMask) [minBound..maxBound]
55 where
56 testMask bits x = bits .&. x > 0
57
58
59data Extension
60 = ExtDHT -- ^ BEP 5
61 | ExtFast -- ^ BEP 6
62 deriving (Show, Eq, Ord, Enum, Bounded)
63
64instance Pretty Extension where
65 pretty ExtDHT = "DHT"
66 pretty ExtFast = "Fast Extension"
67
68instance Capability Extension where
69 capMask ExtDHT = 0x01
70 capMask ExtFast = 0x04
diff --git a/src/Network/BitTorrent/Exchange/Message.hs b/src/Network/BitTorrent/Exchange/Message.hs
index 546288b2..6f649030 100644
--- a/src/Network/BitTorrent/Exchange/Message.hs
+++ b/src/Network/BitTorrent/Exchange/Message.hs
@@ -28,19 +28,25 @@
28{-# LANGUAGE TemplateHaskell #-} 28{-# LANGUAGE TemplateHaskell #-}
29{-# OPTIONS -fno-warn-orphans #-} 29{-# OPTIONS -fno-warn-orphans #-}
30module Network.BitTorrent.Exchange.Message 30module Network.BitTorrent.Exchange.Message
31 ( -- * Initial handshake 31 ( -- * Extensions
32 Handshake(..) 32 Extension (..)
33 , handshake 33 , Caps
34 , handshakeCaps 34 , requires
35 , recvHandshake 35 , allowed
36 , sendHandshake 36 , toCaps
37 37 , fromCaps
38 -- ** Defaults 38
39 -- * Handshake
40 , Handshake(..)
39 , defaultHandshake 41 , defaultHandshake
40 , defaultBTProtocol 42 , defaultBTProtocol
41 , defaultReserved
42 , handshakeMaxSize 43 , handshakeMaxSize
43 44
45 -- * TODO remove this section from this module
46 , handshake
47 , recvHandshake
48 , sendHandshake
49
44 -- * Messages 50 -- * Messages
45 , Message (..) 51 , Message (..)
46 , StatusUpdate (..) 52 , StatusUpdate (..)
@@ -51,10 +57,13 @@ module Network.BitTorrent.Exchange.Message
51import Control.Applicative 57import Control.Applicative
52import Control.Exception 58import Control.Exception
53import Control.Monad 59import Control.Monad
60import Data.Bits
54import Data.ByteString as BS 61import Data.ByteString as BS
55import Data.ByteString.Char8 as BC 62import Data.ByteString.Char8 as BC
56import Data.ByteString.Lazy as BL 63import Data.ByteString.Lazy as BL
57import Data.Default 64import Data.Default
65import Data.List as L
66import Data.Monoid
58import Data.Serialize as S 67import Data.Serialize as S
59import Data.Word 68import Data.Word
60import Network 69import Network
@@ -67,7 +76,66 @@ import Data.Torrent.Block
67import Data.Torrent.InfoHash 76import Data.Torrent.InfoHash
68import Network.BitTorrent.Core.PeerId 77import Network.BitTorrent.Core.PeerId
69import Network.BitTorrent.Core.PeerAddr () 78import Network.BitTorrent.Core.PeerAddr ()
70import Network.BitTorrent.Exchange.Extension 79
80{-----------------------------------------------------------------------
81-- Extensions
82-----------------------------------------------------------------------}
83
84-- | See <http://www.bittorrent.org/beps/bep_0004.html> for more
85-- information.
86--
87data Extension
88 = ExtDHT -- ^ BEP 5
89 | ExtFast -- ^ BEP 6
90 deriving (Show, Eq, Ord, Enum, Bounded)
91
92instance Pretty Extension where
93 pretty ExtDHT = "DHT"
94 pretty ExtFast = "Fast Extension"
95
96capMask :: Extension -> Caps
97capMask ExtDHT = Caps 0x01
98capMask ExtFast = Caps 0x04
99
100{-----------------------------------------------------------------------
101-- Capabilities
102-----------------------------------------------------------------------}
103
104-- | A set of 'Extension's.
105newtype Caps = Caps { unCaps :: Word64 }
106 deriving (Show, Eq)
107
108instance Pretty Caps where
109 pretty = hcat . punctuate ", " . L.map pretty . fromCaps
110
111instance Default Caps where
112 def = Caps 0
113 {-# INLINE def #-}
114
115instance Monoid Caps where
116 mempty = Caps (-1)
117 {-# INLINE mempty #-}
118
119 mappend (Caps a) (Caps b) = Caps (a .&. b)
120 {-# INLINE mappend #-}
121
122instance Serialize Caps where
123 put (Caps caps) = S.putWord64be caps
124 {-# INLINE put #-}
125
126 get = Caps <$> S.getWord64be
127 {-# INLINE get #-}
128
129allowed :: Caps -> Extension -> Bool
130allowed (Caps caps) = testMask . capMask
131 where
132 testMask (Caps bits) = (bits .&. caps) == bits
133
134toCaps :: [Extension] -> Caps
135toCaps = Caps . L.foldr (.|.) 0 . L.map (unCaps . capMask)
136
137fromCaps :: Caps -> [Extension]
138fromCaps caps = L.filter (allowed caps) [minBound..maxBound]
71 139
72{----------------------------------------------------------------------- 140{-----------------------------------------------------------------------
73 Handshake 141 Handshake
@@ -77,11 +145,11 @@ import Network.BitTorrent.Exchange.Extension
77-- to establish connection between peers. 145-- to establish connection between peers.
78-- 146--
79data Handshake = Handshake { 147data Handshake = Handshake {
80 -- | Identifier of the protocol. 148 -- | Identifier of the protocol. This is usually equal to defaultProtocol
81 hsProtocol :: BS.ByteString 149 hsProtocol :: BS.ByteString
82 150
83 -- | Reserved bytes used to specify supported BEP's. 151 -- | Reserved bytes used to specify supported BEP's.
84 , hsReserved :: Capabilities 152 , hsReserved :: Caps
85 153
86 -- | Info hash of the info part of the metainfo file. that is 154 -- | Info hash of the info part of the metainfo file. that is
87 -- transmitted in tracker requests. Info hash of the initiator 155 -- transmitted in tracker requests. Info hash of the initiator
@@ -98,17 +166,17 @@ data Handshake = Handshake {
98 } deriving (Show, Eq) 166 } deriving (Show, Eq)
99 167
100instance Serialize Handshake where 168instance Serialize Handshake where
101 put hs = do 169 put Handshake {..} = do
102 S.putWord8 (fromIntegral (BS.length (hsProtocol hs))) 170 S.putWord8 (fromIntegral (BS.length hsProtocol))
103 S.putByteString (hsProtocol hs) 171 S.putByteString hsProtocol
104 S.putWord64be (hsReserved hs) 172 S.put hsReserved
105 S.put (hsInfoHash hs) 173 S.put hsInfoHash
106 S.put (hsPeerId hs) 174 S.put hsPeerId
107 175
108 get = do 176 get = do
109 len <- S.getWord8 177 len <- S.getWord8
110 Handshake <$> S.getBytes (fromIntegral len) 178 Handshake <$> S.getBytes (fromIntegral len)
111 <*> S.getWord64be 179 <*> S.get
112 <*> S.get 180 <*> S.get
113 <*> S.get 181 <*> S.get
114 182
@@ -116,11 +184,6 @@ instance Pretty Handshake where
116 pretty Handshake {..} 184 pretty Handshake {..}
117 = text (BC.unpack hsProtocol) <+> pretty (clientInfo hsPeerId) 185 = text (BC.unpack hsProtocol) <+> pretty (clientInfo hsPeerId)
118 186
119-- | Extract capabilities from a peer handshake message.
120handshakeCaps :: Handshake -> Capabilities
121handshakeCaps = hsReserved
122
123
124-- | Get handshake message size in bytes from the length of protocol 187-- | Get handshake message size in bytes from the length of protocol
125-- string. 188-- string.
126handshakeSize :: Word8 -> Int 189handshakeSize :: Word8 -> Int
@@ -128,21 +191,18 @@ handshakeSize n = 1 + fromIntegral n + 8 + 20 + 20
128 191
129-- | Maximum size of handshake message in bytes. 192-- | Maximum size of handshake message in bytes.
130handshakeMaxSize :: Int 193handshakeMaxSize :: Int
131handshakeMaxSize = handshakeSize 255 194handshakeMaxSize = handshakeSize maxBound
132 195
133-- | Default protocol string "BitTorrent protocol" as is. 196-- | Default protocol string "BitTorrent protocol" as is.
134defaultBTProtocol :: BS.ByteString 197defaultBTProtocol :: BS.ByteString
135defaultBTProtocol = "BitTorrent protocol" 198defaultBTProtocol = "BitTorrent protocol"
136 199
137-- | Default reserved word is 0.
138defaultReserved :: Word64
139defaultReserved = 0
140
141-- | Length of info hash and peer id is unchecked, so it /should/ be 200-- | Length of info hash and peer id is unchecked, so it /should/ be
142-- equal 20. 201-- equal 20.
143defaultHandshake :: InfoHash -> PeerId -> Handshake 202defaultHandshake :: InfoHash -> PeerId -> Handshake
144defaultHandshake = Handshake defaultBTProtocol defaultReserved 203defaultHandshake = Handshake defaultBTProtocol def
145 204
205-- | TODO remove socket stuff to corresponding module
146sendHandshake :: Socket -> Handshake -> IO () 206sendHandshake :: Socket -> Handshake -> IO ()
147sendHandshake sock hs = sendAll sock (S.encode hs) 207sendHandshake sock hs = sendAll sock (S.encode hs)
148 208
@@ -206,6 +266,14 @@ data RegularMessage =
206 | Cancel !BlockIx 266 | Cancel !BlockIx
207 deriving (Show, Eq) 267 deriving (Show, Eq)
208 268
269-- TODO
270-- data Availability = Have | Bitfield
271-- data Transfer
272-- = Request !BlockIx
273-- | Piece !(Block BL.ByteString)
274-- | Cancel !BlockIx
275
276
209instance Pretty RegularMessage where 277instance Pretty RegularMessage where
210 pretty (Have ix ) = "Have" <+> int ix 278 pretty (Have ix ) = "Have" <+> int ix
211 pretty (Bitfield _ ) = "Bitfield" 279 pretty (Bitfield _ ) = "Bitfield"
@@ -349,3 +417,11 @@ putFast HaveNone = putInt 1 >> S.putWord8 0x0F
349putFast (SuggestPiece pix) = putInt 5 >> S.putWord8 0x0D >> putInt pix 417putFast (SuggestPiece pix) = putInt 5 >> S.putWord8 0x0D >> putInt pix
350putFast (RejectRequest i ) = putInt 13 >> S.putWord8 0x10 >> S.put i 418putFast (RejectRequest i ) = putInt 13 >> S.putWord8 0x10 >> S.put i
351putFast (AllowedFast i ) = putInt 5 >> S.putWord8 0x11 >> putInt i 419putFast (AllowedFast i ) = putInt 5 >> S.putWord8 0x11 >> putInt i
420
421
422requires :: Message -> Maybe Extension
423requires KeepAlive = Nothing
424requires (Status _) = Nothing
425requires (Regular _) = Nothing
426requires (Port _) = Just ExtDHT
427requires (Fast _) = Just ExtFast \ No newline at end of file
diff --git a/src/Network/BitTorrent/Exchange/Status.hs b/src/Network/BitTorrent/Exchange/Status.hs
index 683ac594..7920f2a1 100644
--- a/src/Network/BitTorrent/Exchange/Status.hs
+++ b/src/Network/BitTorrent/Exchange/Status.hs
@@ -4,6 +4,7 @@ module Network.BitTorrent.Exchange.Status
4 PeerStatus(..) 4 PeerStatus(..)
5 , choking 5 , choking
6 , interested 6 , interested
7 , updateStatus
7 8
8 -- * Session status 9 -- * Session status
9 , SessionStatus(..) 10 , SessionStatus(..)
@@ -24,6 +25,9 @@ import Data.Aeson.TH
24import Data.List as L 25import Data.List as L
25import Data.Default 26import Data.Default
26 27
28import Network.BitTorrent.Exchange.Message
29
30
27-- | 31-- |
28data PeerStatus = PeerStatus { 32data PeerStatus = PeerStatus {
29 _choking :: !Bool 33 _choking :: !Bool
@@ -36,6 +40,15 @@ $(deriveJSON L.tail ''PeerStatus)
36instance Default PeerStatus where 40instance Default PeerStatus where
37 def = PeerStatus True False 41 def = PeerStatus True False
38 42
43updateStatus :: StatusUpdate -> PeerStatus -> PeerStatus
44updateStatus Choke = choking .~ True
45updateStatus Unchoke = choking .~ False
46updateStatus Interested = interested .~ True
47updateStatus NotInterested = interested .~ False
48
49statusUpdates :: PeerStatus -> PeerStatus -> [StatusUpdate]
50statusUpdates a b = undefined
51
39-- | 52-- |
40data SessionStatus = SessionStatus { 53data SessionStatus = SessionStatus {
41 _clientStatus :: !PeerStatus 54 _clientStatus :: !PeerStatus