restore old registerurl location tracking behavior
registerurl: When an url is claimed by a special remote other than the web,
update location tracking for that special remote.
registerurl's behavior was changed in commit
451171b7c1
, apparently accidentially to not
update location tracking except for the web.
This makes registerurl followed by unregisterurl not be a no-op, when the
url happens to be claimed by a remote other than the web. It is a noop when
the url is unclaimed except by the web. I don't like the inconsistency,
and wish that registerurl and unregisterurl never updated location
tracking, which would be more in keeping with them being plumbing.
But there is the fact that it used to behave this way, and also it was
inconsistent that it updated location tracking for the web but not for
other remotes, unlike addurl. And there's an argument that the user might
not know what remote to expect to claim an url, so would be considerably in
the dark when using registerurl. (Although they have to know what content
gets downloaded, since they specify a key..)
Sponsored-By: the NIH-funded NICEMAN (ReproNim TR&D3) project
This commit is contained in:
parent
26a094ac1a
commit
98a3ba0ea5
9 changed files with 59 additions and 17 deletions
|
@ -1,6 +1,6 @@
|
|||
{- git-annex command
|
||||
-
|
||||
- Copyright 2015-2022 Joey Hess <id@joeyh.name>
|
||||
- Copyright 2015-2023 Joey Hess <id@joeyh.name>
|
||||
-
|
||||
- Licensed under the GNU AGPL version 3 or higher.
|
||||
-}
|
||||
|
@ -9,6 +9,7 @@ module Command.RegisterUrl where
|
|||
|
||||
import Command
|
||||
import Logs.Web
|
||||
import Logs.Location
|
||||
import Command.FromKey (keyOpt, keyOpt')
|
||||
import qualified Remote
|
||||
import Annex.UUID
|
||||
|
@ -33,12 +34,12 @@ optParser desc = RegisterUrlOptions
|
|||
|
||||
seek :: RegisterUrlOptions -> CommandSeek
|
||||
seek o = case (batchOption o, keyUrlPairs o) of
|
||||
(Batch fmt, _) -> seekBatch setUrlPresent o fmt
|
||||
(Batch fmt, _) -> seekBatch registerUrl o fmt
|
||||
-- older way of enabling batch input, does not support BatchNull
|
||||
(NoBatch, []) -> seekBatch setUrlPresent o (BatchFormat BatchLine (BatchKeys False))
|
||||
(NoBatch, ps) -> commandAction (start setUrlPresent o ps)
|
||||
(NoBatch, []) -> seekBatch registerUrl o (BatchFormat BatchLine (BatchKeys False))
|
||||
(NoBatch, ps) -> commandAction (start registerUrl o ps)
|
||||
|
||||
seekBatch :: (Key -> URLString -> Annex ()) -> RegisterUrlOptions -> BatchFormat -> CommandSeek
|
||||
seekBatch :: (Remote -> Key -> URLString -> Annex ()) -> RegisterUrlOptions -> BatchFormat -> CommandSeek
|
||||
seekBatch a o fmt = batchOnly Nothing (keyUrlPairs o) $
|
||||
batchInput fmt (pure . parsebatch) $
|
||||
batchCommandAction . start' a o
|
||||
|
@ -51,20 +52,20 @@ seekBatch a o fmt = batchOnly Nothing (keyUrlPairs o) $
|
|||
Left e -> Left e
|
||||
Right k -> Right (k, u)
|
||||
|
||||
start :: (Key -> URLString -> Annex ()) -> RegisterUrlOptions -> [String] -> CommandStart
|
||||
start :: (Remote -> Key -> URLString -> Annex ()) -> RegisterUrlOptions -> [String] -> CommandStart
|
||||
start a o (keyname:url:[]) = start' a o (si, (keyOpt keyname, url))
|
||||
where
|
||||
si = SeekInput [keyname, url]
|
||||
start _ _ _ = giveup "specify a key and an url"
|
||||
|
||||
start' :: (Key -> URLString -> Annex ()) -> RegisterUrlOptions -> (SeekInput, (Key, URLString)) -> CommandStart
|
||||
start' :: (Remote -> Key -> URLString -> Annex ()) -> RegisterUrlOptions -> (SeekInput, (Key, URLString)) -> CommandStart
|
||||
start' a o (si, (key, url)) =
|
||||
starting "registerurl" ai si $
|
||||
perform a o key url
|
||||
where
|
||||
ai = ActionItemOther (Just url)
|
||||
|
||||
perform :: (Key -> URLString -> Annex ()) -> RegisterUrlOptions -> Key -> URLString -> CommandPerform
|
||||
perform :: (Remote -> Key -> URLString -> Annex ()) -> RegisterUrlOptions -> Key -> URLString -> CommandPerform
|
||||
perform a o key url = do
|
||||
needremote <- maybe (pure Nothing) (Just <$$> getParsed) (remoteOption o)
|
||||
r <- case needremote of
|
||||
|
@ -75,5 +76,15 @@ perform a o key url = do
|
|||
showNote $ "The url " ++ url ++ " is claimed by remote " ++ Remote.name r
|
||||
next $ return False
|
||||
_ -> do
|
||||
a key (setDownloader' url r)
|
||||
a r key (setDownloader' url r)
|
||||
next $ return True
|
||||
|
||||
registerUrl :: Remote -> Key -> String -> Annex ()
|
||||
registerUrl remote key url = do
|
||||
setUrlPresent key url
|
||||
-- setUrlPresent only updates location tracking when the url
|
||||
-- does not have an OtherDownloader, but this command needs to do
|
||||
-- it for urls claimed by other remotes as well.
|
||||
case snd (getDownloader url) of
|
||||
OtherDownloader -> logChange key (Remote.uuid remote) InfoPresent
|
||||
_ -> return ()
|
||||
|
|
|
@ -62,3 +62,7 @@ cleanup url key = do
|
|||
forM_ [minBound..maxBound] $ \dl ->
|
||||
setUrlMissing key (setDownloader url dl)
|
||||
return True
|
||||
-- Unlike addurl, this does not update location tracking
|
||||
-- for remotes other than the web special remote. Doing so with
|
||||
-- a remote that git-annex can drop content from would rather
|
||||
-- unexpectedly leave content stranded on that remote.
|
||||
|
|
|
@ -24,11 +24,15 @@ seek o = case (batchOption o, keyUrlPairs o) of
|
|||
(Batch fmt, _) -> seekBatch unregisterUrl o fmt
|
||||
(NoBatch, ps) -> commandAction (start unregisterUrl o ps)
|
||||
|
||||
unregisterUrl :: Key -> String -> Annex ()
|
||||
unregisterUrl key url = do
|
||||
unregisterUrl :: Remote -> Key -> String -> Annex ()
|
||||
unregisterUrl _remote key url = do
|
||||
-- Remove the url no matter what downloader;
|
||||
-- registerurl can set OtherDownloader, and this should also
|
||||
-- be able to remove urls added by addurl, which may use
|
||||
-- YoutubeDownloader.
|
||||
forM_ [minBound..maxBound] $ \dl ->
|
||||
setUrlMissing key (setDownloader url dl)
|
||||
-- Unlike unregisterurl, this does not update location tracking
|
||||
-- for remotes other than the web special remote. Doing so with
|
||||
-- a remote that git-annex can drop content from would rather
|
||||
-- unexpectedly leave content stranded on that remote.
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue