summaryrefslogtreecommitdiff
path: root/src/Network/BitTorrent/Exchange/Wire.hs
diff options
context:
space:
mode:
authorSam Truzjan <pxqr.sta@gmail.com>2013-12-05 20:00:01 +0400
committerSam Truzjan <pxqr.sta@gmail.com>2013-12-05 20:00:01 +0400
commit2367c9c0ab45a843cb4d1b8762af4ca06291348c (patch)
tree5124617196b8558cf876d62e2dd7f7052c49fccb /src/Network/BitTorrent/Exchange/Wire.hs
parent6f092fb275367b6afe4f0745f975e8ee53012d56 (diff)
Make extended caps mutable
Diffstat (limited to 'src/Network/BitTorrent/Exchange/Wire.hs')
-rw-r--r--src/Network/BitTorrent/Exchange/Wire.hs73
1 files changed, 56 insertions, 17 deletions
diff --git a/src/Network/BitTorrent/Exchange/Wire.hs b/src/Network/BitTorrent/Exchange/Wire.hs
index 68c9b355..6a161762 100644
--- a/src/Network/BitTorrent/Exchange/Wire.hs
+++ b/src/Network/BitTorrent/Exchange/Wire.hs
@@ -4,20 +4,29 @@
4-- Duplex channell 4-- Duplex channell
5-- This module control /integrity/ of data send and received. 5-- This module control /integrity/ of data send and received.
6-- 6--
7 7--
8{-# LANGUAGE DeriveDataTypeable #-} 8{-# LANGUAGE DeriveDataTypeable #-}
9module Network.BitTorrent.Exchange.Wire 9module Network.BitTorrent.Exchange.Wire
10 ( -- * Exception 10 ( -- * Wire
11 ProtocolError (..) 11 Wire
12
13 -- ** Exceptions
14 , ProtocolError (..)
12 , WireFailure (..) 15 , WireFailure (..)
13 , isWireFailure 16 , isWireFailure
17 , disconnectPeer
14 18
15 -- * Wire 19 -- ** Connection
16 , Connection (..) 20 , Connection (..)
17 , Wire 21
22 -- ** Setup
18 , runWire 23 , runWire
19 , connectWire 24 , connectWire
20 , acceptWire 25 , acceptWire
26
27 -- ** Query
28 , getConnection
29 , getExtCaps
21 ) where 30 ) where
22 31
23import Control.Exception 32import Control.Exception
@@ -27,6 +36,7 @@ import Data.Conduit
27import Data.Conduit.Cereal as S 36import Data.Conduit.Cereal as S
28import Data.Conduit.Network 37import Data.Conduit.Network
29import Data.Default 38import Data.Default
39import Data.IORef
30import Data.Maybe 40import Data.Maybe
31import Data.Monoid 41import Data.Monoid
32import Data.Serialize as S 42import Data.Serialize as S
@@ -56,6 +66,7 @@ data ProtocolError
56 = UnexpectedTopic InfoHash -- ^ peer replied with unexpected infohash. 66 = UnexpectedTopic InfoHash -- ^ peer replied with unexpected infohash.
57 | UnexpectedPeerId PeerId -- ^ peer replied with unexpected peer id. 67 | UnexpectedPeerId PeerId -- ^ peer replied with unexpected peer id.
58 | UnknownTopic InfoHash -- ^ peer requested unknown torrent. 68 | UnknownTopic InfoHash -- ^ peer requested unknown torrent.
69 | HandshakeRefused -- ^ peer do not send an extended handshake back.
59 | InvalidMessage 70 | InvalidMessage
60 { violentSender :: ChannelSide -- ^ endpoint sent invalid message 71 { violentSender :: ChannelSide -- ^ endpoint sent invalid message
61 , extensionRequired :: Extension -- ^ 72 , extensionRequired :: Extension -- ^
@@ -87,11 +98,11 @@ isWireFailure _ = return ()
87 98
88data Connection = Connection 99data Connection = Connection
89 { connCaps :: !Caps 100 { connCaps :: !Caps
90 , connExtCaps :: !ExtendedCaps -- TODO caps can be enabled during communication 101 , connExtCaps :: !(IORef ExtendedCaps)
91 , connTopic :: !InfoHash 102 , connTopic :: !InfoHash
92 , connRemotePeerId :: !PeerId 103 , connRemotePeerId :: !PeerId
93 , connThisPeerId :: !PeerId 104 , connThisPeerId :: !PeerId
94 } deriving Show 105 }
95 106
96instance Pretty Connection where 107instance Pretty Connection where
97 pretty Connection {..} = "Connection" 108 pretty Connection {..} = "Connection"
@@ -146,6 +157,25 @@ connectToPeer p = do
146 157
147type Wire = ConduitM Message Message (ReaderT Connection IO) 158type Wire = ConduitM Message Message (ReaderT Connection IO)
148 159
160protocolError :: ProtocolError -> Wire a
161protocolError = monadThrow . ProtocolError
162
163disconnectPeer :: Wire a
164disconnectPeer = monadThrow DisconnectPeer
165
166getExtCaps :: Wire ExtendedCaps
167getExtCaps = do
168 capsRef <- lift $ asks connExtCaps
169 liftIO $ readIORef capsRef
170
171setExtCaps :: ExtendedCaps -> Wire ()
172setExtCaps caps = do
173 capsRef <- lift $ asks connExtCaps
174 liftIO $ writeIORef capsRef caps
175
176getConnection :: Wire Connection
177getConnection = lift ask
178
149validate :: ChannelSide -> Wire () 179validate :: ChannelSide -> Wire ()
150validate side = await >>= maybe (return ()) yieldCheck 180validate side = await >>= maybe (return ()) yieldCheck
151 where 181 where
@@ -155,9 +185,10 @@ validate side = await >>= maybe (return ()) yieldCheck
155 Nothing -> return () 185 Nothing -> return ()
156 Just ext 186 Just ext
157 | allowed caps ext -> yield msg 187 | allowed caps ext -> yield msg
158 | otherwise -> monadThrow $ ProtocolError $ InvalidMessage side ext 188 | otherwise -> protocolError $ InvalidMessage side ext
159 189
160validate' action = do 190validateBoth :: Wire () -> Wire ()
191validateBoth action = do
161 validate RemotePeer 192 validate RemotePeer
162 action 193 action
163 validate ThisPeer 194 validate ThisPeer
@@ -172,17 +203,23 @@ runWire action sock = runReaderT $
172 203
173sendMessage :: PeerMessage msg => msg -> Wire () 204sendMessage :: PeerMessage msg => msg -> Wire ()
174sendMessage msg = do 205sendMessage msg = do
175 ecaps <- lift $ asks connExtCaps 206 ecaps <- getExtCaps
176 yield $ envelop ecaps msg 207 yield $ envelop ecaps msg
177 208
178recvMessage :: Wire Message 209recvMessage :: Wire Message
179recvMessage = undefined 210recvMessage = undefined
180 211
181extendedHandshake :: Wire () 212extendedHandshake :: ExtendedCaps -> Wire ()
182extendedHandshake = undefined 213extendedHandshake caps = do
214 sendMessage $ nullExtendedHandshake caps
215 msg <- recvMessage
216 case msg of
217 Extended (EHandshake ExtendedHandshake {..}) ->
218 setExtCaps $ ehsCaps <> caps
219 _ -> protocolError HandshakeRefused
183 220
184connectWire :: Handshake -> PeerAddr -> ExtendedCaps -> Wire () -> IO () 221connectWire :: Handshake -> PeerAddr -> ExtendedCaps -> Wire () -> IO ()
185connectWire hs addr caps wire = 222connectWire hs addr extCaps wire =
186 bracket (connectToPeer addr) close $ \ sock -> do 223 bracket (connectToPeer addr) close $ \ sock -> do
187 hs' <- initiateHandshake sock hs 224 hs' <- initiateHandshake sock hs
188 225
@@ -193,12 +230,14 @@ connectWire hs addr caps wire =
193 throwIO $ ProtocolError $ UnexpectedPeerId (hsPeerId hs') 230 throwIO $ ProtocolError $ UnexpectedPeerId (hsPeerId hs')
194 231
195 let caps = hsReserved hs <> hsReserved hs' 232 let caps = hsReserved hs <> hsReserved hs'
196 if allowed caps ExtExtended 233 let wire' = if allowed caps ExtExtended
197 then return () else return () 234 then extendedHandshake extCaps >> wire
235 else wire
198 236
199 runWire wire sock $ Connection 237 extCapsRef <- newIORef def
238 runWire wire' sock $ Connection
200 { connCaps = caps 239 { connCaps = caps
201 , connExtCaps = def 240 , connExtCaps = extCapsRef
202 , connTopic = hsInfoHash hs 241 , connTopic = hsInfoHash hs
203 , connRemotePeerId = hsPeerId hs' 242 , connRemotePeerId = hsPeerId hs'
204 , connThisPeerId = hsPeerId hs 243 , connThisPeerId = hsPeerId hs