diff options
-rw-r--r-- | bittorrent.cabal | 4 | ||||
-rw-r--r-- | src/Network/BitTorrent/Core.hs | 14 | ||||
-rw-r--r-- | src/Network/BitTorrent/Core/PeerAddr.hs | 109 | ||||
-rw-r--r-- | src/Network/BitTorrent/Exchange/Wire.hs | 4 | ||||
-rw-r--r-- | src/Network/BitTorrent/Tracker/Message.hs | 9 | ||||
-rw-r--r-- | tests/Network/BitTorrent/Core/PeerIdSpec.hs | 7 | ||||
-rw-r--r-- | tests/Network/BitTorrent/Tracker/MessageSpec.hs | 36 |
7 files changed, 130 insertions, 53 deletions
diff --git a/bittorrent.cabal b/bittorrent.cabal index c2785f02..8e7fda46 100644 --- a/bittorrent.cabal +++ b/bittorrent.cabal | |||
@@ -163,8 +163,9 @@ test-suite spec | |||
163 | Data.Torrent.PieceSpec | 163 | Data.Torrent.PieceSpec |
164 | Data.Torrent.ProgressSpec | 164 | Data.Torrent.ProgressSpec |
165 | Network.BitTorrent.CoreSpec | 165 | Network.BitTorrent.CoreSpec |
166 | Network.BitTorrent.Core.PeerIdSpec | ||
167 | Network.BitTorrent.Core.FingerprintSpec | 166 | Network.BitTorrent.Core.FingerprintSpec |
167 | Network.BitTorrent.Core.PeerAddrSpec | ||
168 | Network.BitTorrent.Core.PeerIdSpec | ||
168 | Network.BitTorrent.Tracker.MessageSpec | 169 | Network.BitTorrent.Tracker.MessageSpec |
169 | Network.BitTorrent.Tracker.RPCSpec | 170 | Network.BitTorrent.Tracker.RPCSpec |
170 | Network.BitTorrent.Tracker.RPC.HTTPSpec | 171 | Network.BitTorrent.Tracker.RPC.HTTPSpec |
@@ -181,6 +182,7 @@ test-suite spec | |||
181 | , data-default | 182 | , data-default |
182 | , monad-loops | 183 | , monad-loops |
183 | , containers | 184 | , containers |
185 | , iproute | ||
184 | 186 | ||
185 | , aeson | 187 | , aeson |
186 | , cereal | 188 | , cereal |
diff --git a/src/Network/BitTorrent/Core.hs b/src/Network/BitTorrent/Core.hs index 990a5975..7b8ff07d 100644 --- a/src/Network/BitTorrent/Core.hs +++ b/src/Network/BitTorrent/Core.hs | |||
@@ -7,7 +7,17 @@ | |||
7 | -- | 7 | -- |
8 | -- Re-export every @Network.BitTorrent.Core.*@ module. | 8 | -- Re-export every @Network.BitTorrent.Core.*@ module. |
9 | -- | 9 | -- |
10 | module Network.BitTorrent.Core (module Core) where | 10 | module Network.BitTorrent.Core |
11 | ( module Core | ||
12 | |||
13 | -- * Re-exports from Data.IP | ||
14 | , IPv4 | ||
15 | , IPv6 | ||
16 | , IP (..) | ||
17 | ) where | ||
18 | |||
19 | import Data.IP | ||
20 | |||
11 | import Network.BitTorrent.Core.Fingerprint as Core | 21 | import Network.BitTorrent.Core.Fingerprint as Core |
12 | import Network.BitTorrent.Core.PeerId as Core | 22 | import Network.BitTorrent.Core.PeerId as Core |
13 | import Network.BitTorrent.Core.PeerAddr as Core \ No newline at end of file | 23 | import Network.BitTorrent.Core.PeerAddr as Core |
diff --git a/src/Network/BitTorrent/Core/PeerAddr.hs b/src/Network/BitTorrent/Core/PeerAddr.hs index 60ada54d..3c3e98c5 100644 --- a/src/Network/BitTorrent/Core/PeerAddr.hs +++ b/src/Network/BitTorrent/Core/PeerAddr.hs | |||
@@ -14,6 +14,7 @@ | |||
14 | {-# LANGUAGE DeriveDataTypeable #-} | 14 | {-# LANGUAGE DeriveDataTypeable #-} |
15 | {-# LANGUAGE FlexibleInstances #-} | 15 | {-# LANGUAGE FlexibleInstances #-} |
16 | {-# LANGUAGE DeriveFunctor #-} | 16 | {-# LANGUAGE DeriveFunctor #-} |
17 | {-# LANGUAGE ViewPatterns #-} | ||
17 | {-# OPTIONS -fno-warn-orphans #-} -- for PortNumber instances | 18 | {-# OPTIONS -fno-warn-orphans #-} -- for PortNumber instances |
18 | module Network.BitTorrent.Core.PeerAddr | 19 | module Network.BitTorrent.Core.PeerAddr |
19 | ( -- * Peer address | 20 | ( -- * Peer address |
@@ -24,25 +25,26 @@ module Network.BitTorrent.Core.PeerAddr | |||
24 | -- * IP | 25 | -- * IP |
25 | , mergeIPLists | 26 | , mergeIPLists |
26 | , splitIPList | 27 | , splitIPList |
27 | , IP, IPv4, IPv6 --re-export Data.IP constructors | ||
28 | , IPAddress () | 28 | , IPAddress () |
29 | ) where | 29 | ) where |
30 | 30 | ||
31 | import Control.Applicative | 31 | import Control.Applicative |
32 | import Control.Monad | ||
32 | import Data.Aeson (ToJSON, FromJSON) | 33 | import Data.Aeson (ToJSON, FromJSON) |
33 | import Data.BEncode as BS | 34 | import Data.BEncode as BS |
34 | import Data.BEncode.BDict (BKey) | 35 | import Data.BEncode.BDict (BKey) |
35 | import Data.ByteString.Char8 as BS8 | 36 | import Data.ByteString.Char8 as BS8 |
36 | import Data.Char | 37 | import Data.Char |
37 | import Data.Default | 38 | import Data.Default |
39 | import Data.Either | ||
40 | import Data.Foldable | ||
41 | import Data.IP | ||
38 | import Data.List as L | 42 | import Data.List as L |
39 | import Data.List.Split | 43 | import Data.List.Split |
40 | import Data.Serialize as S | 44 | import Data.Serialize as S |
41 | import Data.String | 45 | import Data.String |
42 | import Data.Typeable | 46 | import Data.Typeable |
43 | import Data.IP | 47 | import Data.Word |
44 | import Data.Foldable | ||
45 | import Data.Either | ||
46 | import Network.Socket | 48 | import Network.Socket |
47 | import Text.PrettyPrint | 49 | import Text.PrettyPrint |
48 | import Text.PrettyPrint.Class | 50 | import Text.PrettyPrint.Class |
@@ -52,12 +54,22 @@ import qualified Text.ParserCombinators.ReadP as RP | |||
52 | import Network.BitTorrent.Core.PeerId | 54 | import Network.BitTorrent.Core.PeerId |
53 | 55 | ||
54 | 56 | ||
57 | {----------------------------------------------------------------------- | ||
58 | -- Port number | ||
59 | -----------------------------------------------------------------------} | ||
60 | |||
55 | deriving instance ToJSON PortNumber | 61 | deriving instance ToJSON PortNumber |
56 | deriving instance FromJSON PortNumber | 62 | deriving instance FromJSON PortNumber |
57 | 63 | ||
58 | instance BEncode PortNumber where | 64 | instance BEncode PortNumber where |
59 | toBEncode = toBEncode . fromEnum | 65 | toBEncode = toBEncode . fromEnum |
60 | fromBEncode b = toEnum <$> fromBEncode b | 66 | fromBEncode = fromBEncode >=> portNumber |
67 | where | ||
68 | portNumber :: Integer -> BS.Result PortNumber | ||
69 | portNumber n | ||
70 | | 0 <= n && n <= fromIntegral (maxBound :: Word16) | ||
71 | = pure $ fromIntegral n | ||
72 | | otherwise = decodingError $ "PortNumber: " ++ show n | ||
61 | 73 | ||
62 | instance Serialize PortNumber where | 74 | instance Serialize PortNumber where |
63 | get = fromIntegral <$> getWord16be | 75 | get = fromIntegral <$> getWord16be |
@@ -65,57 +77,59 @@ instance Serialize PortNumber where | |||
65 | put = putWord16be . fromIntegral | 77 | put = putWord16be . fromIntegral |
66 | {-# INLINE put #-} | 78 | {-# INLINE put #-} |
67 | 79 | ||
68 | class (Show i, Read i) => IPAddress i where | 80 | {----------------------------------------------------------------------- |
69 | showIp :: i -> String | 81 | -- IP addr |
70 | showIp = show | 82 | -----------------------------------------------------------------------} |
71 | 83 | ||
72 | readIp :: String -> i | 84 | class IPAddress i where |
73 | readIp = read | 85 | toHostAddr :: i -> Either HostAddress HostAddress6 |
74 | |||
75 | toHostAddr :: i -> Either HostAddress HostAddress6 | ||
76 | 86 | ||
77 | instance IPAddress IPv4 where | 87 | instance IPAddress IPv4 where |
78 | toHostAddr = Left . toHostAddress | 88 | toHostAddr = Left . toHostAddress |
79 | 89 | ||
80 | instance IPAddress IPv6 where | 90 | instance IPAddress IPv6 where |
81 | toHostAddr = Right . toHostAddress6 | 91 | toHostAddr = Right . toHostAddress6 |
82 | 92 | ||
83 | instance IPAddress IP where | 93 | instance IPAddress IP where |
84 | toHostAddr (IPv4 ip) = toHostAddr ip | 94 | toHostAddr (IPv4 ip) = toHostAddr ip |
85 | toHostAddr (IPv6 ip) = toHostAddr ip | 95 | toHostAddr (IPv6 ip) = toHostAddr ip |
86 | |||
87 | 96 | ||
88 | deriving instance Typeable IP | 97 | deriving instance Typeable IP |
89 | deriving instance Typeable IPv4 | 98 | deriving instance Typeable IPv4 |
90 | deriving instance Typeable IPv6 | 99 | deriving instance Typeable IPv6 |
91 | 100 | ||
92 | ipToBEncode :: IPAddress i => i -> BValue | 101 | ipToBEncode :: Show i => i -> BValue |
93 | ipToBEncode ip = BString $ BS8.pack $ showIp ip | 102 | ipToBEncode ip = BString $ BS8.pack $ show ip |
94 | 103 | ||
95 | ipFromBEncode :: Monad m => IPAddress a => BValue -> m a | 104 | ipFromBEncode :: Read a => BValue -> BS.Result a |
96 | ipFromBEncode (BString ip) = return $ readIp $ BS8.unpack ip | 105 | ipFromBEncode (BString (BS8.unpack -> ipStr)) |
97 | ipFromBEncode _ = fail "ipFromBEncode" | 106 | | Just ip <- readMaybe (ipStr) = pure ip |
107 | | otherwise = decodingError $ "IP: " ++ ipStr | ||
108 | ipFromBEncode _ = decodingError $ "IP: addr should be a bstring" | ||
98 | 109 | ||
99 | instance BEncode IP where | 110 | instance BEncode IP where |
100 | toBEncode = ipToBEncode | 111 | toBEncode = ipToBEncode |
101 | fromBEncode = ipFromBEncode | 112 | fromBEncode = ipFromBEncode |
102 | 113 | ||
103 | instance BEncode IPv4 where | 114 | instance BEncode IPv4 where |
104 | toBEncode = ipToBEncode | 115 | toBEncode = ipToBEncode |
105 | fromBEncode = ipFromBEncode | 116 | fromBEncode = ipFromBEncode |
106 | 117 | ||
107 | instance BEncode IPv6 where | 118 | instance BEncode IPv6 where |
108 | toBEncode = ipToBEncode | 119 | toBEncode = ipToBEncode |
109 | fromBEncode = ipFromBEncode | 120 | fromBEncode = ipFromBEncode |
110 | 121 | ||
111 | instance Serialize IPv4 where | 122 | instance Serialize IPv4 where |
112 | put ip = put $ toHostAddress ip | 123 | put = putWord32host . toHostAddress |
113 | get = fromHostAddress <$> get | 124 | get = fromHostAddress <$> getWord32host |
114 | 125 | ||
115 | instance Serialize IPv6 where | 126 | instance Serialize IPv6 where |
116 | put ip = put $ toHostAddress6 ip | 127 | put ip = put $ toHostAddress6 ip |
117 | get = fromHostAddress6 <$> get | 128 | get = fromHostAddress6 <$> get |
118 | 129 | ||
130 | {----------------------------------------------------------------------- | ||
131 | -- Peer addr | ||
132 | -----------------------------------------------------------------------} | ||
119 | -- TODO check semantic of ord and eq instances | 133 | -- TODO check semantic of ord and eq instances |
120 | 134 | ||
121 | -- | Peer address info normally extracted from peer list or peer | 135 | -- | Peer address info normally extracted from peer list or peer |
@@ -126,23 +140,25 @@ data PeerAddr a = PeerAddr | |||
126 | , peerPort :: {-# UNPACK #-} !PortNumber | 140 | , peerPort :: {-# UNPACK #-} !PortNumber |
127 | } deriving (Show, Eq, Typeable, Functor) | 141 | } deriving (Show, Eq, Typeable, Functor) |
128 | 142 | ||
129 | peer_id_key, peer_ip_key, peer_port_key :: BKey | 143 | peer_ip_key, peer_id_key, peer_port_key :: BKey |
130 | peer_id_key = "peer id" | ||
131 | peer_ip_key = "ip" | 144 | peer_ip_key = "ip" |
145 | peer_id_key = "peer id" | ||
132 | peer_port_key = "port" | 146 | peer_port_key = "port" |
133 | 147 | ||
134 | -- | The tracker's 'announce response' compatible encoding. | 148 | -- | The tracker's 'announce response' compatible encoding. |
135 | instance (Typeable a, BEncode a) => BEncode (PeerAddr a) where | 149 | instance (Typeable a, BEncode a) => BEncode (PeerAddr a) where |
136 | toBEncode PeerAddr {..} = toDict $ | 150 | toBEncode PeerAddr {..} = toDict $ |
137 | peer_id_key .=? peerId | 151 | peer_ip_key .=! peerAddr |
138 | .: peer_ip_key .=! peerAddr | 152 | .: peer_id_key .=? peerId |
139 | .: peer_port_key .=! peerPort | 153 | .: peer_port_key .=! peerPort |
140 | .: endDict | 154 | .: endDict |
141 | 155 | ||
142 | fromBEncode = fromDict $ do | 156 | fromBEncode = fromDict $ do |
143 | PeerAddr <$>? peer_id_key | 157 | peerAddr <$>? peer_id_key |
144 | <*>! peer_ip_key | 158 | <*>! peer_ip_key |
145 | <*>! peer_port_key | 159 | <*>! peer_port_key |
160 | where | ||
161 | peerAddr ip pid port = PeerAddr ip pid port | ||
146 | 162 | ||
147 | mergeIPLists :: [PeerAddr IPv4] -> Maybe [PeerAddr IPv6] -> [PeerAddr IP] | 163 | mergeIPLists :: [PeerAddr IPv4] -> Maybe [PeerAddr IPv6] -> [PeerAddr IP] |
148 | mergeIPLists v4 v6 = (fmap IPv4 `L.map` v4) | 164 | mergeIPLists v4 v6 = (fmap IPv4 `L.map` v4) |
@@ -162,10 +178,8 @@ splitIPList xs = partitionEithers $ toEither <$> xs | |||
162 | -- | 178 | -- |
163 | -- TODO: test byte order | 179 | -- TODO: test byte order |
164 | instance (Serialize a) => Serialize (PeerAddr a) where | 180 | instance (Serialize a) => Serialize (PeerAddr a) where |
165 | put PeerAddr {..} = | 181 | put PeerAddr {..} = put peerAddr >> put peerPort |
166 | put peerAddr >> put peerPort | 182 | get = PeerAddr Nothing <$> get <*> get |
167 | get = | ||
168 | PeerAddr Nothing <$> get <*> get | ||
169 | 183 | ||
170 | -- | @127.0.0.1:6881@ | 184 | -- | @127.0.0.1:6881@ |
171 | instance Default (PeerAddr IPv4) where | 185 | instance Default (PeerAddr IPv4) where |
@@ -178,7 +192,7 @@ instance Default (PeerAddr IPv4) where | |||
178 | instance IsString (PeerAddr IPv4) where | 192 | instance IsString (PeerAddr IPv4) where |
179 | fromString str | 193 | fromString str |
180 | | [hostAddrStr, portStr] <- splitWhen (== ':') str | 194 | | [hostAddrStr, portStr] <- splitWhen (== ':') str |
181 | , hostAddr <- read hostAddrStr | 195 | , Just hostAddr <- readMaybe hostAddrStr |
182 | , Just portNum <- toEnum <$> readMaybe portStr | 196 | , Just portNum <- toEnum <$> readMaybe portStr |
183 | = PeerAddr Nothing hostAddr portNum | 197 | = PeerAddr Nothing hostAddr portNum |
184 | | otherwise = error $ "fromString: unable to parse (PeerAddr IPv4): " ++ str | 198 | | otherwise = error $ "fromString: unable to parse (PeerAddr IPv4): " ++ str |
@@ -196,6 +210,11 @@ instance IsString (PeerAddr IPv6) where | |||
196 | PeerAddr Nothing ip port | 210 | PeerAddr Nothing ip port |
197 | | otherwise = error $ "fromString: unable to parse (PeerAddr IPv6): " ++ str | 211 | | otherwise = error $ "fromString: unable to parse (PeerAddr IPv6): " ++ str |
198 | 212 | ||
213 | instance IsString (PeerAddr IP) where | ||
214 | fromString str | ||
215 | | '[' `L.elem` str = IPv6 <$> fromString str | ||
216 | | otherwise = IPv4 <$> fromString str | ||
217 | |||
199 | -- | fingerprint + "at" + dotted.host.inet.addr:port | 218 | -- | fingerprint + "at" + dotted.host.inet.addr:port |
200 | -- TODO: instances for IPv6, HostName | 219 | -- TODO: instances for IPv6, HostName |
201 | instance Pretty (PeerAddr IP) where | 220 | instance Pretty (PeerAddr IP) where |
@@ -215,8 +234,8 @@ _resolvePeerAddr = undefined | |||
215 | -- | Convert peer info from tracker response to socket address. Used | 234 | -- | Convert peer info from tracker response to socket address. Used |
216 | -- for establish connection between peers. | 235 | -- for establish connection between peers. |
217 | -- | 236 | -- |
218 | peerSockAddr :: (IPAddress i) => PeerAddr i -> SockAddr | 237 | peerSockAddr :: PeerAddr IP -> SockAddr |
219 | peerSockAddr PeerAddr {..} = | 238 | peerSockAddr PeerAddr {..} = |
220 | case toHostAddr peerAddr of | 239 | case peerAddr of |
221 | Left host4 -> SockAddrInet peerPort host4 | 240 | IPv4 ipv4 -> SockAddrInet peerPort (toHostAddress ipv4) |
222 | Right host6 -> SockAddrInet6 peerPort 0 host6 0 | 241 | IPv6 ipv6 -> SockAddrInet6 peerPort 0 (toHostAddress6 ipv6) 0 |
diff --git a/src/Network/BitTorrent/Exchange/Wire.hs b/src/Network/BitTorrent/Exchange/Wire.hs index 27b4be12..2a7d2aeb 100644 --- a/src/Network/BitTorrent/Exchange/Wire.hs +++ b/src/Network/BitTorrent/Exchange/Wire.hs | |||
@@ -505,7 +505,7 @@ initiateHandshake sock hs = do | |||
505 | recvHandshake sock | 505 | recvHandshake sock |
506 | 506 | ||
507 | -- | Tries to connect to peer using reasonable default parameters. | 507 | -- | Tries to connect to peer using reasonable default parameters. |
508 | connectToPeer :: (IPAddress i) => PeerAddr i -> IO Socket | 508 | connectToPeer :: PeerAddr IP -> IO Socket |
509 | connectToPeer p = do | 509 | connectToPeer p = do |
510 | sock <- socket AF_INET Stream Network.Socket.defaultProtocol | 510 | sock <- socket AF_INET Stream Network.Socket.defaultProtocol |
511 | connect sock (peerSockAddr p) | 511 | connect sock (peerSockAddr p) |
@@ -628,7 +628,7 @@ reconnect = undefined | |||
628 | -- | 628 | -- |
629 | -- This function can throw 'WireFailure' exception. | 629 | -- This function can throw 'WireFailure' exception. |
630 | -- | 630 | -- |
631 | connectWire :: (IPAddress i) => Handshake -> PeerAddr i -> ExtendedCaps -> Wire () -> IO () | 631 | connectWire :: Handshake -> PeerAddr IP -> ExtendedCaps -> Wire () -> IO () |
632 | connectWire hs addr extCaps wire = | 632 | connectWire hs addr extCaps wire = |
633 | bracket (connectToPeer addr) close $ \ sock -> do | 633 | bracket (connectToPeer addr) close $ \ sock -> do |
634 | hs' <- initiateHandshake sock hs | 634 | hs' <- initiateHandshake sock hs |
diff --git a/src/Network/BitTorrent/Tracker/Message.hs b/src/Network/BitTorrent/Tracker/Message.hs index 95b9c7ca..0d720471 100644 --- a/src/Network/BitTorrent/Tracker/Message.hs +++ b/src/Network/BitTorrent/Tracker/Message.hs | |||
@@ -81,6 +81,7 @@ import Data.Default | |||
81 | import Data.List as L | 81 | import Data.List as L |
82 | import Data.Maybe | 82 | import Data.Maybe |
83 | import Data.Serialize as S hiding (Result) | 83 | import Data.Serialize as S hiding (Result) |
84 | import Data.String | ||
84 | import Data.Text (Text) | 85 | import Data.Text (Text) |
85 | import Data.Text.Encoding | 86 | import Data.Text.Encoding |
86 | import Data.Typeable | 87 | import Data.Typeable |
@@ -480,7 +481,7 @@ data AnnounceInfo = | |||
480 | 481 | ||
481 | -- | Human readable warning. | 482 | -- | Human readable warning. |
482 | , respWarning :: !(Maybe Text) | 483 | , respWarning :: !(Maybe Text) |
483 | } deriving (Show, Typeable) | 484 | } deriving (Show, Eq, Typeable) |
484 | 485 | ||
485 | -- | HTTP tracker protocol compatible encoding. | 486 | -- | HTTP tracker protocol compatible encoding. |
486 | instance BEncode AnnounceInfo where | 487 | instance BEncode AnnounceInfo where |
@@ -535,6 +536,12 @@ instance Serialize AnnounceInfo where | |||
535 | , respPeers = PeerList peers | 536 | , respPeers = PeerList peers |
536 | } | 537 | } |
537 | 538 | ||
539 | -- | Decodes announce response from bencoded string, for debugging only. | ||
540 | instance IsString AnnounceInfo where | ||
541 | fromString str = either (error . format) id $ BE.decode (fromString str) | ||
542 | where | ||
543 | format msg = "fromString: unable to decode AnnounceInfo: " ++ msg | ||
544 | |||
538 | -- | Above 25, new peers are highly unlikely to increase download | 545 | -- | Above 25, new peers are highly unlikely to increase download |
539 | -- speed. Even 30 peers is /plenty/, the official client version 3 | 546 | -- speed. Even 30 peers is /plenty/, the official client version 3 |
540 | -- in fact only actively forms new connections if it has less than | 547 | -- in fact only actively forms new connections if it has less than |
diff --git a/tests/Network/BitTorrent/Core/PeerIdSpec.hs b/tests/Network/BitTorrent/Core/PeerIdSpec.hs index a4cc30b8..4b0c2398 100644 --- a/tests/Network/BitTorrent/Core/PeerIdSpec.hs +++ b/tests/Network/BitTorrent/Core/PeerIdSpec.hs | |||
@@ -1,6 +1,7 @@ | |||
1 | {-# OPTIONS -fno-warn-orphans #-} | 1 | {-# OPTIONS -fno-warn-orphans #-} |
2 | module Network.BitTorrent.Core.PeerIdSpec (spec) where | 2 | module Network.BitTorrent.Core.PeerIdSpec (spec) where |
3 | import Control.Applicative | 3 | import Control.Applicative |
4 | import Data.BEncode as BE | ||
4 | import Data.Text.Encoding as T | 5 | import Data.Text.Encoding as T |
5 | import Test.Hspec | 6 | import Test.Hspec |
6 | import Test.QuickCheck | 7 | import Test.QuickCheck |
@@ -17,4 +18,8 @@ instance Arbitrary PeerId where | |||
17 | ] | 18 | ] |
18 | 19 | ||
19 | spec :: Spec | 20 | spec :: Spec |
20 | spec = return () \ No newline at end of file | 21 | spec = do |
22 | describe "PeerId" $ do | ||
23 | it "properly bencoded" $ do | ||
24 | BE.decode "20:01234567890123456789" | ||
25 | `shouldBe` Right ("01234567890123456789" :: PeerId) \ No newline at end of file | ||
diff --git a/tests/Network/BitTorrent/Tracker/MessageSpec.hs b/tests/Network/BitTorrent/Tracker/MessageSpec.hs index ac770905..bf89e717 100644 --- a/tests/Network/BitTorrent/Tracker/MessageSpec.hs +++ b/tests/Network/BitTorrent/Tracker/MessageSpec.hs | |||
@@ -7,6 +7,8 @@ module Network.BitTorrent.Tracker.MessageSpec | |||
7 | ) where | 7 | ) where |
8 | 8 | ||
9 | import Control.Applicative | 9 | import Control.Applicative |
10 | import Control.Exception | ||
11 | import Data.BEncode as BE | ||
10 | import Data.List as L | 12 | import Data.List as L |
11 | import Data.Maybe | 13 | import Data.Maybe |
12 | import Data.Word | 14 | import Data.Word |
@@ -56,10 +58,42 @@ arbitrarySample = L.head <$> sample' arbitrary | |||
56 | 58 | ||
57 | spec :: Spec | 59 | spec :: Spec |
58 | spec = do | 60 | spec = do |
59 | describe "Announce" $ do | 61 | describe "AnnounceQuery" $ do |
60 | it "properly url encoded" $ property $ \ q -> | 62 | it "properly url encoded" $ property $ \ q -> |
61 | parseAnnounceQuery (renderAnnounceQuery q) | 63 | parseAnnounceQuery (renderAnnounceQuery q) |
62 | `shouldBe` Right q | 64 | `shouldBe` Right q |
63 | 65 | ||
66 | describe "AnnounceInfo" $ do | ||
67 | it "parses minimal sample" $ do | ||
68 | "d8:intervali0e5:peerslee" | ||
69 | `shouldBe` | ||
70 | AnnounceInfo Nothing Nothing 0 Nothing (PeerList []) Nothing | ||
71 | |||
72 | it "parses optional fields" $ do | ||
73 | "d8:completei1e\ | ||
74 | \10:incompletei2e\ | ||
75 | \8:intervali3e\ | ||
76 | \12:min intervali4e\ | ||
77 | \5:peersle\ | ||
78 | \15:warning message3:str\ | ||
79 | \e" | ||
80 | `shouldBe` | ||
81 | AnnounceInfo (Just 1) (Just 2) 3 (Just 4) (PeerList []) (Just "str") | ||
82 | |||
83 | it "parses failed response" $ do | ||
84 | "d14:failure reason10:any reasone" | ||
85 | `shouldBe` | ||
86 | Message.Failure "any reason" | ||
87 | |||
88 | it "fail if no peer list present" $ do | ||
89 | evaluate ("d8:intervali0ee" :: AnnounceInfo) | ||
90 | `shouldThrow` | ||
91 | errorCall "fromString: unable to decode AnnounceInfo: \ | ||
92 | \required field `peers' not found" | ||
93 | |||
94 | it "parses peer list" $ do -- TODO | ||
95 | "d8:intervali0e5:peerslee" `shouldBe` | ||
96 | AnnounceInfo Nothing Nothing 0 Nothing (PeerList []) Nothing | ||
97 | |||
64 | describe "Scrape" $ do | 98 | describe "Scrape" $ do |
65 | return () | 99 | return () |