summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Data/Torrent/Client.hs9
-rw-r--r--src/Network/BitTorrent/Core.hs1
-rw-r--r--src/Network/BitTorrent/Core/PeerId.hs3
-rw-r--r--src/Network/BitTorrent/Exchange.hs66
-rw-r--r--src/Network/BitTorrent/Exchange/Bus.hs63
-rw-r--r--src/Network/BitTorrent/Exchange/Message.hs2
-rw-r--r--src/Network/BitTorrent/Exchange/Session.hs147
-rw-r--r--src/Network/BitTorrent/Tracker/Server.hs4
8 files changed, 221 insertions, 74 deletions
diff --git a/src/Data/Torrent/Client.hs b/src/Data/Torrent/Client.hs
index 6437cbbf..f21a5e92 100644
--- a/src/Data/Torrent/Client.hs
+++ b/src/Data/Torrent/Client.hs
@@ -26,13 +26,9 @@ module Data.Torrent.Client
26 , libClientInfo 26 , libClientInfo
27 ) where 27 ) where
28 28
29import Control.Applicative
30import Data.ByteString as BS
31import Data.ByteString.Char8 as BC
32import Data.Default 29import Data.Default
33import Data.List as L 30import Data.List as L
34import Data.List.Split as L 31import Data.List.Split as L
35import Data.Maybe
36import Data.Monoid 32import Data.Monoid
37import Data.String 33import Data.String
38import Data.Text as T 34import Data.Text as T
@@ -40,8 +36,11 @@ import Data.Version
40import Text.PrettyPrint hiding ((<>)) 36import Text.PrettyPrint hiding ((<>))
41import Text.PrettyPrint.Class 37import Text.PrettyPrint.Class
42import Text.Read (readMaybe) 38import Text.Read (readMaybe)
43import Paths_bittorrent (version) 39-- import Paths_bittorrent (version)
44 40
41-- TODO FIXME
42version :: Version
43version = Version [0, 0, 0, 3] []
45 44
46-- | List of registered client versions + 'IlibHSbittorrent' (this 45-- | List of registered client versions + 'IlibHSbittorrent' (this
47-- package) + 'IUnknown' (for not recognized software). All names are 46-- package) + 'IUnknown' (for not recognized software). All names are
diff --git a/src/Network/BitTorrent/Core.hs b/src/Network/BitTorrent/Core.hs
new file mode 100644
index 00000000..70fe83c3
--- /dev/null
+++ b/src/Network/BitTorrent/Core.hs
@@ -0,0 +1 @@
module Network.BitTorrent.Core () where \ No newline at end of file
diff --git a/src/Network/BitTorrent/Core/PeerId.hs b/src/Network/BitTorrent/Core/PeerId.hs
index 3f90347c..8bd175e5 100644
--- a/src/Network/BitTorrent/Core/PeerId.hs
+++ b/src/Network/BitTorrent/Core/PeerId.hs
@@ -58,7 +58,6 @@ import System.Locale (defaultTimeLocale)
58import Text.PrettyPrint hiding ((<>)) 58import Text.PrettyPrint hiding ((<>))
59import Text.PrettyPrint.Class 59import Text.PrettyPrint.Class
60import Text.Read (readMaybe) 60import Text.Read (readMaybe)
61import Paths_bittorrent (version)
62 61
63import Data.Torrent.Client 62import Data.Torrent.Client
64 63
@@ -173,7 +172,7 @@ defaultClientId = "HS"
173-- package. Version is taken from .cabal file. 172-- package. Version is taken from .cabal file.
174defaultVersionNumber :: ByteString 173defaultVersionNumber :: ByteString
175defaultVersionNumber = BS.take 4 $ BC.pack $ foldMap show $ 174defaultVersionNumber = BS.take 4 $ BC.pack $ foldMap show $
176 versionBranch version 175 versionBranch $ ciVersion libClientInfo
177 176
178{----------------------------------------------------------------------- 177{-----------------------------------------------------------------------
179-- Generation 178-- Generation
diff --git a/src/Network/BitTorrent/Exchange.hs b/src/Network/BitTorrent/Exchange.hs
index 74aeab94..57b2c81f 100644
--- a/src/Network/BitTorrent/Exchange.hs
+++ b/src/Network/BitTorrent/Exchange.hs
@@ -98,72 +98,6 @@ import Network.BitTorrent.Exchange.Protocol
98import Network.BitTorrent.Sessions.Types 98import Network.BitTorrent.Sessions.Types
99import System.Torrent.Storage 99import System.Torrent.Storage
100 100
101{-----------------------------------------------------------------------
102 Peer wire
103-----------------------------------------------------------------------}
104
105type PeerWire = ConduitM Message Message IO
106
107runPeerWire :: Socket -> PeerWire () -> IO ()
108runPeerWire sock action =
109 sourceSocket sock $=
110 S.conduitGet S.get $=
111-- B.conduitDecode $=
112 action $=
113 S.conduitPut S.put $$
114-- B.conduitEncode $$
115 sinkSocket sock
116
117awaitMessage :: P2P Message
118awaitMessage = P2P $ ReaderT $ const $ {-# SCC awaitMessage #-} go
119 where
120 go = await >>= maybe (monadThrow PeerDisconnected) return
121{-# INLINE awaitMessage #-}
122
123yieldMessage :: Message -> P2P ()
124yieldMessage msg = P2P $ ReaderT $ const $ {-# SCC yieldMessage #-} do
125 C.yield msg
126{-# INLINE yieldMessage #-}
127
128-- TODO send vectored
129flushPending :: P2P ()
130flushPending = {-# SCC flushPending #-} do
131 session <- ask
132 queue <- liftIO (getPending session)
133 mapM_ yieldMessage queue
134
135{-----------------------------------------------------------------------
136 P2P monad
137-----------------------------------------------------------------------}
138
139-- |
140-- Exceptions:
141--
142-- * SessionException: is visible only within one peer
143-- session. Use this exception to terminate P2P session, but not
144-- the swarm session.
145--
146newtype P2P a = P2P {
147 unP2P :: ReaderT PeerSession PeerWire a
148 } deriving ( Functor, Applicative, Monad
149 , MonadIO, MonadThrow, MonadActive
150 , MonadReader PeerSession
151 )
152
153instance MonadState SessionState P2P where
154 {-# SPECIALIZE instance MonadState SessionState P2P #-}
155 get = asks sessionState >>= liftIO . readIORef
156 {-# INLINE get #-}
157 put !s = asks sessionState >>= \ref -> liftIO $ writeIORef ref s
158 {-# INLINE put #-}
159
160runP2P :: (Socket, PeerSession) -> P2P () -> IO ()
161runP2P (sock, ses) action =
162 handle isIOException $
163 runPeerWire sock (runReaderT (unP2P action) ses)
164 where
165 isIOException :: IOException -> IO ()
166 isIOException _ = return ()
167 101
168{----------------------------------------------------------------------- 102{-----------------------------------------------------------------------
169 Exceptions 103 Exceptions
diff --git a/src/Network/BitTorrent/Exchange/Bus.hs b/src/Network/BitTorrent/Exchange/Bus.hs
new file mode 100644
index 00000000..4800c4a0
--- /dev/null
+++ b/src/Network/BitTorrent/Exchange/Bus.hs
@@ -0,0 +1,63 @@
1module Network.BitTorrent.Exchange.Bus ( ) where
2
3type PeerWire = ConduitM Message Message IO
4
5runPeerWire :: Socket -> PeerWire () -> IO ()
6runPeerWire sock action =
7 sourceSocket sock $=
8 S.conduitGet S.get $=
9-- B.conduitDecode $=
10 action $=
11 S.conduitPut S.put $$
12-- B.conduitEncode $$
13 sinkSocket sock
14
15awaitMessage :: P2P Message
16awaitMessage = P2P $ ReaderT $ const $ {-# SCC awaitMessage #-} go
17 where
18 go = await >>= maybe (monadThrow PeerDisconnected) return
19{-# INLINE awaitMessage #-}
20
21yieldMessage :: Message -> P2P ()
22yieldMessage msg = P2P $ ReaderT $ const $ {-# SCC yieldMessage #-} do
23 C.yield msg
24{-# INLINE yieldMessage #-}
25
26-- TODO send vectored
27flushPending :: P2P ()
28flushPending = {-# SCC flushPending #-} do
29 session <- ask
30 queue <- liftIO (getPending session)
31 mapM_ yieldMessage queue
32
33{-----------------------------------------------------------------------
34 P2P monad
35-----------------------------------------------------------------------}
36
37-- |
38-- Exceptions:
39--
40-- * SessionException: is visible only within one peer
41-- session. Use this exception to terminate P2P session, but not
42-- the swarm session.
43--
44newtype P2P a = P2P {
45 unP2P :: ReaderT PeerSession PeerWire a
46 } deriving ( Functor, Applicative, Monad
47 , MonadIO, MonadThrow, MonadActive
48 , MonadReader PeerSession
49 )
50
51instance MonadState SessionState P2P where
52 get = asks sessionState >>= liftIO . readIORef
53 {-# INLINE get #-}
54 put !s = asks sessionState >>= \ref -> liftIO $ writeIORef ref s
55 {-# INLINE put #-}
56
57runP2P :: (Socket, PeerSession) -> P2P () -> IO ()
58runP2P (sock, ses) action =
59 handle isIOException $
60 runPeerWire sock (runReaderT (unP2P action) ses)
61 where
62 isIOException :: IOException -> IO ()
63 isIOException _ = return ()
diff --git a/src/Network/BitTorrent/Exchange/Message.hs b/src/Network/BitTorrent/Exchange/Message.hs
index 4ef7baf3..4d4a97e2 100644
--- a/src/Network/BitTorrent/Exchange/Message.hs
+++ b/src/Network/BitTorrent/Exchange/Message.hs
@@ -27,7 +27,7 @@
27-- 27--
28{-# LANGUAGE TemplateHaskell #-} 28{-# LANGUAGE TemplateHaskell #-}
29{-# OPTIONS -fno-warn-orphans #-} 29{-# OPTIONS -fno-warn-orphans #-}
30module Network.BitTorrent.Exchange.Protocol 30module Network.BitTorrent.Exchange.Message
31 ( -- * Initial handshake 31 ( -- * Initial handshake
32 Handshake(..) 32 Handshake(..)
33 , handshake 33 , handshake
diff --git a/src/Network/BitTorrent/Exchange/Session.hs b/src/Network/BitTorrent/Exchange/Session.hs
new file mode 100644
index 00000000..ffc7816e
--- /dev/null
+++ b/src/Network/BitTorrent/Exchange/Session.hs
@@ -0,0 +1,147 @@
1{-# LANGUAGE TemplateHaskell #-}
2{-# LANGUAGE DeriveDataTypeable #-}
3module Network.BitTorrent.Exchange.Session
4 (
5 ) where
6
7import Control.Concurrent.STM
8import Control.Exception
9import Control.Lens
10import Data.Function
11import Data.IORef
12import Data.Ord
13import Data.Typeable
14import Text.PrettyPrint
15
16import Data.Torrent.Bitfield
17import Data.Torrent.InfoHash
18import Network.BitTorrent.Core.PeerAddr
19import Network.BitTorrent.Exchange.Message
20import Network.BitTorrent.Exchange.Status
21
22
23type Extension = ()
24
25-- | Peer session contain all data necessary for peer to peer
26-- communication.
27data ExchangeSession = ExchangeSession
28 { -- | Used as unique identifier of the session.
29 connectedPeerAddr :: !PeerAddr
30
31 -- | Extensions such that both peer and client support.
32 , enabledExtensions :: [Extension]
33
34 -- | Broadcast messages waiting to be sent to peer.
35 , pendingMessages :: !(TChan Message)
36
37 -- | Dymanic P2P data.
38 , sessionState :: !(IORef SessionState)
39 }
40
41instance Eq ExchangeSession where
42 (==) = (==) `on` connectedPeerAddr
43 {-# INLINE (==) #-}
44
45instance Ord ExchangeSession where
46 compare = comparing connectedPeerAddr
47 {-# INLINE compare #-}
48
49enqueueBroadcast :: ExchangeSession -> Message -> IO ()
50enqueueBroadcast = undefined
51
52dequeueBroadcast :: ExchangeSession -> IO Message
53dequeueBroadcast = undefined
54
55{-----------------------------------------------------------------------
56-- Session state
57-----------------------------------------------------------------------}
58
59data SessionState = SessionState
60 { _bitfield :: !Bitfield -- ^ Other peer Have bitfield.
61 , _status :: !SessionStatus -- ^ Status of both peers.
62 } deriving (Show, Eq)
63
64$(makeLenses ''SessionState)
65
66--initialSessionState :: PieceCount -> SessionState
67--initialSessionState pc = SessionState (haveNone pc) def
68
69--getSessionState :: PeerSession -> IO SessionState
70--getSessionState PeerSession {..} = readIORef sessionState
71
72{-----------------------------------------------------------------------
73-- Exceptions
74-----------------------------------------------------------------------}
75
76-- | Exceptions used to interrupt the current P2P session. This
77-- exceptions will NOT affect other P2P sessions, DHT, peer <->
78-- tracker, or any other session.
79--
80data ExchangeFailure
81 = PeerDisconnected
82 | ProtocolError Doc
83 | UnknownTorrent InfoHash
84 deriving (Show, Typeable)
85
86instance Exception ExchangeFailure
87
88-- | Do nothing with exception, used with 'handle' or 'try'.
89isSessionException :: Monad m => ExchangeFailure -> m ()
90isSessionException _ = return ()
91
92-- | The same as 'isSessionException' but output to stdout the catched
93-- exception, for debugging purposes only.
94putSessionException :: ExchangeFailure -> IO ()
95putSessionException = print
96{-
97{-----------------------------------------------------------------------
98-- Broadcasting: Have, Cancel, Bitfield, SuggestPiece
99-----------------------------------------------------------------------}
100{-
101Here we should enqueue broadcast messages and keep in mind that:
102 * We should enqueue broadcast events as they are appear.
103 * We should yield broadcast messages as fast as we get them.
104
105these 2 phases might differ in time significantly
106
107**TODO**: do this; but only when it'll be clean which other broadcast
108messages & events we should send.
109
1101. Update client have bitfield --\____ in one transaction;
1112. Update downloaded stats --/
1123. Signal to the all other peer about this.
113-}
114
115available :: Bitfield -> SwarmSession -> STM ()
116available bf SwarmSession {..} = {-# SCC available #-} do
117 updateProgress >> broadcast
118 where
119 updateProgress = do
120 let piLen = ciPieceLength $ tInfo $ torrentMeta
121 let bytes = piLen * BF.haveCount bf
122 modifyTVar' (currentProgress clientSession) (downloadedProgress bytes)
123
124 broadcast = mapM_ (writeTChan broadcastMessages . Have) (BF.toList bf)
125
126-- TODO compute size of messages: if it's faster to send Bitfield
127-- instead many Have do that
128
129-- Also if there is single Have message in queue then the
130-- corresponding piece is likely still in memory or disc cache,
131-- when we can send SuggestPiece.
132
133readAvail :: TChan a -> STM [a]
134readAvail chan = do
135 m <- tryReadTChan chan
136 case m of
137 Just a -> (:) <$> pure a <*> readAvail chan
138 Nothing -> return []
139
140-- | Get pending messages queue appeared in result of asynchronously
141-- changed client state. Resulting queue should be sent to a peer
142-- immediately.
143--
144getPending :: PeerSession -> IO [Message]
145getPending PeerSession {..} = {-# SCC getPending #-} do
146 atomically (readAvail pendingMessages)
147-} \ No newline at end of file
diff --git a/src/Network/BitTorrent/Tracker/Server.hs b/src/Network/BitTorrent/Tracker/Server.hs
new file mode 100644
index 00000000..4ed19588
--- /dev/null
+++ b/src/Network/BitTorrent/Tracker/Server.hs
@@ -0,0 +1,4 @@
1module Network.BitTorrent.Tracker.Server
2 (
3 ) where
4