2012-05-31 23:47:18 +00:00
|
|
|
{- git-annex command
|
|
|
|
-
|
2015-01-21 16:50:09 +00:00
|
|
|
- Copyright 2012-2013 Joey Hess <id@joeyh.name>
|
2012-05-31 23:47:18 +00:00
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
|
|
|
module Command.Import where
|
|
|
|
|
|
|
|
import Command
|
2015-05-11 16:57:47 +00:00
|
|
|
import qualified Git
|
2012-05-31 23:47:18 +00:00
|
|
|
import qualified Annex
|
|
|
|
import qualified Command.Add
|
2013-08-11 18:31:54 +00:00
|
|
|
import Utility.CopyFile
|
2013-08-20 15:00:52 +00:00
|
|
|
import Backend
|
|
|
|
import Remote
|
|
|
|
import Types.KeySource
|
2015-04-29 17:46:12 +00:00
|
|
|
import Annex.CheckIgnore
|
2015-04-30 18:03:24 +00:00
|
|
|
import Annex.NumCopies
|
2015-12-02 18:48:42 +00:00
|
|
|
import Annex.FileMatcher
|
2012-05-31 23:47:18 +00:00
|
|
|
|
2015-07-08 16:33:27 +00:00
|
|
|
cmd :: Command
|
2016-01-19 15:54:13 +00:00
|
|
|
cmd = withGlobalOptions (jobsOption : jsonOption : fileMatchingOptions) $ notBareRepo $
|
2015-07-08 19:08:02 +00:00
|
|
|
command "import" SectionCommon
|
|
|
|
"move and add files from outside git working copy"
|
2015-07-13 15:15:21 +00:00
|
|
|
paramPaths (seek <$$> optParser)
|
2013-08-11 18:31:54 +00:00
|
|
|
|
2015-02-08 19:04:58 +00:00
|
|
|
data DuplicateMode = Default | Duplicate | DeDuplicate | CleanDuplicates | SkipDuplicates
|
2015-07-13 15:15:21 +00:00
|
|
|
deriving (Eq)
|
2013-08-11 18:31:54 +00:00
|
|
|
|
2015-07-13 15:15:21 +00:00
|
|
|
data ImportOptions = ImportOptions
|
|
|
|
{ importFiles :: CmdParams
|
|
|
|
, duplicateMode :: DuplicateMode
|
|
|
|
}
|
2013-12-04 17:13:30 +00:00
|
|
|
|
2015-07-13 15:15:21 +00:00
|
|
|
optParser :: CmdParamsDesc -> Parser ImportOptions
|
|
|
|
optParser desc = ImportOptions
|
|
|
|
<$> cmdParams desc
|
|
|
|
<*> (fromMaybe Default <$> optional duplicateModeParser)
|
2013-08-11 18:31:54 +00:00
|
|
|
|
2015-07-13 15:15:21 +00:00
|
|
|
duplicateModeParser :: Parser DuplicateMode
|
|
|
|
duplicateModeParser =
|
|
|
|
flag' Duplicate
|
|
|
|
( long "duplicate"
|
|
|
|
<> help "do not delete source files"
|
|
|
|
)
|
|
|
|
<|> flag' DeDuplicate
|
|
|
|
( long "deduplicate"
|
|
|
|
<> help "delete source files whose content was imported before"
|
|
|
|
)
|
|
|
|
<|> flag' CleanDuplicates
|
|
|
|
( long "clean-duplicates"
|
|
|
|
<> help "delete duplicate source files (import nothing)"
|
|
|
|
)
|
|
|
|
<|> flag' SkipDuplicates
|
|
|
|
( long "skip-duplicates"
|
|
|
|
<> help "import only new files"
|
|
|
|
)
|
2013-08-11 18:31:54 +00:00
|
|
|
|
2015-07-13 15:15:21 +00:00
|
|
|
seek :: ImportOptions -> CommandSeek
|
2015-11-06 19:39:51 +00:00
|
|
|
seek o = allowConcurrentOutput $ do
|
2015-05-11 16:57:47 +00:00
|
|
|
repopath <- liftIO . absPath =<< fromRepo Git.repoPath
|
2015-07-13 15:15:21 +00:00
|
|
|
inrepops <- liftIO $ filter (dirContains repopath) <$> mapM absPath (importFiles o)
|
2015-05-11 16:57:47 +00:00
|
|
|
unless (null inrepops) $ do
|
|
|
|
error $ "cannot import files from inside the working tree (use git annex add instead): " ++ unwords inrepops
|
2015-12-02 18:48:42 +00:00
|
|
|
largematcher <- largeFilesMatcher
|
|
|
|
withPathContents (start largematcher (duplicateMode o)) (importFiles o)
|
2012-05-31 23:47:18 +00:00
|
|
|
|
2016-02-02 19:18:17 +00:00
|
|
|
start :: GetFileMatcher -> DuplicateMode -> (FilePath, FilePath) -> CommandStart
|
2015-12-02 18:48:42 +00:00
|
|
|
start largematcher mode (srcfile, destfile) =
|
2012-05-31 23:47:18 +00:00
|
|
|
ifM (liftIO $ isRegularFile <$> getSymbolicLinkStatus srcfile)
|
|
|
|
( do
|
2015-02-08 18:43:42 +00:00
|
|
|
ma <- pickaction
|
|
|
|
case ma of
|
2013-12-04 17:13:30 +00:00
|
|
|
Nothing -> stop
|
|
|
|
Just a -> do
|
|
|
|
showStart "import" destfile
|
|
|
|
next a
|
2012-05-31 23:47:18 +00:00
|
|
|
, stop
|
|
|
|
)
|
2013-08-20 15:00:52 +00:00
|
|
|
where
|
2015-03-31 19:36:02 +00:00
|
|
|
deletedup k = do
|
|
|
|
showNote $ "duplicate of " ++ key2file k
|
2015-10-09 15:09:46 +00:00
|
|
|
verifyExisting k destfile
|
2015-04-30 18:03:24 +00:00
|
|
|
( do
|
|
|
|
liftIO $ removeFile srcfile
|
|
|
|
next $ return True
|
|
|
|
, do
|
2015-04-30 18:10:28 +00:00
|
|
|
warning "Could not verify that the content is still present in the annex; not removing from the import location."
|
2015-04-30 18:03:24 +00:00
|
|
|
stop
|
|
|
|
)
|
2015-11-05 22:45:52 +00:00
|
|
|
importfile = checkdestdir $ do
|
2015-04-29 17:46:12 +00:00
|
|
|
ignored <- not <$> Annex.getState Annex.force <&&> checkIgnored destfile
|
|
|
|
if ignored
|
2015-04-29 17:56:41 +00:00
|
|
|
then do
|
|
|
|
warning $ "not importing " ++ destfile ++ " which is .gitignored (use --force to override)"
|
|
|
|
stop
|
2015-04-29 17:46:12 +00:00
|
|
|
else do
|
2015-04-29 17:56:41 +00:00
|
|
|
existing <- liftIO (catchMaybeIO $ getSymbolicLinkStatus destfile)
|
|
|
|
case existing of
|
|
|
|
Nothing -> importfilechecked
|
2015-11-05 22:45:52 +00:00
|
|
|
Just s
|
2015-04-29 17:56:41 +00:00
|
|
|
| isDirectory s -> notoverwriting "(is a directory)"
|
2015-11-05 22:45:52 +00:00
|
|
|
| isSymbolicLink s -> notoverwriting "(is a symlink)"
|
2015-04-29 17:56:41 +00:00
|
|
|
| otherwise -> ifM (Annex.getState Annex.force)
|
|
|
|
( do
|
|
|
|
liftIO $ nukeFile destfile
|
|
|
|
importfilechecked
|
|
|
|
, notoverwriting "(use --force to override, or a duplication option such as --deduplicate to clean up)"
|
|
|
|
)
|
2015-11-05 22:45:52 +00:00
|
|
|
checkdestdir cont = do
|
|
|
|
let destdir = parentDir destfile
|
|
|
|
existing <- liftIO (catchMaybeIO $ getSymbolicLinkStatus destdir)
|
|
|
|
case existing of
|
|
|
|
Nothing -> cont
|
|
|
|
Just s
|
|
|
|
| isDirectory s -> cont
|
|
|
|
| otherwise -> do
|
|
|
|
warning $ "not importing " ++ destfile ++ " because " ++ destdir ++ " is not a directory"
|
|
|
|
stop
|
|
|
|
|
2015-04-29 17:56:41 +00:00
|
|
|
importfilechecked = do
|
|
|
|
liftIO $ createDirectoryIfMissing True (parentDir destfile)
|
|
|
|
liftIO $ if mode == Duplicate || mode == SkipDuplicates
|
|
|
|
then void $ copyFileExternal CopyAllMetaData srcfile destfile
|
|
|
|
else moveFile srcfile destfile
|
2015-12-02 18:48:42 +00:00
|
|
|
ifM (checkFileMatcher largematcher destfile)
|
|
|
|
( Command.Add.perform destfile
|
2015-12-02 19:12:33 +00:00
|
|
|
, next $ Command.Add.addSmall destfile
|
2015-12-02 18:48:42 +00:00
|
|
|
)
|
2015-04-29 17:56:41 +00:00
|
|
|
notoverwriting why = do
|
|
|
|
warning $ "not overwriting existing " ++ destfile ++ " " ++ why
|
|
|
|
stop
|
2015-02-08 18:43:42 +00:00
|
|
|
checkdup dupa notdupa = do
|
|
|
|
backend <- chooseBackend destfile
|
|
|
|
let ks = KeySource srcfile srcfile Nothing
|
|
|
|
v <- genKey ks backend
|
2015-03-31 19:36:02 +00:00
|
|
|
case v of
|
|
|
|
Just (k, _) -> ifM (not . null <$> keyLocations k)
|
|
|
|
( return (maybe Nothing (\a -> Just (a k)) dupa)
|
|
|
|
, return notdupa
|
|
|
|
)
|
|
|
|
_ -> return notdupa
|
2015-02-08 18:43:42 +00:00
|
|
|
pickaction = case mode of
|
|
|
|
DeDuplicate -> checkdup (Just deletedup) (Just importfile)
|
|
|
|
CleanDuplicates -> checkdup (Just deletedup) Nothing
|
|
|
|
SkipDuplicates -> checkdup Nothing (Just importfile)
|
|
|
|
_ -> return (Just importfile)
|
2015-04-30 18:03:24 +00:00
|
|
|
|
2015-10-09 15:09:46 +00:00
|
|
|
verifyExisting :: Key -> FilePath -> (CommandPerform, CommandPerform) -> CommandPerform
|
|
|
|
verifyExisting key destfile (yes, no) = do
|
2015-04-30 18:03:24 +00:00
|
|
|
-- Look up the numcopies setting for the file that it would be
|
|
|
|
-- imported to, if it were imported.
|
|
|
|
need <- getFileNumCopies destfile
|
|
|
|
|
2015-10-09 18:57:32 +00:00
|
|
|
(tocheck, preverified) <- verifiableCopies key []
|
2015-10-09 19:48:02 +00:00
|
|
|
verifyEnoughCopiesToDrop [] key Nothing need [] preverified tocheck
|
2015-10-09 15:09:46 +00:00
|
|
|
(const yes) no
|