2014-12-17 03:22:46 +00:00
|
|
|
{- BitTorrent remote.
|
|
|
|
-
|
2015-01-21 16:50:09 +00:00
|
|
|
- Copyright 2014 Joey Hess <id@joeyh.name>
|
2014-12-17 03:22:46 +00:00
|
|
|
-
|
2019-03-13 19:48:14 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2014-12-17 03:22:46 +00:00
|
|
|
-}
|
|
|
|
|
2020-10-29 18:20:57 +00:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2014-12-18 18:22:43 +00:00
|
|
|
{-# LANGUAGE CPP #-}
|
|
|
|
|
2014-12-17 03:22:46 +00:00
|
|
|
module Remote.BitTorrent (remote) where
|
|
|
|
|
2016-01-20 20:36:33 +00:00
|
|
|
import Annex.Common
|
2014-12-17 03:22:46 +00:00
|
|
|
import Types.Remote
|
|
|
|
import qualified Annex
|
|
|
|
import qualified Git
|
|
|
|
import qualified Git.Construct
|
2018-06-23 22:16:37 +00:00
|
|
|
import Config
|
2014-12-17 03:22:46 +00:00
|
|
|
import Config.Cost
|
|
|
|
import Logs.Web
|
|
|
|
import Types.UrlContents
|
|
|
|
import Types.CleanupActions
|
2015-04-03 20:48:30 +00:00
|
|
|
import Messages.Progress
|
2014-12-17 03:22:46 +00:00
|
|
|
import Utility.Metered
|
|
|
|
import Utility.Tmp
|
2023-08-14 16:28:10 +00:00
|
|
|
import Utility.Url.Parse
|
2014-12-17 03:22:46 +00:00
|
|
|
import Backend.URL
|
|
|
|
import Annex.Perms
|
2019-01-17 19:40:44 +00:00
|
|
|
import Annex.Tmp
|
2014-12-17 17:57:52 +00:00
|
|
|
import Annex.UUID
|
2014-12-17 03:22:46 +00:00
|
|
|
import qualified Annex.Url as Url
|
2019-02-20 19:55:01 +00:00
|
|
|
import Remote.Helper.ExportImport
|
fix encryption of content to gcrypt and git-lfs
Fix serious regression in gcrypt and encrypted git-lfs remotes.
Since version 7.20200202.7, git-annex incorrectly stored content
on those remotes without encrypting it.
Problem was, Remote.Git enumerates all git remotes, including git-lfs
and gcrypt. It then dispatches to those. So, Remote.List used the
RemoteConfigParser from Remote.Git, instead of from git-lfs or gcrypt,
and that parser does not know about encryption fields, so did not
include them in the ParsedRemoteConfig. (Also didn't include other
fields specific to those remotes, perhaps chunking etc also didn't
get through.)
To fix, had to move RemoteConfig parsing down into the generate methods
of each remote, rather than doing it in Remote.List.
And a consequence of that was that ParsedRemoteConfig had to change to
include the RemoteConfig that got parsed, so that testremote can
generate a new remote based on an existing remote.
(I would have rather fixed this just inside Remote.Git, but that was not
practical, at least not w/o re-doing work that Remote.List already did.
Big ugly mostly mechanical patch seemed preferable to making git-annex
slower.)
2020-02-26 21:20:56 +00:00
|
|
|
import Annex.SpecialRemote.Config
|
2020-10-29 18:20:57 +00:00
|
|
|
import qualified Utility.RawFilePath as R
|
2014-12-17 03:22:46 +00:00
|
|
|
|
|
|
|
import Network.URI
|
2020-10-29 18:20:57 +00:00
|
|
|
import qualified System.FilePath.ByteString as P
|
2014-12-17 03:22:46 +00:00
|
|
|
|
2014-12-18 18:22:43 +00:00
|
|
|
#ifdef WITH_TORRENTPARSER
|
|
|
|
import Data.Torrent
|
|
|
|
import qualified Data.ByteString.Lazy as B
|
|
|
|
#endif
|
|
|
|
|
2014-12-17 03:22:46 +00:00
|
|
|
remote :: RemoteType
|
2017-09-07 17:45:31 +00:00
|
|
|
remote = RemoteType
|
|
|
|
{ typename = "bittorrent"
|
|
|
|
, enumerate = list
|
|
|
|
, generate = gen
|
2020-01-14 19:41:34 +00:00
|
|
|
, configParser = mkRemoteConfigParser []
|
2023-04-10 17:38:14 +00:00
|
|
|
, setup = giveup "not supported"
|
2017-09-07 17:45:31 +00:00
|
|
|
, exportSupported = exportUnsupported
|
2019-02-20 19:55:01 +00:00
|
|
|
, importSupported = importUnsupported
|
add thirdPartyPopulated interface
This is to support, eg a borg repo as a special remote, which is
populated not by running git-annex commands, but by using borg. Then
git-annex sync lists the content of the remote, learns which files are
annex objects, and treats those as present in the remote.
So, most of the import machinery is reused, to a new purpose. While
normally importtree maintains a remote tracking branch, this does not,
because the files stored in the remote are annex object files, not
user-visible filenames. But, internally, a git tree is still generated,
of the files on the remote that are annex objects. This tree is used
by retrieveExportWithContentIdentifier, etc. As with other import/export
remotes, that the tree is recorded in the export log, and gets grafted
into the git-annex branch.
importKey changed to be able to return Nothing, to indicate when an
ImportLocation is not an annex object and so should be skipped from
being included in the tree.
It did not seem to make sense to have git-annex import do this, since
from the user's perspective, it's not like other imports. So only
git-annex sync does it.
Note that, git-annex sync does not yet download objects from such
remotes that are preferred content. importKeys is run with
content downloading disabled, to avoid getting the content of all
objects. Perhaps what's needed is for seekSyncContent to be run with these
remotes, but I don't know if it will just work (in particular, it needs
to avoid trying to transfer objects to them), so I skipped that for now.
(Untested and unused as of yet.)
This commit was sponsored by Jochen Bartl on Patreon.
2020-12-18 18:52:57 +00:00
|
|
|
, thirdPartyPopulated = False
|
2017-09-07 17:45:31 +00:00
|
|
|
}
|
2014-12-17 03:22:46 +00:00
|
|
|
|
|
|
|
-- There is only one bittorrent remote, and it always exists.
|
2015-08-05 17:49:54 +00:00
|
|
|
list :: Bool -> Annex [Git.Repo]
|
|
|
|
list _autoinit = do
|
2015-02-12 19:33:05 +00:00
|
|
|
r <- liftIO $ Git.Construct.remoteNamed "bittorrent" (pure Git.Construct.fromUnknown)
|
2014-12-17 03:22:46 +00:00
|
|
|
return [r]
|
|
|
|
|
fix encryption of content to gcrypt and git-lfs
Fix serious regression in gcrypt and encrypted git-lfs remotes.
Since version 7.20200202.7, git-annex incorrectly stored content
on those remotes without encrypting it.
Problem was, Remote.Git enumerates all git remotes, including git-lfs
and gcrypt. It then dispatches to those. So, Remote.List used the
RemoteConfigParser from Remote.Git, instead of from git-lfs or gcrypt,
and that parser does not know about encryption fields, so did not
include them in the ParsedRemoteConfig. (Also didn't include other
fields specific to those remotes, perhaps chunking etc also didn't
get through.)
To fix, had to move RemoteConfig parsing down into the generate methods
of each remote, rather than doing it in Remote.List.
And a consequence of that was that ParsedRemoteConfig had to change to
include the RemoteConfig that got parsed, so that testremote can
generate a new remote based on an existing remote.
(I would have rather fixed this just inside Remote.Git, but that was not
practical, at least not w/o re-doing work that Remote.List already did.
Big ugly mostly mechanical patch seemed preferable to making git-annex
slower.)
2020-02-26 21:20:56 +00:00
|
|
|
gen :: Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> RemoteStateHandle -> Annex (Maybe Remote)
|
|
|
|
gen r _ rc gc rs = do
|
|
|
|
c <- parsedRemoteConfig remote rc
|
2023-01-12 17:42:28 +00:00
|
|
|
cst <- remoteCost gc c expensiveRemoteCost
|
2014-12-17 03:22:46 +00:00
|
|
|
return $ Just Remote
|
|
|
|
{ uuid = bitTorrentUUID
|
2018-06-23 22:16:37 +00:00
|
|
|
, cost = cst
|
2014-12-17 03:22:46 +00:00
|
|
|
, name = Git.repoDescribe r
|
|
|
|
, storeKey = uploadKey
|
|
|
|
, retrieveKeyFile = downloadKey
|
2020-05-13 21:05:56 +00:00
|
|
|
, retrieveKeyFileCheap = Nothing
|
2018-06-21 15:35:27 +00:00
|
|
|
-- Bittorrent does its own hash checks.
|
|
|
|
, retrievalSecurityPolicy = RetrievalAllKeysSecure
|
2014-12-17 03:22:46 +00:00
|
|
|
, removeKey = dropKey
|
2015-10-08 19:01:38 +00:00
|
|
|
, lockContent = Nothing
|
2014-12-17 03:22:46 +00:00
|
|
|
, checkPresent = checkKey
|
|
|
|
, checkPresentCheap = False
|
2017-09-01 17:02:07 +00:00
|
|
|
, exportActions = exportUnsupported
|
2019-02-20 19:55:01 +00:00
|
|
|
, importActions = importUnsupported
|
2014-12-17 03:22:46 +00:00
|
|
|
, whereisKey = Nothing
|
|
|
|
, remoteFsck = Nothing
|
|
|
|
, repairRepo = Nothing
|
|
|
|
, config = c
|
|
|
|
, gitconfig = gc
|
|
|
|
, localpath = Nothing
|
2018-06-04 18:31:55 +00:00
|
|
|
, getRepo = return r
|
2014-12-17 03:22:46 +00:00
|
|
|
, readonly = True
|
2018-08-30 15:12:18 +00:00
|
|
|
, appendonly = False
|
2020-12-28 19:08:53 +00:00
|
|
|
, untrustworthy = False
|
2014-12-17 03:22:46 +00:00
|
|
|
, availability = GloballyAvailable
|
|
|
|
, remotetype = remote
|
|
|
|
, mkUnavailable = return Nothing
|
|
|
|
, getInfo = return []
|
|
|
|
, claimUrl = Just (pure . isSupportedUrl)
|
|
|
|
, checkUrl = Just checkTorrentUrl
|
add RemoteStateHandle
This solves the problem of sameas remotes trampling over per-remote
state. Used for:
* per-remote state, of course
* per-remote metadata, also of course
* per-remote content identifiers, because two remote implementations
could in theory generate the same content identifier for two different
peices of content
While chunk logs are per-remote data, they don't use this, because the
number and size of chunks stored is a common property across sameas
remotes.
External special remote had a complication, where it was theoretically
possible for a remote to send SETSTATE or GETSTATE during INITREMOTE or
EXPORTSUPPORTED. Since the uuid of the remote is typically generate in
Remote.setup, it would only be possible to pass a Maybe
RemoteStateHandle into it, and it would otherwise have to construct its
own. Rather than go that route, I decided to send an ERROR in this case.
It seems unlikely that any existing external special remote will be
affected. They would have to make up a git-annex key, and set state for
some reason during INITREMOTE. I can imagine such a hack, but it doesn't
seem worth complicating the code in such an ugly way to support it.
Unfortunately, both TestRemote and Annex.Import needed the Remote
to have a new field added that holds its RemoteStateHandle.
2019-10-14 16:33:27 +00:00
|
|
|
, remoteStateHandle = rs
|
2014-12-17 03:22:46 +00:00
|
|
|
}
|
|
|
|
|
2021-08-17 16:41:36 +00:00
|
|
|
downloadKey :: Key -> AssociatedFile -> FilePath -> MeterUpdate -> VerifyConfig -> Annex Verification
|
|
|
|
downloadKey key _file dest p _ = do
|
2014-12-17 03:22:46 +00:00
|
|
|
get . map (torrentUrlNum . fst . getDownloader) =<< getBitTorrentUrls key
|
2021-02-09 17:42:16 +00:00
|
|
|
-- While bittorrent verifies the hash in the torrent file,
|
|
|
|
-- the torrent file itself is downloaded without verification,
|
|
|
|
-- so the overall download is not verified.
|
2020-05-13 21:05:56 +00:00
|
|
|
return UnVerified
|
2014-12-17 03:22:46 +00:00
|
|
|
where
|
2020-05-13 21:05:56 +00:00
|
|
|
get [] = giveup "could not download torrent"
|
2014-12-17 03:22:46 +00:00
|
|
|
get urls = do
|
|
|
|
showOutput -- make way for download progress bar
|
2020-05-13 21:05:56 +00:00
|
|
|
ok <- untilTrue urls $ \(u, filenum) -> do
|
2014-12-17 03:22:46 +00:00
|
|
|
registerTorrentCleanup u
|
|
|
|
checkDependencies
|
2014-12-17 18:38:04 +00:00
|
|
|
ifM (downloadTorrentFile u)
|
|
|
|
( downloadTorrentContent key u dest filenum p
|
|
|
|
, return False
|
|
|
|
)
|
2020-05-13 21:05:56 +00:00
|
|
|
unless ok $
|
|
|
|
get []
|
2014-12-17 03:22:46 +00:00
|
|
|
|
2020-05-13 18:03:00 +00:00
|
|
|
uploadKey :: Key -> AssociatedFile -> MeterUpdate -> Annex ()
|
|
|
|
uploadKey _ _ _ = giveup "upload to bittorrent not supported"
|
2014-12-17 03:22:46 +00:00
|
|
|
|
2020-05-14 18:08:09 +00:00
|
|
|
dropKey :: Key -> Annex ()
|
|
|
|
dropKey k = mapM_ (setUrlMissing k) =<< getBitTorrentUrls k
|
2014-12-17 03:22:46 +00:00
|
|
|
|
2014-12-17 18:54:54 +00:00
|
|
|
{- We punt and don't try to check if a torrent has enough seeders
|
|
|
|
- with all the pieces etc. That would be quite hard.. and even if
|
|
|
|
- implemented, it tells us nothing about the later state of the torrent.
|
2014-12-17 03:22:46 +00:00
|
|
|
-}
|
|
|
|
checkKey :: Key -> Annex Bool
|
2016-11-16 01:29:54 +00:00
|
|
|
checkKey = giveup "cannot reliably check torrent status"
|
2014-12-17 03:22:46 +00:00
|
|
|
|
|
|
|
getBitTorrentUrls :: Key -> Annex [URLString]
|
|
|
|
getBitTorrentUrls key = filter supported <$> getUrls key
|
|
|
|
where
|
|
|
|
supported u =
|
|
|
|
let (u', dl) = (getDownloader u)
|
|
|
|
in dl == OtherDownloader && isSupportedUrl u'
|
|
|
|
|
|
|
|
isSupportedUrl :: URLString -> Bool
|
|
|
|
isSupportedUrl u = isTorrentMagnetUrl u || isTorrentUrl u
|
|
|
|
|
|
|
|
isTorrentUrl :: URLString -> Bool
|
2023-03-27 17:38:02 +00:00
|
|
|
isTorrentUrl = maybe False (\u -> ".torrent" `isSuffixOf` uriPath u) . parseURIPortable
|
2014-12-17 03:22:46 +00:00
|
|
|
|
|
|
|
isTorrentMagnetUrl :: URLString -> Bool
|
2023-03-27 17:38:02 +00:00
|
|
|
isTorrentMagnetUrl u = "magnet:" `isPrefixOf` u && checkbt (parseURIPortable u)
|
2014-12-17 03:22:46 +00:00
|
|
|
where
|
|
|
|
checkbt (Just uri) | "xt=urn:btih:" `isInfixOf` uriQuery uri = True
|
|
|
|
checkbt _ = False
|
|
|
|
|
|
|
|
checkTorrentUrl :: URLString -> Annex UrlContents
|
|
|
|
checkTorrentUrl u = do
|
|
|
|
checkDependencies
|
|
|
|
registerTorrentCleanup u
|
|
|
|
ifM (downloadTorrentFile u)
|
|
|
|
( torrentContents u
|
2016-11-16 01:29:54 +00:00
|
|
|
, giveup "could not download torrent file"
|
2014-12-17 03:22:46 +00:00
|
|
|
)
|
|
|
|
|
|
|
|
{- To specify which file inside a multi-url torrent, the file number is
|
|
|
|
- appended to the url. -}
|
|
|
|
torrentUrlWithNum :: URLString -> Int -> URLString
|
|
|
|
torrentUrlWithNum u n = u ++ "#" ++ show n
|
|
|
|
|
|
|
|
torrentUrlNum :: URLString -> (URLString, Int)
|
2014-12-17 18:07:05 +00:00
|
|
|
torrentUrlNum u
|
|
|
|
| '#' `elem` u =
|
|
|
|
let (n, ru) = separate (== '#') (reverse u)
|
|
|
|
in (reverse ru, fromMaybe 1 $ readish $ reverse n)
|
|
|
|
| otherwise = (u, 1)
|
2014-12-17 03:22:46 +00:00
|
|
|
|
|
|
|
{- A Key corresponding to the URL of a torrent file. -}
|
|
|
|
torrentUrlKey :: URLString -> Annex Key
|
2015-05-23 02:41:36 +00:00
|
|
|
torrentUrlKey u = return $ fromUrl (fst $ torrentUrlNum u) Nothing
|
2014-12-17 03:22:46 +00:00
|
|
|
|
|
|
|
{- Temporary filename to use to store the torrent file. -}
|
2020-10-29 18:20:57 +00:00
|
|
|
tmpTorrentFile :: URLString -> Annex RawFilePath
|
2014-12-17 03:22:46 +00:00
|
|
|
tmpTorrentFile u = fromRepo . gitAnnexTmpObjectLocation =<< torrentUrlKey u
|
|
|
|
|
2019-01-17 19:40:44 +00:00
|
|
|
{- A cleanup action is registered to delete the torrent file
|
|
|
|
- when git-annex exits.
|
2014-12-17 03:22:46 +00:00
|
|
|
-
|
2019-01-17 19:40:44 +00:00
|
|
|
- This allows multiple actions that use the same torrent file
|
|
|
|
- directory to run in a single git-annex run, and only download the
|
|
|
|
- torrent file once.
|
2014-12-17 03:22:46 +00:00
|
|
|
-}
|
|
|
|
registerTorrentCleanup :: URLString -> Annex ()
|
2020-12-11 19:28:58 +00:00
|
|
|
registerTorrentCleanup u = Annex.addCleanupAction (TorrentCleanup u) $
|
2020-10-29 18:20:57 +00:00
|
|
|
liftIO . removeWhenExistsWith R.removeLink =<< tmpTorrentFile u
|
2014-12-17 03:22:46 +00:00
|
|
|
|
|
|
|
{- Downloads the torrent file. (Not its contents.) -}
|
|
|
|
downloadTorrentFile :: URLString -> Annex Bool
|
|
|
|
downloadTorrentFile u = do
|
|
|
|
torrent <- tmpTorrentFile u
|
2020-10-29 18:20:57 +00:00
|
|
|
ifM (liftIO $ doesFileExist (fromRawFilePath torrent))
|
2014-12-17 03:22:46 +00:00
|
|
|
( return True
|
|
|
|
, do
|
|
|
|
showAction "downloading torrent file"
|
2015-01-09 17:11:56 +00:00
|
|
|
createAnnexDirectory (parentDir torrent)
|
2014-12-17 03:22:46 +00:00
|
|
|
if isTorrentMagnetUrl u
|
2019-01-17 19:40:44 +00:00
|
|
|
then withOtherTmp $ \othertmp -> do
|
2020-10-29 18:20:57 +00:00
|
|
|
kf <- keyFile <$> torrentUrlKey u
|
|
|
|
let metadir = othertmp P.</> "torrentmeta" P.</> kf
|
2014-12-17 03:22:46 +00:00
|
|
|
createAnnexDirectory metadir
|
2018-04-06 21:00:46 +00:00
|
|
|
showOutput
|
2020-10-29 18:20:57 +00:00
|
|
|
ok <- downloadMagnetLink u
|
|
|
|
(fromRawFilePath metadir)
|
|
|
|
(fromRawFilePath torrent)
|
|
|
|
liftIO $ removeDirectoryRecursive
|
|
|
|
(fromRawFilePath metadir)
|
2014-12-17 03:22:46 +00:00
|
|
|
return ok
|
2019-01-17 19:40:44 +00:00
|
|
|
else withOtherTmp $ \othertmp -> do
|
2020-10-29 18:20:57 +00:00
|
|
|
withTmpFileIn (fromRawFilePath othertmp) "torrent" $ \f h -> do
|
2014-12-30 17:07:06 +00:00
|
|
|
liftIO $ hClose h
|
2020-11-06 18:10:58 +00:00
|
|
|
resetAnnexFilePerm (toRawFilePath f)
|
2018-04-04 19:00:51 +00:00
|
|
|
ok <- Url.withUrlOptions $
|
2021-08-18 18:49:01 +00:00
|
|
|
Url.download nullMeterUpdate Nothing u f
|
2014-12-17 03:22:46 +00:00
|
|
|
when ok $
|
2022-12-20 19:17:50 +00:00
|
|
|
liftIO $ moveFile (toRawFilePath f) torrent
|
2014-12-17 03:22:46 +00:00
|
|
|
return ok
|
|
|
|
)
|
|
|
|
|
|
|
|
downloadMagnetLink :: URLString -> FilePath -> FilePath -> Annex Bool
|
|
|
|
downloadMagnetLink u metadir dest = ifM download
|
|
|
|
( liftIO $ do
|
2015-04-14 16:57:01 +00:00
|
|
|
ts <- filter (".torrent" `isSuffixOf`)
|
2014-12-17 03:22:46 +00:00
|
|
|
<$> dirContents metadir
|
|
|
|
case ts of
|
|
|
|
(t:[]) -> do
|
2022-12-20 19:17:50 +00:00
|
|
|
moveFile (toRawFilePath t) (toRawFilePath dest)
|
2014-12-17 03:22:46 +00:00
|
|
|
return True
|
|
|
|
_ -> return False
|
|
|
|
, return False
|
|
|
|
)
|
|
|
|
where
|
|
|
|
download = runAria
|
|
|
|
[ Param "--bt-metadata-only"
|
|
|
|
, Param "--bt-save-metadata"
|
|
|
|
, Param u
|
|
|
|
, Param "--seed-time=0"
|
2014-12-17 17:40:04 +00:00
|
|
|
, Param "--summary-interval=0"
|
2014-12-17 03:22:46 +00:00
|
|
|
, Param "-d"
|
|
|
|
, File metadir
|
|
|
|
]
|
|
|
|
|
2014-12-17 17:40:04 +00:00
|
|
|
downloadTorrentContent :: Key -> URLString -> FilePath -> Int -> MeterUpdate -> Annex Bool
|
|
|
|
downloadTorrentContent k u dest filenum p = do
|
2014-12-17 03:22:46 +00:00
|
|
|
torrent <- tmpTorrentFile u
|
2019-01-17 19:40:44 +00:00
|
|
|
withOtherTmp $ \othertmp -> do
|
2020-10-29 18:20:57 +00:00
|
|
|
kf <- keyFile <$> torrentUrlKey u
|
|
|
|
let downloaddir = othertmp P.</> "torrent" P.</> kf
|
2019-01-17 19:40:44 +00:00
|
|
|
createAnnexDirectory downloaddir
|
|
|
|
f <- wantedfile torrent
|
2020-10-29 18:20:57 +00:00
|
|
|
let dlf = fromRawFilePath downloaddir </> f
|
2019-01-17 19:40:44 +00:00
|
|
|
showOutput
|
2020-10-29 18:20:57 +00:00
|
|
|
ifM (download torrent downloaddir <&&> liftIO (doesFileExist dlf))
|
2019-01-17 19:40:44 +00:00
|
|
|
( do
|
2022-12-20 19:17:50 +00:00
|
|
|
liftIO $ moveFile (toRawFilePath dlf) (toRawFilePath dest)
|
2019-01-17 19:40:44 +00:00
|
|
|
-- The downloaddir is not removed here,
|
|
|
|
-- so if aria downloaded parts of other
|
|
|
|
-- files, and this is called again, it will
|
|
|
|
-- resume where it left off.
|
|
|
|
-- withOtherTmp registers a cleanup action
|
|
|
|
-- that will clean up leftover files when
|
|
|
|
-- git-annex terminates.
|
|
|
|
return True
|
|
|
|
, return False
|
|
|
|
)
|
2014-12-17 03:22:46 +00:00
|
|
|
where
|
2019-11-22 20:24:04 +00:00
|
|
|
download torrent tmpdir = ariaProgress (fromKey keySize k) p
|
2014-12-17 03:22:46 +00:00
|
|
|
[ Param $ "--select-file=" ++ show filenum
|
2020-10-29 18:20:57 +00:00
|
|
|
, File (fromRawFilePath torrent)
|
2014-12-17 03:22:46 +00:00
|
|
|
, Param "-d"
|
2020-10-29 18:20:57 +00:00
|
|
|
, File (fromRawFilePath tmpdir)
|
2014-12-17 03:22:46 +00:00
|
|
|
, Param "--seed-time=0"
|
2014-12-17 17:40:04 +00:00
|
|
|
, Param "--summary-interval=0"
|
|
|
|
, Param "--file-allocation=none"
|
2014-12-17 18:21:48 +00:00
|
|
|
-- Needed so aria will resume partially downloaded files
|
|
|
|
-- in multi-file torrents.
|
|
|
|
, Param "--check-integrity=true"
|
2014-12-17 03:22:46 +00:00
|
|
|
]
|
|
|
|
|
|
|
|
{- aria2c will create part of the directory structure
|
|
|
|
- contained in the torrent. It may download parts of other files
|
|
|
|
- in addition to the one we asked for. So, we need to find
|
|
|
|
- out the filename we want based on the filenum.
|
|
|
|
-}
|
|
|
|
wantedfile torrent = do
|
|
|
|
fs <- liftIO $ map fst <$> torrentFileSizes torrent
|
|
|
|
if length fs >= filenum
|
2014-12-17 18:21:48 +00:00
|
|
|
then return (fs !! (filenum - 1))
|
2016-11-16 01:29:54 +00:00
|
|
|
else giveup "Number of files in torrent seems to have changed."
|
2014-12-17 03:22:46 +00:00
|
|
|
|
|
|
|
checkDependencies :: Annex ()
|
|
|
|
checkDependencies = do
|
2021-02-02 23:01:45 +00:00
|
|
|
missing <- liftIO $ filterM (not <$$> inSearchPath) deps
|
2014-12-17 03:22:46 +00:00
|
|
|
unless (null missing) $
|
2016-11-16 01:29:54 +00:00
|
|
|
giveup $ "need to install additional software in order to download from bittorrent: " ++ unwords missing
|
2014-12-18 18:22:43 +00:00
|
|
|
where
|
|
|
|
deps =
|
|
|
|
[ "aria2c"
|
2018-11-26 14:15:02 +00:00
|
|
|
#ifndef WITH_TORRENTPARSER
|
2014-12-18 18:22:43 +00:00
|
|
|
, "btshowmetainfo"
|
|
|
|
#endif
|
|
|
|
]
|
2014-12-17 03:22:46 +00:00
|
|
|
|
2014-12-17 17:40:04 +00:00
|
|
|
ariaParams :: [CommandParam] -> Annex [CommandParam]
|
|
|
|
ariaParams ps = do
|
2014-12-17 03:22:46 +00:00
|
|
|
opts <- map Param . annexAriaTorrentOptions <$> Annex.getGitConfig
|
2014-12-17 17:40:04 +00:00
|
|
|
return (ps ++ opts)
|
|
|
|
|
|
|
|
runAria :: [CommandParam] -> Annex Bool
|
2015-04-04 18:34:03 +00:00
|
|
|
runAria ps = progressCommand "aria2c" =<< ariaParams ps
|
2014-12-17 17:40:04 +00:00
|
|
|
|
|
|
|
-- Parse aria output to find "(n%)" and update the progress meter
|
2015-04-03 20:48:30 +00:00
|
|
|
-- with it.
|
2014-12-17 17:40:04 +00:00
|
|
|
ariaProgress :: Maybe Integer -> MeterUpdate -> [CommandParam] -> Annex Bool
|
|
|
|
ariaProgress Nothing _ ps = runAria ps
|
2015-04-03 20:48:30 +00:00
|
|
|
ariaProgress (Just sz) meter ps = do
|
2015-04-04 18:34:03 +00:00
|
|
|
oh <- mkOutputHandler
|
2020-09-29 21:53:48 +00:00
|
|
|
liftIO . commandMeter (parseAriaProgress sz) oh Nothing meter "aria2c"
|
2014-12-17 17:40:04 +00:00
|
|
|
=<< ariaParams ps
|
|
|
|
|
|
|
|
parseAriaProgress :: Integer -> ProgressParser
|
2017-01-31 22:40:42 +00:00
|
|
|
parseAriaProgress totalsize = go [] . reverse . splitc '\r'
|
2014-12-17 17:40:04 +00:00
|
|
|
where
|
2020-09-29 21:53:48 +00:00
|
|
|
go remainder [] = (Nothing, Nothing, remainder)
|
2014-12-17 17:40:04 +00:00
|
|
|
go remainder (x:xs) = case readish (findpercent x) of
|
|
|
|
Nothing -> go (x++remainder) xs
|
2020-09-29 21:53:48 +00:00
|
|
|
Just p -> (Just (frompercent p), Nothing, remainder)
|
2014-12-17 17:40:04 +00:00
|
|
|
|
|
|
|
-- "(N%)"
|
|
|
|
findpercent = takeWhile (/= '%') . drop 1 . dropWhile (/= '(')
|
|
|
|
|
|
|
|
frompercent p = toBytesProcessed $ totalsize * p `div` 100
|
2014-12-17 03:22:46 +00:00
|
|
|
|
2014-12-18 18:22:43 +00:00
|
|
|
{- Used only if the haskell torrent library is not available. -}
|
|
|
|
#ifndef WITH_TORRENTPARSER
|
2014-12-17 03:22:46 +00:00
|
|
|
btshowmetainfo :: FilePath -> String -> IO [String]
|
|
|
|
btshowmetainfo torrent field =
|
|
|
|
findfield [] . lines <$> readProcess "btshowmetainfo" [torrent]
|
|
|
|
where
|
|
|
|
findfield c [] = reverse c
|
|
|
|
findfield c (l:ls)
|
|
|
|
| l == fieldkey = multiline c ls
|
|
|
|
| fieldkey `isPrefixOf` l =
|
|
|
|
findfield ((drop (length fieldkey) l):c) ls
|
|
|
|
| otherwise = findfield c ls
|
|
|
|
|
|
|
|
multiline c (l:ls)
|
|
|
|
| " " `isPrefixOf` l = multiline (drop 3 l:c) ls
|
|
|
|
| otherwise = findfield c ls
|
|
|
|
multiline c [] = findfield c []
|
|
|
|
|
|
|
|
fieldkey = field ++ take (14 - length field) (repeat '.') ++ ": "
|
2014-12-18 18:22:43 +00:00
|
|
|
#endif
|
2014-12-17 03:22:46 +00:00
|
|
|
|
|
|
|
{- Examines the torrent file and gets the list of files in it,
|
|
|
|
- and their sizes.
|
|
|
|
-}
|
2020-10-29 18:20:57 +00:00
|
|
|
torrentFileSizes :: RawFilePath -> IO [(FilePath, Integer)]
|
2014-12-17 03:22:46 +00:00
|
|
|
torrentFileSizes torrent = do
|
2014-12-18 18:22:43 +00:00
|
|
|
#ifdef WITH_TORRENTPARSER
|
2019-01-01 18:54:06 +00:00
|
|
|
let mkfile = joinPath . map (scrub . decodeBL)
|
2020-10-29 18:20:57 +00:00
|
|
|
b <- B.readFile (fromRawFilePath torrent)
|
2014-12-18 18:22:43 +00:00
|
|
|
return $ case readTorrent b of
|
2016-11-16 01:29:54 +00:00
|
|
|
Left e -> giveup $ "failed to parse torrent: " ++ e
|
2014-12-18 18:22:43 +00:00
|
|
|
Right t -> case tInfo t of
|
|
|
|
SingleFile { tLength = l, tName = f } ->
|
|
|
|
[ (mkfile [f], l) ]
|
|
|
|
MultiFile { tFiles = fs, tName = dir } ->
|
|
|
|
map (\tf -> (mkfile $ dir:filePath tf, fileLength tf)) fs
|
|
|
|
where
|
|
|
|
#else
|
2014-12-17 03:22:46 +00:00
|
|
|
files <- getfield "files"
|
|
|
|
if null files
|
|
|
|
then do
|
|
|
|
fnl <- getfield "file name"
|
|
|
|
szl <- map readish <$> getfield "file size"
|
|
|
|
case (fnl, szl) of
|
|
|
|
((fn:[]), (Just sz:[])) -> return [(scrub fn, sz)]
|
|
|
|
_ -> parsefailed (show (fnl, szl))
|
|
|
|
else do
|
2014-12-18 18:22:43 +00:00
|
|
|
v <- getfield "directory name"
|
2014-12-17 03:22:46 +00:00
|
|
|
case v of
|
|
|
|
(d:[]) -> return $ map (splitsize d) files
|
|
|
|
_ -> parsefailed (show v)
|
|
|
|
where
|
2020-11-19 17:14:22 +00:00
|
|
|
getfield = btshowmetainfo (fromRawFilePath torrent)
|
2016-11-16 01:29:54 +00:00
|
|
|
parsefailed s = giveup $ "failed to parse btshowmetainfo output for torrent file: " ++ show s
|
2014-12-17 03:22:46 +00:00
|
|
|
|
|
|
|
-- btshowmetainfo outputs a list of "filename (size)"
|
|
|
|
splitsize d l = (scrub (d </> fn), sz)
|
|
|
|
where
|
|
|
|
sz = fromMaybe (parsefailed l) $ readish $
|
|
|
|
reverse $ takeWhile (/= '(') $ dropWhile (== ')') $
|
|
|
|
reverse l
|
|
|
|
fn = reverse $ drop 2 $
|
|
|
|
dropWhile (/= '(') $ dropWhile (== ')') $ reverse l
|
2014-12-18 18:22:43 +00:00
|
|
|
#endif
|
2014-12-17 18:17:19 +00:00
|
|
|
-- a malicious torrent file might try to do directory traversal
|
2014-12-17 03:22:46 +00:00
|
|
|
scrub f = if isAbsolute f || any (== "..") (splitPath f)
|
2016-11-16 01:29:54 +00:00
|
|
|
then giveup "found unsafe filename in torrent!"
|
2014-12-17 03:22:46 +00:00
|
|
|
else f
|
|
|
|
|
|
|
|
torrentContents :: URLString -> Annex UrlContents
|
|
|
|
torrentContents u = convert
|
|
|
|
<$> (liftIO . torrentFileSizes =<< tmpTorrentFile u)
|
|
|
|
where
|
2020-05-11 18:04:56 +00:00
|
|
|
convert [(fn, sz)] = UrlContents (Just sz) (Just fn)
|
2014-12-17 03:22:46 +00:00
|
|
|
convert l = UrlMulti $ map mkmulti (zip l [1..])
|
|
|
|
|
|
|
|
mkmulti ((fn, sz), n) =
|
2020-05-11 18:04:56 +00:00
|
|
|
(torrentUrlWithNum u n, Just sz, joinPath $ drop 1 $ splitPath fn)
|