2013-12-25 21:53:24 +00:00
|
|
|
{- External special remote interface.
|
|
|
|
-
|
2022-05-09 17:18:47 +00:00
|
|
|
- Copyright 2013-2022 Joey Hess <id@joeyh.name>
|
2013-12-25 21:53:24 +00:00
|
|
|
-
|
2018-06-08 15:52:20 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2013-12-25 21:53:24 +00:00
|
|
|
-}
|
|
|
|
|
2019-12-02 16:26:33 +00:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2020-08-14 18:40:30 +00:00
|
|
|
{-# LANGUAGE BangPatterns #-}
|
incremental verify for byteRetriever special remotes
Several special remotes verify content while it is being retrieved,
avoiding a separate checksum pass. They are: S3, bup, ddar, and
gcrypt (with a local repository).
Not done when using chunking, yet.
Complicated by Retriever needing to change to be polymorphic. Which in turn
meant RankNTypes is needed, and also needed some code changes. The
change in Remote.External does not change behavior at all but avoids
the type checking failing because of a "rigid, skolem type" which
"would escape its scope". So I refactored slightly to make the type
checker's job easier there.
Unfortunately, directory uses fileRetriever (except when chunked),
so it is not amoung the improved ones. Fixing that would need a way for
FileRetriever to return a Verification. But, since the file retrieved
may be encrypted or chunked, it would be extra work to always
incrementally checksum the file while retrieving it. Hm.
Some other special remotes use fileRetriever, and so don't get incremental
verification, but could be converted to byteRetriever later. One is
GitLFS, which uses downloadConduit, which writes to the file, so could
verify as it goes. Other special remotes like web could too, but don't
use Remote.Helper.Special and so will need to be addressed separately.
Sponsored-by: Dartmouth College's DANDI project
2021-08-11 17:43:30 +00:00
|
|
|
{-# LANGUAGE RankNTypes #-}
|
2019-12-02 16:26:33 +00:00
|
|
|
|
2013-12-25 21:53:24 +00:00
|
|
|
module Remote.External (remote) where
|
|
|
|
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
import Remote.External.Types
|
2020-08-12 19:17:53 +00:00
|
|
|
import Remote.External.AsyncExtension
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
import qualified Annex
|
2016-01-20 20:36:33 +00:00
|
|
|
import Annex.Common
|
2020-08-12 16:30:45 +00:00
|
|
|
import qualified Annex.ExternalAddonProcess as AddonProcess
|
2013-12-25 21:53:24 +00:00
|
|
|
import Types.Remote
|
2017-09-15 20:34:45 +00:00
|
|
|
import Types.Export
|
2014-03-13 23:06:26 +00:00
|
|
|
import Types.CleanupActions
|
2014-12-11 19:32:42 +00:00
|
|
|
import Types.UrlContents
|
2020-01-10 18:10:20 +00:00
|
|
|
import Types.ProposedAccepted
|
2013-12-25 21:53:24 +00:00
|
|
|
import qualified Git
|
|
|
|
import Config
|
2020-01-15 17:01:22 +00:00
|
|
|
import Git.Config (boolConfig)
|
|
|
|
import Annex.SpecialRemote.Config
|
2013-12-25 21:53:24 +00:00
|
|
|
import Remote.Helper.Special
|
2019-02-20 19:55:01 +00:00
|
|
|
import Remote.Helper.ExportImport
|
2015-08-17 15:22:22 +00:00
|
|
|
import Remote.Helper.ReadOnly
|
2013-12-25 21:53:24 +00:00
|
|
|
import Utility.Metered
|
2016-08-03 16:37:12 +00:00
|
|
|
import Types.Transfer
|
2014-01-02 00:12:20 +00:00
|
|
|
import Logs.PreferredContent.Raw
|
add remote state logs
This allows a remote to store a piece of arbitrary state associated with a
key. This is needed to support Tahoe, where the file-cap is calculated from
the data stored in it, and used to retrieve a key later. Glacier also would
be much improved by using this.
GETSTATE and SETSTATE are added to the external special remote protocol.
Note that the state is left as-is even when a key is removed from a remote.
It's up to the remote to decide when it wants to clear the state.
The remote state log, $KEY.log.rmt, is a UUID-based log. However,
rather than using the old UUID-based log format, I created a new variant
of that format. The new varient is more space efficient (since it lacks the
"timestamp=" hack, and easier to parse (and the parser doesn't mess with
whitespace in the value), and avoids compatability cruft in the old one.
This seemed worth cleaning up for these new files, since there could be a
lot of them, while before UUID-based logs were only used for a few log
files at the top of the git-annex branch. The transition code has also
been updated to handle these new UUID-based logs.
This commit was sponsored by Daniel Hofer.
2014-01-03 20:35:57 +00:00
|
|
|
import Logs.RemoteState
|
2014-12-08 17:32:27 +00:00
|
|
|
import Logs.Web
|
2013-12-25 21:53:24 +00:00
|
|
|
import Config.Cost
|
2015-08-17 15:22:22 +00:00
|
|
|
import Annex.Content
|
|
|
|
import Annex.Url
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
import Annex.UUID
|
2022-05-09 17:18:47 +00:00
|
|
|
import Annex.Verify
|
2013-12-27 20:01:43 +00:00
|
|
|
import Creds
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
|
|
|
|
import Control.Concurrent.STM
|
|
|
|
import qualified Data.Map as M
|
add LISTCONFIGS to external special remote protocol
Special remote programs that use GETCONFIG/SETCONFIG are recommended
to implement it.
The description is not yet used, but will be useful later when adding a way
to make initremote list all accepted configs.
configParser now takes a RemoteConfig parameter. Normally, that's not
needed, because configParser returns a parter, it does not parse it
itself. But, it's needed to look at externaltype and work out what
external remote program to run for LISTCONFIGS.
Note that, while externalUUID is changed to a Maybe UUID, checkExportSupported
used to use NoUUID. The code that now checks for Nothing used to behave
in some undefined way if the external program made requests that
triggered it.
Also, note that in externalSetup, once it generates external,
it parses the RemoteConfig strictly. That generates a
ParsedRemoteConfig, which is thrown away. The reason it's ok to throw
that away, is that, if the strict parse succeeded, the result must be
the same as the earlier, lenient parse.
initremote of an external special remote now runs the program three
times. First for LISTCONFIGS, then EXPORTSUPPORTED, and again
LISTCONFIGS+INITREMOTE. It would not be hard to eliminate at least
one of those, and it should be possible to only run the program once.
2020-01-17 19:30:14 +00:00
|
|
|
import qualified Data.Set as S
|
2013-12-25 21:53:24 +00:00
|
|
|
|
|
|
|
remote :: RemoteType
|
add LISTCONFIGS to external special remote protocol
Special remote programs that use GETCONFIG/SETCONFIG are recommended
to implement it.
The description is not yet used, but will be useful later when adding a way
to make initremote list all accepted configs.
configParser now takes a RemoteConfig parameter. Normally, that's not
needed, because configParser returns a parter, it does not parse it
itself. But, it's needed to look at externaltype and work out what
external remote program to run for LISTCONFIGS.
Note that, while externalUUID is changed to a Maybe UUID, checkExportSupported
used to use NoUUID. The code that now checks for Nothing used to behave
in some undefined way if the external program made requests that
triggered it.
Also, note that in externalSetup, once it generates external,
it parses the RemoteConfig strictly. That generates a
ParsedRemoteConfig, which is thrown away. The reason it's ok to throw
that away, is that, if the strict parse succeeded, the result must be
the same as the earlier, lenient parse.
initremote of an external special remote now runs the program three
times. First for LISTCONFIGS, then EXPORTSUPPORTED, and again
LISTCONFIGS+INITREMOTE. It would not be hard to eliminate at least
one of those, and it should be possible to only run the program once.
2020-01-17 19:30:14 +00:00
|
|
|
remote = specialRemoteType $ RemoteType
|
2017-09-07 17:45:31 +00:00
|
|
|
{ typename = "external"
|
|
|
|
, enumerate = const (findSpecialRemotes "externaltype")
|
|
|
|
, generate = gen
|
add LISTCONFIGS to external special remote protocol
Special remote programs that use GETCONFIG/SETCONFIG are recommended
to implement it.
The description is not yet used, but will be useful later when adding a way
to make initremote list all accepted configs.
configParser now takes a RemoteConfig parameter. Normally, that's not
needed, because configParser returns a parter, it does not parse it
itself. But, it's needed to look at externaltype and work out what
external remote program to run for LISTCONFIGS.
Note that, while externalUUID is changed to a Maybe UUID, checkExportSupported
used to use NoUUID. The code that now checks for Nothing used to behave
in some undefined way if the external program made requests that
triggered it.
Also, note that in externalSetup, once it generates external,
it parses the RemoteConfig strictly. That generates a
ParsedRemoteConfig, which is thrown away. The reason it's ok to throw
that away, is that, if the strict parse succeeded, the result must be
the same as the earlier, lenient parse.
initremote of an external special remote now runs the program three
times. First for LISTCONFIGS, then EXPORTSUPPORTED, and again
LISTCONFIGS+INITREMOTE. It would not be hard to eliminate at least
one of those, and it should be possible to only run the program once.
2020-01-17 19:30:14 +00:00
|
|
|
, configParser = remoteConfigParser
|
2017-09-07 17:45:31 +00:00
|
|
|
, setup = externalSetup
|
2017-09-08 18:24:05 +00:00
|
|
|
, exportSupported = checkExportSupported
|
2019-02-20 19:55:01 +00:00
|
|
|
, importSupported = importUnsupported
|
add thirdPartyPopulated interface
This is to support, eg a borg repo as a special remote, which is
populated not by running git-annex commands, but by using borg. Then
git-annex sync lists the content of the remote, learns which files are
annex objects, and treats those as present in the remote.
So, most of the import machinery is reused, to a new purpose. While
normally importtree maintains a remote tracking branch, this does not,
because the files stored in the remote are annex object files, not
user-visible filenames. But, internally, a git tree is still generated,
of the files on the remote that are annex objects. This tree is used
by retrieveExportWithContentIdentifier, etc. As with other import/export
remotes, that the tree is recorded in the export log, and gets grafted
into the git-annex branch.
importKey changed to be able to return Nothing, to indicate when an
ImportLocation is not an annex object and so should be skipped from
being included in the tree.
It did not seem to make sense to have git-annex import do this, since
from the user's perspective, it's not like other imports. So only
git-annex sync does it.
Note that, git-annex sync does not yet download objects from such
remotes that are preferred content. importKeys is run with
content downloading disabled, to avoid getting the content of all
objects. Perhaps what's needed is for seekSyncContent to be run with these
remotes, but I don't know if it will just work (in particular, it needs
to avoid trying to transfer objects to them), so I skipped that for now.
(Untested and unused as of yet.)
This commit was sponsored by Jochen Bartl on Patreon.
2020-12-18 18:52:57 +00:00
|
|
|
, thirdPartyPopulated = False
|
2017-09-07 17:45:31 +00:00
|
|
|
}
|
2013-12-25 21:53:24 +00:00
|
|
|
|
2020-01-15 17:01:22 +00:00
|
|
|
externaltypeField :: RemoteConfigField
|
|
|
|
externaltypeField = Accepted "externaltype"
|
|
|
|
|
|
|
|
readonlyField :: RemoteConfigField
|
|
|
|
readonlyField = Accepted "readonly"
|
|
|
|
|
fix encryption of content to gcrypt and git-lfs
Fix serious regression in gcrypt and encrypted git-lfs remotes.
Since version 7.20200202.7, git-annex incorrectly stored content
on those remotes without encrypting it.
Problem was, Remote.Git enumerates all git remotes, including git-lfs
and gcrypt. It then dispatches to those. So, Remote.List used the
RemoteConfigParser from Remote.Git, instead of from git-lfs or gcrypt,
and that parser does not know about encryption fields, so did not
include them in the ParsedRemoteConfig. (Also didn't include other
fields specific to those remotes, perhaps chunking etc also didn't
get through.)
To fix, had to move RemoteConfig parsing down into the generate methods
of each remote, rather than doing it in Remote.List.
And a consequence of that was that ParsedRemoteConfig had to change to
include the RemoteConfig that got parsed, so that testremote can
generate a new remote based on an existing remote.
(I would have rather fixed this just inside Remote.Git, but that was not
practical, at least not w/o re-doing work that Remote.List already did.
Big ugly mostly mechanical patch seemed preferable to making git-annex
slower.)
2020-02-26 21:20:56 +00:00
|
|
|
gen :: Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> RemoteStateHandle -> Annex (Maybe Remote)
|
|
|
|
gen r u rc gc rs
|
2015-08-17 15:22:22 +00:00
|
|
|
-- readonly mode only downloads urls; does not use external program
|
2020-04-23 18:56:03 +00:00
|
|
|
| externaltype == "readonly" = do
|
fix encryption of content to gcrypt and git-lfs
Fix serious regression in gcrypt and encrypted git-lfs remotes.
Since version 7.20200202.7, git-annex incorrectly stored content
on those remotes without encrypting it.
Problem was, Remote.Git enumerates all git remotes, including git-lfs
and gcrypt. It then dispatches to those. So, Remote.List used the
RemoteConfigParser from Remote.Git, instead of from git-lfs or gcrypt,
and that parser does not know about encryption fields, so did not
include them in the ParsedRemoteConfig. (Also didn't include other
fields specific to those remotes, perhaps chunking etc also didn't
get through.)
To fix, had to move RemoteConfig parsing down into the generate methods
of each remote, rather than doing it in Remote.List.
And a consequence of that was that ParsedRemoteConfig had to change to
include the RemoteConfig that got parsed, so that testremote can
generate a new remote based on an existing remote.
(I would have rather fixed this just inside Remote.Git, but that was not
practical, at least not w/o re-doing work that Remote.List already did.
Big ugly mostly mechanical patch seemed preferable to making git-annex
slower.)
2020-02-26 21:20:56 +00:00
|
|
|
c <- parsedRemoteConfig remote rc
|
2023-01-12 17:42:28 +00:00
|
|
|
cst <- remoteCost gc c expensiveRemoteCost
|
incremental verify for byteRetriever special remotes
Several special remotes verify content while it is being retrieved,
avoiding a separate checksum pass. They are: S3, bup, ddar, and
gcrypt (with a local repository).
Not done when using chunking, yet.
Complicated by Retriever needing to change to be polymorphic. Which in turn
meant RankNTypes is needed, and also needed some code changes. The
change in Remote.External does not change behavior at all but avoids
the type checking failing because of a "rigid, skolem type" which
"would escape its scope". So I refactored slightly to make the type
checker's job easier there.
Unfortunately, directory uses fileRetriever (except when chunked),
so it is not amoung the improved ones. Fixing that would need a way for
FileRetriever to return a Verification. But, since the file retrieved
may be encrypted or chunked, it would be extra work to always
incrementally checksum the file while retrieving it. Hm.
Some other special remotes use fileRetriever, and so don't get incremental
verification, but could be converted to byteRetriever later. One is
GitLFS, which uses downloadConduit, which writes to the file, so could
verify as it goes. Other special remotes like web could too, but don't
use Remote.Helper.Special and so will need to be addressed separately.
Sponsored-by: Dartmouth College's DANDI project
2021-08-11 17:43:30 +00:00
|
|
|
let rmt = mk c cst GloballyAvailable
|
2015-08-17 15:22:22 +00:00
|
|
|
Nothing
|
2018-06-08 15:52:20 +00:00
|
|
|
(externalInfo externaltype)
|
2015-08-17 15:22:22 +00:00
|
|
|
Nothing
|
|
|
|
Nothing
|
2017-09-08 18:24:05 +00:00
|
|
|
exportUnsupported
|
|
|
|
exportUnsupported
|
incremental verify for byteRetriever special remotes
Several special remotes verify content while it is being retrieved,
avoiding a separate checksum pass. They are: S3, bup, ddar, and
gcrypt (with a local repository).
Not done when using chunking, yet.
Complicated by Retriever needing to change to be polymorphic. Which in turn
meant RankNTypes is needed, and also needed some code changes. The
change in Remote.External does not change behavior at all but avoids
the type checking failing because of a "rigid, skolem type" which
"would escape its scope". So I refactored slightly to make the type
checker's job easier there.
Unfortunately, directory uses fileRetriever (except when chunked),
so it is not amoung the improved ones. Fixing that would need a way for
FileRetriever to return a Verification. But, since the file retrieved
may be encrypted or chunked, it would be extra work to always
incrementally checksum the file while retrieving it. Hm.
Some other special remotes use fileRetriever, and so don't get incremental
verification, but could be converted to byteRetriever later. One is
GitLFS, which uses downloadConduit, which writes to the file, so could
verify as it goes. Other special remotes like web could too, but don't
use Remote.Helper.Special and so will need to be addressed separately.
Sponsored-by: Dartmouth College's DANDI project
2021-08-11 17:43:30 +00:00
|
|
|
return $ Just $ specialRemote c
|
|
|
|
readonlyStorer
|
|
|
|
retrieveUrl
|
|
|
|
readonlyRemoveKey
|
|
|
|
checkKeyUrl
|
|
|
|
rmt
|
2015-08-17 15:22:22 +00:00
|
|
|
| otherwise = do
|
fix encryption of content to gcrypt and git-lfs
Fix serious regression in gcrypt and encrypted git-lfs remotes.
Since version 7.20200202.7, git-annex incorrectly stored content
on those remotes without encrypting it.
Problem was, Remote.Git enumerates all git remotes, including git-lfs
and gcrypt. It then dispatches to those. So, Remote.List used the
RemoteConfigParser from Remote.Git, instead of from git-lfs or gcrypt,
and that parser does not know about encryption fields, so did not
include them in the ParsedRemoteConfig. (Also didn't include other
fields specific to those remotes, perhaps chunking etc also didn't
get through.)
To fix, had to move RemoteConfig parsing down into the generate methods
of each remote, rather than doing it in Remote.List.
And a consequence of that was that ParsedRemoteConfig had to change to
include the RemoteConfig that got parsed, so that testremote can
generate a new remote based on an existing remote.
(I would have rather fixed this just inside Remote.Git, but that was not
practical, at least not w/o re-doing work that Remote.List already did.
Big ugly mostly mechanical patch seemed preferable to making git-annex
slower.)
2020-02-26 21:20:56 +00:00
|
|
|
c <- parsedRemoteConfig remote rc
|
2021-01-26 16:42:47 +00:00
|
|
|
external <- newExternal externaltype (Just u) c (Just gc)
|
|
|
|
(Git.remoteName r) (Just rs)
|
2020-12-11 19:28:58 +00:00
|
|
|
Annex.addCleanupAction (RemoteCleanup u) $ stopExternal external
|
2023-01-12 17:42:28 +00:00
|
|
|
cst <- getCost external r gc c
|
2015-08-17 15:22:22 +00:00
|
|
|
avail <- getAvailability external r gc
|
2017-09-28 19:44:45 +00:00
|
|
|
exportsupported <- if exportTree c
|
|
|
|
then checkExportSupported' external
|
|
|
|
else return False
|
2017-09-08 18:24:05 +00:00
|
|
|
let exportactions = if exportsupported
|
2019-01-30 18:55:28 +00:00
|
|
|
then ExportActions
|
2017-09-15 17:15:47 +00:00
|
|
|
{ storeExport = storeExportM external
|
|
|
|
, retrieveExport = retrieveExportM external
|
|
|
|
, removeExport = removeExportM external
|
2020-12-28 18:37:15 +00:00
|
|
|
, versionedExport = False
|
2017-09-15 17:15:47 +00:00
|
|
|
, checkPresentExport = checkPresentExportM external
|
|
|
|
, removeExportDirectory = Just $ removeExportDirectoryM external
|
|
|
|
, renameExport = renameExportM external
|
2017-09-08 18:24:05 +00:00
|
|
|
}
|
|
|
|
else exportUnsupported
|
|
|
|
-- Cheap exportSupported that replaces the expensive
|
|
|
|
-- checkExportSupported now that we've already checked it.
|
|
|
|
let cheapexportsupported = if exportsupported
|
|
|
|
then exportIsSupported
|
|
|
|
else exportUnsupported
|
incremental verify for byteRetriever special remotes
Several special remotes verify content while it is being retrieved,
avoiding a separate checksum pass. They are: S3, bup, ddar, and
gcrypt (with a local repository).
Not done when using chunking, yet.
Complicated by Retriever needing to change to be polymorphic. Which in turn
meant RankNTypes is needed, and also needed some code changes. The
change in Remote.External does not change behavior at all but avoids
the type checking failing because of a "rigid, skolem type" which
"would escape its scope". So I refactored slightly to make the type
checker's job easier there.
Unfortunately, directory uses fileRetriever (except when chunked),
so it is not amoung the improved ones. Fixing that would need a way for
FileRetriever to return a Verification. But, since the file retrieved
may be encrypted or chunked, it would be extra work to always
incrementally checksum the file while retrieving it. Hm.
Some other special remotes use fileRetriever, and so don't get incremental
verification, but could be converted to byteRetriever later. One is
GitLFS, which uses downloadConduit, which writes to the file, so could
verify as it goes. Other special remotes like web could too, but don't
use Remote.Helper.Special and so will need to be addressed separately.
Sponsored-by: Dartmouth College's DANDI project
2021-08-11 17:43:30 +00:00
|
|
|
let rmt = mk c cst avail
|
2017-09-15 17:15:47 +00:00
|
|
|
(Just (whereisKeyM external))
|
2018-06-08 15:52:20 +00:00
|
|
|
(getInfoM external)
|
2017-09-15 17:15:47 +00:00
|
|
|
(Just (claimUrlM external))
|
|
|
|
(Just (checkUrlM external))
|
2017-09-08 18:24:05 +00:00
|
|
|
exportactions
|
|
|
|
cheapexportsupported
|
incremental verify for byteRetriever special remotes
Several special remotes verify content while it is being retrieved,
avoiding a separate checksum pass. They are: S3, bup, ddar, and
gcrypt (with a local repository).
Not done when using chunking, yet.
Complicated by Retriever needing to change to be polymorphic. Which in turn
meant RankNTypes is needed, and also needed some code changes. The
change in Remote.External does not change behavior at all but avoids
the type checking failing because of a "rigid, skolem type" which
"would escape its scope". So I refactored slightly to make the type
checker's job easier there.
Unfortunately, directory uses fileRetriever (except when chunked),
so it is not amoung the improved ones. Fixing that would need a way for
FileRetriever to return a Verification. But, since the file retrieved
may be encrypted or chunked, it would be extra work to always
incrementally checksum the file while retrieving it. Hm.
Some other special remotes use fileRetriever, and so don't get incremental
verification, but could be converted to byteRetriever later. One is
GitLFS, which uses downloadConduit, which writes to the file, so could
verify as it goes. Other special remotes like web could too, but don't
use Remote.Helper.Special and so will need to be addressed separately.
Sponsored-by: Dartmouth College's DANDI project
2021-08-11 17:43:30 +00:00
|
|
|
return $ Just $ specialRemote c
|
|
|
|
(storeKeyM external)
|
|
|
|
(retrieveKeyFileM external)
|
|
|
|
(removeKeyM external)
|
|
|
|
(checkPresentM external)
|
|
|
|
rmt
|
2015-08-17 15:22:22 +00:00
|
|
|
where
|
incremental verify for byteRetriever special remotes
Several special remotes verify content while it is being retrieved,
avoiding a separate checksum pass. They are: S3, bup, ddar, and
gcrypt (with a local repository).
Not done when using chunking, yet.
Complicated by Retriever needing to change to be polymorphic. Which in turn
meant RankNTypes is needed, and also needed some code changes. The
change in Remote.External does not change behavior at all but avoids
the type checking failing because of a "rigid, skolem type" which
"would escape its scope". So I refactored slightly to make the type
checker's job easier there.
Unfortunately, directory uses fileRetriever (except when chunked),
so it is not amoung the improved ones. Fixing that would need a way for
FileRetriever to return a Verification. But, since the file retrieved
may be encrypted or chunked, it would be extra work to always
incrementally checksum the file while retrieving it. Hm.
Some other special remotes use fileRetriever, and so don't get incremental
verification, but could be converted to byteRetriever later. One is
GitLFS, which uses downloadConduit, which writes to the file, so could
verify as it goes. Other special remotes like web could too, but don't
use Remote.Helper.Special and so will need to be addressed separately.
Sponsored-by: Dartmouth College's DANDI project
2021-08-11 17:43:30 +00:00
|
|
|
mk c cst avail towhereis togetinfo toclaimurl tocheckurl exportactions cheapexportsupported =
|
|
|
|
Remote
|
2014-12-16 19:26:13 +00:00
|
|
|
{ uuid = u
|
|
|
|
, cost = cst
|
|
|
|
, name = Git.repoDescribe r
|
|
|
|
, storeKey = storeKeyDummy
|
2020-05-13 21:05:56 +00:00
|
|
|
, retrieveKeyFile = retrieveKeyFileDummy
|
|
|
|
, retrieveKeyFileCheap = Nothing
|
2018-06-21 15:35:27 +00:00
|
|
|
-- External special remotes use many http libraries
|
|
|
|
-- and have no protection against redirects to
|
|
|
|
-- local private web servers, or in some cases
|
|
|
|
-- to file:// urls.
|
2018-09-25 19:32:50 +00:00
|
|
|
, retrievalSecurityPolicy = mkRetrievalVerifiableKeysSecure gc
|
2014-12-16 19:26:13 +00:00
|
|
|
, removeKey = removeKeyDummy
|
2015-10-08 19:01:38 +00:00
|
|
|
, lockContent = Nothing
|
2014-12-16 19:26:13 +00:00
|
|
|
, checkPresent = checkPresentDummy
|
|
|
|
, checkPresentCheap = False
|
2017-09-08 18:24:05 +00:00
|
|
|
, exportActions = exportactions
|
2019-02-20 19:55:01 +00:00
|
|
|
, importActions = importUnsupported
|
2015-08-17 15:22:22 +00:00
|
|
|
, whereisKey = towhereis
|
2014-12-16 19:26:13 +00:00
|
|
|
, remoteFsck = Nothing
|
|
|
|
, repairRepo = Nothing
|
|
|
|
, config = c
|
|
|
|
, localpath = Nothing
|
2018-06-04 18:31:55 +00:00
|
|
|
, getRepo = return r
|
2014-12-16 19:26:13 +00:00
|
|
|
, gitconfig = gc
|
|
|
|
, readonly = False
|
2018-08-30 15:12:18 +00:00
|
|
|
, appendonly = False
|
2020-12-28 19:08:53 +00:00
|
|
|
, untrustworthy = False
|
2014-12-16 19:26:13 +00:00
|
|
|
, availability = avail
|
2017-09-08 18:24:05 +00:00
|
|
|
, remotetype = remote
|
|
|
|
{ exportSupported = cheapexportsupported }
|
fix encryption of content to gcrypt and git-lfs
Fix serious regression in gcrypt and encrypted git-lfs remotes.
Since version 7.20200202.7, git-annex incorrectly stored content
on those remotes without encrypting it.
Problem was, Remote.Git enumerates all git remotes, including git-lfs
and gcrypt. It then dispatches to those. So, Remote.List used the
RemoteConfigParser from Remote.Git, instead of from git-lfs or gcrypt,
and that parser does not know about encryption fields, so did not
include them in the ParsedRemoteConfig. (Also didn't include other
fields specific to those remotes, perhaps chunking etc also didn't
get through.)
To fix, had to move RemoteConfig parsing down into the generate methods
of each remote, rather than doing it in Remote.List.
And a consequence of that was that ParsedRemoteConfig had to change to
include the RemoteConfig that got parsed, so that testremote can
generate a new remote based on an existing remote.
(I would have rather fixed this just inside Remote.Git, but that was not
practical, at least not w/o re-doing work that Remote.List already did.
Big ugly mostly mechanical patch seemed preferable to making git-annex
slower.)
2020-02-26 21:20:56 +00:00
|
|
|
, mkUnavailable = gen r u rc
|
add RemoteStateHandle
This solves the problem of sameas remotes trampling over per-remote
state. Used for:
* per-remote state, of course
* per-remote metadata, also of course
* per-remote content identifiers, because two remote implementations
could in theory generate the same content identifier for two different
peices of content
While chunk logs are per-remote data, they don't use this, because the
number and size of chunks stored is a common property across sameas
remotes.
External special remote had a complication, where it was theoretically
possible for a remote to send SETSTATE or GETSTATE during INITREMOTE or
EXPORTSUPPORTED. Since the uuid of the remote is typically generate in
Remote.setup, it would only be possible to pass a Maybe
RemoteStateHandle into it, and it would otherwise have to construct its
own. Rather than go that route, I decided to send an ERROR in this case.
It seems unlikely that any existing external special remote will be
affected. They would have to make up a git-annex key, and set state for
some reason during INITREMOTE. I can imagine such a hack, but it doesn't
seem worth complicating the code in such an ugly way to support it.
Unfortunately, both TestRemote and Annex.Import needed the Remote
to have a new field added that holds its RemoteStateHandle.
2019-10-14 16:33:27 +00:00
|
|
|
(gc { remoteAnnexExternalType = Just "!dne!" }) rs
|
2018-06-08 15:52:20 +00:00
|
|
|
, getInfo = togetinfo
|
2015-08-17 15:22:22 +00:00
|
|
|
, claimUrl = toclaimurl
|
|
|
|
, checkUrl = tocheckurl
|
add RemoteStateHandle
This solves the problem of sameas remotes trampling over per-remote
state. Used for:
* per-remote state, of course
* per-remote metadata, also of course
* per-remote content identifiers, because two remote implementations
could in theory generate the same content identifier for two different
peices of content
While chunk logs are per-remote data, they don't use this, because the
number and size of chunks stored is a common property across sameas
remotes.
External special remote had a complication, where it was theoretically
possible for a remote to send SETSTATE or GETSTATE during INITREMOTE or
EXPORTSUPPORTED. Since the uuid of the remote is typically generate in
Remote.setup, it would only be possible to pass a Maybe
RemoteStateHandle into it, and it would otherwise have to construct its
own. Rather than go that route, I decided to send an ERROR in this case.
It seems unlikely that any existing external special remote will be
affected. They would have to make up a git-annex key, and set state for
some reason during INITREMOTE. I can imagine such a hack, but it doesn't
seem worth complicating the code in such an ugly way to support it.
Unfortunately, both TestRemote and Annex.Import needed the Remote
to have a new field added that holds its RemoteStateHandle.
2019-10-14 16:33:27 +00:00
|
|
|
, remoteStateHandle = rs
|
2014-12-16 19:26:13 +00:00
|
|
|
}
|
2016-11-16 01:29:54 +00:00
|
|
|
externaltype = fromMaybe (giveup "missing externaltype") (remoteAnnexExternalType gc)
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
|
2017-02-07 18:35:58 +00:00
|
|
|
externalSetup :: SetupStage -> Maybe UUID -> Maybe CredPair -> RemoteConfig -> RemoteGitConfig -> Annex (RemoteConfig, UUID)
|
|
|
|
externalSetup _ mu _ c gc = do
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
u <- maybe (liftIO genUUID) return mu
|
add LISTCONFIGS to external special remote protocol
Special remote programs that use GETCONFIG/SETCONFIG are recommended
to implement it.
The description is not yet used, but will be useful later when adding a way
to make initremote list all accepted configs.
configParser now takes a RemoteConfig parameter. Normally, that's not
needed, because configParser returns a parter, it does not parse it
itself. But, it's needed to look at externaltype and work out what
external remote program to run for LISTCONFIGS.
Note that, while externalUUID is changed to a Maybe UUID, checkExportSupported
used to use NoUUID. The code that now checks for Nothing used to behave
in some undefined way if the external program made requests that
triggered it.
Also, note that in externalSetup, once it generates external,
it parses the RemoteConfig strictly. That generates a
ParsedRemoteConfig, which is thrown away. The reason it's ok to throw
that away, is that, if the strict parse succeeded, the result must be
the same as the earlier, lenient parse.
initremote of an external special remote now runs the program three
times. First for LISTCONFIGS, then EXPORTSUPPORTED, and again
LISTCONFIGS+INITREMOTE. It would not be hard to eliminate at least
one of those, and it should be possible to only run the program once.
2020-01-17 19:30:14 +00:00
|
|
|
pc <- either giveup return $ parseRemoteConfig c lenientRemoteConfigParser
|
2020-04-23 18:56:03 +00:00
|
|
|
let readonlyconfig = getRemoteConfigValue readonlyField pc == Just True
|
|
|
|
let externaltype = if readonlyconfig
|
|
|
|
then "readonly"
|
|
|
|
else fromMaybe (giveup "Specify externaltype=") $
|
|
|
|
getRemoteConfigValue externaltypeField pc
|
2016-05-23 21:27:15 +00:00
|
|
|
(c', _encsetup) <- encryptionSetup c gc
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
|
2020-04-23 18:56:03 +00:00
|
|
|
c'' <- if readonlyconfig
|
|
|
|
then do
|
|
|
|
-- Setting annex-readonly is not really necessary
|
|
|
|
-- anymore, but older versions of git-annex used
|
|
|
|
-- this, not externaltype=readonly, so still set
|
|
|
|
-- it.
|
2020-02-19 17:45:11 +00:00
|
|
|
setConfig (remoteAnnexConfig (fromJust (lookupName c)) "readonly") (boolConfig True)
|
2015-08-17 15:22:22 +00:00
|
|
|
return c'
|
2020-04-23 18:56:03 +00:00
|
|
|
else do
|
add LISTCONFIGS to external special remote protocol
Special remote programs that use GETCONFIG/SETCONFIG are recommended
to implement it.
The description is not yet used, but will be useful later when adding a way
to make initremote list all accepted configs.
configParser now takes a RemoteConfig parameter. Normally, that's not
needed, because configParser returns a parter, it does not parse it
itself. But, it's needed to look at externaltype and work out what
external remote program to run for LISTCONFIGS.
Note that, while externalUUID is changed to a Maybe UUID, checkExportSupported
used to use NoUUID. The code that now checks for Nothing used to behave
in some undefined way if the external program made requests that
triggered it.
Also, note that in externalSetup, once it generates external,
it parses the RemoteConfig strictly. That generates a
ParsedRemoteConfig, which is thrown away. The reason it's ok to throw
that away, is that, if the strict parse succeeded, the result must be
the same as the earlier, lenient parse.
initremote of an external special remote now runs the program three
times. First for LISTCONFIGS, then EXPORTSUPPORTED, and again
LISTCONFIGS+INITREMOTE. It would not be hard to eliminate at least
one of those, and it should be possible to only run the program once.
2020-01-17 19:30:14 +00:00
|
|
|
pc' <- either giveup return $ parseRemoteConfig c' lenientRemoteConfigParser
|
2021-01-26 16:42:47 +00:00
|
|
|
external <- newExternal externaltype (Just u) pc' (Just gc) Nothing Nothing
|
add LISTCONFIGS to external special remote protocol
Special remote programs that use GETCONFIG/SETCONFIG are recommended
to implement it.
The description is not yet used, but will be useful later when adding a way
to make initremote list all accepted configs.
configParser now takes a RemoteConfig parameter. Normally, that's not
needed, because configParser returns a parter, it does not parse it
itself. But, it's needed to look at externaltype and work out what
external remote program to run for LISTCONFIGS.
Note that, while externalUUID is changed to a Maybe UUID, checkExportSupported
used to use NoUUID. The code that now checks for Nothing used to behave
in some undefined way if the external program made requests that
triggered it.
Also, note that in externalSetup, once it generates external,
it parses the RemoteConfig strictly. That generates a
ParsedRemoteConfig, which is thrown away. The reason it's ok to throw
that away, is that, if the strict parse succeeded, the result must be
the same as the earlier, lenient parse.
initremote of an external special remote now runs the program three
times. First for LISTCONFIGS, then EXPORTSUPPORTED, and again
LISTCONFIGS+INITREMOTE. It would not be hard to eliminate at least
one of those, and it should be possible to only run the program once.
2020-01-17 19:30:14 +00:00
|
|
|
-- Now that we have an external, ask it to LISTCONFIGS,
|
|
|
|
-- and re-parse the RemoteConfig strictly, so we can
|
|
|
|
-- error out if the user provided an unexpected config.
|
2020-01-17 21:23:19 +00:00
|
|
|
_ <- either giveup return . parseRemoteConfig c'
|
2020-01-17 21:13:44 +00:00
|
|
|
=<< strictRemoteConfigParser external
|
2020-07-29 19:23:18 +00:00
|
|
|
handleRequest external INITREMOTE Nothing $ \case
|
2018-06-08 15:52:20 +00:00
|
|
|
INITREMOTE_SUCCESS -> result ()
|
2020-02-27 18:09:18 +00:00
|
|
|
INITREMOTE_FAILURE errmsg -> Just $ giveup $
|
|
|
|
respErrorMessage "INITREMOTE" errmsg
|
2015-08-17 15:22:22 +00:00
|
|
|
_ -> Nothing
|
2020-01-15 17:01:22 +00:00
|
|
|
-- Any config changes the external made before
|
|
|
|
-- responding to INITREMOTE need to be applied to
|
|
|
|
-- the RemoteConfig.
|
|
|
|
changes <- withExternalState external $
|
2020-08-14 18:40:30 +00:00
|
|
|
liftIO . atomically . readTMVar . externalConfigChanges
|
2020-01-15 17:01:22 +00:00
|
|
|
return (changes c')
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
|
2018-03-27 16:41:57 +00:00
|
|
|
gitConfigSpecialRemote u c'' [("externaltype", externaltype)]
|
external: stop storing readonly=true in remote.log
readonly=true is used to make an external special remote that does not
need the external program to be installed. It was stored in the
remote.log by default, and so every time it was specified in an
enableremote or initremote, whatever value was used became the new
default for subsequent enableremotes of that remote.
That was surprising, and I consider it to be a bug.
It does not make much sense to pass it to initremote because then how
would you populate that remote with anything? You would have to
enableremote elsewhere, and store content there. I'm assuming nobody
used it that way.
Someone might rely on passing it to enableremote once, and then that
being inherited in other clones. But that is not how it's documented to
be used. It is barely documented in git-annex at all, only in the
external special remote protocol, and the documentation there says to
"Document that this external special remote can be used in readonly
mode." (by the user of it passing readonly=true to enableremote). The
one external special remote that I know of that does document that is
<https://github.com/bgilbert/gcsannex> (the one that motivated adding
it). That one's docs do say to pass it to enableremote.
So, it seemed safe to make this behavior change. If someone was in fact
relying on one of those behaviors, all their current repos will still
work as they configured them (although they will need to deal
with the related change in 9f3c2dfedae7ec840365f9578763209abae1005c).
In new clones, they will find enableremote fails, complaining the
external program is not in path. An easy enough problem to recover from.
2020-04-23 18:59:38 +00:00
|
|
|
return (M.delete readonlyField c'', u)
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
|
2020-01-15 17:01:22 +00:00
|
|
|
checkExportSupported :: ParsedRemoteConfig -> RemoteGitConfig -> Annex Bool
|
2017-09-08 18:24:05 +00:00
|
|
|
checkExportSupported c gc = do
|
|
|
|
let externaltype = fromMaybe (giveup "Specify externaltype=") $
|
2020-01-15 17:01:22 +00:00
|
|
|
remoteAnnexExternalType gc <|> getRemoteConfigValue externaltypeField c
|
2020-04-23 18:56:03 +00:00
|
|
|
if externaltype == "readonly"
|
|
|
|
then return False
|
|
|
|
else checkExportSupported'
|
2021-01-26 16:42:47 +00:00
|
|
|
=<< newExternal externaltype Nothing c (Just gc) Nothing Nothing
|
2017-09-08 18:24:05 +00:00
|
|
|
|
|
|
|
checkExportSupported' :: External -> Annex Bool
|
2017-09-28 19:44:45 +00:00
|
|
|
checkExportSupported' external = go `catchNonAsync` (const (return False))
|
|
|
|
where
|
|
|
|
go = handleRequest external EXPORTSUPPORTED Nothing $ \resp -> case resp of
|
2018-06-08 15:52:20 +00:00
|
|
|
EXPORTSUPPORTED_SUCCESS -> result True
|
|
|
|
EXPORTSUPPORTED_FAILURE -> result False
|
|
|
|
UNSUPPORTED_REQUEST -> result False
|
2017-09-08 18:24:05 +00:00
|
|
|
_ -> Nothing
|
|
|
|
|
2017-09-15 17:15:47 +00:00
|
|
|
storeKeyM :: External -> Storer
|
2020-05-14 18:08:09 +00:00
|
|
|
storeKeyM external = fileStorer $ \k f p ->
|
|
|
|
either giveup return =<< go k f p
|
2020-05-13 18:03:00 +00:00
|
|
|
where
|
|
|
|
go k f p = handleRequestKey external (\sk -> TRANSFER Upload sk f) k (Just p) $ \resp ->
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
case resp of
|
2020-05-13 18:03:00 +00:00
|
|
|
TRANSFER_SUCCESS Upload k' | k == k' ->
|
|
|
|
result (Right ())
|
2013-12-27 16:21:55 +00:00
|
|
|
TRANSFER_FAILURE Upload k' errmsg | k == k' ->
|
2020-05-13 18:03:00 +00:00
|
|
|
result (Left (respErrorMessage "TRANSFER" errmsg))
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
_ -> Nothing
|
|
|
|
|
2017-09-15 17:15:47 +00:00
|
|
|
retrieveKeyFileM :: External -> Retriever
|
2020-05-14 18:08:09 +00:00
|
|
|
retrieveKeyFileM external = fileRetriever $ \d k p ->
|
|
|
|
either giveup return =<< go d k p
|
|
|
|
where
|
2021-08-16 20:22:00 +00:00
|
|
|
go d k p = handleRequestKey external (\sk -> TRANSFER Download sk (fromRawFilePath d)) k (Just p) $ \resp ->
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
case resp of
|
|
|
|
TRANSFER_SUCCESS Download k'
|
2020-05-14 18:08:09 +00:00
|
|
|
| k == k' -> result $ Right ()
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
TRANSFER_FAILURE Download k' errmsg
|
2020-05-14 18:08:09 +00:00
|
|
|
| k == k' -> result $ Left $
|
2020-02-27 18:09:18 +00:00
|
|
|
respErrorMessage "TRANSFER" errmsg
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
_ -> Nothing
|
2013-12-25 21:53:24 +00:00
|
|
|
|
2017-09-15 17:15:47 +00:00
|
|
|
removeKeyM :: External -> Remover
|
2020-05-14 18:08:09 +00:00
|
|
|
removeKeyM external k = either giveup return =<< go
|
|
|
|
where
|
|
|
|
go = handleRequestKey external REMOVE k Nothing $ \resp ->
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
case resp of
|
|
|
|
REMOVE_SUCCESS k'
|
2020-05-14 18:08:09 +00:00
|
|
|
| k == k' -> result $ Right ()
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
REMOVE_FAILURE k' errmsg
|
2020-05-14 18:08:09 +00:00
|
|
|
| k == k' -> result $ Left $
|
|
|
|
respErrorMessage "REMOVE" errmsg
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
_ -> Nothing
|
|
|
|
|
2017-09-15 17:15:47 +00:00
|
|
|
checkPresentM :: External -> CheckPresent
|
|
|
|
checkPresentM external k = either giveup id <$> go
|
2013-12-25 21:53:24 +00:00
|
|
|
where
|
external: nice error message for keys with spaces in their name
External special remotes will refuse to operate on keys with spaces in
their names. That has never worked correctly due to the design of the
external special remote protocol. Display an error message suggesting
migration.
Not super happy with this, but it's a pragmatic solution. Better than
complicating the external special remote interface and all external special
remotes.
Note that I only made it use SafeKey in Request, not Response. git-annex
does not construct a Response, so that would not add any safety. And
presumably, if git-annex avoids feeding any such keys to an external
special remote, it will never have a reason to make a Response using such a
key. If it did, it would result in a protocol error anyway.
There's still a Serializeable instance for Key; it's used by P2P.Protocol.
There, the Key is always in the final position, so it's ok if it contains
spaces.
Note that the protocol documentation has been fixed to say that the File
may contain spaces. One way that can happen, even though the Key can't,
is when using direct mode, and the work tree filename contains spaces.
When sending such a file to the external special remote the worktree
filename is used.
This commit was sponsored by Thom May on Patreon.
2017-08-17 20:08:35 +00:00
|
|
|
go = handleRequestKey external CHECKPRESENT k Nothing $ \resp ->
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
case resp of
|
|
|
|
CHECKPRESENT_SUCCESS k'
|
2018-06-08 15:52:20 +00:00
|
|
|
| k' == k -> result $ Right True
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
CHECKPRESENT_FAILURE k'
|
2018-06-08 15:52:20 +00:00
|
|
|
| k' == k -> result $ Right False
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
CHECKPRESENT_UNKNOWN k' errmsg
|
2020-02-27 18:09:18 +00:00
|
|
|
| k' == k -> result $ Left $
|
|
|
|
respErrorMessage "CHECKPRESENT" errmsg
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
_ -> Nothing
|
|
|
|
|
2017-09-15 17:15:47 +00:00
|
|
|
whereisKeyM :: External -> Key -> Annex [String]
|
|
|
|
whereisKeyM external k = handleRequestKey external WHEREIS k Nothing $ \resp -> case resp of
|
2018-06-08 15:52:20 +00:00
|
|
|
WHEREIS_SUCCESS s -> result [s]
|
|
|
|
WHEREIS_FAILURE -> result []
|
|
|
|
UNSUPPORTED_REQUEST -> result []
|
2015-08-13 21:26:09 +00:00
|
|
|
_ -> Nothing
|
|
|
|
|
2020-05-15 16:17:15 +00:00
|
|
|
storeExportM :: External -> FilePath -> Key -> ExportLocation -> MeterUpdate -> Annex ()
|
|
|
|
storeExportM external f k loc p = either giveup return =<< go
|
|
|
|
where
|
|
|
|
go = handleRequestExport external loc req k (Just p) $ \resp -> case resp of
|
|
|
|
TRANSFER_SUCCESS Upload k' | k == k' -> result $ Right ()
|
2017-09-08 18:24:05 +00:00
|
|
|
TRANSFER_FAILURE Upload k' errmsg | k == k' ->
|
2020-05-15 16:17:15 +00:00
|
|
|
result $ Left $ respErrorMessage "TRANSFER" errmsg
|
|
|
|
UNSUPPORTED_REQUEST ->
|
|
|
|
result $ Left "TRANSFEREXPORT not implemented by external special remote"
|
2017-09-08 18:24:05 +00:00
|
|
|
_ -> Nothing
|
|
|
|
req sk = TRANSFEREXPORT Upload sk f
|
|
|
|
|
2022-05-09 16:25:04 +00:00
|
|
|
retrieveExportM :: External -> Key -> ExportLocation -> FilePath -> MeterUpdate -> Annex Verification
|
2022-05-09 17:18:47 +00:00
|
|
|
retrieveExportM external k loc dest p = do
|
|
|
|
verifyKeyContentIncrementally AlwaysVerify k $ \iv ->
|
|
|
|
tailVerify iv (toRawFilePath dest) $
|
|
|
|
either giveup return =<< go
|
2020-05-15 16:51:09 +00:00
|
|
|
where
|
|
|
|
go = handleRequestExport external loc req k (Just p) $ \resp -> case resp of
|
2017-09-08 18:24:05 +00:00
|
|
|
TRANSFER_SUCCESS Download k'
|
2020-05-15 16:51:09 +00:00
|
|
|
| k == k' -> result $ Right ()
|
2017-09-08 18:24:05 +00:00
|
|
|
TRANSFER_FAILURE Download k' errmsg
|
2020-05-15 16:51:09 +00:00
|
|
|
| k == k' -> result $ Left $ respErrorMessage "TRANSFER" errmsg
|
|
|
|
UNSUPPORTED_REQUEST ->
|
|
|
|
result $ Left "TRANSFEREXPORT not implemented by external special remote"
|
2017-09-08 18:24:05 +00:00
|
|
|
_ -> Nothing
|
2022-05-09 17:18:47 +00:00
|
|
|
req sk = TRANSFEREXPORT Download sk dest
|
2017-09-08 18:24:05 +00:00
|
|
|
|
2017-09-15 17:15:47 +00:00
|
|
|
checkPresentExportM :: External -> Key -> ExportLocation -> Annex Bool
|
|
|
|
checkPresentExportM external k loc = either giveup id <$> go
|
|
|
|
where
|
|
|
|
go = handleRequestExport external loc CHECKPRESENTEXPORT k Nothing $ \resp -> case resp of
|
|
|
|
CHECKPRESENT_SUCCESS k'
|
2018-06-08 15:52:20 +00:00
|
|
|
| k' == k -> result $ Right True
|
2017-09-15 17:15:47 +00:00
|
|
|
CHECKPRESENT_FAILURE k'
|
2018-06-08 15:52:20 +00:00
|
|
|
| k' == k -> result $ Right False
|
2017-09-15 17:15:47 +00:00
|
|
|
CHECKPRESENT_UNKNOWN k' errmsg
|
2020-02-27 18:09:18 +00:00
|
|
|
| k' == k -> result $ Left $
|
|
|
|
respErrorMessage "CHECKPRESENT" errmsg
|
2018-06-08 15:52:20 +00:00
|
|
|
UNSUPPORTED_REQUEST -> result $
|
2017-09-15 17:15:47 +00:00
|
|
|
Left "CHECKPRESENTEXPORT not implemented by external special remote"
|
|
|
|
_ -> Nothing
|
|
|
|
|
2020-05-15 18:11:59 +00:00
|
|
|
removeExportM :: External -> Key -> ExportLocation -> Annex ()
|
|
|
|
removeExportM external k loc = either giveup return =<< go
|
|
|
|
where
|
|
|
|
go = handleRequestExport external loc REMOVEEXPORT k Nothing $ \resp -> case resp of
|
2017-09-08 18:24:05 +00:00
|
|
|
REMOVE_SUCCESS k'
|
2020-05-15 18:11:59 +00:00
|
|
|
| k == k' -> result $ Right ()
|
2017-09-08 18:24:05 +00:00
|
|
|
REMOVE_FAILURE k' errmsg
|
2020-05-15 18:11:59 +00:00
|
|
|
| k == k' -> result $ Left $ respErrorMessage "REMOVE" errmsg
|
|
|
|
UNSUPPORTED_REQUEST -> result $
|
|
|
|
Left $ "REMOVEEXPORT not implemented by external special remote"
|
2017-09-08 18:24:05 +00:00
|
|
|
_ -> Nothing
|
|
|
|
|
2020-05-15 18:32:45 +00:00
|
|
|
removeExportDirectoryM :: External -> ExportDirectory -> Annex ()
|
|
|
|
removeExportDirectoryM external dir = either giveup return =<< go
|
2017-09-08 18:24:05 +00:00
|
|
|
where
|
2020-05-15 18:32:45 +00:00
|
|
|
go = handleRequest external req Nothing $ \resp -> case resp of
|
|
|
|
REMOVEEXPORTDIRECTORY_SUCCESS -> result $ Right ()
|
|
|
|
REMOVEEXPORTDIRECTORY_FAILURE -> result $
|
|
|
|
Left "failed to remove directory"
|
|
|
|
UNSUPPORTED_REQUEST -> result $ Right ()
|
|
|
|
_ -> Nothing
|
2017-09-15 17:15:47 +00:00
|
|
|
req = REMOVEEXPORTDIRECTORY dir
|
2017-09-08 18:24:05 +00:00
|
|
|
|
2020-05-15 19:05:52 +00:00
|
|
|
renameExportM :: External -> Key -> ExportLocation -> ExportLocation -> Annex (Maybe ())
|
|
|
|
renameExportM external k src dest = either giveup return =<< go
|
|
|
|
where
|
|
|
|
go = handleRequestExport external src req k Nothing $ \resp -> case resp of
|
2017-09-08 18:24:05 +00:00
|
|
|
RENAMEEXPORT_SUCCESS k'
|
2020-05-15 19:05:52 +00:00
|
|
|
| k' == k -> result $ Right (Just ())
|
2017-09-08 18:24:05 +00:00
|
|
|
RENAMEEXPORT_FAILURE k'
|
2020-05-15 19:05:52 +00:00
|
|
|
| k' == k -> result $ Left "failed to rename exported file"
|
|
|
|
UNSUPPORTED_REQUEST -> result (Right Nothing)
|
2017-09-08 18:24:05 +00:00
|
|
|
_ -> Nothing
|
|
|
|
req sk = RENAMEEXPORT sk dest
|
|
|
|
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
{- Sends a Request to the external remote, and waits for it to generate
|
2013-12-27 06:08:29 +00:00
|
|
|
- a Response. That is fed into the responsehandler, which should return
|
|
|
|
- the action to run for it (or Nothing if there's a protocol error).
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
-
|
|
|
|
- While the external remote is processing the Request, it may send
|
|
|
|
- any number of RemoteRequests, that are handled here.
|
|
|
|
-
|
2016-09-30 18:29:02 +00:00
|
|
|
- An external remote process can only handle one request at a time.
|
|
|
|
- Concurrent requests will start up additional processes.
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
-
|
2013-12-29 17:39:25 +00:00
|
|
|
- May throw exceptions, for example on protocol errors, or
|
|
|
|
- when the repository cannot be used.
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
-}
|
2018-06-08 15:52:20 +00:00
|
|
|
handleRequest :: External -> Request -> Maybe MeterUpdate -> ResponseHandler a -> Annex a
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
handleRequest external req mp responsehandler =
|
2016-09-30 18:29:02 +00:00
|
|
|
withExternalState external $ \st ->
|
|
|
|
handleRequest' st external req mp responsehandler
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
|
2018-06-08 15:52:20 +00:00
|
|
|
handleRequestKey :: External -> (SafeKey -> Request) -> Key -> Maybe MeterUpdate -> ResponseHandler a -> Annex a
|
2023-03-28 19:21:10 +00:00
|
|
|
handleRequestKey external mkreq k mp responsehandler =
|
|
|
|
withSafeKey k $ \sk -> handleRequest external (mkreq sk) mp responsehandler
|
|
|
|
|
|
|
|
withSafeKey :: Key -> (SafeKey -> Annex a) -> Annex a
|
|
|
|
withSafeKey k a = case mkSafeKey k of
|
|
|
|
Right sk -> a sk
|
external: nice error message for keys with spaces in their name
External special remotes will refuse to operate on keys with spaces in
their names. That has never worked correctly due to the design of the
external special remote protocol. Display an error message suggesting
migration.
Not super happy with this, but it's a pragmatic solution. Better than
complicating the external special remote interface and all external special
remotes.
Note that I only made it use SafeKey in Request, not Response. git-annex
does not construct a Response, so that would not add any safety. And
presumably, if git-annex avoids feeding any such keys to an external
special remote, it will never have a reason to make a Response using such a
key. If it did, it would result in a protocol error anyway.
There's still a Serializeable instance for Key; it's used by P2P.Protocol.
There, the Key is always in the final position, so it's ok if it contains
spaces.
Note that the protocol documentation has been fixed to say that the File
may contain spaces. One way that can happen, even though the Key can't,
is when using direct mode, and the work tree filename contains spaces.
When sending such a file to the external special remote the worktree
filename is used.
This commit was sponsored by Thom May on Patreon.
2017-08-17 20:08:35 +00:00
|
|
|
Left e -> giveup e
|
|
|
|
|
2017-09-08 18:24:05 +00:00
|
|
|
{- Export location is first sent in an EXPORT message before
|
|
|
|
- the main request. This is done because the ExportLocation can
|
|
|
|
- contain spaces etc. -}
|
2018-06-08 15:52:20 +00:00
|
|
|
handleRequestExport :: External -> ExportLocation -> (SafeKey -> Request) -> Key -> Maybe MeterUpdate -> ResponseHandler a -> Annex a
|
2023-03-28 19:21:10 +00:00
|
|
|
handleRequestExport external loc mkreq k mp responsehandler =
|
|
|
|
withSafeKey k $ \sk ->
|
|
|
|
-- Both the EXPORT and subsequent request must be sent to the
|
|
|
|
-- same external process, so run both with the same external
|
|
|
|
-- state.
|
|
|
|
withExternalState external $ \st -> do
|
|
|
|
checkPrepared st external
|
|
|
|
sendMessage st (EXPORT loc)
|
|
|
|
handleRequest' st external (mkreq sk) mp responsehandler
|
2017-09-08 18:24:05 +00:00
|
|
|
|
2018-06-08 15:52:20 +00:00
|
|
|
handleRequest' :: ExternalState -> External -> Request -> Maybe MeterUpdate -> ResponseHandler a -> Annex a
|
2016-09-30 18:29:02 +00:00
|
|
|
handleRequest' st external req mp responsehandler
|
2013-12-29 17:39:25 +00:00
|
|
|
| needsPREPARE req = do
|
2016-09-30 18:29:02 +00:00
|
|
|
checkPrepared st external
|
2013-12-29 17:39:25 +00:00
|
|
|
go
|
|
|
|
| otherwise = go
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
where
|
2014-10-09 18:53:13 +00:00
|
|
|
go = do
|
2020-07-29 19:23:18 +00:00
|
|
|
sendMessage st req
|
2013-12-29 17:39:25 +00:00
|
|
|
loop
|
2016-09-30 18:29:02 +00:00
|
|
|
loop = receiveMessage st external responsehandler
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
(\rreq -> Just $ handleRemoteRequest rreq >> loop)
|
2020-08-12 16:04:12 +00:00
|
|
|
(\msg -> Just $ handleExceptionalMessage msg >> loop)
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
|
|
|
|
handleRemoteRequest (PROGRESS bytesprocessed) =
|
|
|
|
maybe noop (\a -> liftIO $ a bytesprocessed) mp
|
|
|
|
handleRemoteRequest (DIRHASH k) =
|
2019-12-11 18:12:22 +00:00
|
|
|
send $ VALUE $ fromRawFilePath $ hashDirMixed def k
|
2016-05-03 17:36:59 +00:00
|
|
|
handleRemoteRequest (DIRHASH_LOWER k) =
|
2019-12-11 18:12:22 +00:00
|
|
|
send $ VALUE $ fromRawFilePath $ hashDirLower def k
|
2013-12-27 16:37:23 +00:00
|
|
|
handleRemoteRequest (SETCONFIG setting value) =
|
2020-01-15 17:01:22 +00:00
|
|
|
liftIO $ atomically $ do
|
2020-08-14 18:40:30 +00:00
|
|
|
ParsedRemoteConfig m c <- takeTMVar (externalConfig st)
|
|
|
|
let !m' = M.insert
|
|
|
|
(Accepted setting)
|
|
|
|
(RemoteConfigValue (PassedThrough value))
|
|
|
|
m
|
|
|
|
let !c' = M.insert
|
|
|
|
(Accepted setting)
|
|
|
|
(Accepted value)
|
|
|
|
c
|
|
|
|
putTMVar (externalConfig st) (ParsedRemoteConfig m' c')
|
|
|
|
f <- takeTMVar (externalConfigChanges st)
|
|
|
|
let !f' = M.insert (Accepted setting) (Accepted value) . f
|
|
|
|
putTMVar (externalConfigChanges st) f'
|
2013-12-27 16:37:23 +00:00
|
|
|
handleRemoteRequest (GETCONFIG setting) = do
|
2020-03-09 16:38:04 +00:00
|
|
|
value <- maybe "" fromProposedAccepted
|
fix encryption of content to gcrypt and git-lfs
Fix serious regression in gcrypt and encrypted git-lfs remotes.
Since version 7.20200202.7, git-annex incorrectly stored content
on those remotes without encrypting it.
Problem was, Remote.Git enumerates all git remotes, including git-lfs
and gcrypt. It then dispatches to those. So, Remote.List used the
RemoteConfigParser from Remote.Git, instead of from git-lfs or gcrypt,
and that parser does not know about encryption fields, so did not
include them in the ParsedRemoteConfig. (Also didn't include other
fields specific to those remotes, perhaps chunking etc also didn't
get through.)
To fix, had to move RemoteConfig parsing down into the generate methods
of each remote, rather than doing it in Remote.List.
And a consequence of that was that ParsedRemoteConfig had to change to
include the RemoteConfig that got parsed, so that testremote can
generate a new remote based on an existing remote.
(I would have rather fixed this just inside Remote.Git, but that was not
practical, at least not w/o re-doing work that Remote.List already did.
Big ugly mostly mechanical patch seemed preferable to making git-annex
slower.)
2020-02-26 21:20:56 +00:00
|
|
|
. (M.lookup (Accepted setting))
|
2020-03-09 16:38:04 +00:00
|
|
|
. unparsedRemoteConfig
|
2020-08-14 18:40:30 +00:00
|
|
|
<$> liftIO (atomically $ readTMVar $ externalConfig st)
|
2014-01-02 00:12:20 +00:00
|
|
|
send $ VALUE value
|
add LISTCONFIGS to external special remote protocol
Special remote programs that use GETCONFIG/SETCONFIG are recommended
to implement it.
The description is not yet used, but will be useful later when adding a way
to make initremote list all accepted configs.
configParser now takes a RemoteConfig parameter. Normally, that's not
needed, because configParser returns a parter, it does not parse it
itself. But, it's needed to look at externaltype and work out what
external remote program to run for LISTCONFIGS.
Note that, while externalUUID is changed to a Maybe UUID, checkExportSupported
used to use NoUUID. The code that now checks for Nothing used to behave
in some undefined way if the external program made requests that
triggered it.
Also, note that in externalSetup, once it generates external,
it parses the RemoteConfig strictly. That generates a
ParsedRemoteConfig, which is thrown away. The reason it's ok to throw
that away, is that, if the strict parse succeeded, the result must be
the same as the earlier, lenient parse.
initremote of an external special remote now runs the program three
times. First for LISTCONFIGS, then EXPORTSUPPORTED, and again
LISTCONFIGS+INITREMOTE. It would not be hard to eliminate at least
one of those, and it should be possible to only run the program once.
2020-01-17 19:30:14 +00:00
|
|
|
handleRemoteRequest (SETCREDS setting login password) = case (externalUUID external, externalGitConfig external) of
|
|
|
|
(Just u, Just gc) -> do
|
2020-08-14 18:40:30 +00:00
|
|
|
pc <- liftIO $ atomically $ takeTMVar (externalConfig st)
|
2020-06-16 21:24:24 +00:00
|
|
|
pc' <- setRemoteCredPair' pc encryptionAlreadySetup gc
|
add LISTCONFIGS to external special remote protocol
Special remote programs that use GETCONFIG/SETCONFIG are recommended
to implement it.
The description is not yet used, but will be useful later when adding a way
to make initremote list all accepted configs.
configParser now takes a RemoteConfig parameter. Normally, that's not
needed, because configParser returns a parter, it does not parse it
itself. But, it's needed to look at externaltype and work out what
external remote program to run for LISTCONFIGS.
Note that, while externalUUID is changed to a Maybe UUID, checkExportSupported
used to use NoUUID. The code that now checks for Nothing used to behave
in some undefined way if the external program made requests that
triggered it.
Also, note that in externalSetup, once it generates external,
it parses the RemoteConfig strictly. That generates a
ParsedRemoteConfig, which is thrown away. The reason it's ok to throw
that away, is that, if the strict parse succeeded, the result must be
the same as the earlier, lenient parse.
initremote of an external special remote now runs the program three
times. First for LISTCONFIGS, then EXPORTSUPPORTED, and again
LISTCONFIGS+INITREMOTE. It would not be hard to eliminate at least
one of those, and it should be possible to only run the program once.
2020-01-17 19:30:14 +00:00
|
|
|
(credstorage setting u)
|
|
|
|
(Just (login, password))
|
2020-06-16 21:24:24 +00:00
|
|
|
let configchanges = M.differenceWithKey
|
|
|
|
(\_k a b -> if a == b then Nothing else Just a)
|
|
|
|
(unparsedRemoteConfig pc')
|
|
|
|
(unparsedRemoteConfig pc)
|
|
|
|
void $ liftIO $ atomically $ do
|
2020-08-14 18:40:30 +00:00
|
|
|
putTMVar (externalConfig st) pc'
|
|
|
|
f <- takeTMVar (externalConfigChanges st)
|
|
|
|
let !f' = M.union configchanges . f
|
|
|
|
putTMVar (externalConfigChanges st) f'
|
add LISTCONFIGS to external special remote protocol
Special remote programs that use GETCONFIG/SETCONFIG are recommended
to implement it.
The description is not yet used, but will be useful later when adding a way
to make initremote list all accepted configs.
configParser now takes a RemoteConfig parameter. Normally, that's not
needed, because configParser returns a parter, it does not parse it
itself. But, it's needed to look at externaltype and work out what
external remote program to run for LISTCONFIGS.
Note that, while externalUUID is changed to a Maybe UUID, checkExportSupported
used to use NoUUID. The code that now checks for Nothing used to behave
in some undefined way if the external program made requests that
triggered it.
Also, note that in externalSetup, once it generates external,
it parses the RemoteConfig strictly. That generates a
ParsedRemoteConfig, which is thrown away. The reason it's ok to throw
that away, is that, if the strict parse succeeded, the result must be
the same as the earlier, lenient parse.
initremote of an external special remote now runs the program three
times. First for LISTCONFIGS, then EXPORTSUPPORTED, and again
LISTCONFIGS+INITREMOTE. It would not be hard to eliminate at least
one of those, and it should be possible to only run the program once.
2020-01-17 19:30:14 +00:00
|
|
|
_ -> senderror "cannot send SETCREDS here"
|
|
|
|
handleRemoteRequest (GETCREDS setting) = case (externalUUID external, externalGitConfig external) of
|
|
|
|
(Just u, Just gc) -> do
|
2020-08-14 18:40:30 +00:00
|
|
|
c <- liftIO $ atomically $ readTMVar $ externalConfig st
|
add LISTCONFIGS to external special remote protocol
Special remote programs that use GETCONFIG/SETCONFIG are recommended
to implement it.
The description is not yet used, but will be useful later when adding a way
to make initremote list all accepted configs.
configParser now takes a RemoteConfig parameter. Normally, that's not
needed, because configParser returns a parter, it does not parse it
itself. But, it's needed to look at externaltype and work out what
external remote program to run for LISTCONFIGS.
Note that, while externalUUID is changed to a Maybe UUID, checkExportSupported
used to use NoUUID. The code that now checks for Nothing used to behave
in some undefined way if the external program made requests that
triggered it.
Also, note that in externalSetup, once it generates external,
it parses the RemoteConfig strictly. That generates a
ParsedRemoteConfig, which is thrown away. The reason it's ok to throw
that away, is that, if the strict parse succeeded, the result must be
the same as the earlier, lenient parse.
initremote of an external special remote now runs the program three
times. First for LISTCONFIGS, then EXPORTSUPPORTED, and again
LISTCONFIGS+INITREMOTE. It would not be hard to eliminate at least
one of those, and it should be possible to only run the program once.
2020-01-17 19:30:14 +00:00
|
|
|
creds <- fromMaybe ("", "") <$>
|
|
|
|
getRemoteCredPair c gc (credstorage setting u)
|
|
|
|
send $ CREDS (fst creds) (snd creds)
|
|
|
|
_ -> senderror "cannot send GETCREDS here"
|
|
|
|
handleRemoteRequest GETUUID = case externalUUID external of
|
|
|
|
Just u -> send $ VALUE $ fromUUID u
|
|
|
|
Nothing -> senderror "cannot send GETUUID here"
|
2019-12-09 17:49:05 +00:00
|
|
|
handleRemoteRequest GETGITDIR =
|
|
|
|
send . VALUE . fromRawFilePath =<< fromRepo Git.localGitDir
|
2021-01-26 16:42:47 +00:00
|
|
|
handleRemoteRequest GETGITREMOTENAME =
|
|
|
|
case externalRemoteName external of
|
|
|
|
Just n -> send $ VALUE n
|
|
|
|
Nothing -> senderror "git remote name not known"
|
add LISTCONFIGS to external special remote protocol
Special remote programs that use GETCONFIG/SETCONFIG are recommended
to implement it.
The description is not yet used, but will be useful later when adding a way
to make initremote list all accepted configs.
configParser now takes a RemoteConfig parameter. Normally, that's not
needed, because configParser returns a parter, it does not parse it
itself. But, it's needed to look at externaltype and work out what
external remote program to run for LISTCONFIGS.
Note that, while externalUUID is changed to a Maybe UUID, checkExportSupported
used to use NoUUID. The code that now checks for Nothing used to behave
in some undefined way if the external program made requests that
triggered it.
Also, note that in externalSetup, once it generates external,
it parses the RemoteConfig strictly. That generates a
ParsedRemoteConfig, which is thrown away. The reason it's ok to throw
that away, is that, if the strict parse succeeded, the result must be
the same as the earlier, lenient parse.
initremote of an external special remote now runs the program three
times. First for LISTCONFIGS, then EXPORTSUPPORTED, and again
LISTCONFIGS+INITREMOTE. It would not be hard to eliminate at least
one of those, and it should be possible to only run the program once.
2020-01-17 19:30:14 +00:00
|
|
|
handleRemoteRequest (SETWANTED expr) = case externalUUID external of
|
|
|
|
Just u -> preferredContentSet u expr
|
|
|
|
Nothing -> senderror "cannot send SETWANTED here"
|
|
|
|
handleRemoteRequest GETWANTED = case externalUUID external of
|
|
|
|
Just u -> do
|
|
|
|
expr <- fromMaybe "" . M.lookup u
|
|
|
|
<$> preferredContentMapRaw
|
|
|
|
send $ VALUE expr
|
|
|
|
Nothing -> senderror "cannot send GETWANTED here"
|
add remote state logs
This allows a remote to store a piece of arbitrary state associated with a
key. This is needed to support Tahoe, where the file-cap is calculated from
the data stored in it, and used to retrieve a key later. Glacier also would
be much improved by using this.
GETSTATE and SETSTATE are added to the external special remote protocol.
Note that the state is left as-is even when a key is removed from a remote.
It's up to the remote to decide when it wants to clear the state.
The remote state log, $KEY.log.rmt, is a UUID-based log. However,
rather than using the old UUID-based log format, I created a new variant
of that format. The new varient is more space efficient (since it lacks the
"timestamp=" hack, and easier to parse (and the parser doesn't mess with
whitespace in the value), and avoids compatability cruft in the old one.
This seemed worth cleaning up for these new files, since there could be a
lot of them, while before UUID-based logs were only used for a few log
files at the top of the git-annex branch. The transition code has also
been updated to handle these new UUID-based logs.
This commit was sponsored by Daniel Hofer.
2014-01-03 20:35:57 +00:00
|
|
|
handleRemoteRequest (SETSTATE key state) =
|
add RemoteStateHandle
This solves the problem of sameas remotes trampling over per-remote
state. Used for:
* per-remote state, of course
* per-remote metadata, also of course
* per-remote content identifiers, because two remote implementations
could in theory generate the same content identifier for two different
peices of content
While chunk logs are per-remote data, they don't use this, because the
number and size of chunks stored is a common property across sameas
remotes.
External special remote had a complication, where it was theoretically
possible for a remote to send SETSTATE or GETSTATE during INITREMOTE or
EXPORTSUPPORTED. Since the uuid of the remote is typically generate in
Remote.setup, it would only be possible to pass a Maybe
RemoteStateHandle into it, and it would otherwise have to construct its
own. Rather than go that route, I decided to send an ERROR in this case.
It seems unlikely that any existing external special remote will be
affected. They would have to make up a git-annex key, and set state for
some reason during INITREMOTE. I can imagine such a hack, but it doesn't
seem worth complicating the code in such an ugly way to support it.
Unfortunately, both TestRemote and Annex.Import needed the Remote
to have a new field added that holds its RemoteStateHandle.
2019-10-14 16:33:27 +00:00
|
|
|
case externalRemoteStateHandle external of
|
|
|
|
Just h -> setRemoteState h key state
|
|
|
|
Nothing -> senderror "cannot send SETSTATE here"
|
|
|
|
handleRemoteRequest (GETSTATE key) =
|
|
|
|
case externalRemoteStateHandle external of
|
|
|
|
Just h -> do
|
|
|
|
state <- fromMaybe ""
|
|
|
|
<$> getRemoteState h key
|
|
|
|
send $ VALUE state
|
|
|
|
Nothing -> senderror "cannot send GETSTATE here"
|
2014-12-08 23:14:24 +00:00
|
|
|
handleRemoteRequest (SETURLPRESENT key url) =
|
2018-10-04 21:33:25 +00:00
|
|
|
setUrlPresent key url
|
2014-12-08 23:14:24 +00:00
|
|
|
handleRemoteRequest (SETURLMISSING key url) =
|
2018-10-04 21:33:25 +00:00
|
|
|
setUrlMissing key url
|
2015-03-05 17:50:15 +00:00
|
|
|
handleRemoteRequest (SETURIPRESENT key uri) =
|
|
|
|
withurl (SETURLPRESENT key) uri
|
|
|
|
handleRemoteRequest (SETURIMISSING key uri) =
|
|
|
|
withurl (SETURLMISSING key) uri
|
2014-12-08 17:32:27 +00:00
|
|
|
handleRemoteRequest (GETURLS key prefix) = do
|
2015-03-27 22:49:03 +00:00
|
|
|
mapM_ (send . VALUE) =<< getUrlsWithPrefix key prefix
|
2014-12-08 17:32:27 +00:00
|
|
|
send (VALUE "") -- end of list
|
2021-04-06 19:41:24 +00:00
|
|
|
handleRemoteRequest (DEBUG msg) = fastDebug "Remote.External" msg
|
2023-04-10 21:03:41 +00:00
|
|
|
handleRemoteRequest (INFO msg) = showInfo (UnquotedString msg)
|
add RemoteStateHandle
This solves the problem of sameas remotes trampling over per-remote
state. Used for:
* per-remote state, of course
* per-remote metadata, also of course
* per-remote content identifiers, because two remote implementations
could in theory generate the same content identifier for two different
peices of content
While chunk logs are per-remote data, they don't use this, because the
number and size of chunks stored is a common property across sameas
remotes.
External special remote had a complication, where it was theoretically
possible for a remote to send SETSTATE or GETSTATE during INITREMOTE or
EXPORTSUPPORTED. Since the uuid of the remote is typically generate in
Remote.setup, it would only be possible to pass a Maybe
RemoteStateHandle into it, and it would otherwise have to construct its
own. Rather than go that route, I decided to send an ERROR in this case.
It seems unlikely that any existing external special remote will be
affected. They would have to make up a git-annex key, and set state for
some reason during INITREMOTE. I can imagine such a hack, but it doesn't
seem worth complicating the code in such an ugly way to support it.
Unfortunately, both TestRemote and Annex.Import needed the Remote
to have a new field added that holds its RemoteStateHandle.
2019-10-14 16:33:27 +00:00
|
|
|
handleRemoteRequest (VERSION _) = senderror "too late to send VERSION"
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
|
2020-08-12 16:04:12 +00:00
|
|
|
handleExceptionalMessage (ERROR err) = giveup $ "external special remote error: " ++ err
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
|
2020-07-29 19:23:18 +00:00
|
|
|
send = sendMessage st
|
|
|
|
senderror = sendMessage st . ERROR
|
2014-01-02 00:12:20 +00:00
|
|
|
|
add LISTCONFIGS to external special remote protocol
Special remote programs that use GETCONFIG/SETCONFIG are recommended
to implement it.
The description is not yet used, but will be useful later when adding a way
to make initremote list all accepted configs.
configParser now takes a RemoteConfig parameter. Normally, that's not
needed, because configParser returns a parter, it does not parse it
itself. But, it's needed to look at externaltype and work out what
external remote program to run for LISTCONFIGS.
Note that, while externalUUID is changed to a Maybe UUID, checkExportSupported
used to use NoUUID. The code that now checks for Nothing used to behave
in some undefined way if the external program made requests that
triggered it.
Also, note that in externalSetup, once it generates external,
it parses the RemoteConfig strictly. That generates a
ParsedRemoteConfig, which is thrown away. The reason it's ok to throw
that away, is that, if the strict parse succeeded, the result must be
the same as the earlier, lenient parse.
initremote of an external special remote now runs the program three
times. First for LISTCONFIGS, then EXPORTSUPPORTED, and again
LISTCONFIGS+INITREMOTE. It would not be hard to eliminate at least
one of those, and it should be possible to only run the program once.
2020-01-17 19:30:14 +00:00
|
|
|
credstorage setting u = CredPairStorage
|
2013-12-27 20:01:43 +00:00
|
|
|
{ credPairFile = base
|
|
|
|
, credPairEnvironment = (base ++ "login", base ++ "password")
|
2020-01-10 18:10:20 +00:00
|
|
|
, credPairRemoteField = Accepted setting
|
2013-12-27 20:01:43 +00:00
|
|
|
}
|
|
|
|
where
|
add LISTCONFIGS to external special remote protocol
Special remote programs that use GETCONFIG/SETCONFIG are recommended
to implement it.
The description is not yet used, but will be useful later when adding a way
to make initremote list all accepted configs.
configParser now takes a RemoteConfig parameter. Normally, that's not
needed, because configParser returns a parter, it does not parse it
itself. But, it's needed to look at externaltype and work out what
external remote program to run for LISTCONFIGS.
Note that, while externalUUID is changed to a Maybe UUID, checkExportSupported
used to use NoUUID. The code that now checks for Nothing used to behave
in some undefined way if the external program made requests that
triggered it.
Also, note that in externalSetup, once it generates external,
it parses the RemoteConfig strictly. That generates a
ParsedRemoteConfig, which is thrown away. The reason it's ok to throw
that away, is that, if the strict parse succeeded, the result must be
the same as the earlier, lenient parse.
initremote of an external special remote now runs the program three
times. First for LISTCONFIGS, then EXPORTSUPPORTED, and again
LISTCONFIGS+INITREMOTE. It would not be hard to eliminate at least
one of those, and it should be possible to only run the program once.
2020-01-17 19:30:14 +00:00
|
|
|
base = replace "/" "_" $ fromUUID u ++ "-" ++ setting
|
2015-03-05 17:50:15 +00:00
|
|
|
|
|
|
|
withurl mk uri = handleRemoteRequest $ mk $
|
|
|
|
setDownloader (show uri) OtherDownloader
|
2013-12-27 20:01:43 +00:00
|
|
|
|
2020-08-13 19:49:43 +00:00
|
|
|
sendMessage :: (Sendable m, ToAsyncWrapped m) => ExternalState -> m -> Annex ()
|
|
|
|
sendMessage st m = liftIO $ externalSend st m
|
2020-08-12 16:30:45 +00:00
|
|
|
|
2020-08-13 19:49:43 +00:00
|
|
|
sendMessageAddonProcess :: Sendable m => AddonProcess.ExternalAddonProcess -> m -> IO ()
|
|
|
|
sendMessageAddonProcess p m = do
|
2020-08-12 16:30:45 +00:00
|
|
|
AddonProcess.protocolDebug p True line
|
2016-09-30 18:29:02 +00:00
|
|
|
hPutStrLn h line
|
|
|
|
hFlush h
|
2013-12-27 07:10:00 +00:00
|
|
|
where
|
2020-08-12 16:30:45 +00:00
|
|
|
h = AddonProcess.externalSend p
|
2020-08-13 19:49:43 +00:00
|
|
|
line = unwords $ formatMessage m
|
2020-08-12 16:30:45 +00:00
|
|
|
|
|
|
|
receiveMessageAddonProcess :: AddonProcess.ExternalAddonProcess -> IO (Maybe String)
|
|
|
|
receiveMessageAddonProcess p = do
|
|
|
|
v <- catchMaybeIO $ hGetLine $ AddonProcess.externalReceive p
|
|
|
|
maybe noop (AddonProcess.protocolDebug p False) v
|
|
|
|
return v
|
|
|
|
|
|
|
|
shutdownAddonProcess :: AddonProcess.ExternalAddonProcess -> Bool -> IO ()
|
|
|
|
shutdownAddonProcess = AddonProcess.externalShutdown
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
|
2023-03-14 02:39:16 +00:00
|
|
|
{- A response handler can yield a result, or it can request that another
|
2020-07-29 19:23:18 +00:00
|
|
|
- message be consumed from the external. -}
|
2018-06-08 15:52:20 +00:00
|
|
|
data ResponseHandlerResult a
|
|
|
|
= Result a
|
|
|
|
| GetNextMessage (ResponseHandler a)
|
|
|
|
|
|
|
|
type ResponseHandler a = Response -> Maybe (Annex (ResponseHandlerResult a))
|
|
|
|
|
|
|
|
result :: a -> Maybe (Annex (ResponseHandlerResult a))
|
|
|
|
result = Just . return . Result
|
|
|
|
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
{- Waits for a message from the external remote, and passes it to the
|
2023-03-14 02:39:16 +00:00
|
|
|
- appropriate handler.
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
-
|
|
|
|
- If the handler returns Nothing, this is a protocol error.-}
|
|
|
|
receiveMessage
|
2016-09-30 18:29:02 +00:00
|
|
|
:: ExternalState
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
-> External
|
2018-06-08 15:52:20 +00:00
|
|
|
-> ResponseHandler a
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
-> (RemoteRequest -> Maybe (Annex a))
|
2020-08-12 16:04:12 +00:00
|
|
|
-> (ExceptionalMessage -> Maybe (Annex a))
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
-> Annex a
|
2020-08-12 16:04:12 +00:00
|
|
|
receiveMessage st external handleresponse handlerequest handleexceptional =
|
2020-08-12 16:30:45 +00:00
|
|
|
go =<< liftIO (externalReceive st)
|
2013-12-25 21:53:24 +00:00
|
|
|
where
|
2020-08-13 19:49:43 +00:00
|
|
|
go Nothing = protocolError False "<EOF>"
|
2020-08-12 16:30:45 +00:00
|
|
|
go (Just s) = case parseMessage s :: Maybe Response of
|
|
|
|
Just resp -> case handleresponse resp of
|
|
|
|
Nothing -> protocolError True s
|
|
|
|
Just callback -> callback >>= \case
|
|
|
|
Result a -> return a
|
|
|
|
GetNextMessage handleresponse' ->
|
|
|
|
receiveMessage st external handleresponse' handlerequest handleexceptional
|
|
|
|
Nothing -> case parseMessage s :: Maybe RemoteRequest of
|
|
|
|
Just req -> maybe (protocolError True s) id (handlerequest req)
|
|
|
|
Nothing -> case parseMessage s :: Maybe ExceptionalMessage of
|
|
|
|
Just msg -> maybe (protocolError True s) id (handleexceptional msg)
|
|
|
|
Nothing -> protocolError False s
|
2020-08-14 19:38:31 +00:00
|
|
|
protocolError parsed s = 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 $ "external special remote protocol error, unexpectedly received \"" ++ s ++ "\" " ++
|
2020-08-14 19:38:31 +00:00
|
|
|
if parsed
|
|
|
|
then "(command not allowed at this time)"
|
|
|
|
else "(unable to parse command)"
|
|
|
|
giveup "unable to use special remote due to protocol error"
|
2013-12-25 21:53:24 +00:00
|
|
|
|
2016-09-30 18:29:02 +00:00
|
|
|
{- While the action is running, the ExternalState provided to it will not
|
|
|
|
- be available to any other calls.
|
|
|
|
-
|
async exception safety for external special remote processes
Since an external process can be in the middle of some operation when an
async exception is received, it has to be shut down then. Using
cleanupProcess will close its IO handles and send it a SIGTERM.
If a special remote choses to catch SIGTERM, it's fine for it to do some
cleanup then, but until it finishes, git-annex will be blocked waiting
for it. If a special remote blocked SIGTERM, it would cause a hang.
Mentioned in docs.
Also, in passing, fixed a FD leak, it was not closing the error handle
when shutting down the external. In practice that didn't matter before because
it was only run when git-annex was itself shutting down, but now that it
can run on exception, it would have been a problem.
2020-06-09 16:13:06 +00:00
|
|
|
- Starts up a new process if no ExternalStates are available.
|
|
|
|
-
|
|
|
|
- If the action is interrupted by an async exception, the external process
|
|
|
|
- is in an unknown state, and may eg be still performing a transfer. So it
|
|
|
|
- is killed. The action should not normally throw any exception itself,
|
|
|
|
- unless perhaps there's a problem communicating with the external
|
|
|
|
- process.
|
|
|
|
-}
|
2016-09-30 18:29:02 +00:00
|
|
|
withExternalState :: External -> (ExternalState -> Annex a) -> Annex a
|
async exception safety for external special remote processes
Since an external process can be in the middle of some operation when an
async exception is received, it has to be shut down then. Using
cleanupProcess will close its IO handles and send it a SIGTERM.
If a special remote choses to catch SIGTERM, it's fine for it to do some
cleanup then, but until it finishes, git-annex will be blocked waiting
for it. If a special remote blocked SIGTERM, it would cause a hang.
Mentioned in docs.
Also, in passing, fixed a FD leak, it was not closing the error handle
when shutting down the external. In practice that didn't matter before because
it was only run when git-annex was itself shutting down, but now that it
can run on exception, it would have been a problem.
2020-06-09 16:13:06 +00:00
|
|
|
withExternalState external a = do
|
|
|
|
st <- get
|
2020-08-12 16:30:45 +00:00
|
|
|
r <- a st `onException` liftIO (externalShutdown st True)
|
async exception safety for external special remote processes
Since an external process can be in the middle of some operation when an
async exception is received, it has to be shut down then. Using
cleanupProcess will close its IO handles and send it a SIGTERM.
If a special remote choses to catch SIGTERM, it's fine for it to do some
cleanup then, but until it finishes, git-annex will be blocked waiting
for it. If a special remote blocked SIGTERM, it would cause a hang.
Mentioned in docs.
Also, in passing, fixed a FD leak, it was not closing the error handle
when shutting down the external. In practice that didn't matter before because
it was only run when git-annex was itself shutting down, but now that it
can run on exception, it would have been a problem.
2020-06-09 16:13:06 +00:00
|
|
|
put st -- only when no exception is thrown
|
|
|
|
return r
|
2013-12-25 21:53:24 +00:00
|
|
|
where
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
v = externalState external
|
|
|
|
|
async exception safety for external special remote processes
Since an external process can be in the middle of some operation when an
async exception is received, it has to be shut down then. Using
cleanupProcess will close its IO handles and send it a SIGTERM.
If a special remote choses to catch SIGTERM, it's fine for it to do some
cleanup then, but until it finishes, git-annex will be blocked waiting
for it. If a special remote blocked SIGTERM, it would cause a hang.
Mentioned in docs.
Also, in passing, fixed a FD leak, it was not closing the error handle
when shutting down the external. In practice that didn't matter before because
it was only run when git-annex was itself shutting down, but now that it
can run on exception, it would have been a problem.
2020-06-09 16:13:06 +00:00
|
|
|
get = do
|
2016-09-30 18:29:02 +00:00
|
|
|
ms <- liftIO $ atomically $ do
|
2016-09-30 23:51:16 +00:00
|
|
|
l <- readTVar v
|
2016-09-30 18:29:02 +00:00
|
|
|
case l of
|
2016-09-30 23:51:16 +00:00
|
|
|
[] -> return Nothing
|
2016-09-30 18:29:02 +00:00
|
|
|
(st:rest) -> do
|
2016-09-30 23:51:16 +00:00
|
|
|
writeTVar v rest
|
2016-09-30 18:29:02 +00:00
|
|
|
return (Just st)
|
|
|
|
maybe (startExternal external) return ms
|
|
|
|
|
async exception safety for external special remote processes
Since an external process can be in the middle of some operation when an
async exception is received, it has to be shut down then. Using
cleanupProcess will close its IO handles and send it a SIGTERM.
If a special remote choses to catch SIGTERM, it's fine for it to do some
cleanup then, but until it finishes, git-annex will be blocked waiting
for it. If a special remote blocked SIGTERM, it would cause a hang.
Mentioned in docs.
Also, in passing, fixed a FD leak, it was not closing the error handle
when shutting down the external. In practice that didn't matter before because
it was only run when git-annex was itself shutting down, but now that it
can run on exception, it would have been a problem.
2020-06-09 16:13:06 +00:00
|
|
|
put st = liftIO $ atomically $ modifyTVar' v (st:)
|
2016-09-30 18:29:02 +00:00
|
|
|
|
2018-02-07 19:02:12 +00:00
|
|
|
{- Starts an external remote process running, and checks VERSION and
|
2020-08-12 19:17:53 +00:00
|
|
|
- exchanges EXTENSIONS.
|
|
|
|
-
|
|
|
|
- When the ASYNC extension is negotiated, a single process is used,
|
|
|
|
- and this constructs a external state that communicates with a thread
|
|
|
|
- that relays to it.
|
|
|
|
-}
|
2016-09-30 17:36:50 +00:00
|
|
|
startExternal :: External -> Annex ExternalState
|
2020-08-12 19:17:53 +00:00
|
|
|
startExternal external =
|
|
|
|
liftIO (atomically $ takeTMVar (externalAsync external)) >>= \case
|
|
|
|
UncheckedExternalAsync -> do
|
|
|
|
(st, extensions) <- startExternal' external
|
2020-08-19 16:20:07 +00:00
|
|
|
`onException` store UncheckedExternalAsync
|
2020-08-12 19:17:53 +00:00
|
|
|
if asyncExtensionEnabled extensions
|
|
|
|
then do
|
2020-12-02 18:57:43 +00:00
|
|
|
annexrunner <- Annex.makeRunner
|
|
|
|
relay <- liftIO $ runRelayToExternalAsync external st annexrunner
|
2020-08-12 20:25:53 +00:00
|
|
|
st' <- liftIO $ asyncRelayExternalState relay
|
|
|
|
store (ExternalAsync relay)
|
2020-08-12 19:17:53 +00:00
|
|
|
return st'
|
|
|
|
else do
|
|
|
|
store NoExternalAsync
|
|
|
|
return st
|
|
|
|
v@NoExternalAsync -> do
|
|
|
|
store v
|
|
|
|
fst <$> startExternal' external
|
2020-08-12 19:54:30 +00:00
|
|
|
v@(ExternalAsync relay) -> do
|
2020-08-12 19:17:53 +00:00
|
|
|
store v
|
2020-08-12 20:25:53 +00:00
|
|
|
liftIO $ asyncRelayExternalState relay
|
2020-08-12 19:17:53 +00:00
|
|
|
where
|
|
|
|
store = liftIO . atomically . putTMVar (externalAsync external)
|
|
|
|
|
|
|
|
startExternal' :: External -> Annex (ExternalState, ExtensionList)
|
|
|
|
startExternal' external = do
|
2020-07-29 19:23:18 +00:00
|
|
|
pid <- liftIO $ atomically $ do
|
|
|
|
n <- succ <$> readTVar (externalLastPid external)
|
|
|
|
writeTVar (externalLastPid external) n
|
|
|
|
return n
|
2020-08-12 16:30:45 +00:00
|
|
|
AddonProcess.startExternalAddonProcess basecmd pid >>= \case
|
2020-08-14 19:38:31 +00:00
|
|
|
Left (AddonProcess.ProgramFailure err) -> do
|
|
|
|
unusable err
|
2020-08-12 16:30:45 +00:00
|
|
|
Left (AddonProcess.ProgramNotInstalled err) ->
|
2020-07-29 16:00:27 +00:00
|
|
|
case (lookupName (unparsedRemoteConfig (externalDefaultConfig external)), remoteAnnexReadOnly <$> externalGitConfig external) of
|
2020-08-14 19:38:31 +00:00
|
|
|
(Just rname, Just True) -> unusable $ unlines
|
2020-07-29 16:00:27 +00:00
|
|
|
[ err
|
|
|
|
, "This remote has annex-readonly=true, and previous versions of"
|
|
|
|
, "git-annex would tried to download from it without"
|
|
|
|
, "installing " ++ basecmd ++ ". If you want that, you need to set:"
|
|
|
|
, "git config remote." ++ rname ++ ".annex-externaltype readonly"
|
|
|
|
]
|
2020-08-14 19:38:31 +00:00
|
|
|
_ -> unusable err
|
2020-07-29 16:00:27 +00:00
|
|
|
Right p -> do
|
2020-08-14 18:40:30 +00:00
|
|
|
cv <- liftIO $ newTMVarIO $ externalDefaultConfig external
|
|
|
|
ccv <- liftIO $ newTMVarIO id
|
|
|
|
pv <- liftIO $ newTMVarIO Unprepared
|
2020-07-29 16:00:27 +00:00
|
|
|
let st = ExternalState
|
2020-08-12 16:30:45 +00:00
|
|
|
{ externalSend = sendMessageAddonProcess p
|
|
|
|
, externalReceive = receiveMessageAddonProcess p
|
|
|
|
, externalShutdown = shutdownAddonProcess p
|
2020-07-29 16:00:27 +00:00
|
|
|
, externalPrepared = pv
|
|
|
|
, externalConfig = cv
|
|
|
|
, externalConfigChanges = ccv
|
|
|
|
}
|
2020-08-12 19:17:53 +00:00
|
|
|
extensions <- startproto st
|
|
|
|
return (st, extensions)
|
2016-09-30 18:29:02 +00:00
|
|
|
where
|
2020-07-29 19:23:18 +00:00
|
|
|
basecmd = "git-annex-remote-" ++ externalType external
|
2020-07-29 16:00:27 +00:00
|
|
|
startproto st = do
|
|
|
|
receiveMessage st external
|
|
|
|
(const Nothing)
|
2020-07-29 19:23:18 +00:00
|
|
|
(checkVersion st)
|
2020-07-29 16:00:27 +00:00
|
|
|
(const Nothing)
|
2020-07-29 19:23:18 +00:00
|
|
|
sendMessage st (EXTENSIONS supportedExtensionList)
|
2020-07-29 16:00:27 +00:00
|
|
|
-- It responds with a EXTENSIONS_RESPONSE; that extensions
|
|
|
|
-- list is reserved for future expansion. UNSUPPORTED_REQUEST
|
|
|
|
-- is also accepted.
|
2020-08-12 19:17:53 +00:00
|
|
|
exwanted <- receiveMessage st external
|
2020-07-29 16:00:27 +00:00
|
|
|
(\resp -> case resp of
|
2020-08-12 19:17:53 +00:00
|
|
|
EXTENSIONS_RESPONSE l -> result l
|
2020-08-12 19:54:30 +00:00
|
|
|
UNSUPPORTED_REQUEST -> result mempty
|
2020-07-29 16:00:27 +00:00
|
|
|
_ -> Nothing
|
|
|
|
)
|
|
|
|
(const Nothing)
|
|
|
|
(const Nothing)
|
2020-08-12 19:17:53 +00:00
|
|
|
case filter (`notElem` fromExtensionList supportedExtensionList) (fromExtensionList exwanted) of
|
|
|
|
[] -> return exwanted
|
2020-08-14 19:38:31 +00:00
|
|
|
exrest -> unusable $ unwords $
|
2020-08-12 19:17:53 +00:00
|
|
|
[ basecmd
|
|
|
|
, "requested extensions that this version of git-annex does not support:"
|
|
|
|
] ++ exrest
|
2013-12-25 21:53:24 +00:00
|
|
|
|
2020-08-14 19:38:31 +00:00
|
|
|
unusable msg = 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 msg)
|
2020-08-14 19:38:31 +00:00
|
|
|
giveup ("unable to use external special remote " ++ basecmd)
|
|
|
|
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
stopExternal :: External -> Annex ()
|
2016-09-30 18:29:02 +00:00
|
|
|
stopExternal external = liftIO $ do
|
2016-09-30 23:51:16 +00:00
|
|
|
l <- atomically $ swapTVar (externalState external) []
|
2020-08-12 16:30:45 +00:00
|
|
|
mapM_ (flip externalShutdown False) l
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
|
2020-07-29 19:23:18 +00:00
|
|
|
checkVersion :: ExternalState -> RemoteRequest -> Maybe (Annex ())
|
|
|
|
checkVersion st (VERSION v) = Just $
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
if v `elem` supportedProtocolVersions
|
|
|
|
then noop
|
2020-07-29 19:23:18 +00:00
|
|
|
else sendMessage st (ERROR "unsupported VERSION")
|
|
|
|
checkVersion _ _ = Nothing
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
|
2013-12-29 17:39:25 +00:00
|
|
|
{- If repo has not been prepared, sends PREPARE.
|
|
|
|
-
|
|
|
|
- If the repo fails to prepare, or failed before, throws an exception with
|
|
|
|
- the error message. -}
|
2016-09-30 18:29:02 +00:00
|
|
|
checkPrepared :: ExternalState -> External -> Annex ()
|
|
|
|
checkPrepared st external = do
|
2020-08-14 18:40:30 +00:00
|
|
|
v <- liftIO $ atomically $ takeTMVar $ externalPrepared st
|
2016-09-30 18:29:02 +00:00
|
|
|
case v of
|
2020-08-14 18:40:30 +00:00
|
|
|
Prepared -> setprepared Prepared
|
|
|
|
FailedPrepare errmsg -> do
|
|
|
|
setprepared (FailedPrepare errmsg)
|
|
|
|
giveup errmsg
|
2016-09-30 18:29:02 +00:00
|
|
|
Unprepared ->
|
|
|
|
handleRequest' st external PREPARE Nothing $ \resp ->
|
|
|
|
case resp of
|
2018-06-08 15:52:20 +00:00
|
|
|
PREPARE_SUCCESS -> Just $ do
|
2016-09-30 18:29:02 +00:00
|
|
|
setprepared Prepared
|
2018-06-08 15:52:20 +00:00
|
|
|
return (Result ())
|
2016-09-30 18:29:02 +00:00
|
|
|
PREPARE_FAILURE errmsg -> Just $ do
|
2020-02-27 18:09:18 +00:00
|
|
|
let errmsg' = respErrorMessage "PREPARE" errmsg
|
|
|
|
setprepared $ FailedPrepare errmsg'
|
|
|
|
giveup errmsg'
|
2016-09-30 18:29:02 +00:00
|
|
|
_ -> Nothing
|
2013-12-29 17:39:25 +00:00
|
|
|
where
|
2020-08-14 18:40:30 +00:00
|
|
|
setprepared status = liftIO $ atomically $
|
|
|
|
putTMVar (externalPrepared st) status
|
2013-12-27 06:49:10 +00:00
|
|
|
|
2020-02-27 18:09:18 +00:00
|
|
|
respErrorMessage :: String -> String -> String
|
|
|
|
respErrorMessage req err
|
|
|
|
| null err = req ++ " failed with no reason given"
|
|
|
|
| otherwise = err
|
|
|
|
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
{- Caches the cost in the git config to avoid needing to start up an
|
|
|
|
- external special remote every time time just to ask it what its
|
|
|
|
- cost is. -}
|
2023-01-12 17:42:28 +00:00
|
|
|
getCost :: External -> Git.Repo -> RemoteGitConfig -> ParsedRemoteConfig -> Annex Cost
|
|
|
|
getCost external r gc pc =
|
|
|
|
(go =<< remoteCost' gc pc) `catchNonAsync` const (pure defcst)
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
where
|
|
|
|
go (Just c) = return c
|
|
|
|
go Nothing = do
|
|
|
|
c <- handleRequest external GETCOST Nothing $ \req -> case req of
|
2018-06-08 15:52:20 +00:00
|
|
|
COST c -> result c
|
|
|
|
UNSUPPORTED_REQUEST -> result defcst
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
_ -> Nothing
|
|
|
|
setRemoteCost r c
|
|
|
|
return c
|
2018-06-08 15:52:20 +00:00
|
|
|
defcst = expensiveRemoteCost
|
2014-01-13 18:41:10 +00:00
|
|
|
|
|
|
|
{- Caches the availability in the git config to avoid needing to start up an
|
|
|
|
- external special remote every time time just to ask it what its
|
|
|
|
- availability is.
|
|
|
|
-
|
|
|
|
- Most remotes do not bother to implement a reply to this request;
|
|
|
|
- globally available is the default.
|
|
|
|
-}
|
|
|
|
getAvailability :: External -> Git.Repo -> RemoteGitConfig -> Annex Availability
|
2016-07-05 20:34:39 +00:00
|
|
|
getAvailability external r gc =
|
2018-06-08 15:52:20 +00:00
|
|
|
maybe (catchNonAsync query (const (pure defavail))) return
|
|
|
|
(remoteAnnexAvailability gc)
|
2014-01-13 18:41:10 +00:00
|
|
|
where
|
|
|
|
query = do
|
|
|
|
avail <- handleRequest external GETAVAILABILITY Nothing $ \req -> case req of
|
2018-06-08 15:52:20 +00:00
|
|
|
AVAILABILITY avail -> result avail
|
|
|
|
UNSUPPORTED_REQUEST -> result defavail
|
2014-01-13 18:41:10 +00:00
|
|
|
_ -> Nothing
|
|
|
|
setRemoteAvailability r avail
|
|
|
|
return avail
|
2018-06-08 15:52:20 +00:00
|
|
|
defavail = GloballyAvailable
|
2014-12-08 17:57:13 +00:00
|
|
|
|
2017-09-15 17:15:47 +00:00
|
|
|
claimUrlM :: External -> URLString -> Annex Bool
|
|
|
|
claimUrlM external url =
|
2014-12-08 17:57:13 +00:00
|
|
|
handleRequest external (CLAIMURL url) Nothing $ \req -> case req of
|
2018-06-08 15:52:20 +00:00
|
|
|
CLAIMURL_SUCCESS -> result True
|
|
|
|
CLAIMURL_FAILURE -> result False
|
|
|
|
UNSUPPORTED_REQUEST -> result False
|
2014-12-08 17:57:13 +00:00
|
|
|
_ -> Nothing
|
|
|
|
|
2017-09-15 17:15:47 +00:00
|
|
|
checkUrlM :: External -> URLString -> Annex UrlContents
|
|
|
|
checkUrlM external url =
|
2014-12-08 23:14:24 +00:00
|
|
|
handleRequest external (CHECKURL url) Nothing $ \req -> case req of
|
2018-06-08 15:52:20 +00:00
|
|
|
CHECKURL_CONTENTS sz f -> result $ UrlContents sz $
|
2020-05-11 18:04:56 +00:00
|
|
|
if null f then Nothing else Just f
|
2018-06-08 15:52:20 +00:00
|
|
|
CHECKURL_MULTI l -> result $ UrlMulti $ map mkmulti l
|
2020-02-27 18:09:18 +00:00
|
|
|
CHECKURL_FAILURE errmsg -> Just $ giveup $
|
|
|
|
respErrorMessage "CHECKURL" errmsg
|
2016-11-16 01:29:54 +00:00
|
|
|
UNSUPPORTED_REQUEST -> giveup "CHECKURL not implemented by external special remote"
|
2014-12-08 23:14:24 +00:00
|
|
|
_ -> Nothing
|
2014-12-12 00:08:49 +00:00
|
|
|
where
|
2020-05-11 18:04:56 +00:00
|
|
|
mkmulti (u, s, f) = (u, s, f)
|
2015-08-17 15:22:22 +00:00
|
|
|
|
|
|
|
retrieveUrl :: Retriever
|
2021-08-18 18:49:01 +00:00
|
|
|
retrieveUrl = fileRetriever' $ \f k p iv -> do
|
2015-08-17 15:22:22 +00:00
|
|
|
us <- getWebUrls k
|
2021-09-01 19:28:22 +00:00
|
|
|
unlessM (withUrlOptions $ downloadUrl True k p iv us (fromRawFilePath f)) $
|
2016-11-16 01:29:54 +00:00
|
|
|
giveup "failed to download content"
|
2015-08-17 15:22:22 +00:00
|
|
|
|
remove "checking remotename" message
This fixes fsck of a remote that uses chunking displaying
(checking remotename) (checking remotename)" for every chunk.
Also, some remotes displayed the message, and others did not, with no
consistency. It was originally displayed only when accessing remotes
that were expensive or might involve a password prompt, I think, but
nothing in the API said when to do it so it became an inconsistent mess.
Originally I thought fsck should always display it. But it only displays
in fsck --from remote, so the user knows the remote is being accessed,
so there is no reason to tell them it's accessing it over and over.
It was also possible for git-annex move to sometimes display it twice,
due to checking if content is present twice. But, the user of move
specifies --from/--to, so it does not need to display when it's
accessing the remote, as the user expects it to access the remote.
git-annex get might display it, but only if the remote also supports
hasKeyCheap, which is really only local git remotes, which didn't
display it always; and in any case nothing displayed it before hasKeyCheap,
which is checked first, so I don't think this needs to display it ever.
mirror is like move. And that's all the main places it would have been
displayed.
This commit was sponsored by Jochen Bartl on Patreon.
2021-04-27 16:50:45 +00:00
|
|
|
checkKeyUrl :: CheckPresent
|
|
|
|
checkKeyUrl k = do
|
2015-08-17 15:22:22 +00:00
|
|
|
us <- getWebUrls k
|
2019-11-22 20:24:04 +00:00
|
|
|
anyM (\u -> withUrlOptions $ checkBoth u (fromKey keySize k)) us
|
2015-08-17 15:22:22 +00:00
|
|
|
|
|
|
|
getWebUrls :: Key -> Annex [URLString]
|
|
|
|
getWebUrls key = filter supported <$> getUrls key
|
|
|
|
where
|
|
|
|
supported u = snd (getDownloader u) == WebDownloader
|
2018-06-08 15:52:20 +00:00
|
|
|
|
|
|
|
externalInfo :: ExternalType -> Annex [(String, String)]
|
|
|
|
externalInfo et = return [("externaltype", et)]
|
|
|
|
|
|
|
|
getInfoM :: External -> Annex [(String, String)]
|
|
|
|
getInfoM external = (++)
|
|
|
|
<$> externalInfo (externalType external)
|
|
|
|
<*> handleRequest external GETINFO Nothing (collect [])
|
|
|
|
where
|
|
|
|
collect l req = case req of
|
|
|
|
INFOFIELD f -> Just $ return $
|
|
|
|
GetNextMessage $ collectvalue l f
|
|
|
|
INFOEND -> result (reverse l)
|
|
|
|
UNSUPPORTED_REQUEST -> result []
|
|
|
|
_ -> Nothing
|
|
|
|
|
|
|
|
collectvalue l f req = case req of
|
|
|
|
INFOVALUE v -> Just $ return $
|
|
|
|
GetNextMessage $ collect ((f, v) : l)
|
|
|
|
_ -> Nothing
|
add LISTCONFIGS to external special remote protocol
Special remote programs that use GETCONFIG/SETCONFIG are recommended
to implement it.
The description is not yet used, but will be useful later when adding a way
to make initremote list all accepted configs.
configParser now takes a RemoteConfig parameter. Normally, that's not
needed, because configParser returns a parter, it does not parse it
itself. But, it's needed to look at externaltype and work out what
external remote program to run for LISTCONFIGS.
Note that, while externalUUID is changed to a Maybe UUID, checkExportSupported
used to use NoUUID. The code that now checks for Nothing used to behave
in some undefined way if the external program made requests that
triggered it.
Also, note that in externalSetup, once it generates external,
it parses the RemoteConfig strictly. That generates a
ParsedRemoteConfig, which is thrown away. The reason it's ok to throw
that away, is that, if the strict parse succeeded, the result must be
the same as the earlier, lenient parse.
initremote of an external special remote now runs the program three
times. First for LISTCONFIGS, then EXPORTSUPPORTED, and again
LISTCONFIGS+INITREMOTE. It would not be hard to eliminate at least
one of those, and it should be possible to only run the program once.
2020-01-17 19:30:14 +00:00
|
|
|
|
|
|
|
{- All unknown configs are passed through in case the external program
|
|
|
|
- uses them. -}
|
|
|
|
lenientRemoteConfigParser :: RemoteConfigParser
|
2020-01-20 20:56:34 +00:00
|
|
|
lenientRemoteConfigParser =
|
|
|
|
addRemoteConfigParser specialRemoteConfigParsers baseRemoteConfigParser
|
|
|
|
|
|
|
|
baseRemoteConfigParser :: RemoteConfigParser
|
|
|
|
baseRemoteConfigParser = RemoteConfigParser
|
|
|
|
{ remoteConfigFieldParsers =
|
|
|
|
[ optionalStringParser externaltypeField
|
|
|
|
(FieldDesc "type of external special remote to use")
|
2020-06-16 21:59:55 +00:00
|
|
|
, trueFalseParser readonlyField (Just False)
|
2020-01-20 20:56:34 +00:00
|
|
|
(FieldDesc "enable readonly mode")
|
|
|
|
]
|
|
|
|
, remoteConfigRestPassthrough = Just
|
|
|
|
( const True
|
|
|
|
, [("*", FieldDesc "all other parameters are passed to external special remote program")]
|
|
|
|
)
|
|
|
|
}
|
add LISTCONFIGS to external special remote protocol
Special remote programs that use GETCONFIG/SETCONFIG are recommended
to implement it.
The description is not yet used, but will be useful later when adding a way
to make initremote list all accepted configs.
configParser now takes a RemoteConfig parameter. Normally, that's not
needed, because configParser returns a parter, it does not parse it
itself. But, it's needed to look at externaltype and work out what
external remote program to run for LISTCONFIGS.
Note that, while externalUUID is changed to a Maybe UUID, checkExportSupported
used to use NoUUID. The code that now checks for Nothing used to behave
in some undefined way if the external program made requests that
triggered it.
Also, note that in externalSetup, once it generates external,
it parses the RemoteConfig strictly. That generates a
ParsedRemoteConfig, which is thrown away. The reason it's ok to throw
that away, is that, if the strict parse succeeded, the result must be
the same as the earlier, lenient parse.
initremote of an external special remote now runs the program three
times. First for LISTCONFIGS, then EXPORTSUPPORTED, and again
LISTCONFIGS+INITREMOTE. It would not be hard to eliminate at least
one of those, and it should be possible to only run the program once.
2020-01-17 19:30:14 +00:00
|
|
|
|
|
|
|
{- When the remote supports LISTCONFIGS, only accept the ones it listed.
|
|
|
|
- When it does not, accept all configs. -}
|
|
|
|
strictRemoteConfigParser :: External -> Annex RemoteConfigParser
|
|
|
|
strictRemoteConfigParser external = listConfigs external >>= \case
|
|
|
|
Nothing -> return lenientRemoteConfigParser
|
|
|
|
Just l -> do
|
|
|
|
let s = S.fromList (map fst l)
|
|
|
|
let listed f = S.member (fromProposedAccepted f) s
|
|
|
|
return $ lenientRemoteConfigParser
|
2020-01-20 20:23:35 +00:00
|
|
|
{ remoteConfigRestPassthrough = Just (listed, l) }
|
add LISTCONFIGS to external special remote protocol
Special remote programs that use GETCONFIG/SETCONFIG are recommended
to implement it.
The description is not yet used, but will be useful later when adding a way
to make initremote list all accepted configs.
configParser now takes a RemoteConfig parameter. Normally, that's not
needed, because configParser returns a parter, it does not parse it
itself. But, it's needed to look at externaltype and work out what
external remote program to run for LISTCONFIGS.
Note that, while externalUUID is changed to a Maybe UUID, checkExportSupported
used to use NoUUID. The code that now checks for Nothing used to behave
in some undefined way if the external program made requests that
triggered it.
Also, note that in externalSetup, once it generates external,
it parses the RemoteConfig strictly. That generates a
ParsedRemoteConfig, which is thrown away. The reason it's ok to throw
that away, is that, if the strict parse succeeded, the result must be
the same as the earlier, lenient parse.
initremote of an external special remote now runs the program three
times. First for LISTCONFIGS, then EXPORTSUPPORTED, and again
LISTCONFIGS+INITREMOTE. It would not be hard to eliminate at least
one of those, and it should be possible to only run the program once.
2020-01-17 19:30:14 +00:00
|
|
|
|
2020-01-20 20:23:35 +00:00
|
|
|
listConfigs :: External -> Annex (Maybe [(Setting, FieldDesc)])
|
add LISTCONFIGS to external special remote protocol
Special remote programs that use GETCONFIG/SETCONFIG are recommended
to implement it.
The description is not yet used, but will be useful later when adding a way
to make initremote list all accepted configs.
configParser now takes a RemoteConfig parameter. Normally, that's not
needed, because configParser returns a parter, it does not parse it
itself. But, it's needed to look at externaltype and work out what
external remote program to run for LISTCONFIGS.
Note that, while externalUUID is changed to a Maybe UUID, checkExportSupported
used to use NoUUID. The code that now checks for Nothing used to behave
in some undefined way if the external program made requests that
triggered it.
Also, note that in externalSetup, once it generates external,
it parses the RemoteConfig strictly. That generates a
ParsedRemoteConfig, which is thrown away. The reason it's ok to throw
that away, is that, if the strict parse succeeded, the result must be
the same as the earlier, lenient parse.
initremote of an external special remote now runs the program three
times. First for LISTCONFIGS, then EXPORTSUPPORTED, and again
LISTCONFIGS+INITREMOTE. It would not be hard to eliminate at least
one of those, and it should be possible to only run the program once.
2020-01-17 19:30:14 +00:00
|
|
|
listConfigs external = handleRequest external LISTCONFIGS Nothing (collect [])
|
|
|
|
where
|
|
|
|
collect l req = case req of
|
|
|
|
CONFIG s d -> Just $ return $
|
2020-01-20 20:23:35 +00:00
|
|
|
GetNextMessage $ collect ((s, FieldDesc d) : l)
|
add LISTCONFIGS to external special remote protocol
Special remote programs that use GETCONFIG/SETCONFIG are recommended
to implement it.
The description is not yet used, but will be useful later when adding a way
to make initremote list all accepted configs.
configParser now takes a RemoteConfig parameter. Normally, that's not
needed, because configParser returns a parter, it does not parse it
itself. But, it's needed to look at externaltype and work out what
external remote program to run for LISTCONFIGS.
Note that, while externalUUID is changed to a Maybe UUID, checkExportSupported
used to use NoUUID. The code that now checks for Nothing used to behave
in some undefined way if the external program made requests that
triggered it.
Also, note that in externalSetup, once it generates external,
it parses the RemoteConfig strictly. That generates a
ParsedRemoteConfig, which is thrown away. The reason it's ok to throw
that away, is that, if the strict parse succeeded, the result must be
the same as the earlier, lenient parse.
initremote of an external special remote now runs the program three
times. First for LISTCONFIGS, then EXPORTSUPPORTED, and again
LISTCONFIGS+INITREMOTE. It would not be hard to eliminate at least
one of those, and it should be possible to only run the program once.
2020-01-17 19:30:14 +00:00
|
|
|
CONFIGEND -> result (Just (reverse l))
|
|
|
|
UNSUPPORTED_REQUEST -> result Nothing
|
|
|
|
_ -> Nothing
|
|
|
|
|
|
|
|
remoteConfigParser :: RemoteConfig -> Annex RemoteConfigParser
|
|
|
|
remoteConfigParser c
|
2020-01-17 21:23:19 +00:00
|
|
|
-- No need to start the external when there is no config to parse,
|
|
|
|
-- or when everything in the config was already accepted; in those
|
|
|
|
-- cases the lenient parser will do the same thing as the strict
|
|
|
|
-- parser.
|
|
|
|
| M.null (M.filter isproposed c) = return lenientRemoteConfigParser
|
2020-01-20 20:56:34 +00:00
|
|
|
| otherwise = case parseRemoteConfig c baseRemoteConfigParser of
|
add LISTCONFIGS to external special remote protocol
Special remote programs that use GETCONFIG/SETCONFIG are recommended
to implement it.
The description is not yet used, but will be useful later when adding a way
to make initremote list all accepted configs.
configParser now takes a RemoteConfig parameter. Normally, that's not
needed, because configParser returns a parter, it does not parse it
itself. But, it's needed to look at externaltype and work out what
external remote program to run for LISTCONFIGS.
Note that, while externalUUID is changed to a Maybe UUID, checkExportSupported
used to use NoUUID. The code that now checks for Nothing used to behave
in some undefined way if the external program made requests that
triggered it.
Also, note that in externalSetup, once it generates external,
it parses the RemoteConfig strictly. That generates a
ParsedRemoteConfig, which is thrown away. The reason it's ok to throw
that away, is that, if the strict parse succeeded, the result must be
the same as the earlier, lenient parse.
initremote of an external special remote now runs the program three
times. First for LISTCONFIGS, then EXPORTSUPPORTED, and again
LISTCONFIGS+INITREMOTE. It would not be hard to eliminate at least
one of those, and it should be possible to only run the program once.
2020-01-17 19:30:14 +00:00
|
|
|
Left _ -> return lenientRemoteConfigParser
|
|
|
|
Right pc -> case (getRemoteConfigValue externaltypeField pc, getRemoteConfigValue readonlyField pc) of
|
|
|
|
(Nothing, _) -> return lenientRemoteConfigParser
|
|
|
|
(_, Just True) -> return lenientRemoteConfigParser
|
|
|
|
(Just externaltype, _) -> do
|
2021-01-26 16:42:47 +00:00
|
|
|
external <- newExternal externaltype Nothing pc Nothing Nothing Nothing
|
add LISTCONFIGS to external special remote protocol
Special remote programs that use GETCONFIG/SETCONFIG are recommended
to implement it.
The description is not yet used, but will be useful later when adding a way
to make initremote list all accepted configs.
configParser now takes a RemoteConfig parameter. Normally, that's not
needed, because configParser returns a parter, it does not parse it
itself. But, it's needed to look at externaltype and work out what
external remote program to run for LISTCONFIGS.
Note that, while externalUUID is changed to a Maybe UUID, checkExportSupported
used to use NoUUID. The code that now checks for Nothing used to behave
in some undefined way if the external program made requests that
triggered it.
Also, note that in externalSetup, once it generates external,
it parses the RemoteConfig strictly. That generates a
ParsedRemoteConfig, which is thrown away. The reason it's ok to throw
that away, is that, if the strict parse succeeded, the result must be
the same as the earlier, lenient parse.
initremote of an external special remote now runs the program three
times. First for LISTCONFIGS, then EXPORTSUPPORTED, and again
LISTCONFIGS+INITREMOTE. It would not be hard to eliminate at least
one of those, and it should be possible to only run the program once.
2020-01-17 19:30:14 +00:00
|
|
|
strictRemoteConfigParser external
|
2020-01-17 21:23:19 +00:00
|
|
|
where
|
|
|
|
isproposed (Accepted _) = False
|
|
|
|
isproposed (Proposed _) = True
|