2020-12-09 16:32:29 +00:00
|
|
|
{- git-annex command, used internally by assistant in version
|
|
|
|
- 8.20201127 and older and provided only to avoid upgrade breakage.
|
|
|
|
- Remove at some point when such old versions of git-annex are unlikely
|
|
|
|
- to be running any longer.
|
2013-03-19 20:58:36 +00:00
|
|
|
-
|
2020-12-09 16:32:29 +00:00
|
|
|
- Copyright 2012, 2013 Joey Hess <id@joeyh.name>
|
2013-03-19 20:58:36 +00:00
|
|
|
-
|
2019-03-13 19:48:14 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2013-03-19 20:58:36 +00:00
|
|
|
-}
|
|
|
|
|
2020-12-09 16:32:29 +00:00
|
|
|
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-}
|
|
|
|
|
2013-03-19 20:58:36 +00:00
|
|
|
module Command.TransferKeys where
|
|
|
|
|
|
|
|
import Command
|
|
|
|
import Annex.Content
|
|
|
|
import Logs.Location
|
2014-03-22 14:42:38 +00:00
|
|
|
import Annex.Transfer
|
2013-03-19 20:58:36 +00:00
|
|
|
import qualified Remote
|
2015-04-03 19:33:28 +00:00
|
|
|
import Utility.SimpleProtocol (dupIoHandles)
|
2020-12-09 16:32:29 +00:00
|
|
|
import Git.Types (RemoteName)
|
2016-05-16 18:49:12 +00:00
|
|
|
import qualified Database.Keys
|
2020-04-09 17:54:43 +00:00
|
|
|
import Annex.BranchState
|
new protocol for transferkeys, with message serialization
Necessarily threw out the old protocol, so if an old git-annex assistant
is running, and starts a transferkeys from the new git-annex, it would
fail. But, that seems unlikely; the assistant starts up transferkeys
processes and then keeps them running. Still, may need to test that
scenario.
The new protocol is simple read/show and looks like this:
TransferRequest Download (Right "origin") (Key {keyName = "f8f8766a836fb6120abf4d5328ce8761404e437529e997aaa0363bdd4fecd7bb", keyVariety = SHA2Key (HashSize 256) (HasExt True), keySize = Just 30, keyMtime = Nothing, keyChunkSize = Nothing, keyChunkNum = Nothing}) (AssociatedFile (Just "foo"))
TransferOutput (ProgressMeter (Just 30) (MeterState {meterBytesProcessed = BytesProcessed 0, meterTimeStamp = 1.6070268727892535e9}) (MeterState {meterBytesProcessed = BytesProcessed 30, meterTimeStamp = 1.6070268728043e9}))
TransferOutput (OutputMessage "(checksum...) ")
TransferResult True
Granted, this is not optimally fast, but it seems good enough, and is
probably nearly as fast as the old protocol anyhow.
emitSerializedOutput for ProgressMeter is not yet implemented. It needs
to somehow start or update a progress meter. There may need to be a new
message that allocates a progress meter, and then have ProgressMeter
update it.
This commit was sponsored by Ethan Aubin
2020-12-03 20:21:20 +00:00
|
|
|
|
2020-12-09 16:32:29 +00:00
|
|
|
data TransferRequest = TransferRequest Direction Remote Key AssociatedFile
|
new protocol for transferkeys, with message serialization
Necessarily threw out the old protocol, so if an old git-annex assistant
is running, and starts a transferkeys from the new git-annex, it would
fail. But, that seems unlikely; the assistant starts up transferkeys
processes and then keeps them running. Still, may need to test that
scenario.
The new protocol is simple read/show and looks like this:
TransferRequest Download (Right "origin") (Key {keyName = "f8f8766a836fb6120abf4d5328ce8761404e437529e997aaa0363bdd4fecd7bb", keyVariety = SHA2Key (HashSize 256) (HasExt True), keySize = Just 30, keyMtime = Nothing, keyChunkSize = Nothing, keyChunkNum = Nothing}) (AssociatedFile (Just "foo"))
TransferOutput (ProgressMeter (Just 30) (MeterState {meterBytesProcessed = BytesProcessed 0, meterTimeStamp = 1.6070268727892535e9}) (MeterState {meterBytesProcessed = BytesProcessed 30, meterTimeStamp = 1.6070268728043e9}))
TransferOutput (OutputMessage "(checksum...) ")
TransferResult True
Granted, this is not optimally fast, but it seems good enough, and is
probably nearly as fast as the old protocol anyhow.
emitSerializedOutput for ProgressMeter is not yet implemented. It needs
to somehow start or update a progress meter. There may need to be a new
message that allocates a progress meter, and then have ProgressMeter
update it.
This commit was sponsored by Ethan Aubin
2020-12-03 20:21:20 +00:00
|
|
|
|
2015-07-08 16:33:27 +00:00
|
|
|
cmd :: Command
|
2020-12-09 16:32:29 +00:00
|
|
|
cmd = command "transferkeys" SectionPlumbing "transfers keys (deprecated)"
|
2015-07-08 19:08:02 +00:00
|
|
|
paramNothing (withParams seek)
|
2013-03-19 20:58:36 +00:00
|
|
|
|
2015-07-08 19:08:02 +00:00
|
|
|
seek :: CmdParams -> CommandSeek
|
2018-10-01 18:12:06 +00:00
|
|
|
seek = withNothing (commandAction start)
|
2013-03-19 20:58:36 +00:00
|
|
|
|
2013-12-11 03:19:18 +00:00
|
|
|
start :: CommandStart
|
2014-04-08 18:02:25 +00:00
|
|
|
start = do
|
2020-07-06 16:09:53 +00:00
|
|
|
enableInteractiveBranchAccess
|
2015-04-03 19:33:28 +00:00
|
|
|
(readh, writeh) <- liftIO dupIoHandles
|
2013-12-11 03:19:18 +00:00
|
|
|
runRequests readh writeh runner
|
2013-03-19 20:58:36 +00:00
|
|
|
stop
|
|
|
|
where
|
2020-12-09 16:32:29 +00:00
|
|
|
runner (TransferRequest direction remote key file)
|
2014-03-22 14:42:38 +00:00
|
|
|
| direction == Upload = notifyTransfer direction file $
|
2021-02-03 19:35:32 +00:00
|
|
|
upload' (Remote.uuid remote) key file Nothing stdRetry $ \p -> do
|
2020-05-13 18:03:00 +00:00
|
|
|
tryNonAsync (Remote.storeKey remote key file p) >>= \case
|
|
|
|
Left e -> do
|
filter out control characters in warning messages
Converted warning and similar to use StringContainingQuotedPath. Most
warnings are static strings, some do refer to filepaths that need to be
quoted, and others don't need quoting.
Note that, since quote filters out control characters of even
UnquotedString, this makes all warnings safe, even when an attacker
sneaks in a control character in some other way.
When json is being output, no quoting is done, since json gets its own
quoting.
This does, as a side effect, make warning messages in json output not
be indented. The indentation is only needed to offset warning messages
underneath the display of the file they apply to, so that's ok.
Sponsored-by: Brett Eisenberg on Patreon
2023-04-10 18:47:32 +00:00
|
|
|
warning (UnquotedString (show e))
|
2020-05-13 18:03:00 +00:00
|
|
|
return False
|
|
|
|
Right () -> do
|
|
|
|
Remote.logStatus remote key InfoPresent
|
|
|
|
return True
|
2014-03-22 14:42:38 +00:00
|
|
|
| otherwise = notifyTransfer direction file $
|
2021-02-03 19:35:32 +00:00
|
|
|
download' (Remote.uuid remote) key file Nothing stdRetry $ \p ->
|
2020-12-11 15:33:10 +00:00
|
|
|
logStatusAfter key $ getViaTmp (Remote.retrievalSecurityPolicy remote) (RemoteVerify remote) key file $ \t -> do
|
2021-08-17 16:41:36 +00:00
|
|
|
r <- tryNonAsync (Remote.retrieveKeyFile remote key file (fromRawFilePath t) p (RemoteVerify remote)) >>= \case
|
2020-05-13 21:05:56 +00:00
|
|
|
Left e -> do
|
filter out control characters in warning messages
Converted warning and similar to use StringContainingQuotedPath. Most
warnings are static strings, some do refer to filepaths that need to be
quoted, and others don't need quoting.
Note that, since quote filters out control characters of even
UnquotedString, this makes all warnings safe, even when an attacker
sneaks in a control character in some other way.
When json is being output, no quoting is done, since json gets its own
quoting.
This does, as a side effect, make warning messages in json output not
be indented. The indentation is only needed to offset warning messages
underneath the display of the file they apply to, so that's ok.
Sponsored-by: Brett Eisenberg on Patreon
2023-04-10 18:47:32 +00:00
|
|
|
warning (UnquotedString (show e))
|
2020-05-13 21:05:56 +00:00
|
|
|
return (False, UnVerified)
|
|
|
|
Right v -> return (True, v)
|
2016-05-16 18:49:12 +00:00
|
|
|
-- Make sure we get the current
|
|
|
|
-- associated files data for the key,
|
|
|
|
-- not old cached data.
|
|
|
|
Database.Keys.closeDb
|
|
|
|
return r
|
2013-03-19 20:58:36 +00:00
|
|
|
|
|
|
|
runRequests
|
|
|
|
:: Handle
|
|
|
|
-> Handle
|
2020-12-09 16:32:29 +00:00
|
|
|
-> (TransferRequest -> Annex Bool)
|
2013-03-19 20:58:36 +00:00
|
|
|
-> Annex ()
|
2020-12-09 16:32:29 +00:00
|
|
|
runRequests readh writeh a = do
|
|
|
|
liftIO $ hSetBuffering readh NoBuffering
|
|
|
|
go =<< readrequests
|
2013-03-19 20:58:36 +00:00
|
|
|
where
|
2020-12-09 16:32:29 +00:00
|
|
|
go (d:rn:k:f:rest) = do
|
|
|
|
case (deserialize d, deserialize rn, deserialize k, deserialize f) of
|
|
|
|
(Just direction, Just remotename, Just key, Just file) -> do
|
|
|
|
mremote <- Remote.byName' remotename
|
2013-03-19 20:58:36 +00:00
|
|
|
case mremote of
|
2020-12-09 16:32:29 +00:00
|
|
|
Left _ -> sendresult False
|
|
|
|
Right remote -> sendresult =<< a
|
|
|
|
(TransferRequest direction remote key file)
|
|
|
|
_ -> sendresult False
|
|
|
|
go rest
|
|
|
|
go [] = noop
|
|
|
|
go [""] = noop
|
2023-04-10 17:38:14 +00:00
|
|
|
go v = giveup $ "transferkeys protocol error: " ++ show v
|
2013-03-19 20:58:36 +00:00
|
|
|
|
2020-12-09 16:32:29 +00:00
|
|
|
readrequests = liftIO $ split fieldSep <$> hGetContents readh
|
2013-03-19 20:58:36 +00:00
|
|
|
sendresult b = liftIO $ do
|
2020-12-09 16:32:29 +00:00
|
|
|
hPutStrLn writeh $ serialize b
|
2013-03-19 20:58:36 +00:00
|
|
|
hFlush writeh
|
2020-12-09 16:32:29 +00:00
|
|
|
|
|
|
|
sendRequest :: Transfer -> TransferInfo -> Handle -> IO ()
|
|
|
|
sendRequest t tinfo h = do
|
|
|
|
hPutStr h $ intercalate fieldSep
|
|
|
|
[ serialize (transferDirection t)
|
|
|
|
, maybe (serialize ((fromUUID (transferUUID t)) :: String))
|
|
|
|
(serialize . Remote.name)
|
|
|
|
(transferRemote tinfo)
|
|
|
|
, serialize (transferKey t)
|
|
|
|
, serialize (associatedFile tinfo)
|
|
|
|
, "" -- adds a trailing null
|
|
|
|
]
|
|
|
|
hFlush h
|
|
|
|
|
|
|
|
readResponse :: Handle -> IO Bool
|
|
|
|
readResponse h = fromMaybe False . deserialize <$> hGetLine h
|
|
|
|
|
|
|
|
fieldSep :: String
|
|
|
|
fieldSep = "\0"
|
|
|
|
|
|
|
|
class TCSerialized a where
|
|
|
|
serialize :: a -> String
|
|
|
|
deserialize :: String -> Maybe a
|
|
|
|
|
|
|
|
instance TCSerialized Bool where
|
|
|
|
serialize True = "1"
|
|
|
|
serialize False = "0"
|
|
|
|
deserialize "1" = Just True
|
|
|
|
deserialize "0" = Just False
|
|
|
|
deserialize _ = Nothing
|
|
|
|
|
|
|
|
instance TCSerialized Direction where
|
|
|
|
serialize Upload = "u"
|
|
|
|
serialize Download = "d"
|
|
|
|
deserialize "u" = Just Upload
|
|
|
|
deserialize "d" = Just Download
|
|
|
|
deserialize _ = Nothing
|
|
|
|
|
|
|
|
instance TCSerialized AssociatedFile where
|
|
|
|
serialize (AssociatedFile (Just f)) = fromRawFilePath f
|
|
|
|
serialize (AssociatedFile Nothing) = ""
|
|
|
|
deserialize "" = Just (AssociatedFile Nothing)
|
|
|
|
deserialize f = Just (AssociatedFile (Just (toRawFilePath f)))
|
|
|
|
|
|
|
|
instance TCSerialized RemoteName where
|
|
|
|
serialize n = n
|
|
|
|
deserialize n = Just n
|
|
|
|
|
|
|
|
instance TCSerialized Key where
|
|
|
|
serialize = serializeKey
|
|
|
|
deserialize = deserializeKey
|