summaryrefslogtreecommitdiff
path: root/src/Data/Torrent.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Data/Torrent.hs')
-rw-r--r--src/Data/Torrent.hs44
1 files changed, 37 insertions, 7 deletions
diff --git a/src/Data/Torrent.hs b/src/Data/Torrent.hs
index c22ca189..8746fff5 100644
--- a/src/Data/Torrent.hs
+++ b/src/Data/Torrent.hs
@@ -100,7 +100,9 @@ module Data.Torrent
100 , layoutInfo 100 , layoutInfo
101 , pieceInfo 101 , pieceInfo
102 , isPrivate 102 , isPrivate
103#ifdef VERSION_bencoding
103 , infoDictionary 104 , infoDictionary
105#endif
104 106
105 -- * Torrent file 107 -- * Torrent file
106 , Torrent(..) 108 , Torrent(..)
@@ -122,8 +124,10 @@ module Data.Torrent
122 , typeTorrent 124 , typeTorrent
123 , torrentExt 125 , torrentExt
124 , isTorrentPath 126 , isTorrentPath
127#ifdef VERSION_bencoding
125 , fromFile 128 , fromFile
126 , toFile 129 , toFile
130#endif
127 131
128 -- * Magnet 132 -- * Magnet
129 -- $magnet-link 133 -- $magnet-link
@@ -150,8 +154,10 @@ import Control.Exception
150import Control.Lens 154import Control.Lens
151import Control.Monad 155import Control.Monad
152import Crypto.Hash.SHA1 as SHA1 156import Crypto.Hash.SHA1 as SHA1
157#ifdef VERSION_bencoding
153import Data.BEncode as BE 158import Data.BEncode as BE
154import Data.BEncode.Types as BE 159import Data.BEncode.Types as BE
160#endif
155import Data.Bits 161import Data.Bits
156#ifdef VERSION_bits_extras 162#ifdef VERSION_bits_extras
157import Data.Bits.Extras 163import Data.Bits.Extras
@@ -223,10 +229,12 @@ instance Hashable InfoHash where
223 hashWithSalt s (InfoHash ih) = hashWithSalt s ih 229 hashWithSalt s (InfoHash ih) = hashWithSalt s ih
224 {-# INLINE hashWithSalt #-} 230 {-# INLINE hashWithSalt #-}
225 231
232#ifdef VERSION_bencoding
226-- | Convert to\/from raw bencoded string. (no encoding) 233-- | Convert to\/from raw bencoded string. (no encoding)
227instance BEncode InfoHash where 234instance BEncode InfoHash where
228 toBEncode = toBEncode . getInfoHash 235 toBEncode = toBEncode . getInfoHash
229 fromBEncode be = InfoHash <$> fromBEncode be 236 fromBEncode be = InfoHash <$> fromBEncode be
237#endif
230 238
231-- | Convert to\/from raw bytestring. (no encoding) 239-- | Convert to\/from raw bytestring. (no encoding)
232instance Serialize InfoHash where 240instance Serialize InfoHash where
@@ -321,7 +329,9 @@ shortHex = T.take 7 . longHex
321-- | Size of a file in bytes. 329-- | Size of a file in bytes.
322type FileSize = FileOffset 330type FileSize = FileOffset
323 331
332#ifdef VERSION_bencoding
324deriving instance BEncode FileOffset 333deriving instance BEncode FileOffset
334#endif
325 335
326-- | Contain metainfo about one single file. 336-- | Contain metainfo about one single file.
327data FileInfo a = FileInfo { 337data FileInfo a = FileInfo {
@@ -360,6 +370,7 @@ instance NFData a => NFData (FileInfo a) where
360 rnf FileInfo {..} = rnf fiName 370 rnf FileInfo {..} = rnf fiName
361 {-# INLINE rnf #-} 371 {-# INLINE rnf #-}
362 372
373#ifdef VERSION_bencoding
363instance BEncode (FileInfo [BS.ByteString]) where 374instance BEncode (FileInfo [BS.ByteString]) where
364 toBEncode FileInfo {..} = toDict $ 375 toBEncode FileInfo {..} = toDict $
365 "length" .=! fiLength 376 "length" .=! fiLength
@@ -375,7 +386,9 @@ instance BEncode (FileInfo [BS.ByteString]) where
375 {-# INLINE fromBEncode #-} 386 {-# INLINE fromBEncode #-}
376 387
377type Put a = a -> BDict -> BDict 388type Put a = a -> BDict -> BDict
389#endif
378 390
391#ifdef VERSION_bencoding
379putFileInfoSingle :: Data.Torrent.Put (FileInfo BS.ByteString) 392putFileInfoSingle :: Data.Torrent.Put (FileInfo BS.ByteString)
380putFileInfoSingle FileInfo {..} cont = 393putFileInfoSingle FileInfo {..} cont =
381 "length" .=! fiLength 394 "length" .=! fiLength
@@ -395,6 +408,7 @@ instance BEncode (FileInfo BS.ByteString) where
395 408
396 fromBEncode = fromDict getFileInfoSingle 409 fromBEncode = fromDict getFileInfoSingle
397 {-# INLINE fromBEncode #-} 410 {-# INLINE fromBEncode #-}
411#endif
398 412
399instance Pretty (FileInfo BS.ByteString) where 413instance Pretty (FileInfo BS.ByteString) where
400 pPrint FileInfo {..} = 414 pPrint FileInfo {..} =
@@ -447,6 +461,7 @@ instance NFData LayoutInfo where
447instance Default LayoutInfo where 461instance Default LayoutInfo where
448 def = MultiFile [] "" 462 def = MultiFile [] ""
449 463
464#ifdef VERSION_bencoding
450getLayoutInfo :: BE.Get LayoutInfo 465getLayoutInfo :: BE.Get LayoutInfo
451getLayoutInfo = single <|> multi 466getLayoutInfo = single <|> multi
452 where 467 where
@@ -463,6 +478,7 @@ putLayoutInfo MultiFile {..} = \ cont ->
463instance BEncode LayoutInfo where 478instance BEncode LayoutInfo where
464 toBEncode = toDict . (`putLayoutInfo` endDict) 479 toBEncode = toDict . (`putLayoutInfo` endDict)
465 fromBEncode = fromDict getLayoutInfo 480 fromBEncode = fromDict getLayoutInfo
481#endif
466 482
467instance Pretty LayoutInfo where 483instance Pretty LayoutInfo where
468 pPrint SingleFile {..} = pPrint liFile 484 pPrint SingleFile {..} = pPrint liFile
@@ -637,7 +653,11 @@ hashPiece Piece {..} = SHA1.hashlazy pieceData
637 653
638-- | A flat array of SHA1 hash for each piece. 654-- | A flat array of SHA1 hash for each piece.
639newtype HashList = HashList { unHashList :: BS.ByteString } 655newtype HashList = HashList { unHashList :: BS.ByteString }
640 deriving (Show, Read, Eq, BEncode, Typeable) 656 deriving ( Show, Read, Eq, Typeable
657#ifdef VERSION_bencoding
658 , BEncode
659#endif
660 )
641 661
642-- | Empty hash list. 662-- | Empty hash list.
643instance Default HashList where 663instance Default HashList where
@@ -665,6 +685,7 @@ instance Default PieceInfo where
665 def = PieceInfo 1 def 685 def = PieceInfo 1 def
666 686
667 687
688#ifdef VERSION_bencoding
668putPieceInfo :: Data.Torrent.Put PieceInfo 689putPieceInfo :: Data.Torrent.Put PieceInfo
669putPieceInfo PieceInfo {..} cont = 690putPieceInfo PieceInfo {..} cont =
670 "piece length" .=! piPieceLength 691 "piece length" .=! piPieceLength
@@ -679,6 +700,7 @@ getPieceInfo = do
679instance BEncode PieceInfo where 700instance BEncode PieceInfo where
680 toBEncode = toDict . (`putPieceInfo` endDict) 701 toBEncode = toDict . (`putPieceInfo` endDict)
681 fromBEncode = fromDict getPieceInfo 702 fromBEncode = fromDict getPieceInfo
703#endif
682 704
683-- | Hashes are omitted. 705-- | Hashes are omitted.
684instance Pretty PieceInfo where 706instance Pretty PieceInfo where
@@ -750,6 +772,13 @@ instance Hashable InfoDict where
750 hashWithSalt = Hashable.hashUsing idInfoHash 772 hashWithSalt = Hashable.hashUsing idInfoHash
751 {-# INLINE hashWithSalt #-} 773 {-# INLINE hashWithSalt #-}
752 774
775-- | Hash lazy bytestring using SHA1 algorithm.
776hashLazyIH :: BL.ByteString -> InfoHash
777hashLazyIH = either (const (error msg)) id . safeConvert . SHA1.hashlazy
778 where
779 msg = "Infohash.hash: impossible: SHA1 is always 20 bytes long"
780
781#ifdef VERSION_bencoding
753-- | Empty info dictionary with zero-length content. 782-- | Empty info dictionary with zero-length content.
754instance Default InfoDict where 783instance Default InfoDict where
755 def = infoDictionary def def False 784 def = infoDictionary def def False
@@ -767,12 +796,6 @@ putPrivate :: Bool -> BDict -> BDict
767putPrivate False = id 796putPrivate False = id
768putPrivate True = \ cont -> "private" .=! True .: cont 797putPrivate True = \ cont -> "private" .=! True .: cont
769 798
770-- | Hash lazy bytestring using SHA1 algorithm.
771hashLazyIH :: BL.ByteString -> InfoHash
772hashLazyIH = either (const (error msg)) id . safeConvert . SHA1.hashlazy
773 where
774 msg = "Infohash.hash: impossible: SHA1 is always 20 bytes long"
775
776instance BEncode InfoDict where 799instance BEncode InfoDict where
777 toBEncode InfoDict {..} = toDict $ 800 toBEncode InfoDict {..} = toDict $
778 putLayoutInfo idLayoutInfo $ 801 putLayoutInfo idLayoutInfo $
@@ -786,6 +809,7 @@ instance BEncode InfoDict where
786 <*> getPrivate 809 <*> getPrivate
787 where 810 where
788 ih = hashLazyIH (BE.encode dict) 811 ih = hashLazyIH (BE.encode dict)
812#endif
789 813
790ppPrivacy :: Bool -> Doc 814ppPrivacy :: Bool -> Doc
791ppPrivacy privacy = "Privacy: " <> if privacy then "private" else "public" 815ppPrivacy privacy = "Privacy: " <> if privacy then "private" else "public"
@@ -868,6 +892,7 @@ makeLensesFor
868instance NFData Torrent where 892instance NFData Torrent where
869 rnf Torrent {..} = rnf tInfoDict 893 rnf Torrent {..} = rnf tInfoDict
870 894
895#ifdef VERSION_bencoding
871-- TODO move to bencoding 896-- TODO move to bencoding
872instance BEncode URI where 897instance BEncode URI where
873 toBEncode uri = toBEncode (BC.pack (uriToString id uri "")) 898 toBEncode uri = toBEncode (BC.pack (uriToString id uri ""))
@@ -918,6 +943,7 @@ instance BEncode Torrent where
918 <*>? "publisher" 943 <*>? "publisher"
919 <*>? "publisher-url" 944 <*>? "publisher-url"
920 <*>? "signature" 945 <*>? "signature"
946#endif
921 947
922(<:>) :: Doc -> Doc -> Doc 948(<:>) :: Doc -> Doc -> Doc
923name <:> v = name <> ":" <+> v 949name <:> v = name <> ":" <+> v
@@ -949,9 +975,11 @@ instance Pretty Torrent where
949 "Publisher URL" <:>? ((text . show) <$> tPublisherURL) $$ 975 "Publisher URL" <:>? ((text . show) <$> tPublisherURL) $$
950 "Signature" <:>? ((text . show) <$> tSignature) 976 "Signature" <:>? ((text . show) <$> tSignature)
951 977
978#ifdef VERSION_bencoding
952-- | No files, no trackers, no nodes, etc... 979-- | No files, no trackers, no nodes, etc...
953instance Default Torrent where 980instance Default Torrent where
954 def = nullTorrent def 981 def = nullTorrent def
982#endif
955 983
956-- | A simple torrent contains only required fields. 984-- | A simple torrent contains only required fields.
957nullTorrent :: InfoDict -> Torrent 985nullTorrent :: InfoDict -> Torrent
@@ -971,6 +999,7 @@ torrentExt = "torrent"
971isTorrentPath :: FilePath -> Bool 999isTorrentPath :: FilePath -> Bool
972isTorrentPath filepath = takeExtension filepath == extSeparator : torrentExt 1000isTorrentPath filepath = takeExtension filepath == extSeparator : torrentExt
973 1001
1002#ifdef VERSION_bencoding
974-- | Read and decode a .torrent file. 1003-- | Read and decode a .torrent file.
975fromFile :: FilePath -> IO Torrent 1004fromFile :: FilePath -> IO Torrent
976fromFile filepath = do 1005fromFile filepath = do
@@ -982,6 +1011,7 @@ fromFile filepath = do
982-- | Encode and write a .torrent file. 1011-- | Encode and write a .torrent file.
983toFile :: FilePath -> Torrent -> IO () 1012toFile :: FilePath -> Torrent -> IO ()
984toFile filepath = BL.writeFile filepath . BE.encode 1013toFile filepath = BL.writeFile filepath . BE.encode
1014#endif
985 1015
986{----------------------------------------------------------------------- 1016{-----------------------------------------------------------------------
987-- URN 1017-- URN