diff options
Diffstat (limited to 'src/Network/BitTorrent.hs')
-rw-r--r-- | src/Network/BitTorrent.hs | 123 |
1 files changed, 1 insertions, 122 deletions
diff --git a/src/Network/BitTorrent.hs b/src/Network/BitTorrent.hs index d8888416..21528efd 100644 --- a/src/Network/BitTorrent.hs +++ b/src/Network/BitTorrent.hs | |||
@@ -7,126 +7,5 @@ | |||
7 | -- | 7 | -- |
8 | {-# LANGUAGE RecordWildCards #-} | 8 | {-# LANGUAGE RecordWildCards #-} |
9 | module Network.BitTorrent | 9 | module Network.BitTorrent |
10 | ( module Data.Torrent | 10 | ( |
11 | |||
12 | , TorrentLoc(..), TorrentMap, Progress(..) | ||
13 | , ThreadCount, SessionCount | ||
14 | |||
15 | , ClientSession( clientPeerId, allowedExtensions ) | ||
16 | , withDefaultClient, defaultThreadCount, defaultPorts | ||
17 | , addTorrent | ||
18 | , removeTorrent | ||
19 | |||
20 | , getCurrentProgress | ||
21 | , getPeerCount | ||
22 | , getSwarmCount | ||
23 | , getSessionCount | ||
24 | , getSwarm | ||
25 | , getStorage | ||
26 | , getTorrentInfo | ||
27 | , getTorrentInfoStr | ||
28 | |||
29 | -- * Torrent Groups | ||
30 | , ClientLoc (..), ppClientLoc | ||
31 | , concreteLoc, concretePath | ||
32 | , addTorrents | ||
33 | , removeTorrents | ||
34 | |||
35 | -- * Extensions | ||
36 | , Extension | ||
37 | , defaultExtensions | ||
38 | , ppExtension | ||
39 | ) where | 11 | ) where |
40 | |||
41 | import Control.Applicative | ||
42 | import Control.Exception | ||
43 | import Control.Monad | ||
44 | import Data.List as L | ||
45 | import Data.HashMap.Strict as HM | ||
46 | import Network | ||
47 | import Text.Read | ||
48 | import Text.PrettyPrint | ||
49 | import System.Directory | ||
50 | import System.FilePath | ||
51 | |||
52 | import Data.Torrent | ||
53 | import Network.BitTorrent.Sessions.Types | ||
54 | import Network.BitTorrent.Sessions | ||
55 | import Network.BitTorrent.Extension | ||
56 | import Network.BitTorrent.Tracker | ||
57 | |||
58 | |||
59 | -- TODO remove fork from Network.BitTorrent.Exchange | ||
60 | -- TODO make all forks in Internal. | ||
61 | |||
62 | -- | Client session with default parameters. Use it for testing only. | ||
63 | withDefaultClient :: PortNumber -> PortNumber -> (ClientSession -> IO ()) -> IO () | ||
64 | withDefaultClient listPort dhtPort action = do | ||
65 | withClientSession defaultThreadCount [] listPort dhtPort action | ||
66 | |||
67 | getTorrentInfoStr :: ClientSession -> String -> IO (Maybe Torrent) | ||
68 | getTorrentInfoStr cs str | ||
69 | | Just infohash <- readMaybe str = getTorrentInfo cs infohash | ||
70 | | otherwise = return Nothing | ||
71 | |||
72 | {----------------------------------------------------------------------- | ||
73 | Torrent management | ||
74 | -----------------------------------------------------------------------} | ||
75 | |||
76 | -- | Register torrent and start downloading. | ||
77 | addTorrent :: ClientSession -> TorrentLoc -> IO () | ||
78 | addTorrent cs loc @ TorrentLoc {..} = do | ||
79 | registerTorrent cs loc | ||
80 | openSwarmSession cs loc | ||
81 | return () | ||
82 | |||
83 | -- | Unregister torrent and stop all running sessions. | ||
84 | removeTorrent :: ClientSession -> InfoHash -> IO () | ||
85 | removeTorrent = unregisterTorrent | ||
86 | |||
87 | {- | ||
88 | -- | The same as 'removeTorrrent' torrent, but delete all torrent | ||
89 | -- content files. | ||
90 | deleteTorrent :: ClientSession -> TorrentLoc -> IO () | ||
91 | deleteTorrent ClientSession {..} TorrentLoc {..} = undefined | ||
92 | -} | ||
93 | |||
94 | {----------------------------------------------------------------------- | ||
95 | Torrent group management | ||
96 | -----------------------------------------------------------------------} | ||
97 | -- TODO better name | ||
98 | |||
99 | data ClientLoc = ClientLoc | ||
100 | { tdir :: FilePath -- ^ Path to directory with .torrent files. | ||
101 | , ddir :: FilePath -- ^ Path to directory to place content. | ||
102 | } deriving (Show, Eq) | ||
103 | |||
104 | ppClientLoc :: ClientLoc -> Doc | ||
105 | ppClientLoc ClientLoc {..} = | ||
106 | text "torrent directory" <+> text tdir $$ | ||
107 | text "data directory" <+> text ddir | ||
108 | |||
109 | concretePath :: ClientLoc -> FilePath -> FilePath | ||
110 | concretePath ClientLoc {..} relPath = tdir </> relPath | ||
111 | |||
112 | concreteLoc :: ClientLoc -> FilePath -> TorrentLoc | ||
113 | concreteLoc loc @ ClientLoc {..} relPath | ||
114 | = TorrentLoc (concretePath loc relPath) ddir | ||
115 | |||
116 | addTorrents :: ClientSession -> ClientLoc -> IO () | ||
117 | addTorrents ses loc @ ClientLoc {..} = do | ||
118 | paths <- L.filter isTorrentPath <$> getDirectoryContents tdir | ||
119 | forM_ paths $ handle handler . addTorrent ses . concreteLoc loc | ||
120 | where | ||
121 | handler :: SomeException -> IO () | ||
122 | handler = print | ||
123 | |||
124 | removeTorrents :: ClientSession -> IO () | ||
125 | removeTorrents cs = do | ||
126 | tm <- getRegistered cs | ||
127 | forM_ (keys tm) (removeTorrent cs) | ||
128 | |||
129 | {- | ||
130 | deleteTorrents :: ClientSession -> IO () | ||
131 | deleteTorrents = undefined | ||
132 | -} \ No newline at end of file | ||