summaryrefslogtreecommitdiff
path: root/src/Network
diff options
context:
space:
mode:
Diffstat (limited to 'src/Network')
-rw-r--r--src/Network/BitTorrent.hs6
-rw-r--r--src/Network/BitTorrent/Exchange.hs57
-rw-r--r--src/Network/BitTorrent/Peer.hs3
3 files changed, 57 insertions, 9 deletions
diff --git a/src/Network/BitTorrent.hs b/src/Network/BitTorrent.hs
index 51ba6aac..ac9ed50a 100644
--- a/src/Network/BitTorrent.hs
+++ b/src/Network/BitTorrent.hs
@@ -5,7 +5,11 @@
5-- Stability : experimental 5-- Stability : experimental
6-- Portability : portable 6-- Portability : portable
7-- 7--
8module Network.BitTorrent (module BT) where 8module Network.BitTorrent
9 (module BT
10
11-- , ClientSession, newClient
12 ) where
9 13
10import Network.BitTorrent.Extension as BT 14import Network.BitTorrent.Extension as BT
11import Network.BitTorrent.Peer as BT 15import Network.BitTorrent.Peer as BT
diff --git a/src/Network/BitTorrent/Exchange.hs b/src/Network/BitTorrent/Exchange.hs
index d75fdf96..425ed2a3 100644
--- a/src/Network/BitTorrent/Exchange.hs
+++ b/src/Network/BitTorrent/Exchange.hs
@@ -6,18 +6,61 @@
6-- Portability : portable 6-- Portability : portable
7-- 7--
8{-# LANGUAGE DoAndIfThenElse #-} 8{-# LANGUAGE DoAndIfThenElse #-}
9module Network.BitTorrent.Exchange (module PW) where 9module Network.BitTorrent.Exchange
10 (
11 -- * Session
12 PeerSession, newLeacher, newSeeder
13 ) where
14
15import Control.Applicative
16import Control.Concurrent
17import Control.Concurrent.STM
18import Data.IORef
19import Data.Function
20import Data.Ord
21import Data.Set as S
22
23import Data.Conduit
24import Data.Conduit.Cereal
25import Data.Conduit.Network
26import Data.Serialize
10 27
11import Network.BitTorrent.Exchange.Selection as PW 28import Network.BitTorrent.Exchange.Selection as PW
12import Network.BitTorrent.Exchange.Protocol as PW 29import Network.BitTorrent.Exchange.Protocol as PW
13 30
31import Network.BitTorrent.Internal
32import Network.BitTorrent.Extension
33import Network.BitTorrent.Peer
34import Data.Bitfield as BF
35import Data.Torrent
36
37{-----------------------------------------------------------------------
38 P2P monad
39-----------------------------------------------------------------------}
40
14{- 41{-
42type P2P = Reader PeerSession (ConduitM Message Message IO)
15 43
16newtype P2P a = P2P { 44conduit :: Socket -> P2P a -> IO a
17 getP2P :: ReaderT PSession State PState (Conduit Message IO Message) a 45conduit sock p2p =
18 } 46 sourceSocket sock $=
47 conduitGet get $=
48 messageLoop p2p $=
49 conduitPut put $$
50 sinkSocket sock
19 51
20runP2P :: PConnection -> P2P a -> IO a 52messageLoop :: P2P () -> P2P ()
21recvMessage :: P2P Message 53messageLoop = undefined
22sendMessage :: Message -> P2P () 54
55runP2P :: SSession -> PeerAddr -> P2P a -> IO a
56runP2P se addr p2p = withPeer se addr $ conduit messageLoop
57
58data Event = Available
59 | Want
60 | Block
61
62{-
63waitForEvent :: P2P Event
64signalEvent :: Event -> P2P ()
65-}
23-} \ No newline at end of file 66-} \ No newline at end of file
diff --git a/src/Network/BitTorrent/Peer.hs b/src/Network/BitTorrent/Peer.hs
index 6ab80fb6..9aa924d3 100644
--- a/src/Network/BitTorrent/Peer.hs
+++ b/src/Network/BitTorrent/Peer.hs
@@ -488,7 +488,8 @@ data PeerAddr = PeerAddr {
488 peerID :: Maybe PeerID 488 peerID :: Maybe PeerID
489 , peerIP :: HostAddress 489 , peerIP :: HostAddress
490 , peerPort :: PortNumber 490 , peerPort :: PortNumber
491 } deriving (Show, Eq) 491 } deriving (Show, Eq, Ord)
492 -- TODO verify semantic of ord and eq instances
492 493
493instance BEncodable PortNumber where 494instance BEncodable PortNumber where
494 toBEncode = toBEncode . fromEnum 495 toBEncode = toBEncode . fromEnum