summaryrefslogtreecommitdiff
path: root/src/Network/BitTorrent/PeerWire
diff options
context:
space:
mode:
Diffstat (limited to 'src/Network/BitTorrent/PeerWire')
-rw-r--r--src/Network/BitTorrent/PeerWire/Block.hs14
-rw-r--r--src/Network/BitTorrent/PeerWire/Handshake.hs9
-rw-r--r--src/Network/BitTorrent/PeerWire/Message.hs16
3 files changed, 24 insertions, 15 deletions
diff --git a/src/Network/BitTorrent/PeerWire/Block.hs b/src/Network/BitTorrent/PeerWire/Block.hs
index fbc65338..dea37321 100644
--- a/src/Network/BitTorrent/PeerWire/Block.hs
+++ b/src/Network/BitTorrent/PeerWire/Block.hs
@@ -1,3 +1,5 @@
1{-# LANGUAGE RecordWildCards #-}
2{-# LANGUAGE OverloadedStrings #-}
1module Network.BitTorrent.PeerWire.Block 3module Network.BitTorrent.PeerWire.Block
2 ( BlockIx(..) 4 ( BlockIx(..)
3 , Block(..), blockSize 5 , Block(..), blockSize
@@ -16,6 +18,7 @@ import Data.ByteString (ByteString)
16import qualified Data.ByteString as B 18import qualified Data.ByteString as B
17import Data.Int 19import Data.Int
18import Data.Serialize 20import Data.Serialize
21import Text.PrettyPrint
19 22
20 23
21type BlockLIx = Int 24type BlockLIx = Int
@@ -51,10 +54,11 @@ instance Serialize BlockIx where
51 putInt (ixLength ix) 54 putInt (ixLength ix)
52 {-# INLINE put #-} 55 {-# INLINE put #-}
53 56
54ppBlockIx :: BlockIx -> String 57ppBlockIx :: BlockIx -> Doc
55ppBlockIx ix = "piece = " ++ show (ixPiece ix) ++ ", " 58ppBlockIx BlockIx {..} =
56 ++ "offset = " ++ show (ixOffset ix) ++ ", " 59 "piece = " <> int ixPiece <> "," <+>
57 ++ "length = " ++ show (ixLength ix) 60 "offset = " <> int ixOffset <> "," <+>
61 "length = " <> int ixLength
58 62
59data Block = Block { 63data Block = Block {
60 -- | Zero-based piece index. 64 -- | Zero-based piece index.
@@ -67,7 +71,7 @@ data Block = Block {
67 , blkData :: ByteString 71 , blkData :: ByteString
68 } deriving (Show, Eq) 72 } deriving (Show, Eq)
69 73
70ppBlock :: Block -> String 74ppBlock :: Block -> Doc
71ppBlock = ppBlockIx . blockIx 75ppBlock = ppBlockIx . blockIx
72 76
73blockSize :: Block -> Int 77blockSize :: Block -> Int
diff --git a/src/Network/BitTorrent/PeerWire/Handshake.hs b/src/Network/BitTorrent/PeerWire/Handshake.hs
index 6f4598ae..ff768cae 100644
--- a/src/Network/BitTorrent/PeerWire/Handshake.hs
+++ b/src/Network/BitTorrent/PeerWire/Handshake.hs
@@ -11,6 +11,7 @@
11-- peer. 11-- peer.
12-- 12--
13{-# LANGUAGE OverloadedStrings #-} 13{-# LANGUAGE OverloadedStrings #-}
14{-# LANGUAGE RecordWildCards #-}
14module Network.BitTorrent.PeerWire.Handshake 15module Network.BitTorrent.PeerWire.Handshake
15 ( Handshake(..), handshakeCaps 16 ( Handshake(..), handshakeCaps
16 , handshake 17 , handshake
@@ -27,6 +28,8 @@ import Data.ByteString (ByteString)
27import qualified Data.ByteString as B 28import qualified Data.ByteString as B
28import qualified Data.ByteString.Char8 as BC 29import qualified Data.ByteString.Char8 as BC
29import Data.Serialize as S 30import Data.Serialize as S
31import Text.PrettyPrint
32
30import Network 33import Network
31import Network.Socket.ByteString 34import Network.Socket.ByteString
32 35
@@ -77,9 +80,9 @@ handshakeCaps :: Handshake -> Capabilities
77handshakeCaps = hsReserved 80handshakeCaps = hsReserved
78 81
79-- | Format handshake in human readable form. 82-- | Format handshake in human readable form.
80ppHandshake :: Handshake -> String 83ppHandshake :: Handshake -> Doc
81ppHandshake hs = BC.unpack (hsProtocol hs) ++ " " 84ppHandshake Handshake {..} =
82 ++ ppClientInfo (clientInfo (hsPeerID hs)) 85 text (BC.unpack hsProtocol) <+> ppClientInfo (clientInfo hsPeerID)
83 86
84-- | Get handshake message size in bytes from the length of protocol string. 87-- | Get handshake message size in bytes from the length of protocol string.
85handshakeSize :: Word8 -> Int 88handshakeSize :: Word8 -> Int
diff --git a/src/Network/BitTorrent/PeerWire/Message.hs b/src/Network/BitTorrent/PeerWire/Message.hs
index f5ad2693..6515fdf2 100644
--- a/src/Network/BitTorrent/PeerWire/Message.hs
+++ b/src/Network/BitTorrent/PeerWire/Message.hs
@@ -1,3 +1,4 @@
1{-# LANGUAGE OverloadedStrings #-}
1module Network.BitTorrent.PeerWire.Message 2module Network.BitTorrent.PeerWire.Message
2 ( Message(..) 3 ( Message(..)
3 , Bitfield 4 , Bitfield
@@ -7,6 +8,7 @@ module Network.BitTorrent.PeerWire.Message
7import Control.Applicative 8import Control.Applicative
8import qualified Data.ByteString as B 9import qualified Data.ByteString as B
9import Data.Serialize 10import Data.Serialize
11import Text.PrettyPrint
10import Network 12import Network
11 13
12import Network.BitTorrent.PeerWire.Block 14import Network.BitTorrent.PeerWire.Block
@@ -141,10 +143,10 @@ instance Serialize Message where
141-- compact and suitable for logging: only useful information but not 143-- compact and suitable for logging: only useful information but not
142-- payload bytes. 144-- payload bytes.
143-- 145--
144ppMessage :: Message -> String 146ppMessage :: Message -> Doc
145ppMessage (Bitfield _) = "Bitfield " 147ppMessage (Bitfield _) = "Bitfield"
146ppMessage (Piece blk) = "Piece " ++ ppBlock blk 148ppMessage (Piece blk) = "Piece" <+> ppBlock blk
147ppMessage (Cancel ix) = "Cancel " ++ ppBlockIx ix 149ppMessage (Cancel ix) = "Cancel" <+> ppBlockIx ix
148ppMessage (SuggestPiece pix) = "Suggest" ++ show pix 150ppMessage (SuggestPiece pix) = "Suggest" <+> int pix
149ppMessage (RejectRequest ix) = "Reject" ++ ppBlockIx ix 151ppMessage (RejectRequest ix) = "Reject" <+> ppBlockIx ix
150ppMessage msg = show msg \ No newline at end of file 152ppMessage msg = text (show msg) \ No newline at end of file