initial export command
Very basic operation works, but of course this is only the beginning. This commit was sponsored by Nick Daly on Patreon.
This commit is contained in:
parent
cca2764f91
commit
9f3630f4e0
5 changed files with 121 additions and 1 deletions
|
@ -95,6 +95,7 @@ import qualified Command.AddUrl
|
||||||
import qualified Command.ImportFeed
|
import qualified Command.ImportFeed
|
||||||
import qualified Command.RmUrl
|
import qualified Command.RmUrl
|
||||||
import qualified Command.Import
|
import qualified Command.Import
|
||||||
|
import qualified Command.Export
|
||||||
import qualified Command.Map
|
import qualified Command.Map
|
||||||
import qualified Command.Direct
|
import qualified Command.Direct
|
||||||
import qualified Command.Indirect
|
import qualified Command.Indirect
|
||||||
|
@ -141,6 +142,7 @@ cmds testoptparser testrunner =
|
||||||
, Command.ImportFeed.cmd
|
, Command.ImportFeed.cmd
|
||||||
, Command.RmUrl.cmd
|
, Command.RmUrl.cmd
|
||||||
, Command.Import.cmd
|
, Command.Import.cmd
|
||||||
|
, Command.Export.cmd
|
||||||
, Command.Init.cmd
|
, Command.Init.cmd
|
||||||
, Command.Describe.cmd
|
, Command.Describe.cmd
|
||||||
, Command.InitRemote.cmd
|
, Command.InitRemote.cmd
|
||||||
|
|
|
@ -94,6 +94,8 @@ paramAddress :: String
|
||||||
paramAddress = "ADDRESS"
|
paramAddress = "ADDRESS"
|
||||||
paramItem :: String
|
paramItem :: String
|
||||||
paramItem = "ITEM"
|
paramItem = "ITEM"
|
||||||
|
paramTreeish :: String
|
||||||
|
paramTreeish = "TREEISH"
|
||||||
paramKeyValue :: String
|
paramKeyValue :: String
|
||||||
paramKeyValue = "K=V"
|
paramKeyValue = "K=V"
|
||||||
paramNothing :: String
|
paramNothing :: String
|
||||||
|
|
103
Command/Export.hs
Normal file
103
Command/Export.hs
Normal file
|
@ -0,0 +1,103 @@
|
||||||
|
{- git-annex command
|
||||||
|
-
|
||||||
|
- Copyright 2017 Joey Hess <id@joeyh.name>
|
||||||
|
-
|
||||||
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
|
-}
|
||||||
|
|
||||||
|
module Command.Export where
|
||||||
|
|
||||||
|
import Command
|
||||||
|
import qualified Git
|
||||||
|
import qualified Git.DiffTree
|
||||||
|
import Git.Sha
|
||||||
|
import Git.FilePath
|
||||||
|
import Types.Key
|
||||||
|
import Types.Remote
|
||||||
|
import Annex.Content
|
||||||
|
import Annex.CatFile
|
||||||
|
import Messages.Progress
|
||||||
|
import Utility.Tmp
|
||||||
|
|
||||||
|
import qualified Data.ByteString.Lazy as L
|
||||||
|
|
||||||
|
cmd :: Command
|
||||||
|
cmd = command "export" SectionCommon
|
||||||
|
"export content to a remote"
|
||||||
|
paramTreeish (seek <$$> optParser)
|
||||||
|
|
||||||
|
data ExportOptions = ExportOptions
|
||||||
|
{ exportTreeish :: Git.Ref
|
||||||
|
, exportRemote :: DeferredParse Remote
|
||||||
|
}
|
||||||
|
|
||||||
|
optParser :: CmdParamsDesc -> Parser ExportOptions
|
||||||
|
optParser _ = ExportOptions
|
||||||
|
<$> (Git.Ref <$> parsetreeish)
|
||||||
|
<*> (parseRemoteOption <$> parseToOption)
|
||||||
|
where
|
||||||
|
parsetreeish = argument str
|
||||||
|
( metavar paramTreeish
|
||||||
|
)
|
||||||
|
|
||||||
|
seek :: ExportOptions -> CommandSeek
|
||||||
|
seek o = do
|
||||||
|
r <- getParsed (exportRemote o)
|
||||||
|
let oldtreeish = emptyTree -- XXX temporary
|
||||||
|
(diff, cleanup) <- inRepo $
|
||||||
|
Git.DiffTree.diffTreeRecursive oldtreeish (exportTreeish o)
|
||||||
|
seekActions $ pure $ map (start r) diff
|
||||||
|
void $ liftIO cleanup
|
||||||
|
|
||||||
|
start :: Remote -> Git.DiffTree.DiffTreeItem -> CommandStart
|
||||||
|
start r diff
|
||||||
|
| Git.DiffTree.dstsha diff == nullSha = do
|
||||||
|
showStart "unexport" f
|
||||||
|
oldk <- either id id <$> exportKey (Git.DiffTree.srcsha diff)
|
||||||
|
next $ performUnexport r oldk loc
|
||||||
|
| otherwise = do
|
||||||
|
showStart "export" f
|
||||||
|
next $ performExport r diff loc
|
||||||
|
where
|
||||||
|
loc = ExportLocation $ toInternalGitPath $
|
||||||
|
getTopFilePath $ Git.DiffTree.file diff
|
||||||
|
f = getTopFilePath $ Git.DiffTree.file diff
|
||||||
|
|
||||||
|
performExport :: Remote -> Git.DiffTree.DiffTreeItem -> ExportLocation -> CommandPerform
|
||||||
|
performExport r diff loc = case storeExport r of
|
||||||
|
Nothing -> error "remote does not support exporting files"
|
||||||
|
Just storer -> next $ do
|
||||||
|
v <- exportKey (Git.DiffTree.dstsha diff)
|
||||||
|
case v of
|
||||||
|
Right k -> metered Nothing k $ \m ->
|
||||||
|
sendAnnex k
|
||||||
|
(void $ performUnexport r k loc)
|
||||||
|
(\f -> storer f k loc m)
|
||||||
|
-- Sending a non-annexed file.
|
||||||
|
Left sha1k -> metered Nothing sha1k $ \m ->
|
||||||
|
withTmpFile "export" $ \tmp h -> do
|
||||||
|
b <- catObject (Git.DiffTree.dstsha diff)
|
||||||
|
liftIO $ L.hPut h b
|
||||||
|
liftIO $ hClose h
|
||||||
|
storer tmp sha1k loc m
|
||||||
|
|
||||||
|
performUnexport :: Remote -> Key -> ExportLocation -> CommandPerform
|
||||||
|
performUnexport r k loc = case removeExport r of
|
||||||
|
Nothing -> error "remote does not support removing exported files"
|
||||||
|
Just remover -> next $ remover k loc
|
||||||
|
|
||||||
|
-- When the Sha points to an annexed file, get the key as Right.
|
||||||
|
-- When the Sha points to a non-annexed file, convert to a SHA1 key,
|
||||||
|
-- as Left.
|
||||||
|
exportKey :: Git.Sha -> Annex (Either Key Key)
|
||||||
|
exportKey sha = mk <$> catKey sha
|
||||||
|
where
|
||||||
|
mk (Just k) = Right k
|
||||||
|
mk Nothing = Left $ Key
|
||||||
|
{ keyName = show sha
|
||||||
|
, keyVariety = SHA1Key (HasExt False)
|
||||||
|
, keySize = Nothing
|
||||||
|
, keyMtime = Nothing
|
||||||
|
, keyChunkSize = Nothing
|
||||||
|
, keyChunkNum = Nothing
|
||||||
|
}
|
|
@ -235,7 +235,7 @@ exportPath d (ExportLocation loc) = d </> loc
|
||||||
|
|
||||||
storeExportDirectory :: FilePath -> FilePath -> Key -> ExportLocation -> MeterUpdate -> Annex Bool
|
storeExportDirectory :: FilePath -> FilePath -> Key -> ExportLocation -> MeterUpdate -> Annex Bool
|
||||||
storeExportDirectory d src _k loc p = liftIO $ catchBoolIO $ do
|
storeExportDirectory d src _k loc p = liftIO $ catchBoolIO $ do
|
||||||
createDirectoryIfMissing True dest
|
createDirectoryIfMissing True (takeDirectory dest)
|
||||||
withMeteredFile src p (L.writeFile dest)
|
withMeteredFile src p (L.writeFile dest)
|
||||||
return True
|
return True
|
||||||
where
|
where
|
||||||
|
|
|
@ -14,3 +14,16 @@ Would this be able to reuse the existing `storeKey` interface, or would
|
||||||
there need to be a new interface in supported remotes?
|
there need to be a new interface in supported remotes?
|
||||||
|
|
||||||
--[[Joey]]
|
--[[Joey]]
|
||||||
|
|
||||||
|
Work is in progress. Todo list:
|
||||||
|
|
||||||
|
* Remember the previously exported tree (in git-annex branch, see design)
|
||||||
|
and use to make next export more efficient.
|
||||||
|
* Only export to remotes that were initialized to support it.
|
||||||
|
* Prevent using export remotes for key/value storage.
|
||||||
|
* When exporting, update location tracking to allow getting from exports,
|
||||||
|
* Use retrieveExport when getting from export remotes.
|
||||||
|
* Efficient handling of renames.
|
||||||
|
* Detect export conflicts (see design)
|
||||||
|
* Support export to aditional special remotes (S3 etc)
|
||||||
|
* Support export to external special remotes.
|
||||||
|
|
Loading…
Add table
Reference in a new issue