2010-11-02 23:04:24 +00:00
|
|
|
{- git-annex command
|
|
|
|
-
|
move --to=here
* move --to=here moves from all reachable remotes to the local repository.
The output of move --from remote is changed slightly, when the remote and
local both have the content. It used to say:
move foo ok
Now:
move foo (from theremote...) ok
That was done so that, when move --to=here is used and the content is
locally present and also in several remotes, it's clear which remotes the
content gets dropped from.
Note that move --to=here will report an error if a non-reachable remote
contains the file, even if the local repository also contains the file. I
think that's reasonable; the user may be intending to move all other copies
of the file from remotes.
OTOH, if a copy of the file is believed to be present in some repository
that is not a configured remote, move --to=here does not report an error.
So a little bit inconsistent, but erroring in this case feels wrong.
copy --to=here came along for free, but it's basically the same behavior as
git-annex get, and probably with not as good messages in edge cases
(especially on failure), so I've not documented it.
This commit was sponsored by Anthony DeRobertis on Patreon.
2017-05-31 20:57:27 +00:00
|
|
|
- Copyright 2010-2017 Joey Hess <id@joeyh.name>
|
2010-11-02 23:04:24 +00:00
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
|
|
|
module Command.Move where
|
|
|
|
|
|
|
|
import Command
|
2010-11-11 22:54:52 +00:00
|
|
|
import qualified Command.Drop
|
2010-11-02 23:04:24 +00:00
|
|
|
import qualified Annex
|
2011-10-04 04:40:47 +00:00
|
|
|
import Annex.Content
|
2011-03-27 21:24:20 +00:00
|
|
|
import qualified Remote
|
2011-10-15 21:47:03 +00:00
|
|
|
import Annex.UUID
|
2014-03-22 14:42:38 +00:00
|
|
|
import Annex.Transfer
|
2012-01-19 19:24:05 +00:00
|
|
|
import Logs.Presence
|
2015-10-09 20:16:03 +00:00
|
|
|
import Annex.NumCopies
|
|
|
|
|
|
|
|
import System.Log.Logger (debugM)
|
2011-03-16 01:34:13 +00:00
|
|
|
|
2015-07-08 16:33:27 +00:00
|
|
|
cmd :: Command
|
2018-02-19 18:28:17 +00:00
|
|
|
cmd = withGlobalOptions [jobsOption, jsonOptions, jsonProgressOption, annexedMatchingOptions] $
|
2015-07-10 17:18:46 +00:00
|
|
|
command "move" SectionCommon
|
|
|
|
"move content of files to/from another repository"
|
|
|
|
paramPaths (seek <--< optParser)
|
2015-07-09 19:23:14 +00:00
|
|
|
|
|
|
|
data MoveOptions = MoveOptions
|
|
|
|
{ moveFiles :: CmdParams
|
2017-05-31 20:20:55 +00:00
|
|
|
, fromToOptions :: Either ToHere FromToOptions
|
2015-07-09 19:23:14 +00:00
|
|
|
, keyOptions :: Maybe KeyOptions
|
2017-08-15 16:39:10 +00:00
|
|
|
, batchOption :: BatchMode
|
2015-07-09 19:23:14 +00:00
|
|
|
}
|
|
|
|
|
2017-05-31 20:20:55 +00:00
|
|
|
data ToHere = ToHere
|
|
|
|
|
2015-07-09 19:23:14 +00:00
|
|
|
optParser :: CmdParamsDesc -> Parser MoveOptions
|
|
|
|
optParser desc = MoveOptions
|
|
|
|
<$> cmdParams desc
|
2017-05-31 20:20:55 +00:00
|
|
|
<*> (parsefrom <|> parseto)
|
2016-08-03 16:37:12 +00:00
|
|
|
<*> optional (parseKeyOptions <|> parseFailedTransfersOption)
|
2017-08-15 16:39:10 +00:00
|
|
|
<*> parseBatchOption
|
2017-05-31 20:20:55 +00:00
|
|
|
where
|
|
|
|
parsefrom = Right . FromRemote . parseRemoteOption <$> parseFromOption
|
|
|
|
parseto = herespecialcase <$> parseToOption
|
|
|
|
where
|
|
|
|
herespecialcase "here" = Left ToHere
|
2017-06-01 17:12:42 +00:00
|
|
|
herespecialcase "." = Left ToHere
|
2017-05-31 20:20:55 +00:00
|
|
|
herespecialcase n = Right $ ToRemote $ parseRemoteOption n
|
2015-07-09 19:23:14 +00:00
|
|
|
|
|
|
|
instance DeferredParseClass MoveOptions where
|
|
|
|
finishParse v = MoveOptions
|
|
|
|
<$> pure (moveFiles v)
|
2017-05-31 20:20:55 +00:00
|
|
|
<*> either (pure . Left) (Right <$$> finishParse) (fromToOptions v)
|
2015-07-09 19:23:14 +00:00
|
|
|
<*> pure (keyOptions v)
|
2017-08-15 16:39:10 +00:00
|
|
|
<*> pure (batchOption v)
|
2015-07-09 19:23:14 +00:00
|
|
|
|
|
|
|
seek :: MoveOptions -> CommandSeek
|
2017-08-15 16:39:10 +00:00
|
|
|
seek o = allowConcurrentOutput $ do
|
|
|
|
let go = whenAnnexed $ start o True
|
|
|
|
case batchOption o of
|
|
|
|
Batch -> batchInput Right (batchCommandAction . go)
|
|
|
|
NoBatch -> withKeyOptions (keyOptions o) False
|
|
|
|
(startKey o True)
|
|
|
|
(withFilesInGit go)
|
2017-10-16 18:10:03 +00:00
|
|
|
=<< workTreeItems (moveFiles o)
|
2015-07-09 19:23:14 +00:00
|
|
|
|
|
|
|
start :: MoveOptions -> Bool -> FilePath -> Key -> CommandStart
|
2016-07-20 19:22:55 +00:00
|
|
|
start o move f k = start' o move afile k (mkActionItem afile)
|
|
|
|
where
|
2017-03-10 17:12:24 +00:00
|
|
|
afile = AssociatedFile (Just f)
|
2015-07-09 19:23:14 +00:00
|
|
|
|
2016-07-20 19:22:55 +00:00
|
|
|
startKey :: MoveOptions -> Bool -> Key -> ActionItem -> CommandStart
|
2017-03-10 17:12:24 +00:00
|
|
|
startKey o move = start' o move (AssociatedFile Nothing)
|
2015-07-09 19:23:14 +00:00
|
|
|
|
2016-07-20 19:22:55 +00:00
|
|
|
start' :: MoveOptions -> Bool -> AssociatedFile -> Key -> ActionItem -> CommandStart
|
2017-10-17 21:54:38 +00:00
|
|
|
start' o move afile key ai = onlyActionOn key $
|
2015-07-09 19:23:14 +00:00
|
|
|
case fromToOptions o of
|
2017-05-31 20:20:55 +00:00
|
|
|
Right (FromRemote src) ->
|
|
|
|
checkFailedTransferDirection ai Download $
|
|
|
|
fromStart move afile key ai =<< getParsed src
|
|
|
|
Right (ToRemote dest) ->
|
|
|
|
checkFailedTransferDirection ai Upload $
|
|
|
|
toStart move afile key ai =<< getParsed dest
|
move --to=here
* move --to=here moves from all reachable remotes to the local repository.
The output of move --from remote is changed slightly, when the remote and
local both have the content. It used to say:
move foo ok
Now:
move foo (from theremote...) ok
That was done so that, when move --to=here is used and the content is
locally present and also in several remotes, it's clear which remotes the
content gets dropped from.
Note that move --to=here will report an error if a non-reachable remote
contains the file, even if the local repository also contains the file. I
think that's reasonable; the user may be intending to move all other copies
of the file from remotes.
OTOH, if a copy of the file is believed to be present in some repository
that is not a configured remote, move --to=here does not report an error.
So a little bit inconsistent, but erroring in this case feels wrong.
copy --to=here came along for free, but it's basically the same behavior as
git-annex get, and probably with not as good messages in edge cases
(especially on failure), so I've not documented it.
This commit was sponsored by Anthony DeRobertis on Patreon.
2017-05-31 20:57:27 +00:00
|
|
|
Left ToHere ->
|
|
|
|
checkFailedTransferDirection ai Download $
|
|
|
|
toHereStart move afile key ai
|
2010-11-02 23:04:24 +00:00
|
|
|
|
2016-07-20 19:22:55 +00:00
|
|
|
showMoveAction :: Bool -> Key -> ActionItem -> Annex ()
|
2017-11-28 18:40:26 +00:00
|
|
|
showMoveAction move = showStartKey (if move then "move" else "copy")
|
2010-11-27 21:02:53 +00:00
|
|
|
|
2011-03-27 21:24:20 +00:00
|
|
|
{- Moves (or copies) the content of an annexed file to a remote.
|
2010-11-02 23:04:24 +00:00
|
|
|
-
|
2011-03-27 21:24:20 +00:00
|
|
|
- If the remote already has the content, it is still removed from
|
|
|
|
- the current repository.
|
2010-11-02 23:04:24 +00:00
|
|
|
-
|
2014-01-20 20:47:56 +00:00
|
|
|
- Note that unlike drop, this does not honor numcopies.
|
2010-11-02 23:04:24 +00:00
|
|
|
- A file's content can be moved even if there are insufficient copies to
|
|
|
|
- allow it to be dropped.
|
|
|
|
-}
|
2016-07-20 19:22:55 +00:00
|
|
|
toStart :: Bool -> AssociatedFile -> Key -> ActionItem -> Remote -> CommandStart
|
|
|
|
toStart move afile key ai dest = do
|
2011-10-11 18:43:45 +00:00
|
|
|
u <- getUUID
|
2010-11-02 23:04:24 +00:00
|
|
|
ishere <- inAnnex key
|
2011-03-27 21:24:20 +00:00
|
|
|
if not ishere || u == Remote.uuid dest
|
2011-05-15 06:02:46 +00:00
|
|
|
then stop -- not here, so nothing to do
|
2016-07-20 19:22:55 +00:00
|
|
|
else toStart' dest move afile key ai
|
2014-03-13 18:51:22 +00:00
|
|
|
|
2016-07-20 19:22:55 +00:00
|
|
|
toStart' :: Remote -> Bool -> AssociatedFile -> Key -> ActionItem -> CommandStart
|
|
|
|
toStart' dest move afile key ai = do
|
2011-03-27 22:34:30 +00:00
|
|
|
fast <- Annex.getState Annex.fast
|
2017-09-29 20:30:43 +00:00
|
|
|
if fast && not move
|
2014-03-13 18:51:22 +00:00
|
|
|
then ifM (expectedPresent dest key)
|
|
|
|
( stop
|
|
|
|
, go True (pure $ Right False)
|
|
|
|
)
|
|
|
|
else go False (Remote.hasKey dest key)
|
|
|
|
where
|
|
|
|
go fastcheck isthere = do
|
2016-07-20 19:22:55 +00:00
|
|
|
showMoveAction move key ai
|
2014-03-13 18:51:22 +00:00
|
|
|
next $ toPerform dest move key afile fastcheck =<< isthere
|
|
|
|
|
|
|
|
expectedPresent :: Remote -> Key -> Annex Bool
|
|
|
|
expectedPresent dest key = do
|
|
|
|
remotes <- Remote.keyPossibilities key
|
|
|
|
return $ dest `elem` remotes
|
|
|
|
|
|
|
|
toPerform :: Remote -> Bool -> Key -> AssociatedFile -> Bool -> Either String Bool -> CommandPerform
|
2014-10-09 19:35:19 +00:00
|
|
|
toPerform dest move key afile fastcheck isthere =
|
2010-11-02 23:04:24 +00:00
|
|
|
case isthere of
|
|
|
|
Left err -> do
|
2011-11-11 05:52:58 +00:00
|
|
|
showNote err
|
2011-05-15 06:02:46 +00:00
|
|
|
stop
|
2010-11-02 23:04:24 +00:00
|
|
|
Right False -> do
|
2011-07-19 18:07:23 +00:00
|
|
|
showAction $ "to " ++ Remote.name dest
|
2014-03-22 14:42:38 +00:00
|
|
|
ok <- notifyTransfer Upload afile $
|
2016-10-26 19:38:22 +00:00
|
|
|
upload (Remote.uuid dest) key afile forwardRetry $
|
2014-03-22 14:42:38 +00:00
|
|
|
Remote.storeKey dest key afile
|
2010-11-22 21:51:55 +00:00
|
|
|
if ok
|
2016-06-05 17:51:22 +00:00
|
|
|
then finish $
|
2013-02-26 18:39:37 +00:00
|
|
|
Remote.logStatus dest key InfoPresent
|
2011-05-16 17:27:19 +00:00
|
|
|
else do
|
|
|
|
when fastcheck $
|
|
|
|
warning "This could have failed because --fast is enabled."
|
|
|
|
stop
|
2016-06-05 17:51:22 +00:00
|
|
|
Right True -> finish $
|
2014-03-13 18:51:22 +00:00
|
|
|
unlessM (expectedPresent dest key) $
|
2013-02-26 18:39:37 +00:00
|
|
|
Remote.logStatus dest key InfoPresent
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
2016-06-05 17:51:22 +00:00
|
|
|
finish :: Annex () -> CommandPerform
|
|
|
|
finish setpresentremote
|
2015-10-09 19:48:02 +00:00
|
|
|
| move = lockContentForRemoval key $ \contentlock -> do
|
2016-06-05 17:51:22 +00:00
|
|
|
-- Drop content before updating location logs,
|
|
|
|
-- in case disk space is very low this frees up
|
|
|
|
-- space before writing data to disk.
|
2014-08-21 00:08:45 +00:00
|
|
|
removeAnnex contentlock
|
2016-06-05 17:51:22 +00:00
|
|
|
next $ do
|
|
|
|
setpresentremote
|
|
|
|
Command.Drop.cleanupLocal key
|
|
|
|
| otherwise = next $ do
|
|
|
|
setpresentremote
|
|
|
|
return True
|
2010-11-02 23:04:24 +00:00
|
|
|
|
2011-03-27 21:24:20 +00:00
|
|
|
{- Moves (or copies) the content of an annexed file from a remote
|
|
|
|
- to the current repository.
|
2010-11-02 23:04:24 +00:00
|
|
|
-
|
|
|
|
- If the current repository already has the content, it is still removed
|
2011-03-27 21:24:20 +00:00
|
|
|
- from the remote.
|
2010-11-02 23:04:24 +00:00
|
|
|
-}
|
2016-07-20 19:22:55 +00:00
|
|
|
fromStart :: Bool -> AssociatedFile -> Key -> ActionItem -> Remote -> CommandStart
|
|
|
|
fromStart move afile key ai src
|
2011-11-11 05:52:58 +00:00
|
|
|
| move = go
|
2011-12-09 17:32:09 +00:00
|
|
|
| otherwise = stopUnless (not <$> inAnnex key) go
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
|
|
|
go = stopUnless (fromOk src key) $ do
|
2016-07-20 19:22:55 +00:00
|
|
|
showMoveAction move key ai
|
2013-07-03 17:55:50 +00:00
|
|
|
next $ fromPerform src move key afile
|
2012-11-12 05:05:04 +00:00
|
|
|
|
2011-12-31 08:11:39 +00:00
|
|
|
fromOk :: Remote -> Key -> Annex Bool
|
2013-12-02 19:41:20 +00:00
|
|
|
fromOk src key = go =<< Annex.getState Annex.force
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
2013-12-02 19:41:20 +00:00
|
|
|
go True = either (const $ return True) return =<< haskey
|
|
|
|
go False
|
|
|
|
| Remote.hasKeyCheap src =
|
|
|
|
either (const expensive) return =<< haskey
|
|
|
|
| otherwise = expensive
|
|
|
|
haskey = Remote.hasKey src key
|
2012-11-12 05:05:04 +00:00
|
|
|
expensive = do
|
|
|
|
u <- getUUID
|
|
|
|
remotes <- Remote.keyPossibilities key
|
|
|
|
return $ u /= Remote.uuid src && elem src remotes
|
|
|
|
|
2013-07-03 17:55:50 +00:00
|
|
|
fromPerform :: Remote -> Bool -> Key -> AssociatedFile -> CommandPerform
|
move --to=here
* move --to=here moves from all reachable remotes to the local repository.
The output of move --from remote is changed slightly, when the remote and
local both have the content. It used to say:
move foo ok
Now:
move foo (from theremote...) ok
That was done so that, when move --to=here is used and the content is
locally present and also in several remotes, it's clear which remotes the
content gets dropped from.
Note that move --to=here will report an error if a non-reachable remote
contains the file, even if the local repository also contains the file. I
think that's reasonable; the user may be intending to move all other copies
of the file from remotes.
OTOH, if a copy of the file is believed to be present in some repository
that is not a configured remote, move --to=here does not report an error.
So a little bit inconsistent, but erroring in this case feels wrong.
copy --to=here came along for free, but it's basically the same behavior as
git-annex get, and probably with not as good messages in edge cases
(especially on failure), so I've not documented it.
This commit was sponsored by Anthony DeRobertis on Patreon.
2017-05-31 20:57:27 +00:00
|
|
|
fromPerform src move key afile = do
|
|
|
|
showAction $ "from " ++ Remote.name src
|
|
|
|
ifM (inAnnex key)
|
|
|
|
( dispatch move True
|
|
|
|
, dispatch move =<< go
|
|
|
|
)
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
2014-03-22 14:42:38 +00:00
|
|
|
go = notifyTransfer Download afile $
|
move --to=here
* move --to=here moves from all reachable remotes to the local repository.
The output of move --from remote is changed slightly, when the remote and
local both have the content. It used to say:
move foo ok
Now:
move foo (from theremote...) ok
That was done so that, when move --to=here is used and the content is
locally present and also in several remotes, it's clear which remotes the
content gets dropped from.
Note that move --to=here will report an error if a non-reachable remote
contains the file, even if the local repository also contains the file. I
think that's reasonable; the user may be intending to move all other copies
of the file from remotes.
OTOH, if a copy of the file is believed to be present in some repository
that is not a configured remote, move --to=here does not report an error.
So a little bit inconsistent, but erroring in this case feels wrong.
copy --to=here came along for free, but it's basically the same behavior as
git-annex get, and probably with not as good messages in edge cases
(especially on failure), so I've not documented it.
This commit was sponsored by Anthony DeRobertis on Patreon.
2017-05-31 20:57:27 +00:00
|
|
|
download (Remote.uuid src) key afile forwardRetry $ \p ->
|
2017-10-17 21:54:38 +00:00
|
|
|
getViaTmp (RemoteVerify src) key $ \t ->
|
|
|
|
Remote.retrieveKeyFile src key afile t p
|
unify exception handling into Utility.Exception
Removed old extensible-exceptions, only needed for very old ghc.
Made webdav use Utility.Exception, to work after some changes in DAV's
exception handling.
Removed Annex.Exception. Mostly this was trivial, but note that
tryAnnex is replaced with tryNonAsync and catchAnnex replaced with
catchNonAsync. In theory that could be a behavior change, since the former
caught all exceptions, and the latter don't catch async exceptions.
However, in practice, nothing in the Annex monad uses async exceptions.
Grepping for throwTo and killThread only find stuff in the assistant,
which does not seem related.
Command.Add.undo is changed to accept a SomeException, and things
that use it for rollback now catch non-async exceptions, rather than
only IOExceptions.
2014-08-08 01:55:44 +00:00
|
|
|
dispatch _ False = stop -- failed
|
|
|
|
dispatch False True = next $ return True -- copy complete
|
2015-10-09 20:16:03 +00:00
|
|
|
-- Finish by dropping from remote, taking care to verify that
|
|
|
|
-- the copy here has not been lost somehow.
|
|
|
|
-- (NumCopies is 1 since we're moving.)
|
|
|
|
dispatch True True = verifyEnoughCopiesToDrop "" key Nothing
|
|
|
|
(NumCopies 1) [] [] [UnVerifiedHere] dropremote faileddropremote
|
|
|
|
dropremote proof = do
|
|
|
|
liftIO $ debugM "drop" $ unwords
|
|
|
|
[ "Dropping from remote"
|
|
|
|
, show src
|
|
|
|
, "proof:"
|
|
|
|
, show proof
|
|
|
|
]
|
2012-11-12 05:05:04 +00:00
|
|
|
ok <- Remote.removeKey src key
|
|
|
|
next $ Command.Drop.cleanupRemote key src ok
|
2016-11-16 01:29:54 +00:00
|
|
|
faileddropremote = giveup "Unable to drop from remote."
|
move --to=here
* move --to=here moves from all reachable remotes to the local repository.
The output of move --from remote is changed slightly, when the remote and
local both have the content. It used to say:
move foo ok
Now:
move foo (from theremote...) ok
That was done so that, when move --to=here is used and the content is
locally present and also in several remotes, it's clear which remotes the
content gets dropped from.
Note that move --to=here will report an error if a non-reachable remote
contains the file, even if the local repository also contains the file. I
think that's reasonable; the user may be intending to move all other copies
of the file from remotes.
OTOH, if a copy of the file is believed to be present in some repository
that is not a configured remote, move --to=here does not report an error.
So a little bit inconsistent, but erroring in this case feels wrong.
copy --to=here came along for free, but it's basically the same behavior as
git-annex get, and probably with not as good messages in edge cases
(especially on failure), so I've not documented it.
This commit was sponsored by Anthony DeRobertis on Patreon.
2017-05-31 20:57:27 +00:00
|
|
|
|
|
|
|
{- Moves (or copies) the content of an annexed file from reachable remotes
|
|
|
|
- to the current repository.
|
|
|
|
-
|
|
|
|
- When moving, the content is removed from all the reachable remotes. -}
|
|
|
|
toHereStart :: Bool -> AssociatedFile -> Key -> ActionItem -> CommandStart
|
|
|
|
toHereStart move afile key ai
|
|
|
|
| move = go
|
|
|
|
| otherwise = stopUnless (not <$> inAnnex key) go
|
|
|
|
where
|
|
|
|
go = do
|
|
|
|
rs <- Remote.keyPossibilities key
|
|
|
|
forM_ rs $ \r ->
|
|
|
|
includeCommandAction $ do
|
|
|
|
showMoveAction move key ai
|
|
|
|
next $ fromPerform r move key afile
|
|
|
|
stop
|