module Conjure.Protocol.PWP.Types where import qualified Data.ByteString as BS import Data.ByteString (ByteString) import Data.Word newtype PeerId = PeerId {unPeerId :: ByteString} deriving (Eq,Ord) instance Show PeerId where showsPrec n (PeerId peerId) = showsPrec n peerId data Handshake = Handshake { hsInfoHash :: ByteString , hsPeerId :: PeerId } -- | Message datatype. Should be revamped to use packed strings. data Message = KeepAlive | Choke | Unchoke | Interested | NotInterested | Have !Int -- ^ Note: this is not trustworthy (could claim pieces -- it doesn't have that we will never want, could leave -- out pieces we don't want that it has) | BitField ByteString -- ^ which Pieces this peer boasts to have -- | Request for a block of data. A bit complicated. See spec for detals. | Request { msgIndex :: !Int, -- ^ Piece index msgBegin :: !Int, -- ^ Byte offset within piece msgLength :: !Int -- ^ Length in bytes, normally 2^14 } -- | Such a block of data. | RequestedPiece { msgIndex :: !Int -- ^ Piece index , msgBegin :: !Int -- ^ Byte offset within piece , msgBlock :: ByteString } -- | Cancel a request. | Cancel { msgIndex :: !Int, -- ^ Piece index msgBegin :: !Int, -- ^ Byte offset within piece msgLength :: !Int -- ^ Length in bytes, normally 2^14 } -- | Not a real message type, holds the id of an -- unknown message type | Unknown !Word8 deriving (Eq,Show)