summaryrefslogtreecommitdiff
path: root/src/Data
diff options
context:
space:
mode:
Diffstat (limited to 'src/Data')
-rw-r--r--src/Data/Torrent.hs30
1 files changed, 15 insertions, 15 deletions
diff --git a/src/Data/Torrent.hs b/src/Data/Torrent.hs
index cfc26453..94506d1c 100644
--- a/src/Data/Torrent.hs
+++ b/src/Data/Torrent.hs
@@ -183,7 +183,7 @@ import Network.HTTP.Types.URI
183import Network.URI 183import Network.URI
184import Text.ParserCombinators.ReadP as P 184import Text.ParserCombinators.ReadP as P
185import Text.PrettyPrint as PP 185import Text.PrettyPrint as PP
186import Text.PrettyPrint.Class 186import Text.PrettyPrint.HughesPJClass hiding ((<>),($$))
187import System.FilePath 187import System.FilePath
188import System.Posix.Types 188import System.Posix.Types
189 189
@@ -247,7 +247,7 @@ instance Show InfoHash where
247 247
248-- | Convert to base16 encoded Doc string. 248-- | Convert to base16 encoded Doc string.
249instance Pretty InfoHash where 249instance Pretty InfoHash where
250 pretty = text . show 250 pPrint = text . show
251 251
252-- | Read base16 encoded string. 252-- | Read base16 encoded string.
253instance Read InfoHash where 253instance Read InfoHash where
@@ -397,7 +397,7 @@ instance BEncode (FileInfo BS.ByteString) where
397 {-# INLINE fromBEncode #-} 397 {-# INLINE fromBEncode #-}
398 398
399instance Pretty (FileInfo BS.ByteString) where 399instance Pretty (FileInfo BS.ByteString) where
400 pretty FileInfo {..} = 400 pPrint FileInfo {..} =
401 "Path: " <> text (T.unpack (T.decodeUtf8 fiName)) 401 "Path: " <> text (T.unpack (T.decodeUtf8 fiName))
402 $$ "Size: " <> text (show fiLength) 402 $$ "Size: " <> text (show fiLength)
403 $$ maybe PP.empty ppMD5 fiMD5Sum 403 $$ maybe PP.empty ppMD5 fiMD5Sum
@@ -465,8 +465,8 @@ instance BEncode LayoutInfo where
465 fromBEncode = fromDict getLayoutInfo 465 fromBEncode = fromDict getLayoutInfo
466 466
467instance Pretty LayoutInfo where 467instance Pretty LayoutInfo where
468 pretty SingleFile {..} = pretty liFile 468 pPrint SingleFile {..} = pPrint liFile
469 pretty MultiFile {..} = vcat $ L.map (pretty . joinFilePath) liFiles 469 pPrint MultiFile {..} = vcat $ L.map (pPrint . joinFilePath) liFiles
470 470
471-- | Test if this is single file torrent. 471-- | Test if this is single file torrent.
472isSingleFile :: LayoutInfo -> Bool 472isSingleFile :: LayoutInfo -> Bool
@@ -616,7 +616,7 @@ instance NFData (Piece a)
616 616
617-- | Payload bytes are omitted. 617-- | Payload bytes are omitted.
618instance Pretty (Piece a) where 618instance Pretty (Piece a) where
619 pretty Piece {..} = "Piece" <+> braces ("index" <+> "=" <+> int pieceIndex) 619 pPrint Piece {..} = "Piece" <+> braces ("index" <+> "=" <+> int pieceIndex)
620 620
621-- | Get size of piece in bytes. 621-- | Get size of piece in bytes.
622pieceSize :: Piece BL.ByteString -> PieceSize 622pieceSize :: Piece BL.ByteString -> PieceSize
@@ -685,7 +685,7 @@ instance BEncode PieceInfo where
685 685
686-- | Hashes are omitted. 686-- | Hashes are omitted.
687instance Pretty PieceInfo where 687instance Pretty PieceInfo where
688 pretty PieceInfo {..} = "Piece size: " <> int piPieceLength 688 pPrint PieceInfo {..} = "Piece size: " <> int piPieceLength
689 689
690slice :: Int -> Int -> BS.ByteString -> BS.ByteString 690slice :: Int -> Int -> BS.ByteString -> BS.ByteString
691slice start len = BS.take len . BS.drop start 691slice start len = BS.take len . BS.drop start
@@ -797,9 +797,9 @@ ppPrivacy privacy = "Privacy: " <> if privacy then "private" else "public"
797--ppAdditionalInfo layout = PP.empty 797--ppAdditionalInfo layout = PP.empty
798 798
799instance Pretty InfoDict where 799instance Pretty InfoDict where
800 pretty InfoDict {..} = 800 pPrint InfoDict {..} =
801 pretty idLayoutInfo $$ 801 pPrint idLayoutInfo $$
802 pretty idPieceInfo $$ 802 pPrint idPieceInfo $$
803 ppPrivacy idPrivate 803 ppPrivacy idPrivate
804 804
805{----------------------------------------------------------------------- 805{-----------------------------------------------------------------------
@@ -930,11 +930,11 @@ _ <:>? Nothing = PP.empty
930name <:>? (Just d) = name <:> d 930name <:>? (Just d) = name <:> d
931 931
932instance Pretty Torrent where 932instance Pretty Torrent where
933 pretty Torrent {..} = 933 pPrint Torrent {..} =
934 "InfoHash: " <> pretty (idInfoHash tInfoDict) 934 "InfoHash: " <> pPrint (idInfoHash tInfoDict)
935 $$ hang "General" 4 generalInfo 935 $$ hang "General" 4 generalInfo
936 $$ hang "Tracker" 4 trackers 936 $$ hang "Tracker" 4 trackers
937 $$ pretty tInfoDict 937 $$ pPrint tInfoDict
938 where 938 where
939 trackers = case tAnnounceList of 939 trackers = case tAnnounceList of
940 Nothing -> text (show tAnnounce) 940 Nothing -> text (show tAnnounce)
@@ -1037,7 +1037,7 @@ renderURN URN {..}
1037 = T.intercalate ":" $ "urn" : urnNamespace ++ [urnString] 1037 = T.intercalate ":" $ "urn" : urnNamespace ++ [urnString]
1038 1038
1039instance Pretty URN where 1039instance Pretty URN where
1040 pretty = text . T.unpack . renderURN 1040 pPrint = text . T.unpack . renderURN
1041 1041
1042instance Show URN where 1042instance Show URN where
1043 showsPrec n = showsPrec n . T.unpack . renderURN 1043 showsPrec n = showsPrec n . T.unpack . renderURN
@@ -1260,7 +1260,7 @@ renderMagnetStr :: Magnet -> String
1260renderMagnetStr = show . (convert :: Magnet -> URI) 1260renderMagnetStr = show . (convert :: Magnet -> URI)
1261 1261
1262instance Pretty Magnet where 1262instance Pretty Magnet where
1263 pretty = PP.text . renderMagnetStr 1263 pPrint = PP.text . renderMagnetStr
1264 1264
1265instance Show Magnet where 1265instance Show Magnet where
1266 show = renderMagnetStr 1266 show = renderMagnetStr