rclone special remote

Added rclone special remote, which can be used without needing to install
the git-annex-remote-rclone program. This needs a new version of rclone,
which supports "rclone gitannex".

This is implemented as a variant of an external special remote, that
runs "rclone gitannex" instead of the usual git-annex-remote- command.
Parameterized Remote.External to support that.

Sponsored-by: Luke T. Shumaker on Patreon
This commit is contained in:
Joey Hess 2024-04-17 15:19:42 -04:00
parent 5c542c0382
commit d372553540
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
10 changed files with 114 additions and 48 deletions

View file

@ -15,6 +15,9 @@ git-annex (10.20240228) UNRELEASED; urgency=medium
versions of MinTTY. versions of MinTTY.
* sync, assist, import: Allow -m option to be specified multiple * sync, assist, import: Allow -m option to be specified multiple
times, to provide additional paragraphs for the commit message. times, to provide additional paragraphs for the commit message.
* Added rclone special remote, which can be used without needing
to install the git-annex-remote-rclone program. This needs
a new version of rclone, which supports "rclone gitannex".
-- Joey Hess <id@joeyh.name> Tue, 27 Feb 2024 13:07:10 -0400 -- Joey Hess <id@joeyh.name> Tue, 27 Feb 2024 13:07:10 -0400

View file

@ -9,7 +9,7 @@
{-# LANGUAGE BangPatterns #-} {-# LANGUAGE BangPatterns #-}
{-# LANGUAGE RankNTypes #-} {-# LANGUAGE RankNTypes #-}
module Remote.External (remote) where module Remote.External where
import Remote.External.Types import Remote.External.Types
import Remote.External.AsyncExtension import Remote.External.AsyncExtension
@ -48,10 +48,10 @@ remote :: RemoteType
remote = specialRemoteType $ RemoteType remote = specialRemoteType $ RemoteType
{ typename = "external" { typename = "external"
, enumerate = const (findSpecialRemotes "externaltype") , enumerate = const (findSpecialRemotes "externaltype")
, generate = gen , generate = gen remote Nothing
, configParser = remoteConfigParser , configParser = remoteConfigParser Nothing
, setup = externalSetup , setup = externalSetup Nothing Nothing
, exportSupported = checkExportSupported , exportSupported = checkExportSupported Nothing
, importSupported = importUnsupported , importSupported = importUnsupported
, thirdPartyPopulated = False , thirdPartyPopulated = False
} }
@ -62,15 +62,15 @@ externaltypeField = Accepted "externaltype"
readonlyField :: RemoteConfigField readonlyField :: RemoteConfigField
readonlyField = Accepted "readonly" readonlyField = Accepted "readonly"
gen :: Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> RemoteStateHandle -> Annex (Maybe Remote) gen :: RemoteType -> Maybe ExternalProgram -> Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> RemoteStateHandle -> Annex (Maybe Remote)
gen r u rc gc rs gen rt externalprogram r u rc gc rs
-- readonly mode only downloads urls; does not use external program -- readonly mode only downloads urls; does not use external program
| externaltype == "readonly" = do | externalprogram' == ExternalType "readonly" = do
c <- parsedRemoteConfig remote rc c <- parsedRemoteConfig remote rc
cst <- remoteCost gc c expensiveRemoteCost cst <- remoteCost gc c expensiveRemoteCost
let rmt = mk c cst (pure GloballyAvailable) let rmt = mk c cst (pure GloballyAvailable)
Nothing Nothing
(externalInfo externaltype) (externalInfo externalprogram')
Nothing Nothing
Nothing Nothing
exportUnsupported exportUnsupported
@ -83,7 +83,7 @@ gen r u rc gc rs
rmt rmt
| otherwise = do | otherwise = do
c <- parsedRemoteConfig remote rc c <- parsedRemoteConfig remote rc
external <- newExternal externaltype (Just u) c (Just gc) external <- newExternal externalprogram' (Just u) c (Just gc)
(Git.remoteName r) (Just rs) (Git.remoteName r) (Just rs)
Annex.addCleanupAction (RemoteCleanup u) $ stopExternal external Annex.addCleanupAction (RemoteCleanup u) $ stopExternal external
cst <- getCost external r gc c cst <- getCost external r gc c
@ -150,19 +150,27 @@ gen r u rc gc rs
, appendonly = False , appendonly = False
, untrustworthy = False , untrustworthy = False
, availability = avail , availability = avail
, remotetype = remote , remotetype = rt
{ exportSupported = cheapexportsupported } { exportSupported = cheapexportsupported }
, mkUnavailable = gen r u rc , mkUnavailable =
(gc { remoteAnnexExternalType = Just "!dne!" }) rs let dneprogram = case externalprogram of
Just (ExternalCommand _ _) -> Just (ExternalType "!dne!")
_ -> Nothing
dnegc = gc { remoteAnnexExternalType = Just "!dne!" }
in gen rt dneprogram r u rc dnegc rs
, getInfo = togetinfo , getInfo = togetinfo
, claimUrl = toclaimurl , claimUrl = toclaimurl
, checkUrl = tocheckurl , checkUrl = tocheckurl
, remoteStateHandle = rs , remoteStateHandle = rs
} }
externaltype = fromMaybe (giveup "missing externaltype") (remoteAnnexExternalType gc) externalprogram' = case externalprogram of
Just p -> p
Nothing -> ExternalType $
fromMaybe (giveup "missing externaltype")
(remoteAnnexExternalType gc)
externalSetup :: SetupStage -> Maybe UUID -> Maybe CredPair -> RemoteConfig -> RemoteGitConfig -> Annex (RemoteConfig, UUID) externalSetup :: Maybe ExternalProgram -> Maybe (String, String) -> SetupStage -> Maybe UUID -> Maybe CredPair -> RemoteConfig -> RemoteGitConfig -> Annex (RemoteConfig, UUID)
externalSetup _ mu _ c gc = do externalSetup externalprogram setgitconfig _ mu _ c gc = do
u <- maybe (liftIO genUUID) return mu u <- maybe (liftIO genUUID) return mu
pc <- either giveup return $ parseRemoteConfig c lenientRemoteConfigParser pc <- either giveup return $ parseRemoteConfig c lenientRemoteConfigParser
let readonlyconfig = getRemoteConfigValue readonlyField pc == Just True let readonlyconfig = getRemoteConfigValue readonlyField pc == Just True
@ -182,7 +190,8 @@ externalSetup _ mu _ c gc = do
return c' return c'
else do else do
pc' <- either giveup return $ parseRemoteConfig c' lenientRemoteConfigParser pc' <- either giveup return $ parseRemoteConfig c' lenientRemoteConfigParser
external <- newExternal externaltype (Just u) pc' (Just gc) Nothing Nothing let p = fromMaybe (ExternalType externaltype) externalprogram
external <- newExternal p (Just u) pc' (Just gc) Nothing Nothing
-- Now that we have an external, ask it to LISTCONFIGS, -- Now that we have an external, ask it to LISTCONFIGS,
-- and re-parse the RemoteConfig strictly, so we can -- and re-parse the RemoteConfig strictly, so we can
-- error out if the user provided an unexpected config. -- error out if the user provided an unexpected config.
@ -200,17 +209,20 @@ externalSetup _ mu _ c gc = do
liftIO . atomically . readTMVar . externalConfigChanges liftIO . atomically . readTMVar . externalConfigChanges
return (changes c') return (changes c')
gitConfigSpecialRemote u c'' [("externaltype", externaltype)] gitConfigSpecialRemote u c''
[ fromMaybe ("externaltype", externaltype) setgitconfig ]
return (M.delete readonlyField c'', u) return (M.delete readonlyField c'', u)
checkExportSupported :: ParsedRemoteConfig -> RemoteGitConfig -> Annex Bool checkExportSupported :: Maybe ExternalProgram -> ParsedRemoteConfig -> RemoteGitConfig -> Annex Bool
checkExportSupported c gc = do checkExportSupported Nothing c gc = do
let externaltype = fromMaybe (giveup "Specify externaltype=") $ let externaltype = fromMaybe (giveup "Specify externaltype=") $
remoteAnnexExternalType gc <|> getRemoteConfigValue externaltypeField c remoteAnnexExternalType gc <|> getRemoteConfigValue externaltypeField c
if externaltype == "readonly" if externaltype == "readonly"
then return False then return False
else checkExportSupported' else checkExportSupported (Just (ExternalType externaltype)) c gc
=<< newExternal externaltype Nothing c (Just gc) Nothing Nothing checkExportSupported (Just externalprogram) c gc =
checkExportSupported'
=<< newExternal externalprogram Nothing c (Just gc) Nothing Nothing
checkExportSupported' :: External -> Annex Bool checkExportSupported' :: External -> Annex Bool
checkExportSupported' external = go `catchNonAsync` (const (return False)) checkExportSupported' external = go `catchNonAsync` (const (return False))
@ -658,7 +670,7 @@ startExternal' external = do
n <- succ <$> readTVar (externalLastPid external) n <- succ <$> readTVar (externalLastPid external)
writeTVar (externalLastPid external) n writeTVar (externalLastPid external) n
return n return n
AddonProcess.startExternalAddonProcess basecmd [] pid >>= \case AddonProcess.startExternalAddonProcess externalcmd externalparams pid >>= \case
Left (AddonProcess.ProgramFailure err) -> do Left (AddonProcess.ProgramFailure err) -> do
unusable err unusable err
Left (AddonProcess.ProgramNotInstalled err) -> Left (AddonProcess.ProgramNotInstalled err) ->
@ -667,7 +679,7 @@ startExternal' external = do
[ err [ err
, "This remote has annex-readonly=true, and previous versions of" , "This remote has annex-readonly=true, and previous versions of"
, "git-annex would try to download from it without" , "git-annex would try to download from it without"
, "installing " ++ basecmd ++ ". If you want that, you need to set:" , "installing " ++ externalcmd ++ ". If you want that, you need to set:"
, "git config remote." ++ rname ++ ".annex-externaltype readonly" , "git config remote." ++ rname ++ ".annex-externaltype readonly"
] ]
_ -> unusable err _ -> unusable err
@ -686,7 +698,9 @@ startExternal' external = do
extensions <- startproto st extensions <- startproto st
return (st, extensions) return (st, extensions)
where where
basecmd = "git-annex-remote-" ++ externalType external (externalcmd, externalparams) = case externalProgram external of
ExternalType t -> ("git-annex-remote-" ++ t, [])
ExternalCommand c ps -> (c, ps)
startproto st = do startproto st = do
receiveMessage st external receiveMessage st external
(const Nothing) (const Nothing)
@ -707,13 +721,13 @@ startExternal' external = do
case filter (`notElem` fromExtensionList supportedExtensionList) (fromExtensionList exwanted) of case filter (`notElem` fromExtensionList supportedExtensionList) (fromExtensionList exwanted) of
[] -> return exwanted [] -> return exwanted
exrest -> unusable $ unwords $ exrest -> unusable $ unwords $
[ basecmd [ externalcmd
, "requested extensions that this version of git-annex does not support:" , "requested extensions that this version of git-annex does not support:"
] ++ exrest ] ++ exrest
unusable msg = do unusable msg = do
warning (UnquotedString msg) warning (UnquotedString msg)
giveup ("unable to use external special remote " ++ basecmd) giveup ("unable to use external special remote " ++ externalcmd)
stopExternal :: External -> Annex () stopExternal :: External -> Annex ()
stopExternal external = liftIO $ do stopExternal external = liftIO $ do
@ -825,12 +839,13 @@ getWebUrls key = filter supported <$> getUrls key
where where
supported u = snd (getDownloader u) == WebDownloader supported u = snd (getDownloader u) == WebDownloader
externalInfo :: ExternalType -> Annex [(String, String)] externalInfo :: ExternalProgram -> Annex [(String, String)]
externalInfo et = return [("externaltype", et)] externalInfo (ExternalType et) = return [("externaltype", et)]
externalInfo (ExternalCommand _ _) = return []
getInfoM :: External -> Annex [(String, String)] getInfoM :: External -> Annex [(String, String)]
getInfoM external = (++) getInfoM external = (++)
<$> externalInfo (externalType external) <$> externalInfo (externalProgram external)
<*> handleRequest external GETINFO Nothing (collect []) <*> handleRequest external GETINFO Nothing (collect [])
where where
collect l req = case req of collect l req = case req of
@ -886,8 +901,8 @@ listConfigs external = handleRequest external LISTCONFIGS Nothing (collect [])
UNSUPPORTED_REQUEST -> result Nothing UNSUPPORTED_REQUEST -> result Nothing
_ -> Nothing _ -> Nothing
remoteConfigParser :: RemoteConfig -> Annex RemoteConfigParser remoteConfigParser :: Maybe ExternalProgram -> RemoteConfig -> Annex RemoteConfigParser
remoteConfigParser c remoteConfigParser externalprogram c
-- No need to start the external when there is no config to parse, -- No need to start the external when there is no config to parse,
-- or when everything in the config was already accepted; in those -- or when everything in the config was already accepted; in those
-- cases the lenient parser will do the same thing as the strict -- cases the lenient parser will do the same thing as the strict
@ -899,7 +914,8 @@ remoteConfigParser c
(Nothing, _) -> return lenientRemoteConfigParser (Nothing, _) -> return lenientRemoteConfigParser
(_, Just True) -> return lenientRemoteConfigParser (_, Just True) -> return lenientRemoteConfigParser
(Just externaltype, _) -> do (Just externaltype, _) -> do
external <- newExternal externaltype Nothing pc Nothing Nothing Nothing let p = fromMaybe (ExternalType externaltype) externalprogram
external <- newExternal p Nothing pc Nothing Nothing Nothing
strictRemoteConfigParser external strictRemoteConfigParser external
where where
isproposed (Accepted _) = False isproposed (Accepted _) = False

View file

@ -1,6 +1,6 @@
{- External special remote data types. {- External special remote data types.
- -
- Copyright 2013-2020 Joey Hess <id@joeyh.name> - Copyright 2013-2024 Joey Hess <id@joeyh.name>
- -
- Licensed under the GNU AGPL version 3 or higher. - Licensed under the GNU AGPL version 3 or higher.
-} -}
@ -12,7 +12,7 @@
module Remote.External.Types ( module Remote.External.Types (
External(..), External(..),
newExternal, newExternal,
ExternalType, ExternalProgram(..),
ExternalState(..), ExternalState(..),
PrepareStatus(..), PrepareStatus(..),
ExtensionList(..), ExtensionList(..),
@ -64,7 +64,7 @@ import Text.Read
import qualified Data.ByteString.Short as S (fromShort) import qualified Data.ByteString.Short as S (fromShort)
data External = External data External = External
{ externalType :: ExternalType { externalProgram :: ExternalProgram
, externalUUID :: Maybe UUID , externalUUID :: Maybe UUID
, externalState :: TVar [ExternalState] , externalState :: TVar [ExternalState]
-- ^ Contains states for external special remote processes -- ^ Contains states for external special remote processes
@ -77,9 +77,9 @@ data External = External
, externalAsync :: TMVar ExternalAsync , externalAsync :: TMVar ExternalAsync
} }
newExternal :: ExternalType -> Maybe UUID -> ParsedRemoteConfig -> Maybe RemoteGitConfig -> Maybe RemoteName -> Maybe RemoteStateHandle -> Annex External newExternal :: ExternalProgram -> Maybe UUID -> ParsedRemoteConfig -> Maybe RemoteGitConfig -> Maybe RemoteName -> Maybe RemoteStateHandle -> Annex External
newExternal externaltype u c gc rn rs = liftIO $ External newExternal p u c gc rn rs = liftIO $ External
<$> pure externaltype <$> pure p
<*> pure u <*> pure u
<*> atomically (newTVar []) <*> atomically (newTVar [])
<*> atomically (newTVar 0) <*> atomically (newTVar 0)
@ -89,7 +89,12 @@ newExternal externaltype u c gc rn rs = liftIO $ External
<*> pure rs <*> pure rs
<*> atomically (newTMVar UncheckedExternalAsync) <*> atomically (newTMVar UncheckedExternalAsync)
type ExternalType = String data ExternalProgram
= ExternalType String
-- ^ "git-annex-remote-" is prepended to this to get the program
| ExternalCommand String [CommandParam]
-- ^ to use a program with a different name, and parameters
deriving (Show, Eq)
data ExternalState = ExternalState data ExternalState = ExternalState
{ externalSend :: forall t. (Proto.Sendable t, ToAsyncWrapped t) => t -> IO () { externalSend :: forall t. (Proto.Sendable t, ToAsyncWrapped t) => t -> IO ()

View file

@ -37,6 +37,7 @@ import qualified Remote.Ddar
import qualified Remote.GitLFS import qualified Remote.GitLFS
import qualified Remote.HttpAlso import qualified Remote.HttpAlso
import qualified Remote.Borg import qualified Remote.Borg
import qualified Remote.Rclone
import qualified Remote.Hook import qualified Remote.Hook
import qualified Remote.External import qualified Remote.External
@ -59,6 +60,7 @@ remoteTypes = map adjustExportImportRemoteType
, Remote.GitLFS.remote , Remote.GitLFS.remote
, Remote.HttpAlso.remote , Remote.HttpAlso.remote
, Remote.Borg.remote , Remote.Borg.remote
, Remote.Rclone.remote
, Remote.Hook.remote , Remote.Hook.remote
, Remote.External.remote , Remote.External.remote
] ]

31
Remote/Rclone.hs Normal file
View file

@ -0,0 +1,31 @@
{- Rclone special remote, using "rclone gitannex"
-
- Copyright 2024 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
module Remote.Rclone (remote) where
import Types
import Types.Remote
import Remote.Helper.Special
import Remote.Helper.ExportImport
import Utility.SafeCommand
import qualified Remote.External as External
import Remote.External.Types
remote :: RemoteType
remote = specialRemoteType $ RemoteType
{ typename = "rclone"
, enumerate = const (findSpecialRemotes "rclone")
, generate = External.gen remote p
, configParser = External.remoteConfigParser p
, setup = External.externalSetup p setgitconfig
, exportSupported = External.checkExportSupported p
, importSupported = importUnsupported
, thirdPartyPopulated = False
}
where
p = Just $ ExternalCommand "rclone" [Param "gitannex"]
setgitconfig = Just ("rclone", "true")

View file

@ -1794,6 +1794,11 @@ Remotes are configured using these settings in `.git/config`.
Used to identify Amazon Glacier special remotes. Used to identify Amazon Glacier special remotes.
Normally this is automatically set up by `git annex initremote`. Normally this is automatically set up by `git annex initremote`.
* `remote.<name>.annex-rclone`
Used to identify rclone special remotes.
Normally this is automatically set up by `git annex initremote`.
* `remote.<name>.annex-web` * `remote.<name>.annex-web`
Used to identify web special remotes. Used to identify web special remotes.
@ -1832,7 +1837,7 @@ Remotes are configured using these settings in `.git/config`.
* `remote.<name>.annex-externaltype` * `remote.<name>.annex-externaltype`
Used external special remotes to record the type of the remote. Used by external special remotes to record the type of the remote.
Eg, if this is set to "foo", git-annex will run a "git-annex-remote-foo" Eg, if this is set to "foo", git-annex will run a "git-annex-remote-foo"
program to communicate with the external special remote. program to communicate with the external special remote.

View file

@ -26,6 +26,7 @@ the git history is not stored in them.
* [[git]] * [[git]]
* [[httpalso]] * [[httpalso]]
* [[borg]] * [[borg]]
* [[rclone]]
The above special remotes are built into git-annex, and can be used The above special remotes are built into git-annex, and can be used
to tie git-annex into many cloud services. to tie git-annex into many cloud services.

View file

@ -26,12 +26,12 @@ the time of writing, this includes the following services:
That list is regularly expanding. That list is regularly expanding.
git-annex supports all of those through There are two ways to use rclone as a git-annex special remote.
the use of the [rclone special remote](https://github.com/DanielDent/git-annex-remote-rclone).
Alternatively, rclone recently gained support for being used as a special 1. Install [git-annex-remote-rclone](https://github.com/DanielDent/git-annex-remote-rclone).
remote on its own, without needing installation of the above program. This will work with any versions of rclone and git-annex.
For documentation on using rclone that way, see the output of 2. With a recent version of rclone and git-annex, it is not necessary to
`rclone gitannex -h` or [here](//github.com/rclone/rclone/blob/master/cmd/gitannex/gitannex.md). install anything else, just use `git-annex initremote type=rclone ...`
See their documentation for more concrete examples. For documentation on using rclone that way, see the output of
`rclone gitannex -h` or [here](https://github.com/rclone/rclone/blob/master/cmd/gitannex/gitannex.md).

View file

@ -44,3 +44,5 @@ a wrapper around the external special remote, that makes it use
> I feel that the simplicity of the type=rclone config will pay off in the > I feel that the simplicity of the type=rclone config will pay off in the
> long term, vs short term complication for probably a small subset of users > long term, vs short term complication for probably a small subset of users
> who somehow can upgrade rclone but can't upgrade git-annex. --[[Joey]] > who somehow can upgrade rclone but can't upgrade git-annex. --[[Joey]]
> > [[done]]

View file

@ -900,6 +900,7 @@ Executable git-annex
Remote.List Remote.List
Remote.List.Util Remote.List.Util
Remote.P2P Remote.P2P
Remote.Rclone
Remote.Rsync Remote.Rsync
Remote.Rsync.RsyncUrl Remote.Rsync.RsyncUrl
Remote.S3 Remote.S3