2011-07-01 21:15:46 +00:00
|
|
|
{- git-annex command
|
|
|
|
-
|
2015-01-21 16:50:09 +00:00
|
|
|
- Copyright 2011-2014 Joey Hess <id@joeyh.name>
|
2011-07-01 21:15:46 +00:00
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
|
|
|
module Command.AddUrl where
|
|
|
|
|
|
|
|
import Network.URI
|
|
|
|
|
|
|
|
import Command
|
2012-06-05 23:51:03 +00:00
|
|
|
import Backend
|
2011-07-01 22:46:07 +00:00
|
|
|
import qualified Annex
|
2013-09-28 18:35:21 +00:00
|
|
|
import qualified Annex.Url as Url
|
2011-08-06 18:57:22 +00:00
|
|
|
import qualified Backend.URL
|
2014-12-08 23:14:24 +00:00
|
|
|
import qualified Remote
|
|
|
|
import qualified Types.Remote as Remote
|
2015-12-22 17:23:33 +00:00
|
|
|
import qualified Command.Add
|
2011-10-04 04:40:47 +00:00
|
|
|
import Annex.Content
|
2015-12-22 17:23:33 +00:00
|
|
|
import Annex.Ingest
|
2016-09-21 21:21:48 +00:00
|
|
|
import Annex.CheckIgnore
|
2014-12-17 17:57:52 +00:00
|
|
|
import Annex.UUID
|
2011-10-15 20:36:56 +00:00
|
|
|
import Logs.Web
|
2012-06-20 20:07:14 +00:00
|
|
|
import Types.KeySource
|
2014-12-11 19:32:42 +00:00
|
|
|
import Types.UrlContents
|
2015-12-02 19:12:33 +00:00
|
|
|
import Annex.FileMatcher
|
2013-04-11 17:35:52 +00:00
|
|
|
import Logs.Location
|
2014-12-08 23:14:24 +00:00
|
|
|
import Utility.Metered
|
2016-12-24 18:46:31 +00:00
|
|
|
import Utility.FileSystemEncoding
|
2014-03-22 14:42:38 +00:00
|
|
|
import qualified Annex.Transfer as Transfer
|
2013-08-22 22:25:21 +00:00
|
|
|
import Annex.Quvi
|
|
|
|
import qualified Utility.Quvi as Quvi
|
2011-07-01 21:15:46 +00:00
|
|
|
|
2015-07-08 16:33:27 +00:00
|
|
|
cmd :: Command
|
2016-09-09 19:06:54 +00:00
|
|
|
cmd = notBareRepo $ withGlobalOptions [jobsOption, jsonOption, jsonProgressOption] $
|
2015-07-08 19:08:02 +00:00
|
|
|
command "addurl" SectionCommon "add urls to annex"
|
2015-07-13 14:57:49 +00:00
|
|
|
(paramRepeating paramUrl) (seek <$$> optParser)
|
2012-02-08 19:35:18 +00:00
|
|
|
|
2015-07-13 14:57:49 +00:00
|
|
|
data AddUrlOptions = AddUrlOptions
|
|
|
|
{ addUrls :: CmdParams
|
|
|
|
, fileOption :: Maybe FilePath
|
|
|
|
, pathdepthOption :: Maybe Int
|
2015-07-21 16:50:05 +00:00
|
|
|
, prefixOption :: Maybe String
|
|
|
|
, suffixOption :: Maybe String
|
2015-07-13 14:57:49 +00:00
|
|
|
, relaxedOption :: Bool
|
|
|
|
, rawOption :: Bool
|
2015-12-21 16:57:13 +00:00
|
|
|
, batchOption :: BatchMode
|
2015-12-22 16:20:39 +00:00
|
|
|
, batchFilesOption :: Bool
|
2015-07-13 14:57:49 +00:00
|
|
|
}
|
2011-07-01 21:15:46 +00:00
|
|
|
|
2015-07-13 14:57:49 +00:00
|
|
|
optParser :: CmdParamsDesc -> Parser AddUrlOptions
|
|
|
|
optParser desc = AddUrlOptions
|
|
|
|
<$> cmdParams desc
|
|
|
|
<*> optional (strOption
|
|
|
|
( long "file" <> metavar paramFile
|
|
|
|
<> help "specify what file the url is added to"
|
|
|
|
))
|
|
|
|
<*> optional (option auto
|
|
|
|
( long "pathdepth" <> metavar paramNumber
|
2015-07-21 16:50:05 +00:00
|
|
|
<> help "number of url path components to use in filename"
|
|
|
|
))
|
|
|
|
<*> optional (strOption
|
|
|
|
( long "prefix" <> metavar paramValue
|
|
|
|
<> help "add a prefix to the filename"
|
|
|
|
))
|
|
|
|
<*> optional (strOption
|
|
|
|
( long "suffix" <> metavar paramValue
|
|
|
|
<> help "add a suffix to the filename"
|
2015-07-13 14:57:49 +00:00
|
|
|
))
|
2015-07-13 15:06:41 +00:00
|
|
|
<*> parseRelaxedOption
|
|
|
|
<*> parseRawOption
|
2015-12-21 16:57:13 +00:00
|
|
|
<*> parseBatchOption
|
2015-12-22 16:20:39 +00:00
|
|
|
<*> switch
|
|
|
|
( long "with-files"
|
|
|
|
<> help "parse batch mode lines of the form \"$url $file\""
|
|
|
|
)
|
2015-07-13 15:06:41 +00:00
|
|
|
|
|
|
|
parseRelaxedOption :: Parser Bool
|
|
|
|
parseRelaxedOption = switch
|
|
|
|
( long "relaxed"
|
|
|
|
<> help "skip size check"
|
|
|
|
)
|
|
|
|
|
|
|
|
parseRawOption :: Parser Bool
|
|
|
|
parseRawOption = switch
|
|
|
|
( long "raw"
|
|
|
|
<> help "disable special handling for torrents, quvi, etc"
|
|
|
|
)
|
2012-02-16 16:25:19 +00:00
|
|
|
|
2015-07-13 14:57:49 +00:00
|
|
|
seek :: AddUrlOptions -> CommandSeek
|
2015-12-21 16:57:13 +00:00
|
|
|
seek o = allowConcurrentOutput $ do
|
2015-12-22 16:20:39 +00:00
|
|
|
forM_ (addUrls o) (\u -> go (o, u))
|
2015-12-21 16:57:13 +00:00
|
|
|
case batchOption o of
|
2015-12-22 16:20:39 +00:00
|
|
|
Batch -> batchInput (parseBatchInput o) go
|
2015-12-21 16:57:13 +00:00
|
|
|
NoBatch -> noop
|
|
|
|
where
|
2015-12-22 16:20:39 +00:00
|
|
|
go (o', u) = do
|
2015-11-05 22:24:15 +00:00
|
|
|
r <- Remote.claimingUrl u
|
2015-12-22 16:20:39 +00:00
|
|
|
if Remote.uuid r == webUUID || rawOption o'
|
|
|
|
then void $ commandAction $ startWeb o' u
|
|
|
|
else checkUrl r o' u
|
|
|
|
|
|
|
|
parseBatchInput :: AddUrlOptions -> String -> Either String (AddUrlOptions, URLString)
|
|
|
|
parseBatchInput o s
|
|
|
|
| batchFilesOption o =
|
|
|
|
let (u, f) = separate (== ' ') s
|
|
|
|
in if null u || null f
|
|
|
|
then Left ("parsed empty url or filename in input: " ++ s)
|
|
|
|
else Right (o { fileOption = Just f }, u)
|
|
|
|
| otherwise = Right (o, s)
|
2015-03-31 19:20:29 +00:00
|
|
|
|
2015-07-21 16:50:05 +00:00
|
|
|
checkUrl :: Remote -> AddUrlOptions -> URLString -> Annex ()
|
|
|
|
checkUrl r o u = do
|
2015-03-31 19:20:29 +00:00
|
|
|
pathmax <- liftIO $ fileNameLengthLimit "."
|
2015-07-21 16:50:05 +00:00
|
|
|
let deffile = fromMaybe (urlString2file u (pathdepthOption o) pathmax) (fileOption o)
|
2015-03-31 19:20:29 +00:00
|
|
|
go deffile =<< maybe
|
|
|
|
(error $ "unable to checkUrl of " ++ Remote.name r)
|
|
|
|
(tryNonAsync . flip id u)
|
|
|
|
(Remote.checkUrl r)
|
|
|
|
where
|
|
|
|
|
|
|
|
go _ (Left e) = void $ commandAction $ do
|
|
|
|
showStart "addurl" u
|
|
|
|
warning (show e)
|
|
|
|
next $ next $ return False
|
|
|
|
go deffile (Right (UrlContents sz mf)) = do
|
2015-07-21 16:50:05 +00:00
|
|
|
let f = adjustFile o (fromMaybe (maybe deffile fromSafeFilePath mf) (fileOption o))
|
2015-03-31 19:20:29 +00:00
|
|
|
void $ commandAction $
|
2015-07-21 16:50:05 +00:00
|
|
|
startRemote r (relaxedOption o) f u sz
|
2015-03-31 19:20:29 +00:00
|
|
|
go deffile (Right (UrlMulti l))
|
2015-07-21 16:50:05 +00:00
|
|
|
| isNothing (fileOption o) =
|
|
|
|
forM_ l $ \(u', sz, f) -> do
|
|
|
|
let f' = adjustFile o (deffile </> fromSafeFilePath f)
|
2015-03-31 19:20:29 +00:00
|
|
|
void $ commandAction $
|
2015-07-21 16:50:05 +00:00
|
|
|
startRemote r (relaxedOption o) f' u' sz
|
2016-11-16 01:29:54 +00:00
|
|
|
| otherwise = giveup $ unwords
|
2015-03-31 19:20:29 +00:00
|
|
|
[ "That url contains multiple files according to the"
|
|
|
|
, Remote.name r
|
|
|
|
, " remote; cannot add it to a single file."
|
|
|
|
]
|
2014-12-08 23:14:24 +00:00
|
|
|
|
2014-12-11 20:43:46 +00:00
|
|
|
startRemote :: Remote -> Bool -> FilePath -> URLString -> Maybe Integer -> CommandStart
|
|
|
|
startRemote r relaxed file uri sz = do
|
2014-12-12 00:10:45 +00:00
|
|
|
pathmax <- liftIO $ fileNameLengthLimit "."
|
2014-12-12 00:13:57 +00:00
|
|
|
let file' = joinPath $ map (truncateFilePath pathmax) $ splitDirectories file
|
2014-12-12 00:10:45 +00:00
|
|
|
showStart "addurl" file'
|
2014-12-11 22:22:40 +00:00
|
|
|
showNote $ "from " ++ Remote.name r
|
2014-12-12 00:10:45 +00:00
|
|
|
next $ performRemote r relaxed uri file' sz
|
2014-12-08 23:14:24 +00:00
|
|
|
|
2014-12-11 19:32:42 +00:00
|
|
|
performRemote :: Remote -> Bool -> URLString -> FilePath -> Maybe Integer -> CommandPerform
|
|
|
|
performRemote r relaxed uri file sz = ifAnnexed file adduri geturi
|
2014-12-08 23:14:24 +00:00
|
|
|
where
|
|
|
|
loguri = setDownloader uri OtherDownloader
|
|
|
|
adduri = addUrlChecked relaxed loguri (Remote.uuid r) checkexistssize
|
2014-12-11 19:32:42 +00:00
|
|
|
checkexistssize key = return $ case sz of
|
|
|
|
Nothing -> (True, True)
|
|
|
|
Just n -> (True, n == fromMaybe n (keySize key))
|
2014-12-11 20:43:46 +00:00
|
|
|
geturi = next $ isJust <$> downloadRemoteFile r relaxed uri file sz
|
|
|
|
|
|
|
|
downloadRemoteFile :: Remote -> Bool -> URLString -> FilePath -> Maybe Integer -> Annex (Maybe Key)
|
2016-09-21 21:21:48 +00:00
|
|
|
downloadRemoteFile r relaxed uri file sz = checkCanAdd file $ do
|
2015-05-23 02:41:36 +00:00
|
|
|
let urlkey = Backend.URL.fromUrl uri sz
|
2015-01-09 17:11:56 +00:00
|
|
|
liftIO $ createDirectoryIfMissing True (parentDir file)
|
2014-12-11 20:43:46 +00:00
|
|
|
ifM (Annex.getState Annex.fast <||> pure relaxed)
|
|
|
|
( do
|
|
|
|
cleanup (Remote.uuid r) loguri file urlkey Nothing
|
|
|
|
return (Just urlkey)
|
|
|
|
, do
|
|
|
|
-- Set temporary url for the urlkey
|
|
|
|
-- so that the remote knows what url it
|
|
|
|
-- should use to download it.
|
2014-12-17 18:34:42 +00:00
|
|
|
setTempUrl urlkey loguri
|
2017-03-10 17:12:24 +00:00
|
|
|
let downloader = \dest p -> fst
|
|
|
|
<$> Remote.retrieveKeyFile r urlkey
|
|
|
|
(AssociatedFile (Just file)) dest p
|
2014-12-11 20:43:46 +00:00
|
|
|
ret <- downloadWith downloader urlkey (Remote.uuid r) loguri file
|
|
|
|
removeTempUrl urlkey
|
|
|
|
return ret
|
|
|
|
)
|
|
|
|
where
|
|
|
|
loguri = setDownloader uri OtherDownloader
|
2014-12-08 23:14:24 +00:00
|
|
|
|
2015-07-21 16:50:05 +00:00
|
|
|
startWeb :: AddUrlOptions -> String -> CommandStart
|
|
|
|
startWeb o s = go $ fromMaybe bad $ parseURI urlstring
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
2015-01-22 18:52:52 +00:00
|
|
|
(urlstring, downloader) = getDownloader s
|
2016-11-16 01:29:54 +00:00
|
|
|
bad = fromMaybe (giveup $ "bad url " ++ urlstring) $
|
2015-06-14 17:39:44 +00:00
|
|
|
Url.parseURIRelaxed $ urlstring
|
2013-08-23 03:44:13 +00:00
|
|
|
go url = case downloader of
|
|
|
|
QuviDownloader -> usequvi
|
2016-01-26 12:14:57 +00:00
|
|
|
_ -> ifM (quviSupported urlstring)
|
|
|
|
( usequvi
|
|
|
|
, regulardownload url
|
|
|
|
)
|
2013-09-09 06:16:22 +00:00
|
|
|
regulardownload url = do
|
|
|
|
pathmax <- liftIO $ fileNameLengthLimit "."
|
2015-07-21 16:50:05 +00:00
|
|
|
urlinfo <- if relaxedOption o
|
2015-08-19 16:24:55 +00:00
|
|
|
then pure Url.assumeUrlExists
|
2015-01-22 18:52:52 +00:00
|
|
|
else Url.withUrlOptions (Url.getUrlInfo urlstring)
|
2015-07-21 16:50:05 +00:00
|
|
|
file <- adjustFile o <$> case fileOption o of
|
2015-01-22 18:52:52 +00:00
|
|
|
Just f -> pure f
|
|
|
|
Nothing -> case Url.urlSuggestedFile urlinfo of
|
2015-07-21 16:50:05 +00:00
|
|
|
Nothing -> pure $ url2file url (pathdepthOption o) pathmax
|
2015-01-22 18:52:52 +00:00
|
|
|
Just sf -> do
|
|
|
|
let f = truncateFilePath pathmax $
|
|
|
|
sanitizeFilePath sf
|
|
|
|
ifM (liftIO $ doesFileExist f <||> doesDirectoryExist f)
|
2015-07-21 16:50:05 +00:00
|
|
|
( pure $ url2file url (pathdepthOption o) pathmax
|
2015-01-22 18:52:52 +00:00
|
|
|
, pure f
|
|
|
|
)
|
2013-09-09 06:16:22 +00:00
|
|
|
showStart "addurl" file
|
2015-07-21 16:50:05 +00:00
|
|
|
next $ performWeb (relaxedOption o) urlstring file urlinfo
|
2016-11-16 01:29:54 +00:00
|
|
|
badquvi = giveup $ "quvi does not know how to download url " ++ urlstring
|
2013-08-22 22:25:21 +00:00
|
|
|
usequvi = do
|
|
|
|
page <- fromMaybe badquvi
|
2015-01-22 18:52:52 +00:00
|
|
|
<$> withQuviOptions Quvi.forceQuery [Quvi.quiet, Quvi.httponly] urlstring
|
2013-08-22 22:25:21 +00:00
|
|
|
let link = fromMaybe badquvi $ headMaybe $ Quvi.pageLinks page
|
2013-10-05 17:32:42 +00:00
|
|
|
pathmax <- liftIO $ fileNameLengthLimit "."
|
2015-07-21 16:50:05 +00:00
|
|
|
let file = adjustFile o $ flip fromMaybe (fileOption o) $
|
2015-01-22 18:52:52 +00:00
|
|
|
truncateFilePath pathmax $ sanitizeFilePath $
|
2015-05-08 17:39:00 +00:00
|
|
|
Quvi.pageTitle page ++ "." ++ fromMaybe "m" (Quvi.linkSuffix link)
|
2012-11-12 05:05:04 +00:00
|
|
|
showStart "addurl" file
|
2015-07-21 16:50:05 +00:00
|
|
|
next $ performQuvi (relaxedOption o) urlstring (Quvi.linkUrl link) file
|
2013-08-22 22:25:21 +00:00
|
|
|
|
2015-01-22 18:52:52 +00:00
|
|
|
performWeb :: Bool -> URLString -> FilePath -> Url.UrlInfo -> CommandPerform
|
|
|
|
performWeb relaxed url file urlinfo = ifAnnexed file addurl geturl
|
2014-12-11 20:11:38 +00:00
|
|
|
where
|
2015-01-22 18:52:52 +00:00
|
|
|
geturl = next $ isJust <$> addUrlFile relaxed url urlinfo file
|
|
|
|
addurl = addUrlChecked relaxed url webUUID $ \k -> return $
|
|
|
|
(Url.urlExists urlinfo, Url.urlSize urlinfo == keySize k)
|
2014-12-11 20:11:38 +00:00
|
|
|
|
2013-08-22 22:25:21 +00:00
|
|
|
performQuvi :: Bool -> URLString -> URLString -> FilePath -> CommandPerform
|
|
|
|
performQuvi relaxed pageurl videourl file = ifAnnexed file addurl geturl
|
|
|
|
where
|
2014-10-09 18:53:13 +00:00
|
|
|
quviurl = setDownloader pageurl QuviDownloader
|
2014-12-08 23:14:24 +00:00
|
|
|
addurl key = next $ do
|
|
|
|
cleanup webUUID quviurl file key Nothing
|
|
|
|
return True
|
import metadata from feeds
When annex.genmetadata is set, metadata from the feed is added to files
that are imported from it.
Reused the same feedtitle and itemtitle, feedauthor, itemauthor, etc names
that are used in --template.
Also added title and author, which are the item title/author if available,
falling back to the feed title/author. These are more likely to be common
metadata fields.
(There is a small bit of dupication here, but once git gets
around to packing the object, it will compress it away.)
The itempubdate field is not included in the metadata as a string; instead
it is used to generate year and month fields, same as is done when adding
files with annex.genmetadata set.
This commit was sponsored by Amitai Schlair, who cooincidentially
is responsible for ikiwiki generating nice feed metadata!
2014-07-03 17:46:09 +00:00
|
|
|
geturl = next $ isJust <$> addUrlFileQuvi relaxed quviurl videourl file
|
2013-12-29 19:52:20 +00:00
|
|
|
|
import metadata from feeds
When annex.genmetadata is set, metadata from the feed is added to files
that are imported from it.
Reused the same feedtitle and itemtitle, feedauthor, itemauthor, etc names
that are used in --template.
Also added title and author, which are the item title/author if available,
falling back to the feed title/author. These are more likely to be common
metadata fields.
(There is a small bit of dupication here, but once git gets
around to packing the object, it will compress it away.)
The itempubdate field is not included in the metadata as a string; instead
it is used to generate year and month fields, same as is done when adding
files with annex.genmetadata set.
This commit was sponsored by Amitai Schlair, who cooincidentially
is responsible for ikiwiki generating nice feed metadata!
2014-07-03 17:46:09 +00:00
|
|
|
addUrlFileQuvi :: Bool -> URLString -> URLString -> FilePath -> Annex (Maybe Key)
|
2016-09-21 21:21:48 +00:00
|
|
|
addUrlFileQuvi relaxed quviurl videourl file = checkCanAdd file $ do
|
2015-05-23 02:41:36 +00:00
|
|
|
let key = Backend.URL.fromUrl quviurl Nothing
|
2013-12-29 19:52:20 +00:00
|
|
|
ifM (pure relaxed <||> Annex.getState Annex.fast)
|
import metadata from feeds
When annex.genmetadata is set, metadata from the feed is added to files
that are imported from it.
Reused the same feedtitle and itemtitle, feedauthor, itemauthor, etc names
that are used in --template.
Also added title and author, which are the item title/author if available,
falling back to the feed title/author. These are more likely to be common
metadata fields.
(There is a small bit of dupication here, but once git gets
around to packing the object, it will compress it away.)
The itempubdate field is not included in the metadata as a string; instead
it is used to generate year and month fields, same as is done when adding
files with annex.genmetadata set.
This commit was sponsored by Amitai Schlair, who cooincidentially
is responsible for ikiwiki generating nice feed metadata!
2014-07-03 17:46:09 +00:00
|
|
|
( do
|
2014-12-08 23:14:24 +00:00
|
|
|
cleanup webUUID quviurl file key Nothing
|
import metadata from feeds
When annex.genmetadata is set, metadata from the feed is added to files
that are imported from it.
Reused the same feedtitle and itemtitle, feedauthor, itemauthor, etc names
that are used in --template.
Also added title and author, which are the item title/author if available,
falling back to the feed title/author. These are more likely to be common
metadata fields.
(There is a small bit of dupication here, but once git gets
around to packing the object, it will compress it away.)
The itempubdate field is not included in the metadata as a string; instead
it is used to generate year and month fields, same as is done when adding
files with annex.genmetadata set.
This commit was sponsored by Amitai Schlair, who cooincidentially
is responsible for ikiwiki generating nice feed metadata!
2014-07-03 17:46:09 +00:00
|
|
|
return (Just key)
|
2013-12-29 19:52:20 +00:00
|
|
|
, do
|
2014-01-04 19:38:59 +00:00
|
|
|
{- Get the size, and use that to check
|
|
|
|
- disk space. However, the size info is not
|
|
|
|
- retained, because the size of a video stream
|
|
|
|
- might change and we want to be able to download
|
|
|
|
- it later. -}
|
2015-01-22 18:52:52 +00:00
|
|
|
urlinfo <- Url.withUrlOptions (Url.getUrlInfo videourl)
|
|
|
|
let sizedkey = addSizeUrlKey urlinfo key
|
2015-10-01 18:13:53 +00:00
|
|
|
checkDiskSpaceToGet sizedkey Nothing $ do
|
2014-02-26 20:52:56 +00:00
|
|
|
tmp <- fromRepo $ gitAnnexTmpObjectLocation key
|
2014-01-04 19:38:59 +00:00
|
|
|
showOutput
|
2017-03-10 17:12:24 +00:00
|
|
|
ok <- Transfer.notifyTransfer Transfer.Download afile $
|
|
|
|
Transfer.download webUUID key afile Transfer.forwardRetry $ \p -> do
|
2015-01-09 17:11:56 +00:00
|
|
|
liftIO $ createDirectoryIfMissing True (parentDir tmp)
|
2015-11-17 01:00:54 +00:00
|
|
|
downloadUrl key p [videourl] tmp
|
2014-01-04 19:38:59 +00:00
|
|
|
if ok
|
import metadata from feeds
When annex.genmetadata is set, metadata from the feed is added to files
that are imported from it.
Reused the same feedtitle and itemtitle, feedauthor, itemauthor, etc names
that are used in --template.
Also added title and author, which are the item title/author if available,
falling back to the feed title/author. These are more likely to be common
metadata fields.
(There is a small bit of dupication here, but once git gets
around to packing the object, it will compress it away.)
The itempubdate field is not included in the metadata as a string; instead
it is used to generate year and month fields, same as is done when adding
files with annex.genmetadata set.
This commit was sponsored by Amitai Schlair, who cooincidentially
is responsible for ikiwiki generating nice feed metadata!
2014-07-03 17:46:09 +00:00
|
|
|
then do
|
2014-12-08 23:14:24 +00:00
|
|
|
cleanup webUUID quviurl file key (Just tmp)
|
import metadata from feeds
When annex.genmetadata is set, metadata from the feed is added to files
that are imported from it.
Reused the same feedtitle and itemtitle, feedauthor, itemauthor, etc names
that are used in --template.
Also added title and author, which are the item title/author if available,
falling back to the feed title/author. These are more likely to be common
metadata fields.
(There is a small bit of dupication here, but once git gets
around to packing the object, it will compress it away.)
The itempubdate field is not included in the metadata as a string; instead
it is used to generate year and month fields, same as is done when adding
files with annex.genmetadata set.
This commit was sponsored by Amitai Schlair, who cooincidentially
is responsible for ikiwiki generating nice feed metadata!
2014-07-03 17:46:09 +00:00
|
|
|
return (Just key)
|
|
|
|
else return Nothing
|
2013-12-29 19:52:20 +00:00
|
|
|
)
|
2017-03-10 17:12:24 +00:00
|
|
|
where
|
|
|
|
afile = AssociatedFile (Just file)
|
2011-10-31 20:46:51 +00:00
|
|
|
|
2014-12-08 23:14:24 +00:00
|
|
|
addUrlChecked :: Bool -> URLString -> UUID -> (Key -> Annex (Bool, Bool)) -> Key -> CommandPerform
|
|
|
|
addUrlChecked relaxed url u checkexistssize key
|
|
|
|
| relaxed = do
|
|
|
|
setUrlPresent u key url
|
|
|
|
next $ return True
|
2014-12-29 18:22:47 +00:00
|
|
|
| otherwise = ifM ((elem url <$> getUrls key) <&&> (elem u <$> loggedLocations key))
|
2014-12-11 19:49:40 +00:00
|
|
|
( next $ return True -- nothing to do
|
2014-12-08 23:14:24 +00:00
|
|
|
, do
|
|
|
|
(exists, samesize) <- checkexistssize key
|
|
|
|
if exists && samesize
|
|
|
|
then do
|
|
|
|
setUrlPresent u key url
|
|
|
|
next $ return True
|
|
|
|
else do
|
|
|
|
warning $ "while adding a new url to an already annexed file, " ++ if exists
|
|
|
|
then "url does not have expected file size (use --relaxed to bypass this check) " ++ url
|
|
|
|
else "failed to verify url exists: " ++ url
|
|
|
|
stop
|
|
|
|
)
|
2011-08-06 18:57:22 +00:00
|
|
|
|
2015-01-22 18:52:52 +00:00
|
|
|
addUrlFile :: Bool -> URLString -> Url.UrlInfo -> FilePath -> Annex (Maybe Key)
|
2016-09-21 21:21:48 +00:00
|
|
|
addUrlFile relaxed url urlinfo file = checkCanAdd file $ do
|
2015-01-09 17:11:56 +00:00
|
|
|
liftIO $ createDirectoryIfMissing True (parentDir file)
|
2013-07-28 19:27:36 +00:00
|
|
|
ifM (Annex.getState Annex.fast <||> pure relaxed)
|
2015-01-27 18:53:06 +00:00
|
|
|
( nodownload url urlinfo file
|
2015-01-22 18:52:52 +00:00
|
|
|
, downloadWeb url urlinfo file
|
2013-07-28 19:27:36 +00:00
|
|
|
)
|
|
|
|
|
2015-01-22 18:52:52 +00:00
|
|
|
downloadWeb :: URLString -> Url.UrlInfo -> FilePath -> Annex (Maybe Key)
|
|
|
|
downloadWeb url urlinfo file = do
|
2015-05-23 02:41:36 +00:00
|
|
|
let dummykey = addSizeUrlKey urlinfo $ Backend.URL.fromUrl url Nothing
|
2015-11-17 01:00:54 +00:00
|
|
|
let downloader f p = do
|
2014-12-08 23:14:24 +00:00
|
|
|
showOutput
|
2015-11-17 01:00:54 +00:00
|
|
|
downloadUrl dummykey p [url] f
|
2014-12-08 23:14:24 +00:00
|
|
|
showAction $ "downloading " ++ url ++ " "
|
|
|
|
downloadWith downloader dummykey webUUID url file
|
|
|
|
|
|
|
|
{- The Key should be a dummy key, based on the URL, which is used
|
|
|
|
- for this download, before we can examine the file and find its real key.
|
|
|
|
- For resuming downloads to work, the dummy key for a given url should be
|
|
|
|
- stable. -}
|
|
|
|
downloadWith :: (FilePath -> MeterUpdate -> Annex Bool) -> Key -> UUID -> URLString -> FilePath -> Annex (Maybe Key)
|
|
|
|
downloadWith downloader dummykey u url file =
|
2015-10-01 18:13:53 +00:00
|
|
|
checkDiskSpaceToGet dummykey Nothing $ do
|
2014-02-26 20:52:56 +00:00
|
|
|
tmp <- fromRepo $ gitAnnexTmpObjectLocation dummykey
|
2014-12-08 23:14:24 +00:00
|
|
|
ifM (runtransfer tmp)
|
2014-01-04 19:08:06 +00:00
|
|
|
( do
|
|
|
|
backend <- chooseBackend file
|
|
|
|
let source = KeySource
|
|
|
|
{ keyFilename = file
|
|
|
|
, contentLocation = tmp
|
|
|
|
, inodeCache = Nothing
|
|
|
|
}
|
|
|
|
k <- genKey source backend
|
|
|
|
case k of
|
import metadata from feeds
When annex.genmetadata is set, metadata from the feed is added to files
that are imported from it.
Reused the same feedtitle and itemtitle, feedauthor, itemauthor, etc names
that are used in --template.
Also added title and author, which are the item title/author if available,
falling back to the feed title/author. These are more likely to be common
metadata fields.
(There is a small bit of dupication here, but once git gets
around to packing the object, it will compress it away.)
The itempubdate field is not included in the metadata as a string; instead
it is used to generate year and month fields, same as is done when adding
files with annex.genmetadata set.
This commit was sponsored by Amitai Schlair, who cooincidentially
is responsible for ikiwiki generating nice feed metadata!
2014-07-03 17:46:09 +00:00
|
|
|
Nothing -> return Nothing
|
|
|
|
Just (key, _) -> do
|
2014-12-08 23:14:24 +00:00
|
|
|
cleanup u url file key (Just tmp)
|
import metadata from feeds
When annex.genmetadata is set, metadata from the feed is added to files
that are imported from it.
Reused the same feedtitle and itemtitle, feedauthor, itemauthor, etc names
that are used in --template.
Also added title and author, which are the item title/author if available,
falling back to the feed title/author. These are more likely to be common
metadata fields.
(There is a small bit of dupication here, but once git gets
around to packing the object, it will compress it away.)
The itempubdate field is not included in the metadata as a string; instead
it is used to generate year and month fields, same as is done when adding
files with annex.genmetadata set.
This commit was sponsored by Amitai Schlair, who cooincidentially
is responsible for ikiwiki generating nice feed metadata!
2014-07-03 17:46:09 +00:00
|
|
|
return (Just key)
|
|
|
|
, return Nothing
|
2014-01-04 19:08:06 +00:00
|
|
|
)
|
2013-04-11 20:14:17 +00:00
|
|
|
where
|
2017-03-10 17:12:24 +00:00
|
|
|
runtransfer tmp = Transfer.notifyTransfer Transfer.Download afile $
|
|
|
|
Transfer.download u dummykey afile Transfer.forwardRetry $ \p -> do
|
2015-01-09 17:11:56 +00:00
|
|
|
liftIO $ createDirectoryIfMissing True (parentDir tmp)
|
2014-12-08 23:14:24 +00:00
|
|
|
downloader tmp p
|
2017-03-10 17:12:24 +00:00
|
|
|
afile = AssociatedFile (Just file)
|
2013-04-11 17:35:52 +00:00
|
|
|
|
2015-01-22 18:52:52 +00:00
|
|
|
{- Adds the url size to the Key. -}
|
|
|
|
addSizeUrlKey :: Url.UrlInfo -> Key -> Key
|
|
|
|
addSizeUrlKey urlinfo key = key { keySize = Url.urlSize urlinfo }
|
2014-01-04 19:38:59 +00:00
|
|
|
|
2014-12-08 23:14:24 +00:00
|
|
|
cleanup :: UUID -> URLString -> FilePath -> Key -> Maybe FilePath -> Annex ()
|
2015-12-02 19:12:33 +00:00
|
|
|
cleanup u url file key mtmp = case mtmp of
|
|
|
|
Nothing -> go
|
|
|
|
Just tmp -> do
|
2016-11-22 15:12:33 +00:00
|
|
|
-- Move to final location for large file check.
|
|
|
|
liftIO $ renameFile tmp file
|
2015-12-02 19:12:33 +00:00
|
|
|
largematcher <- largeFilesMatcher
|
2016-11-22 15:12:33 +00:00
|
|
|
large <- checkFileMatcher largematcher file
|
|
|
|
if large
|
|
|
|
then do
|
|
|
|
-- Move back to tmp because addAnnexedFile
|
|
|
|
-- needs the file in a different location
|
|
|
|
-- than the work tree file.
|
|
|
|
liftIO $ renameFile file tmp
|
|
|
|
go
|
|
|
|
else void $ Command.Add.addSmall file
|
2015-12-02 19:12:33 +00:00
|
|
|
where
|
|
|
|
go = do
|
2016-07-26 23:15:34 +00:00
|
|
|
maybeShowJSON $ JSONChunk [("key", key2file key)]
|
2015-12-02 19:12:33 +00:00
|
|
|
setUrlPresent u key url
|
annex.securehashesonly
Cryptographically secure hashes can be forced to be used in a repository,
by setting annex.securehashesonly. This does not prevent the git repository
from containing files with insecure hashes, but it does prevent the content
of such files from being pulled into .git/annex/objects from another
repository.
We want to make sure that at no point does git-annex accept content into
.git/annex/objects that is hashed with an insecure key. Here's how it
was done:
* .git/annex/objects/xx/yy/KEY/ is kept frozen, so nothing can be
written to it normally
* So every place that writes content must call, thawContent or modifyContent.
We can audit for these, and be sure we've considered all cases.
* The main functions are moveAnnex, and linkToAnnex; these were made to
check annex.securehashesonly, and are the main security boundary
for annex.securehashesonly.
* Most other calls to modifyContent deal with other files in the KEY
directory (inode cache etc). The other ones that mess with the content
are:
- Annex.Direct.toDirectGen, in which content already in the
annex directory is moved to the direct mode file, so not relevant.
- fix and lock, which don't add new content
- Command.ReKey.linkKey, which manually unlocks it to make a
copy.
* All other calls to thawContent appear safe.
Made moveAnnex return a Bool, so checked all callsites and made them
deal with a failure in appropriate ways.
linkToAnnex simply returns LinkAnnexFailed; all callsites already deal
with it failing in appropriate ways.
This commit was sponsored by Riku Voipio.
2017-02-27 17:01:32 +00:00
|
|
|
ifM (addAnnexedFile file key mtmp)
|
|
|
|
( do
|
|
|
|
when (isJust mtmp) $
|
|
|
|
logStatus key InfoPresent
|
|
|
|
, liftIO $ maybe noop nukeFile mtmp
|
|
|
|
)
|
2011-07-01 21:15:46 +00:00
|
|
|
|
2015-01-27 18:53:06 +00:00
|
|
|
nodownload :: URLString -> Url.UrlInfo -> FilePath -> Annex (Maybe Key)
|
|
|
|
nodownload url urlinfo file
|
2015-01-22 18:52:52 +00:00
|
|
|
| Url.urlExists urlinfo = do
|
2015-05-23 02:41:36 +00:00
|
|
|
let key = Backend.URL.fromUrl url (Url.urlSize urlinfo)
|
2015-01-22 18:52:52 +00:00
|
|
|
cleanup webUUID url file key Nothing
|
|
|
|
return (Just key)
|
|
|
|
| otherwise = do
|
|
|
|
warning $ "unable to access url: " ++ url
|
|
|
|
return Nothing
|
2011-08-06 18:57:22 +00:00
|
|
|
|
Fix a few bugs involving filenames that are at or near the filesystem's maximum filename length limit.
Started with a problem when running addurl on a really long url,
because the whole url is munged into the filename. Ended up doing
a fairly extensive review for places where filenames could get too large,
although it's hard to say I'm not missed any..
Backend.Url had a 128 character limit, which is fine when the limit is 255,
but not if it's a lot shorter on some systems. So check the pathconf()
limit. Note that this could result in fromUrl creating different keys
for the same url, if run on systems with different limits. I don't see
this is likely to cause any problems. That can already happen when using
addurl --fast, or if the content of an url changes.
Both Command.AddUrl and Backend.Url assumed that urls don't contain a
lot of multi-byte unicode, and would fail to truncate an url that did
properly.
A few places use a filename as the template to make a temp file.
While that's nice in that the temp file name can be easily related back to
the original filename, it could lead to `git annex add` failing to add a
filename that was at or close to the maximum length.
Note that in Command.Add.lockdown, the template is still derived from the
filename, just with enough space left to turn it into a temp file.
This is an important optimisation, because the assistant may lock down
a bunch of files all at once, and using the same template for all of them
would cause openTempFile to iterate through the same set of names,
looking for an unused temp file. I'm not very happy with the relatedTemplate
hack, but it avoids that slowdown.
Backend.WORM does not limit the filename stored in the key.
I have not tried to change that; so git annex add will fail on really long
filenames when using the WORM backend. It seems better to preserve the
invariant that a WORM key always contains the complete filename, since
the filename is the only unique material in the key, other than mtime and
size. Since nobody has complained about add failing (I think I saw it
once?) on WORM, probably it's ok, or nobody but me uses it.
There may be compatability problems if using git annex addurl --fast
or the WORM backend on a system with the 255 limit and then trying to use
that repo in a system with a smaller limit. I have not tried to deal with
those.
This commit was sponsored by Alexander Brem. Thanks!
2013-07-30 21:49:11 +00:00
|
|
|
url2file :: URI -> Maybe Int -> Int -> FilePath
|
|
|
|
url2file url pathdepth pathmax = case pathdepth of
|
2013-10-05 17:32:42 +00:00
|
|
|
Nothing -> truncateFilePath pathmax $ sanitizeFilePath fullurl
|
2012-02-16 16:25:19 +00:00
|
|
|
Just depth
|
2013-07-05 16:46:38 +00:00
|
|
|
| depth >= length urlbits -> frombits id
|
2012-02-16 18:26:53 +00:00
|
|
|
| depth > 0 -> frombits $ drop depth
|
2012-02-16 18:28:17 +00:00
|
|
|
| depth < 0 -> frombits $ reverse . take (negate depth) . reverse
|
2016-11-16 01:29:54 +00:00
|
|
|
| otherwise -> giveup "bad --pathdepth"
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
2014-12-08 23:14:24 +00:00
|
|
|
fullurl = concat
|
|
|
|
[ maybe "" uriRegName (uriAuthority url)
|
|
|
|
, uriPath url
|
|
|
|
, uriQuery url
|
|
|
|
]
|
2013-04-23 00:24:53 +00:00
|
|
|
frombits a = intercalate "/" $ a urlbits
|
2013-10-05 17:30:13 +00:00
|
|
|
urlbits = map (truncateFilePath pathmax . sanitizeFilePath) $
|
2017-01-31 22:40:42 +00:00
|
|
|
filter (not . null) $ splitc '/' fullurl
|
2014-12-11 20:09:56 +00:00
|
|
|
|
|
|
|
urlString2file :: URLString -> Maybe Int -> Int -> FilePath
|
|
|
|
urlString2file s pathdepth pathmax = case Url.parseURIRelaxed s of
|
2016-11-16 01:29:54 +00:00
|
|
|
Nothing -> giveup $ "bad uri " ++ s
|
2014-12-11 20:09:56 +00:00
|
|
|
Just u -> url2file u pathdepth pathmax
|
2015-07-21 16:50:05 +00:00
|
|
|
|
|
|
|
adjustFile :: AddUrlOptions -> FilePath -> FilePath
|
|
|
|
adjustFile o = addprefix . addsuffix
|
|
|
|
where
|
|
|
|
addprefix f = maybe f (++ f) (prefixOption o)
|
|
|
|
addsuffix f = maybe f (f ++) (suffixOption o)
|
2016-09-21 21:21:48 +00:00
|
|
|
|
|
|
|
checkCanAdd :: FilePath -> Annex (Maybe a) -> Annex (Maybe a)
|
|
|
|
checkCanAdd file a = ifM (isJust <$> (liftIO $ catchMaybeIO $ getSymbolicLinkStatus file))
|
|
|
|
( do
|
|
|
|
warning $ file ++ " already exists and is not annexed; not overwriting"
|
|
|
|
return Nothing
|
|
|
|
, ifM ((not <$> Annex.getState Annex.force) <&&> checkIgnored file)
|
|
|
|
( do
|
|
|
|
warning $ "not adding " ++ file ++ " which is .gitignored (use --force to override)"
|
|
|
|
return Nothing
|
|
|
|
, a
|
|
|
|
)
|
|
|
|
)
|