summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--bittorrent.cabal2
-rw-r--r--src/Data/Torrent.hs59
-rw-r--r--tests/Encoding.hs11
-rw-r--r--tests/Main.hs43
4 files changed, 95 insertions, 20 deletions
diff --git a/bittorrent.cabal b/bittorrent.cabal
index 138f5d3b..e0f6df5a 100644
--- a/bittorrent.cabal
+++ b/bittorrent.cabal
@@ -118,11 +118,13 @@ test-suite properties
118 , bytestring >= 0.10.2 118 , bytestring >= 0.10.2
119 , cereal >= 0.3.5.2 119 , cereal >= 0.3.5.2
120 , network >= 2.4.0.13 120 , network >= 2.4.0.13
121 , text
121 122
122 , test-framework 123 , test-framework
123 , test-framework-quickcheck2 124 , test-framework-quickcheck2
124 , QuickCheck 125 , QuickCheck
125 126
127 , bencoding
126 , bittorrent 128 , bittorrent
127 , intset 129 , intset
128 130
diff --git a/src/Data/Torrent.hs b/src/Data/Torrent.hs
index 16b94828..3175e151 100644
--- a/src/Data/Torrent.hs
+++ b/src/Data/Torrent.hs
@@ -17,6 +17,7 @@
17-- <https://wiki.theory.org/BitTorrentSpecification#Metainfo_File_Structure> 17-- <https://wiki.theory.org/BitTorrentSpecification#Metainfo_File_Structure>
18-- 18--
19{-# OPTIONS -fno-warn-orphans #-} 19{-# OPTIONS -fno-warn-orphans #-}
20{-# LANGUAGE CPP #-}
20{-# LANGUAGE FlexibleInstances #-} 21{-# LANGUAGE FlexibleInstances #-}
21{-# LANGUAGE OverloadedStrings #-} 22{-# LANGUAGE OverloadedStrings #-}
22{-# LANGUAGE RecordWildCards #-} 23{-# LANGUAGE RecordWildCards #-}
@@ -24,6 +25,7 @@
24module Data.Torrent 25module Data.Torrent
25 ( -- * Torrent 26 ( -- * Torrent
26 Torrent(..), ContentInfo(..), FileInfo(..) 27 Torrent(..), ContentInfo(..), FileInfo(..)
28 , torrent, simpleTorrent
27 , fromFile 29 , fromFile
28 30
29 -- * Files layout 31 -- * Files layout
@@ -32,15 +34,21 @@ module Data.Torrent
32 , isSingleFile, isMultiFile 34 , isSingleFile, isMultiFile
33 35
34 -- * Info hash 36 -- * Info hash
35 , InfoHash, ppInfoHash 37#if defined (TESTING)
36 , hash, hashlazy 38 , InfoHash(..)
39#else
40 , InfoHash
41#endif
42 , ppInfoHash
37 , addHashToURI 43 , addHashToURI
38 44
39 -- * Extra 45 -- * Extra
40 , sizeInBase 46 , sizeInBase
41 47
48#if defined (TESTING)
42 -- * Internal 49 -- * Internal
43 , InfoHash(..) 50 , hash, hashlazy
51#endif
44 ) where 52 ) where
45 53
46import Prelude hiding (sum) 54import Prelude hiding (sum)
@@ -79,6 +87,10 @@ data Torrent = Torrent {
79 , tAnnounce :: URI 87 , tAnnounce :: URI
80 -- ^ The URL of the tracker. 88 -- ^ The URL of the tracker.
81 89
90 -- NOTE: out of lexicographic order!
91 , tInfo :: ContentInfo
92 -- ^ Info about each content file.
93
82 , tAnnounceList :: Maybe [[URI]] 94 , tAnnounceList :: Maybe [[URI]]
83 -- ^ Announce list add multiple tracker support. 95 -- ^ Announce list add multiple tracker support.
84 -- 96 --
@@ -97,9 +109,6 @@ data Torrent = Torrent {
97 -- ^ String encoding format used to generate the pieces part of 109 -- ^ String encoding format used to generate the pieces part of
98 -- the info dictionary in the .torrent metafile. 110 -- the info dictionary in the .torrent metafile.
99 111
100 , tInfo :: ContentInfo
101 -- ^ Info about each content file.
102
103 , tPublisher :: Maybe URI 112 , tPublisher :: Maybe URI
104 -- ^ Containing the RSA public key of the publisher of the torrent. 113 -- ^ Containing the RSA public key of the publisher of the torrent.
105 -- Private counterpart of this key that has the authority to allow 114 -- Private counterpart of this key that has the authority to allow
@@ -109,7 +118,26 @@ data Torrent = Torrent {
109 , tSignature :: Maybe ByteString 118 , tSignature :: Maybe ByteString
110 -- ^ The RSA signature of the info dictionary (specifically, 119 -- ^ The RSA signature of the info dictionary (specifically,
111 -- the encrypted SHA-1 hash of the info dictionary). 120 -- the encrypted SHA-1 hash of the info dictionary).
112 } deriving Show 121 } deriving (Show, Eq)
122
123{- note that info hash is actually reduntant field
124 but it's better to keep it here to avoid heavy recomputations
125-}
126
127-- | Smart constructor for 'Torrent' which compute info hash.
128torrent :: URI -> ContentInfo
129 -> Maybe [[URI]] -> Maybe Text -> Maybe ByteString
130 -> Maybe Time -> Maybe ByteString -> Maybe URI
131 -> Maybe URI -> Maybe ByteString
132 -> Torrent
133torrent announce info = Torrent (hashlazy (BE.encoded info)) announce info
134
135-- | A simple torrent contains only required fields.
136simpleTorrent :: URI -> ContentInfo -> Torrent
137simpleTorrent announce info = torrent announce info
138 Nothing Nothing Nothing
139 Nothing Nothing Nothing
140 Nothing Nothing
113 141
114-- | Info part of the .torrent file contain info about each content file. 142-- | Info part of the .torrent file contain info about each content file.
115data ContentInfo = 143data ContentInfo =
@@ -133,8 +161,9 @@ data ContentInfo =
133 -- ^ Concatenation of all 20-byte SHA1 hash values. 161 -- ^ Concatenation of all 20-byte SHA1 hash values.
134 162
135 , ciPrivate :: Maybe Bool 163 , ciPrivate :: Maybe Bool
136 -- ^ If set the client MUST publish its presence to get other peers ONLY 164 -- ^ If set the client MUST publish its presence to get other
137 -- via the trackers explicity described in the metainfo file. 165 -- peers ONLY via the trackers explicity described in the
166 -- metainfo file.
138 -- 167 --
139 -- BEP 27: <http://www.bittorrent.org/beps/bep_0027.html> 168 -- BEP 27: <http://www.bittorrent.org/beps/bep_0027.html>
140 } 169 }
@@ -162,10 +191,10 @@ data FileInfo = FileInfo {
162 -- Used by third-party tools, not by bittorrent protocol itself. 191 -- Used by third-party tools, not by bittorrent protocol itself.
163 192
164 , fiPath :: [ByteString] 193 , fiPath :: [ByteString]
165 -- ^ One or more string elements that together represent the path and 194 -- ^ One or more string elements that together represent the
166 -- filename. Each element in the list corresponds to either a directory 195 -- path and filename. Each element in the list corresponds to
167 -- name or (in the case of the last element) the filename. 196 -- either a directory name or (in the case of the last
168 -- For example, the file 197 -- element) the filename. For example, the file:
169 -- 198 --
170 -- > "dir1/dir2/file.ext" 199 -- > "dir1/dir2/file.ext"
171 -- 200 --
@@ -201,15 +230,15 @@ instance BEncodable Torrent where
201 fromBEncode (BDict d) | Just info <- M.lookup "info" d = 230 fromBEncode (BDict d) | Just info <- M.lookup "info" d =
202 Torrent <$> pure (hashlazy (BE.encode info)) -- WARN 231 Torrent <$> pure (hashlazy (BE.encode info)) -- WARN
203 <*> d >-- "announce" 232 <*> d >-- "announce"
233 <*> d >-- "info"
204 <*> d >--? "announce-list" 234 <*> d >--? "announce-list"
205 <*> d >--? "comment" 235 <*> d >--? "comment"
206 <*> d >--? "created by" 236 <*> d >--? "created by"
207 <*> d >--? "creation date" 237 <*> d >--? "creation date"
208 <*> d >--? "encoding" 238 <*> d >--? "encoding"
209 <*> d >-- "info"
210 <*> d >--? "publisher" 239 <*> d >--? "publisher"
211 <*> d >--? "publisher-url" 240 <*> d >--? "publisher-url"
212 <*> d >--? "singature" 241 <*> d >--? "signature"
213 242
214 fromBEncode _ = decodingError "Torrent" 243 fromBEncode _ = decodingError "Torrent"
215 244
diff --git a/tests/Encoding.hs b/tests/Encoding.hs
index a599cd39..78f0dfc1 100644
--- a/tests/Encoding.hs
+++ b/tests/Encoding.hs
@@ -48,12 +48,12 @@ instance Arbitrary Message where
48 , pure Unchoke 48 , pure Unchoke
49 , pure Interested 49 , pure Interested
50 , pure NotInterested 50 , pure NotInterested
51 , Have <$> positive 51 , Have <$> positive
52 , Bitfield <$> arbitrary 52 , Bitfield <$> arbitrary
53 , Request <$> arbitrary 53 , Request <$> arbitrary
54 , Piece <$> arbitrary 54 , Piece <$> arbitrary
55 , Cancel <$> arbitrary 55 , Cancel <$> arbitrary
56 , Port <$> arbitrary 56 , Port <$> arbitrary
57 ] 57 ]
58 58
59instance Arbitrary PeerID where 59instance Arbitrary PeerID where
@@ -67,6 +67,7 @@ instance Arbitrary InfoHash where
67instance Arbitrary Handshake where 67instance Arbitrary Handshake where
68 arbitrary = defaultHandshake <$> arbitrary <*> arbitrary 68 arbitrary = defaultHandshake <$> arbitrary <*> arbitrary
69 69
70
70data T a = T 71data T a = T
71 72
72prop_encoding :: (Serialize a, Eq a) => T a -> [a] -> Bool 73prop_encoding :: (Serialize a, Eq a) => T a -> [a] -> Bool
diff --git a/tests/Main.hs b/tests/Main.hs
index 0aa6423f..ff571b6b 100644
--- a/tests/Main.hs
+++ b/tests/Main.hs
@@ -2,20 +2,35 @@
2module Main (main) where 2module Main (main) where
3 3
4import Control.Applicative 4import Control.Applicative
5import qualified Data.ByteString.Lazy as Lazy
5import Data.IntervalSet 6import Data.IntervalSet
6import Data.List as L 7import Data.List as L
7import Data.Ord 8import Data.Ord
9import Data.Maybe
8import Data.Word 10import Data.Word
11import Data.Text as T
12import Network.URI
9 13
10import Test.Framework (defaultMain) 14import Test.Framework (defaultMain)
11import Test.Framework.Providers.QuickCheck2 (testProperty) 15import Test.Framework.Providers.QuickCheck2 (testProperty)
12import Test.QuickCheck 16import Test.QuickCheck
13 17
18import Data.BEncode
14import Data.Bitfield as BF 19import Data.Bitfield as BF
20import Data.Torrent
15import Network.BitTorrent as BT 21import Network.BitTorrent as BT
16 22
23import Debug.Trace
17import Encoding 24import Encoding
18 25
26
27instance Arbitrary URI where
28 arbitrary = pure $ fromJust
29 $ parseURI "http://exsample.com:80/123365_asd"
30
31instance Arbitrary Text where
32 arbitrary = T.pack <$> arbitrary
33
19{----------------------------------------------------------------------- 34{-----------------------------------------------------------------------
20 Bitfield 35 Bitfield
21-----------------------------------------------------------------------} 36-----------------------------------------------------------------------}
@@ -51,8 +66,29 @@ prop_differenceDeMorgan a b c =
51 Torrent 66 Torrent
52-----------------------------------------------------------------------} 67-----------------------------------------------------------------------}
53 68
69prop_properBEncode :: Show a => BEncodable a => Eq a => T a -> a -> Bool
70prop_properBEncode _ expected = actual == Right expected
71 where
72 actual = decoded $ Lazy.toStrict $ encoded expected
73
74
54-- TODO tests for torrent: encoding <-> decoding 75-- TODO tests for torrent: encoding <-> decoding
76instance Arbitrary FileInfo where
77 arbitrary = FileInfo <$> arbitrary <*> arbitrary <*> arbitrary
55 78
79instance Arbitrary ContentInfo where
80 arbitrary = oneof
81 [ SingleFile <$> arbitrary <*> arbitrary <*> arbitrary
82 <*> arbitrary <*> arbitrary <*> arbitrary
83 , MultiFile <$> arbitrary <*> arbitrary <*> arbitrary
84 <*> arbitrary <*> arbitrary
85 ]
86
87instance Arbitrary Torrent where
88 arbitrary = torrent <$> arbitrary
89 <*> arbitrary <*> arbitrary <*> arbitrary
90 <*> arbitrary <*> arbitrary <*> arbitrary
91 <*> arbitrary <*> pure Nothing <*> arbitrary
56 92
57main :: IO () 93main :: IO ()
58main = defaultMain 94main = defaultMain
@@ -60,4 +96,11 @@ main = defaultMain
60 , testProperty "rarest in range" prop_rarestInRange 96 , testProperty "rarest in range" prop_rarestInRange
61 , testProperty "min less that max" prop_minMax 97 , testProperty "min less that max" prop_minMax
62 , testProperty "difference de morgan" prop_differenceDeMorgan 98 , testProperty "difference de morgan" prop_differenceDeMorgan
99
100 , testProperty "file info encoding" $
101 prop_properBEncode (T :: T FileInfo)
102 , testProperty "content info encoding" $
103 prop_properBEncode (T :: T ContentInfo)
104 , testProperty "torrent encoding" $
105 prop_properBEncode (T :: T Torrent)
63 ] 106 ]