summaryrefslogtreecommitdiff
path: root/src/Network/BitTorrent/PeerWire/Message.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Network/BitTorrent/PeerWire/Message.hs')
-rw-r--r--src/Network/BitTorrent/PeerWire/Message.hs91
1 files changed, 91 insertions, 0 deletions
diff --git a/src/Network/BitTorrent/PeerWire/Message.hs b/src/Network/BitTorrent/PeerWire/Message.hs
new file mode 100644
index 00000000..1bcb2ee5
--- /dev/null
+++ b/src/Network/BitTorrent/PeerWire/Message.hs
@@ -0,0 +1,91 @@
1module Network.BitTorrent.PeerWire.Message
2 ( Message(..)
3 ) where
4
5import Control.Applicative
6import Data.ByteString (ByteString)
7import qualified Data.ByteString as B
8
9import Data.Serialize
10
11import Network.BitTorrent.PeerWire.Block
12
13
14-- TODO comment message constructors
15data Message = KeepAlive
16 | Choke
17 | Unchoke
18 | Interested
19 | NotInterested
20 | Have Int
21 | Bitfield ByteString
22 | Request BlockIx
23 | Piece Block
24 | Cancel BlockIx
25 | Port Int
26 deriving (Show, Eq)
27
28instance Serialize BlockIx where
29 {-# SPECIALIZE instance Serialize BlockIx #-}
30 get = BlockIx <$> getInt <*> getInt <*> getInt
31 {-# INLINE get #-}
32
33 put ix = do putInt (ixPiece ix)
34 putInt (ixOffset ix)
35 putInt (ixLength ix)
36 {-# INLINE put #-}
37
38instance Serialize Message where
39 get = do
40 len <- getInt
41 lookAhead $ ensure len
42 if len == 0 then return KeepAlive -- FIX check if BS is empty instead of reading len
43 else do
44 mid <- getWord8
45 case mid of
46 0 -> return Choke
47 1 -> return Unchoke
48 2 -> return Interested
49 3 -> return NotInterested
50 4 -> Have <$> getInt
51 5 -> Bitfield <$> getBytes (pred len)
52 6 -> Request <$> get
53 7 -> Piece <$> getBlock (len - 9)
54 8 -> Cancel <$> get
55 9 -> (Port . fromIntegral) <$> getWord16be
56 _ -> fail $ "unknown message ID: " ++ show mid
57
58 where
59 getBlock :: Int -> Get Block
60 getBlock len = Block <$> getInt <*> getInt <*> getBytes len
61 {-# INLINE getBlock #-}
62
63 put KeepAlive = putInt 0
64 put Choke = putInt 1 >> putWord8 0
65 put Unchoke = putInt 1 >> putWord8 1
66 put Interested = putInt 1 >> putWord8 2
67 put NotInterested = putInt 1 >> putWord8 3
68 put (Have i) = putInt 5 >> putWord8 4 >> putInt i
69 put (Bitfield b) = putInt l >> putWord8 5 >> putByteString b
70 where l = succ (B.length b)
71 {-# INLINE l #-}
72 put (Request blk) = putInt 13 >> putWord8 6 >> put blk
73 put (Piece blk) = putInt l >> putWord8 7 >> putBlock
74 where l = 9 + B.length (blkData blk)
75 {-# INLINE l #-}
76 putBlock = do putInt (blkPiece blk)
77 putInt (blkOffset blk)
78 putByteString (blkData blk)
79 {-# INLINE putBlock #-}
80
81 put (Cancel blk) = putInt 13 >> putWord8 8 >> put blk
82 put (Port p ) = putInt 3 >> putWord8 9 >> putWord16be (fromIntegral p)
83
84
85getInt :: Get Int
86getInt = fromIntegral <$> getWord32be
87{-# INLINE getInt #-}
88
89putInt :: Putter Int
90putInt = putWord32be . fromIntegral
91{-# INLINE putInt #-}