2011-03-30 18:56:31 +00:00
|
|
|
{- A "remote" that is just a filesystem directory.
|
2011-03-30 17:18:46 +00:00
|
|
|
-
|
2022-03-21 17:12:02 +00:00
|
|
|
- Copyright 2011-2022 Joey Hess <id@joeyh.name>
|
2011-03-30 17:18:46 +00:00
|
|
|
-
|
2019-03-13 19:48:14 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2011-03-30 17:18:46 +00:00
|
|
|
-}
|
|
|
|
|
2020-10-30 14:29:42 +00:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
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 #-}
|
2013-05-11 20:03:00 +00:00
|
|
|
{-# LANGUAGE CPP #-}
|
|
|
|
|
2014-08-04 13:35:57 +00:00
|
|
|
module Remote.Directory (
|
|
|
|
remote,
|
|
|
|
finalizeStoreGeneric,
|
|
|
|
removeDirGeneric,
|
|
|
|
) where
|
2011-03-30 17:18:46 +00:00
|
|
|
|
2012-06-20 17:13:40 +00:00
|
|
|
import qualified Data.ByteString.Lazy as L
|
2011-03-30 17:18:46 +00:00
|
|
|
import qualified Data.Map as M
|
2020-10-30 14:29:42 +00:00
|
|
|
import qualified System.FilePath.ByteString as P
|
2015-01-28 19:55:17 +00:00
|
|
|
import Data.Default
|
2023-03-21 22:22:41 +00:00
|
|
|
import System.PosixCompat.Files (isRegularFile, deviceID)
|
|
|
|
#ifndef mingw32_HOST_OS
|
|
|
|
import System.PosixCompat.Files (getFdStatus)
|
|
|
|
#endif
|
2011-03-30 17:18:46 +00:00
|
|
|
|
2016-01-20 20:36:33 +00:00
|
|
|
import Annex.Common
|
2011-06-02 01:56:04 +00:00
|
|
|
import Types.Remote
|
2017-09-15 20:34:45 +00:00
|
|
|
import Types.Export
|
2014-02-11 18:06:50 +00:00
|
|
|
import Types.Creds
|
2011-06-30 17:16:57 +00:00
|
|
|
import qualified Git
|
2013-03-13 20:16:01 +00:00
|
|
|
import Config.Cost
|
2011-03-30 18:32:08 +00:00
|
|
|
import Config
|
2020-01-14 16:35:08 +00:00
|
|
|
import Annex.SpecialRemote.Config
|
2011-08-17 00:49:54 +00:00
|
|
|
import Remote.Helper.Special
|
2019-02-20 19:55:01 +00:00
|
|
|
import Remote.Helper.ExportImport
|
2023-08-16 19:48:09 +00:00
|
|
|
import Remote.Helper.Path
|
2019-02-27 17:42:34 +00:00
|
|
|
import Types.Import
|
2014-07-27 00:19:24 +00:00
|
|
|
import qualified Remote.Directory.LegacyChunked as Legacy
|
2021-04-14 18:43:08 +00:00
|
|
|
import Annex.CopyFile
|
2012-04-20 20:24:44 +00:00
|
|
|
import Annex.Content
|
2020-09-02 18:25:12 +00:00
|
|
|
import Annex.Perms
|
2013-09-07 22:38:00 +00:00
|
|
|
import Annex.UUID
|
2022-05-09 17:18:47 +00:00
|
|
|
import Annex.Verify
|
2020-07-03 17:41:57 +00:00
|
|
|
import Backend
|
|
|
|
import Types.KeySource
|
2020-10-30 14:29:42 +00:00
|
|
|
import Types.ProposedAccepted
|
2013-03-28 21:03:04 +00:00
|
|
|
import Utility.Metered
|
2017-08-31 18:24:32 +00:00
|
|
|
import Utility.Tmp
|
2019-03-04 17:20:58 +00:00
|
|
|
import Utility.InodeCache
|
2020-10-30 14:29:42 +00:00
|
|
|
import Utility.FileMode
|
|
|
|
import Utility.Directory.Create
|
|
|
|
import qualified Utility.RawFilePath as R
|
2023-08-01 22:41:27 +00:00
|
|
|
#ifndef mingw32_HOST_OS
|
|
|
|
import Utility.OpenFd
|
|
|
|
#endif
|
2011-03-30 17:18:46 +00:00
|
|
|
|
2011-12-31 08:11:39 +00:00
|
|
|
remote :: RemoteType
|
2020-01-14 16:35:08 +00:00
|
|
|
remote = specialRemoteType $ RemoteType
|
2017-09-07 17:45:31 +00:00
|
|
|
{ typename = "directory"
|
|
|
|
, enumerate = const (findSpecialRemotes "directory")
|
|
|
|
, generate = gen
|
2020-01-14 17:18:15 +00:00
|
|
|
, configParser = mkRemoteConfigParser
|
2020-01-20 19:20:04 +00:00
|
|
|
[ optionalStringParser directoryField
|
|
|
|
(FieldDesc "(required) where the special remote stores data")
|
2022-03-21 17:12:02 +00:00
|
|
|
, yesNoParser ignoreinodesField (Just False)
|
|
|
|
(FieldDesc "ignore inodes when importing/exporting")
|
2020-01-20 19:20:04 +00:00
|
|
|
]
|
2017-09-07 17:45:31 +00:00
|
|
|
, setup = directorySetup
|
|
|
|
, exportSupported = exportIsSupported
|
2019-03-04 20:02:56 +00:00
|
|
|
, importSupported = importIsSupported
|
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
|
|
|
}
|
2011-03-30 17:18:46 +00:00
|
|
|
|
2020-01-14 16:35:08 +00:00
|
|
|
directoryField :: RemoteConfigField
|
|
|
|
directoryField = Accepted "directory"
|
|
|
|
|
2022-03-21 17:12:02 +00:00
|
|
|
ignoreinodesField :: RemoteConfigField
|
|
|
|
ignoreinodesField = Accepted "ignoreinodes"
|
|
|
|
|
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 = do
|
|
|
|
c <- parsedRemoteConfig remote rc
|
2023-01-12 17:42:28 +00:00
|
|
|
cst <- remoteCost gc c cheapRemoteCost
|
2014-08-03 19:35:23 +00:00
|
|
|
let chunkconfig = getChunkConfig c
|
2021-04-14 18:43:08 +00:00
|
|
|
cow <- liftIO newCopyCoWTried
|
2022-03-21 17:12:02 +00:00
|
|
|
let ii = IgnoreInodes $ fromMaybe True $
|
|
|
|
getRemoteConfigValue ignoreinodesField c
|
2017-09-07 17:45:31 +00:00
|
|
|
return $ Just $ specialRemote c
|
2021-04-14 19:11:00 +00:00
|
|
|
(storeKeyM dir chunkconfig cow)
|
2021-04-14 18:43:08 +00:00
|
|
|
(retrieveKeyFileM dir chunkconfig cow)
|
2020-05-13 15:50:31 +00:00
|
|
|
(removeKeyM dir)
|
|
|
|
(checkPresentM dir chunkconfig)
|
2014-12-16 19:26:13 +00:00
|
|
|
Remote
|
|
|
|
{ uuid = u
|
|
|
|
, cost = cst
|
|
|
|
, name = Git.repoDescribe r
|
|
|
|
, storeKey = storeKeyDummy
|
2020-05-13 21:05:56 +00:00
|
|
|
, retrieveKeyFile = retrieveKeyFileDummy
|
2017-09-15 17:15:47 +00:00
|
|
|
, retrieveKeyFileCheap = retrieveKeyFileCheapM dir chunkconfig
|
2018-06-21 15:35:27 +00:00
|
|
|
, retrievalSecurityPolicy = RetrievalAllKeysSecure
|
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 = True
|
2019-01-30 18:55:28 +00:00
|
|
|
, exportActions = ExportActions
|
2021-04-14 20:17:43 +00:00
|
|
|
{ storeExport = storeExportM dir cow
|
2021-04-14 20:10:09 +00:00
|
|
|
, retrieveExport = retrieveExportM dir cow
|
2017-09-15 17:15:47 +00:00
|
|
|
, removeExport = removeExportM dir
|
|
|
|
, checkPresentExport = checkPresentExportM dir
|
|
|
|
-- Not needed because removeExportLocation
|
|
|
|
-- auto-removes empty directories.
|
|
|
|
, removeExportDirectory = Nothing
|
2024-03-09 17:37:51 +00:00
|
|
|
, renameExport = Just $ renameExportM dir
|
2017-09-01 17:02:07 +00:00
|
|
|
}
|
2019-02-27 17:42:34 +00:00
|
|
|
, importActions = ImportActions
|
2022-03-21 17:12:02 +00:00
|
|
|
{ listImportableContents = listImportableContentsM ii dir
|
|
|
|
, importKey = Just (importKeyM ii dir)
|
|
|
|
, retrieveExportWithContentIdentifier = retrieveExportWithContentIdentifierM ii dir cow
|
|
|
|
, storeExportWithContentIdentifier = storeExportWithContentIdentifierM ii dir cow
|
|
|
|
, removeExportWithContentIdentifier = removeExportWithContentIdentifierM ii dir
|
2019-05-28 15:12:53 +00:00
|
|
|
-- Not needed because removeExportWithContentIdentifier
|
|
|
|
-- auto-removes empty directories.
|
2019-03-05 18:20:14 +00:00
|
|
|
, removeExportDirectoryWhenEmpty = Nothing
|
2022-03-21 17:12:02 +00:00
|
|
|
, checkPresentExportWithContentIdentifier = checkPresentExportWithContentIdentifierM ii dir
|
2019-02-27 17:42:34 +00:00
|
|
|
}
|
2014-12-16 19:26:13 +00:00
|
|
|
, whereisKey = Nothing
|
|
|
|
, remoteFsck = Nothing
|
|
|
|
, repairRepo = Nothing
|
|
|
|
, config = c
|
2018-06-04 18:31:55 +00:00
|
|
|
, getRepo = return r
|
2014-12-16 19:26:13 +00:00
|
|
|
, gitconfig = gc
|
2020-10-30 14:29:42 +00:00
|
|
|
, localpath = Just dir'
|
2014-12-16 19:26:13 +00:00
|
|
|
, readonly = False
|
2018-08-30 15:12:18 +00:00
|
|
|
, appendonly = False
|
2020-12-28 19:08:53 +00:00
|
|
|
, untrustworthy = False
|
2023-08-16 19:48:09 +00:00
|
|
|
, availability = checkPathAvailability True dir'
|
2014-12-16 19:26:13 +00:00
|
|
|
, remotetype = remote
|
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 { remoteAnnexDirectory = Just "/dev/null" }) rs
|
2020-10-30 14:29:42 +00:00
|
|
|
, getInfo = return [("directory", dir')]
|
2014-12-16 19:26:13 +00:00
|
|
|
, claimUrl = Nothing
|
|
|
|
, checkUrl = Nothing
|
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
|
|
|
}
|
2013-01-01 17:52:47 +00:00
|
|
|
where
|
2020-10-30 14:29:42 +00:00
|
|
|
dir = toRawFilePath dir'
|
|
|
|
dir' = fromMaybe (giveup "missing directory") (remoteAnnexDirectory gc)
|
2012-03-03 22:05:55 +00:00
|
|
|
|
2017-02-07 18:35:58 +00:00
|
|
|
directorySetup :: SetupStage -> Maybe UUID -> Maybe CredPair -> RemoteConfig -> RemoteGitConfig -> Annex (RemoteConfig, UUID)
|
|
|
|
directorySetup _ mu _ c gc = do
|
2013-09-07 22:38:00 +00:00
|
|
|
u <- maybe (liftIO genUUID) return mu
|
2011-03-30 17:18:46 +00:00
|
|
|
-- verify configuration is sane
|
2020-01-10 18:10:20 +00:00
|
|
|
let dir = maybe (giveup "Specify directory=") fromProposedAccepted $
|
2020-01-14 16:35:08 +00:00
|
|
|
M.lookup directoryField c
|
2020-10-30 14:29:42 +00:00
|
|
|
absdir <- liftIO $ fromRawFilePath <$> absPath (toRawFilePath dir)
|
2013-05-06 21:15:36 +00:00
|
|
|
liftIO $ unlessM (doesDirectoryExist absdir) $
|
2016-11-16 01:29:54 +00:00
|
|
|
giveup $ "Directory does not exist: " ++ absdir
|
2016-05-23 21:27:15 +00:00
|
|
|
(c', _encsetup) <- encryptionSetup c gc
|
2011-03-30 17:18:46 +00:00
|
|
|
|
2011-03-30 18:32:08 +00:00
|
|
|
-- The directory is stored in git config, not in this remote's
|
2023-03-14 02:39:16 +00:00
|
|
|
-- persistent state, so it can vary between hosts.
|
2018-03-27 16:41:57 +00:00
|
|
|
gitConfigSpecialRemote u c' [("directory", absdir)]
|
2020-01-14 16:35:08 +00:00
|
|
|
return (M.delete directoryField c', u)
|
2011-03-30 17:18:46 +00:00
|
|
|
|
2014-07-27 00:19:24 +00:00
|
|
|
{- Locations to try to access a given Key in the directory.
|
|
|
|
- We try more than one since we used to write to different hash
|
|
|
|
- directories. -}
|
2020-10-30 14:29:42 +00:00
|
|
|
locations :: RawFilePath -> Key -> [RawFilePath]
|
|
|
|
locations d k = map (d P.</>) (keyPaths k)
|
2011-03-30 17:18:46 +00:00
|
|
|
|
2014-07-27 00:19:24 +00:00
|
|
|
{- Returns the location off a Key in the directory. If the key is
|
|
|
|
- present, returns the location that is actually used, otherwise
|
|
|
|
- returns the first, default location. -}
|
2020-10-30 14:29:42 +00:00
|
|
|
getLocation :: RawFilePath -> Key -> IO RawFilePath
|
2014-07-27 00:19:24 +00:00
|
|
|
getLocation d k = do
|
|
|
|
let locs = locations d k
|
2020-10-30 14:29:42 +00:00
|
|
|
fromMaybe (Prelude.head locs)
|
|
|
|
<$> firstM (doesFileExist . fromRawFilePath) locs
|
2014-07-27 00:19:24 +00:00
|
|
|
|
2012-11-19 17:18:23 +00:00
|
|
|
{- Directory where the file(s) for a key are stored. -}
|
2020-10-30 14:29:42 +00:00
|
|
|
storeDir :: RawFilePath -> Key -> RawFilePath
|
|
|
|
storeDir d k = P.addTrailingPathSeparator $
|
|
|
|
d P.</> hashDirLower def k P.</> keyFile k
|
2012-11-19 17:18:23 +00:00
|
|
|
|
2014-07-27 00:19:24 +00:00
|
|
|
{- Check if there is enough free disk space in the remote's directory to
|
|
|
|
- store the key. Note that the unencrypted key size is checked. -}
|
2021-04-14 19:11:00 +00:00
|
|
|
storeKeyM :: RawFilePath -> ChunkConfig -> CopyCoWTried -> Storer
|
|
|
|
storeKeyM d chunkconfig cow k c m =
|
2020-11-06 18:10:58 +00:00
|
|
|
ifM (checkDiskSpaceDirectory d k)
|
2021-04-14 19:11:00 +00:00
|
|
|
( do
|
2022-08-12 16:45:46 +00:00
|
|
|
void $ liftIO $ tryIO $ createDirectoryUnder [d] tmpdir
|
2021-04-14 19:11:00 +00:00
|
|
|
store
|
2020-05-13 15:50:31 +00:00
|
|
|
, giveup "Not enough free disk space."
|
|
|
|
)
|
2021-04-14 19:11:00 +00:00
|
|
|
where
|
|
|
|
store = case chunkconfig of
|
2020-05-13 18:03:00 +00:00
|
|
|
LegacyChunks chunksize ->
|
2021-04-14 19:11:00 +00:00
|
|
|
let go _k b p = liftIO $ Legacy.store
|
2020-10-30 14:29:42 +00:00
|
|
|
(fromRawFilePath d)
|
|
|
|
chunksize
|
|
|
|
(finalizeStoreGeneric d)
|
|
|
|
k b p
|
|
|
|
(fromRawFilePath tmpdir)
|
|
|
|
(fromRawFilePath destdir)
|
2021-04-14 19:11:00 +00:00
|
|
|
in byteStorer go k c m
|
|
|
|
NoChunks ->
|
2022-05-09 19:38:21 +00:00
|
|
|
let go _k src p = liftIO $ do
|
2021-08-16 19:56:24 +00:00
|
|
|
void $ fileCopier cow src tmpf p Nothing
|
2022-05-09 19:38:21 +00:00
|
|
|
finalizeStoreGeneric d tmpdir destdir
|
2021-04-14 19:11:00 +00:00
|
|
|
in fileStorer go k c m
|
|
|
|
_ ->
|
|
|
|
let go _k b p = liftIO $ do
|
|
|
|
meteredWriteFile p tmpf b
|
|
|
|
finalizeStoreGeneric d tmpdir destdir
|
|
|
|
in byteStorer go k c m
|
|
|
|
|
2020-10-30 14:29:42 +00:00
|
|
|
tmpdir = P.addTrailingPathSeparator $ d P.</> "tmp" P.</> kf
|
2021-04-14 19:11:00 +00:00
|
|
|
tmpf = fromRawFilePath tmpdir </> fromRawFilePath kf
|
2020-10-30 14:29:42 +00:00
|
|
|
kf = keyFile k
|
2014-07-27 00:19:24 +00:00
|
|
|
destdir = storeDir d k
|
2014-08-04 13:35:57 +00:00
|
|
|
|
2021-04-14 19:11:00 +00:00
|
|
|
checkDiskSpaceDirectory :: RawFilePath -> Key -> Annex Bool
|
|
|
|
checkDiskSpaceDirectory d k = do
|
|
|
|
annexdir <- fromRepo gitAnnexObjectDir
|
|
|
|
samefilesystem <- liftIO $ catchDefaultIO False $
|
|
|
|
(\a b -> deviceID a == deviceID b)
|
2022-09-05 17:44:03 +00:00
|
|
|
<$> R.getSymbolicLinkStatus d
|
|
|
|
<*> R.getSymbolicLinkStatus annexdir
|
disk free checking for unsized keys
Improve disk free space checking when transferring unsized keys to
local git remotes. Since the size of the object file is known, can
check that instead.
Getting unsized keys from local git remotes does not check the actual
object size. It would be harder to handle that direction because the size
check is run locally, before anything involving the remote is done. So it
doesn't know the size of the file on the remote.
Also, transferring unsized keys to other remotes, including ssh remotes and
p2p remotes don't do disk size checking for unsized keys. This would need a
change in protocol.
(It does seem like it would be possible to implement the same thing for
directory special remotes though.)
In some sense, it might be better to not ever do disk free checking for
unsized keys, than to do it only sometimes. A user might notice this
direction working and consider it a bug that the other direction does not.
On the other hand, disk reserve checking is not implemented for most
special remotes at all, and yet it is implemented for a few, which is also
inconsistent, but best effort. And so doing this best effort seems to make
some sense. Fundamentally, if the user wants the size to always be checked,
they should not use unsized keys.
Sponsored-by: Brock Spratlen on Patreon
2024-01-16 18:29:10 +00:00
|
|
|
checkDiskSpace Nothing (Just d) k 0 samefilesystem
|
2021-04-14 19:11:00 +00:00
|
|
|
|
2014-08-04 13:35:57 +00:00
|
|
|
{- Passed a temp directory that contains the files that should be placed
|
|
|
|
- in the dest directory, moves it into place. Anything already existing
|
|
|
|
- in the dest directory will be deleted. File permissions will be locked
|
|
|
|
- down. -}
|
2020-10-30 14:29:42 +00:00
|
|
|
finalizeStoreGeneric :: RawFilePath -> RawFilePath -> RawFilePath -> IO ()
|
2020-03-05 18:56:47 +00:00
|
|
|
finalizeStoreGeneric d tmp dest = do
|
2023-07-21 18:57:29 +00:00
|
|
|
removeDirGeneric False (fromRawFilePath d) dest'
|
2022-08-12 16:45:46 +00:00
|
|
|
createDirectoryUnder [d] (parentDir dest)
|
2020-10-30 14:29:42 +00:00
|
|
|
renameDirectory (fromRawFilePath tmp) dest'
|
2014-08-04 13:35:57 +00:00
|
|
|
-- may fail on some filesystems
|
|
|
|
void $ tryIO $ do
|
2020-11-06 18:10:58 +00:00
|
|
|
mapM_ (preventWrite . toRawFilePath) =<< dirContents dest'
|
|
|
|
preventWrite dest
|
2020-10-30 14:29:42 +00:00
|
|
|
where
|
|
|
|
dest' = fromRawFilePath dest
|
2012-03-03 22:05:55 +00:00
|
|
|
|
2021-04-14 18:43:08 +00:00
|
|
|
retrieveKeyFileM :: RawFilePath -> ChunkConfig -> CopyCoWTried -> Retriever
|
|
|
|
retrieveKeyFileM d (LegacyChunks _) _ = Legacy.retrieve locations d
|
2021-08-16 20:22:00 +00:00
|
|
|
retrieveKeyFileM d NoChunks cow = fileRetriever' $ \dest k p iv -> do
|
2021-04-14 18:43:08 +00:00
|
|
|
src <- liftIO $ fromRawFilePath <$> getLocation d k
|
2022-05-09 19:38:21 +00:00
|
|
|
void $ liftIO $ fileCopier cow src (fromRawFilePath dest) p iv
|
2021-04-14 18:43:08 +00:00
|
|
|
retrieveKeyFileM d _ _ = byteRetriever $ \k sink ->
|
2020-10-30 14:29:42 +00:00
|
|
|
sink =<< liftIO (L.readFile . fromRawFilePath =<< getLocation d k)
|
2011-04-17 01:41:14 +00:00
|
|
|
|
2020-10-30 14:29:42 +00:00
|
|
|
retrieveKeyFileCheapM :: RawFilePath -> ChunkConfig -> Maybe (Key -> AssociatedFile -> FilePath -> Annex ())
|
2014-07-27 00:19:24 +00:00
|
|
|
-- no cheap retrieval possible for chunks
|
2020-05-13 21:05:56 +00:00
|
|
|
retrieveKeyFileCheapM _ (UnpaddedChunks _) = Nothing
|
|
|
|
retrieveKeyFileCheapM _ (LegacyChunks _) = Nothing
|
2013-08-02 16:27:32 +00:00
|
|
|
#ifndef mingw32_HOST_OS
|
2020-05-13 21:05:56 +00:00
|
|
|
retrieveKeyFileCheapM d NoChunks = Just $ \k _af f -> liftIO $ do
|
2020-10-30 14:29:42 +00:00
|
|
|
file <- fromRawFilePath <$> (absPath =<< getLocation d k)
|
2015-04-18 17:36:12 +00:00
|
|
|
ifM (doesFileExist file)
|
2023-03-01 19:55:58 +00:00
|
|
|
( R.createSymbolicLink (toRawFilePath file) (toRawFilePath f)
|
2020-05-13 21:05:56 +00:00
|
|
|
, giveup "content file not present in remote"
|
2015-04-18 17:36:12 +00:00
|
|
|
)
|
2013-05-11 20:03:00 +00:00
|
|
|
#else
|
2020-05-13 21:05:56 +00:00
|
|
|
retrieveKeyFileCheapM _ _ = Nothing
|
2013-05-11 20:03:00 +00:00
|
|
|
#endif
|
2012-03-03 22:05:55 +00:00
|
|
|
|
2020-10-30 14:29:42 +00:00
|
|
|
removeKeyM :: RawFilePath -> Remover
|
toward SafeDropProof expiry checking
Added Maybe POSIXTime to SafeDropProof, which gets set when the proof is
based on a LockedCopy. If there are several LockedCopies, it uses the
closest expiry time. That is not optimal, it may be that the proof
expires based on one LockedCopy but another one has not expired. But
that seems unlikely to really happen, and anyway the user can just
re-run a drop if it fails due to expiry.
Pass the SafeDropProof to removeKey, which is responsible for checking
it for expiry in situations where that could be a problem. Which really
only means in Remote.Git.
Made Remote.Git check expiry when dropping from a local remote.
Checking expiry when dropping from a P2P remote is not yet implemented.
P2P.Protocol.remove has SafeDropProof plumbed through to it for that
purpose.
Fixing the remaining 2 build warnings should complete this work.
Note that the use of a POSIXTime here means that if the clock gets set
forward while git-annex is in the middle of a drop, it may say that
dropping took too long. That seems ok. Less ok is that if the clock gets
turned back a sufficient amount (eg 5 minutes), proof expiry won't be
noticed. It might be better to use the Monotonic clock, but that doesn't
advance when a laptop is suspended, and while there is the linux
Boottime clock, that is not available on other systems. Perhaps a
combination of POSIXTime and the Monotonic clock could detect laptop
suspension and also detect clock being turned back?
There is a potential future flag day where
p2pDefaultLockContentRetentionDuration is not assumed, but is probed
using the P2P protocol, and peers that don't support it can no longer
produce a LockedCopy. Until that happens, when git-annex is
communicating with older peers there is a risk of data loss when
a ssh connection closes during LOCKCONTENT.
2024-07-04 16:23:46 +00:00
|
|
|
removeKeyM d _proof k = liftIO $ removeDirGeneric True
|
2020-10-30 14:29:42 +00:00
|
|
|
(fromRawFilePath d)
|
|
|
|
(fromRawFilePath (storeDir d k))
|
2014-08-04 13:00:57 +00:00
|
|
|
|
|
|
|
{- Removes the directory, which must be located under the topdir.
|
|
|
|
-
|
|
|
|
- Succeeds even on directories and contents that do not have write
|
2020-05-14 18:08:09 +00:00
|
|
|
- permission, if it's possible to turn the write bit on.
|
2014-08-04 13:00:57 +00:00
|
|
|
-
|
|
|
|
- If the directory does not exist, succeeds as long as the topdir does
|
|
|
|
- exist. If the topdir does not exist, fails, because in this case the
|
|
|
|
- remote is not currently accessible and probably still has the content
|
|
|
|
- we were supposed to remove from it.
|
2023-07-21 18:57:29 +00:00
|
|
|
-
|
|
|
|
- Empty parent directories (up to but not including the topdir)
|
|
|
|
- can also be removed. Failure to remove such a directory is not treated
|
|
|
|
- as an error.
|
2014-08-04 13:00:57 +00:00
|
|
|
-}
|
2023-07-21 18:57:29 +00:00
|
|
|
removeDirGeneric :: Bool -> FilePath -> FilePath -> IO ()
|
|
|
|
removeDirGeneric removeemptyparents topdir dir = do
|
2020-11-06 18:10:58 +00:00
|
|
|
void $ tryIO $ allowWrite (toRawFilePath dir)
|
2013-08-04 17:39:31 +00:00
|
|
|
#ifdef mingw32_HOST_OS
|
|
|
|
{- Windows needs the files inside the directory to be writable
|
|
|
|
- before it can delete them. -}
|
2020-11-19 16:33:00 +00:00
|
|
|
void $ tryIO $ mapM_ (allowWrite . toRawFilePath) =<< dirContents dir
|
2013-08-04 17:39:31 +00:00
|
|
|
#endif
|
2020-05-14 18:08:09 +00:00
|
|
|
tryNonAsync (removeDirectoryRecursive dir) >>= \case
|
|
|
|
Right () -> return ()
|
|
|
|
Left e ->
|
|
|
|
unlessM (doesDirectoryExist topdir <&&> (not <$> doesDirectoryExist dir)) $
|
|
|
|
throwM e
|
2023-07-21 18:57:29 +00:00
|
|
|
when removeemptyparents $ do
|
|
|
|
subdir <- relPathDirToFile (toRawFilePath topdir) (P.takeDirectory (toRawFilePath dir))
|
|
|
|
goparents (Just (P.takeDirectory subdir)) (Right ())
|
|
|
|
where
|
|
|
|
goparents _ (Left _e) = return ()
|
|
|
|
goparents Nothing _ = return ()
|
|
|
|
goparents (Just subdir) _ = do
|
|
|
|
let d = topdir </> fromRawFilePath subdir
|
|
|
|
goparents (upFrom subdir) =<< tryIO (removeDirectory d)
|
2011-03-30 17:18:46 +00:00
|
|
|
|
2020-10-30 14:29:42 +00:00
|
|
|
checkPresentM :: RawFilePath -> ChunkConfig -> CheckPresent
|
2017-09-15 17:15:47 +00:00
|
|
|
checkPresentM d (LegacyChunks _) k = Legacy.checkKey d locations k
|
|
|
|
checkPresentM d _ k = checkPresentGeneric d (locations d k)
|
add API for exporting
Implemented so far for the directory special remote.
Several remotes don't make sense to export to. Regular Git remotes,
obviously, do not. Bup remotes almost certianly do not, since bup would
need to be used to extract the export; same store for Ddar. Web and
Bittorrent are download-only. GCrypt is always encrypted so exporting to
it would be pointless. There's probably no point complicating the Hook
remotes with exporting at this point. External, S3, Glacier, WebDAV,
Rsync, and possibly Tahoe should be modified to support export.
Thought about trying to reuse the storeKey/retrieveKeyFile/removeKey
interface, rather than adding a new interface. But, it seemed better to
keep it separate, to avoid a complicated interface that sometimes
encrypts/chunks key/value storage and sometimes users non-key/value
storage. Any common parts can be factored out.
Note that storeExport is not atomic.
doc/design/exporting_trees_to_special_remotes.mdwn has some things in
the "resuming exports" section that bear on this decision. Basically,
I don't think, at this time, that an atomic storeExport would help with
resuming, because exports are not key/value storage, and we can't be
sure that a partially uploaded file is the same content we're currently
trying to export.
Also, note that ExportLocation will always use unix path separators.
This is important, because users may export from a mix of windows and
unix, and it avoids complicating the API with path conversions,
and ensures that in such a mix, they always use the same locations for
exports.
This commit was sponsored by Bruno BEAUFILS on Patreon.
2017-08-29 17:00:41 +00:00
|
|
|
|
2020-10-30 14:29:42 +00:00
|
|
|
checkPresentGeneric :: RawFilePath -> [RawFilePath] -> Annex Bool
|
2019-03-05 20:02:33 +00:00
|
|
|
checkPresentGeneric d ps = checkPresentGeneric' d $
|
2020-10-30 14:29:42 +00:00
|
|
|
liftIO $ anyM (doesFileExist . fromRawFilePath) ps
|
2019-03-05 20:02:33 +00:00
|
|
|
|
2020-10-30 14:29:42 +00:00
|
|
|
checkPresentGeneric' :: RawFilePath -> Annex Bool -> Annex Bool
|
2019-03-05 20:02:33 +00:00
|
|
|
checkPresentGeneric' d check = ifM check
|
|
|
|
( return True
|
2020-10-30 14:29:42 +00:00
|
|
|
, ifM (liftIO $ doesDirectoryExist (fromRawFilePath d))
|
2019-03-05 20:02:33 +00:00
|
|
|
( return False
|
2020-10-30 14:29:42 +00:00
|
|
|
, giveup $ "directory " ++ fromRawFilePath d ++ " is not accessible"
|
2014-08-06 17:45:19 +00:00
|
|
|
)
|
2019-03-05 20:02:33 +00:00
|
|
|
)
|
add API for exporting
Implemented so far for the directory special remote.
Several remotes don't make sense to export to. Regular Git remotes,
obviously, do not. Bup remotes almost certianly do not, since bup would
need to be used to extract the export; same store for Ddar. Web and
Bittorrent are download-only. GCrypt is always encrypted so exporting to
it would be pointless. There's probably no point complicating the Hook
remotes with exporting at this point. External, S3, Glacier, WebDAV,
Rsync, and possibly Tahoe should be modified to support export.
Thought about trying to reuse the storeKey/retrieveKeyFile/removeKey
interface, rather than adding a new interface. But, it seemed better to
keep it separate, to avoid a complicated interface that sometimes
encrypts/chunks key/value storage and sometimes users non-key/value
storage. Any common parts can be factored out.
Note that storeExport is not atomic.
doc/design/exporting_trees_to_special_remotes.mdwn has some things in
the "resuming exports" section that bear on this decision. Basically,
I don't think, at this time, that an atomic storeExport would help with
resuming, because exports are not key/value storage, and we can't be
sure that a partially uploaded file is the same content we're currently
trying to export.
Also, note that ExportLocation will always use unix path separators.
This is important, because users may export from a mix of windows and
unix, and it avoids complicating the API with path conversions,
and ensures that in such a mix, they always use the same locations for
exports.
This commit was sponsored by Bruno BEAUFILS on Patreon.
2017-08-29 17:00:41 +00:00
|
|
|
|
2021-04-14 20:17:43 +00:00
|
|
|
storeExportM :: RawFilePath -> CopyCoWTried -> FilePath -> Key -> ExportLocation -> MeterUpdate -> Annex ()
|
2021-08-16 19:56:24 +00:00
|
|
|
storeExportM d cow src _k loc p = do
|
2022-08-12 16:45:46 +00:00
|
|
|
liftIO $ createDirectoryUnder [d] (P.takeDirectory dest)
|
2017-08-31 18:24:32 +00:00
|
|
|
-- Write via temp file so that checkPresentGeneric will not
|
|
|
|
-- see it until it's fully stored.
|
2020-10-30 14:29:42 +00:00
|
|
|
viaTmp go (fromRawFilePath dest) ()
|
add API for exporting
Implemented so far for the directory special remote.
Several remotes don't make sense to export to. Regular Git remotes,
obviously, do not. Bup remotes almost certianly do not, since bup would
need to be used to extract the export; same store for Ddar. Web and
Bittorrent are download-only. GCrypt is always encrypted so exporting to
it would be pointless. There's probably no point complicating the Hook
remotes with exporting at this point. External, S3, Glacier, WebDAV,
Rsync, and possibly Tahoe should be modified to support export.
Thought about trying to reuse the storeKey/retrieveKeyFile/removeKey
interface, rather than adding a new interface. But, it seemed better to
keep it separate, to avoid a complicated interface that sometimes
encrypts/chunks key/value storage and sometimes users non-key/value
storage. Any common parts can be factored out.
Note that storeExport is not atomic.
doc/design/exporting_trees_to_special_remotes.mdwn has some things in
the "resuming exports" section that bear on this decision. Basically,
I don't think, at this time, that an atomic storeExport would help with
resuming, because exports are not key/value storage, and we can't be
sure that a partially uploaded file is the same content we're currently
trying to export.
Also, note that ExportLocation will always use unix path separators.
This is important, because users may export from a mix of windows and
unix, and it avoids complicating the API with path conversions,
and ensures that in such a mix, they always use the same locations for
exports.
This commit was sponsored by Bruno BEAUFILS on Patreon.
2017-08-29 17:00:41 +00:00
|
|
|
where
|
|
|
|
dest = exportPath d loc
|
2022-05-09 19:38:21 +00:00
|
|
|
go tmp () = void $ liftIO $ fileCopier cow src tmp p Nothing
|
add API for exporting
Implemented so far for the directory special remote.
Several remotes don't make sense to export to. Regular Git remotes,
obviously, do not. Bup remotes almost certianly do not, since bup would
need to be used to extract the export; same store for Ddar. Web and
Bittorrent are download-only. GCrypt is always encrypted so exporting to
it would be pointless. There's probably no point complicating the Hook
remotes with exporting at this point. External, S3, Glacier, WebDAV,
Rsync, and possibly Tahoe should be modified to support export.
Thought about trying to reuse the storeKey/retrieveKeyFile/removeKey
interface, rather than adding a new interface. But, it seemed better to
keep it separate, to avoid a complicated interface that sometimes
encrypts/chunks key/value storage and sometimes users non-key/value
storage. Any common parts can be factored out.
Note that storeExport is not atomic.
doc/design/exporting_trees_to_special_remotes.mdwn has some things in
the "resuming exports" section that bear on this decision. Basically,
I don't think, at this time, that an atomic storeExport would help with
resuming, because exports are not key/value storage, and we can't be
sure that a partially uploaded file is the same content we're currently
trying to export.
Also, note that ExportLocation will always use unix path separators.
This is important, because users may export from a mix of windows and
unix, and it avoids complicating the API with path conversions,
and ensures that in such a mix, they always use the same locations for
exports.
This commit was sponsored by Bruno BEAUFILS on Patreon.
2017-08-29 17:00:41 +00:00
|
|
|
|
2022-05-09 16:25:04 +00:00
|
|
|
retrieveExportM :: RawFilePath -> CopyCoWTried -> Key -> ExportLocation -> FilePath -> MeterUpdate -> Annex Verification
|
2022-05-09 17:18:47 +00:00
|
|
|
retrieveExportM d cow k loc dest p =
|
|
|
|
verifyKeyContentIncrementally AlwaysVerify k $ \iv ->
|
2022-05-09 19:38:21 +00:00
|
|
|
void $ liftIO $ fileCopier cow src dest p iv
|
add API for exporting
Implemented so far for the directory special remote.
Several remotes don't make sense to export to. Regular Git remotes,
obviously, do not. Bup remotes almost certianly do not, since bup would
need to be used to extract the export; same store for Ddar. Web and
Bittorrent are download-only. GCrypt is always encrypted so exporting to
it would be pointless. There's probably no point complicating the Hook
remotes with exporting at this point. External, S3, Glacier, WebDAV,
Rsync, and possibly Tahoe should be modified to support export.
Thought about trying to reuse the storeKey/retrieveKeyFile/removeKey
interface, rather than adding a new interface. But, it seemed better to
keep it separate, to avoid a complicated interface that sometimes
encrypts/chunks key/value storage and sometimes users non-key/value
storage. Any common parts can be factored out.
Note that storeExport is not atomic.
doc/design/exporting_trees_to_special_remotes.mdwn has some things in
the "resuming exports" section that bear on this decision. Basically,
I don't think, at this time, that an atomic storeExport would help with
resuming, because exports are not key/value storage, and we can't be
sure that a partially uploaded file is the same content we're currently
trying to export.
Also, note that ExportLocation will always use unix path separators.
This is important, because users may export from a mix of windows and
unix, and it avoids complicating the API with path conversions,
and ensures that in such a mix, they always use the same locations for
exports.
This commit was sponsored by Bruno BEAUFILS on Patreon.
2017-08-29 17:00:41 +00:00
|
|
|
where
|
2020-10-30 14:29:42 +00:00
|
|
|
src = fromRawFilePath $ exportPath d loc
|
add API for exporting
Implemented so far for the directory special remote.
Several remotes don't make sense to export to. Regular Git remotes,
obviously, do not. Bup remotes almost certianly do not, since bup would
need to be used to extract the export; same store for Ddar. Web and
Bittorrent are download-only. GCrypt is always encrypted so exporting to
it would be pointless. There's probably no point complicating the Hook
remotes with exporting at this point. External, S3, Glacier, WebDAV,
Rsync, and possibly Tahoe should be modified to support export.
Thought about trying to reuse the storeKey/retrieveKeyFile/removeKey
interface, rather than adding a new interface. But, it seemed better to
keep it separate, to avoid a complicated interface that sometimes
encrypts/chunks key/value storage and sometimes users non-key/value
storage. Any common parts can be factored out.
Note that storeExport is not atomic.
doc/design/exporting_trees_to_special_remotes.mdwn has some things in
the "resuming exports" section that bear on this decision. Basically,
I don't think, at this time, that an atomic storeExport would help with
resuming, because exports are not key/value storage, and we can't be
sure that a partially uploaded file is the same content we're currently
trying to export.
Also, note that ExportLocation will always use unix path separators.
This is important, because users may export from a mix of windows and
unix, and it avoids complicating the API with path conversions,
and ensures that in such a mix, they always use the same locations for
exports.
This commit was sponsored by Bruno BEAUFILS on Patreon.
2017-08-29 17:00:41 +00:00
|
|
|
|
2020-10-30 14:29:42 +00:00
|
|
|
removeExportM :: RawFilePath -> Key -> ExportLocation -> Annex ()
|
2017-09-15 17:15:47 +00:00
|
|
|
removeExportM d _k loc = liftIO $ do
|
2020-11-24 16:38:12 +00:00
|
|
|
removeWhenExistsWith R.removeLink src
|
2017-08-31 16:32:02 +00:00
|
|
|
removeExportLocation d loc
|
add API for exporting
Implemented so far for the directory special remote.
Several remotes don't make sense to export to. Regular Git remotes,
obviously, do not. Bup remotes almost certianly do not, since bup would
need to be used to extract the export; same store for Ddar. Web and
Bittorrent are download-only. GCrypt is always encrypted so exporting to
it would be pointless. There's probably no point complicating the Hook
remotes with exporting at this point. External, S3, Glacier, WebDAV,
Rsync, and possibly Tahoe should be modified to support export.
Thought about trying to reuse the storeKey/retrieveKeyFile/removeKey
interface, rather than adding a new interface. But, it seemed better to
keep it separate, to avoid a complicated interface that sometimes
encrypts/chunks key/value storage and sometimes users non-key/value
storage. Any common parts can be factored out.
Note that storeExport is not atomic.
doc/design/exporting_trees_to_special_remotes.mdwn has some things in
the "resuming exports" section that bear on this decision. Basically,
I don't think, at this time, that an atomic storeExport would help with
resuming, because exports are not key/value storage, and we can't be
sure that a partially uploaded file is the same content we're currently
trying to export.
Also, note that ExportLocation will always use unix path separators.
This is important, because users may export from a mix of windows and
unix, and it avoids complicating the API with path conversions,
and ensures that in such a mix, they always use the same locations for
exports.
This commit was sponsored by Bruno BEAUFILS on Patreon.
2017-08-29 17:00:41 +00:00
|
|
|
where
|
2020-11-24 16:38:12 +00:00
|
|
|
src = exportPath d loc
|
add API for exporting
Implemented so far for the directory special remote.
Several remotes don't make sense to export to. Regular Git remotes,
obviously, do not. Bup remotes almost certianly do not, since bup would
need to be used to extract the export; same store for Ddar. Web and
Bittorrent are download-only. GCrypt is always encrypted so exporting to
it would be pointless. There's probably no point complicating the Hook
remotes with exporting at this point. External, S3, Glacier, WebDAV,
Rsync, and possibly Tahoe should be modified to support export.
Thought about trying to reuse the storeKey/retrieveKeyFile/removeKey
interface, rather than adding a new interface. But, it seemed better to
keep it separate, to avoid a complicated interface that sometimes
encrypts/chunks key/value storage and sometimes users non-key/value
storage. Any common parts can be factored out.
Note that storeExport is not atomic.
doc/design/exporting_trees_to_special_remotes.mdwn has some things in
the "resuming exports" section that bear on this decision. Basically,
I don't think, at this time, that an atomic storeExport would help with
resuming, because exports are not key/value storage, and we can't be
sure that a partially uploaded file is the same content we're currently
trying to export.
Also, note that ExportLocation will always use unix path separators.
This is important, because users may export from a mix of windows and
unix, and it avoids complicating the API with path conversions,
and ensures that in such a mix, they always use the same locations for
exports.
This commit was sponsored by Bruno BEAUFILS on Patreon.
2017-08-29 17:00:41 +00:00
|
|
|
|
2020-10-30 14:29:42 +00:00
|
|
|
checkPresentExportM :: RawFilePath -> Key -> ExportLocation -> Annex Bool
|
2017-09-15 17:15:47 +00:00
|
|
|
checkPresentExportM d _k loc =
|
add API for exporting
Implemented so far for the directory special remote.
Several remotes don't make sense to export to. Regular Git remotes,
obviously, do not. Bup remotes almost certianly do not, since bup would
need to be used to extract the export; same store for Ddar. Web and
Bittorrent are download-only. GCrypt is always encrypted so exporting to
it would be pointless. There's probably no point complicating the Hook
remotes with exporting at this point. External, S3, Glacier, WebDAV,
Rsync, and possibly Tahoe should be modified to support export.
Thought about trying to reuse the storeKey/retrieveKeyFile/removeKey
interface, rather than adding a new interface. But, it seemed better to
keep it separate, to avoid a complicated interface that sometimes
encrypts/chunks key/value storage and sometimes users non-key/value
storage. Any common parts can be factored out.
Note that storeExport is not atomic.
doc/design/exporting_trees_to_special_remotes.mdwn has some things in
the "resuming exports" section that bear on this decision. Basically,
I don't think, at this time, that an atomic storeExport would help with
resuming, because exports are not key/value storage, and we can't be
sure that a partially uploaded file is the same content we're currently
trying to export.
Also, note that ExportLocation will always use unix path separators.
This is important, because users may export from a mix of windows and
unix, and it avoids complicating the API with path conversions,
and ensures that in such a mix, they always use the same locations for
exports.
This commit was sponsored by Bruno BEAUFILS on Patreon.
2017-08-29 17:00:41 +00:00
|
|
|
checkPresentGeneric d [exportPath d loc]
|
|
|
|
|
2020-10-30 14:29:42 +00:00
|
|
|
renameExportM :: RawFilePath -> Key -> ExportLocation -> ExportLocation -> Annex (Maybe ())
|
2020-05-15 19:05:52 +00:00
|
|
|
renameExportM d _k oldloc newloc = liftIO $ do
|
2022-08-12 16:45:46 +00:00
|
|
|
createDirectoryUnder [d] (P.takeDirectory dest)
|
2020-10-30 14:29:42 +00:00
|
|
|
renameFile (fromRawFilePath src) (fromRawFilePath dest)
|
2020-05-15 19:05:52 +00:00
|
|
|
removeExportLocation d oldloc
|
|
|
|
return (Just ())
|
add API for exporting
Implemented so far for the directory special remote.
Several remotes don't make sense to export to. Regular Git remotes,
obviously, do not. Bup remotes almost certianly do not, since bup would
need to be used to extract the export; same store for Ddar. Web and
Bittorrent are download-only. GCrypt is always encrypted so exporting to
it would be pointless. There's probably no point complicating the Hook
remotes with exporting at this point. External, S3, Glacier, WebDAV,
Rsync, and possibly Tahoe should be modified to support export.
Thought about trying to reuse the storeKey/retrieveKeyFile/removeKey
interface, rather than adding a new interface. But, it seemed better to
keep it separate, to avoid a complicated interface that sometimes
encrypts/chunks key/value storage and sometimes users non-key/value
storage. Any common parts can be factored out.
Note that storeExport is not atomic.
doc/design/exporting_trees_to_special_remotes.mdwn has some things in
the "resuming exports" section that bear on this decision. Basically,
I don't think, at this time, that an atomic storeExport would help with
resuming, because exports are not key/value storage, and we can't be
sure that a partially uploaded file is the same content we're currently
trying to export.
Also, note that ExportLocation will always use unix path separators.
This is important, because users may export from a mix of windows and
unix, and it avoids complicating the API with path conversions,
and ensures that in such a mix, they always use the same locations for
exports.
This commit was sponsored by Bruno BEAUFILS on Patreon.
2017-08-29 17:00:41 +00:00
|
|
|
where
|
|
|
|
src = exportPath d oldloc
|
|
|
|
dest = exportPath d newloc
|
2017-08-31 16:32:02 +00:00
|
|
|
|
2020-10-30 14:29:42 +00:00
|
|
|
exportPath :: RawFilePath -> ExportLocation -> RawFilePath
|
|
|
|
exportPath d loc = d P.</> fromExportLocation loc
|
2017-08-31 16:32:02 +00:00
|
|
|
|
2017-11-08 18:38:24 +00:00
|
|
|
{- Removes the ExportLocation's parent directory and its parents, so long as
|
2017-08-31 16:32:02 +00:00
|
|
|
- they're empty, up to but not including the topdir. -}
|
2020-10-30 14:29:42 +00:00
|
|
|
removeExportLocation :: RawFilePath -> ExportLocation -> IO ()
|
2017-11-08 18:38:24 +00:00
|
|
|
removeExportLocation topdir loc =
|
2020-10-30 14:29:42 +00:00
|
|
|
go (Just $ P.takeDirectory $ fromExportLocation loc) (Right ())
|
2017-08-31 16:32:02 +00:00
|
|
|
where
|
|
|
|
go _ (Left _e) = return ()
|
|
|
|
go Nothing _ = return ()
|
2020-10-30 14:29:42 +00:00
|
|
|
go (Just loc') _ =
|
|
|
|
let p = fromRawFilePath $ exportPath topdir $
|
|
|
|
mkExportLocation loc'
|
|
|
|
in go (upFrom loc') =<< tryIO (removeDirectory p)
|
2019-02-27 17:42:34 +00:00
|
|
|
|
2022-03-21 17:12:02 +00:00
|
|
|
listImportableContentsM :: IgnoreInodes -> RawFilePath -> Annex (Maybe (ImportableContentsChunkable Annex (ContentIdentifier, ByteSize)))
|
|
|
|
listImportableContentsM ii dir = liftIO $ do
|
2022-08-19 17:31:16 +00:00
|
|
|
l <- dirContentsRecursiveSkipping (const False) False (fromRawFilePath dir)
|
2020-11-05 15:26:34 +00:00
|
|
|
l' <- mapM (go . toRawFilePath) l
|
2021-10-06 21:05:32 +00:00
|
|
|
return $ Just $ ImportableContentsComplete $
|
|
|
|
ImportableContents (catMaybes l') []
|
2019-02-27 17:42:34 +00:00
|
|
|
where
|
|
|
|
go f = do
|
2022-09-05 17:44:03 +00:00
|
|
|
st <- R.getSymbolicLinkStatus f
|
2022-03-21 17:12:02 +00:00
|
|
|
mkContentIdentifier ii f st >>= \case
|
2019-03-04 17:20:58 +00:00
|
|
|
Nothing -> return Nothing
|
|
|
|
Just cid -> do
|
2020-11-05 15:26:34 +00:00
|
|
|
relf <- relPathDirToFile dir f
|
2019-03-04 17:20:58 +00:00
|
|
|
sz <- getFileSize' f st
|
|
|
|
return $ Just (mkImportLocation relf, (cid, sz))
|
|
|
|
|
2022-03-21 17:12:02 +00:00
|
|
|
newtype IgnoreInodes = IgnoreInodes Bool
|
|
|
|
|
|
|
|
-- Make a ContentIdentifier that contains the size and mtime of the file,
|
|
|
|
-- and also normally the inode, unless ignoreinodes=yes.
|
2019-03-04 17:20:58 +00:00
|
|
|
--
|
2022-03-21 17:12:02 +00:00
|
|
|
-- If the file is not a regular file, this will return Nothing.
|
|
|
|
mkContentIdentifier :: IgnoreInodes -> RawFilePath -> FileStatus -> IO (Maybe ContentIdentifier)
|
|
|
|
mkContentIdentifier (IgnoreInodes ii) f st =
|
|
|
|
liftIO $ fmap (ContentIdentifier . encodeBS . showInodeCache)
|
|
|
|
<$> if ii
|
|
|
|
then toInodeCache' noTSDelta f st 0
|
|
|
|
else toInodeCache noTSDelta f st
|
2019-02-27 17:42:34 +00:00
|
|
|
|
deal with ignoreinode config setting
Improve handling of directory special remotes with importtree=yes whose
ignoreinode setting has been changed. (By either enableremote or by
upgrading to commit 3e2f1f73cbc5fc10475745b3c3133267bd1850a7.)
When getting a file from such a remote, accept the content that would have
been accepted with the previous ignoreinode setting.
After a change to ignoreinode, importing a tree from the remote will
re-import and generate new content identifiers using the new config. So
when ignoreinode has changed to no, the inodes will be learned, and after
that point, a change in an inode will be detected as a change. Before
re-importing, a change in an inode will be ignored, as it was before the
ignoreinode change. This seems acceptble, because the user can re-import
immediately if they urgently need to add inodes. And if not, they'll
do it sometime, presumably, and the change will take effect then.
Sponsored-by: Erik Bjäreholt on Patreon
2022-09-16 18:11:25 +00:00
|
|
|
-- Since ignoreinodes can be changed by enableremote, and since previous
|
|
|
|
-- versions of git-annex ignored inodes by default, treat two content
|
2024-04-06 13:50:58 +00:00
|
|
|
-- identifiers as the same if they differ only by one having the inode
|
deal with ignoreinode config setting
Improve handling of directory special remotes with importtree=yes whose
ignoreinode setting has been changed. (By either enableremote or by
upgrading to commit 3e2f1f73cbc5fc10475745b3c3133267bd1850a7.)
When getting a file from such a remote, accept the content that would have
been accepted with the previous ignoreinode setting.
After a change to ignoreinode, importing a tree from the remote will
re-import and generate new content identifiers using the new config. So
when ignoreinode has changed to no, the inodes will be learned, and after
that point, a change in an inode will be detected as a change. Before
re-importing, a change in an inode will be ignored, as it was before the
ignoreinode change. This seems acceptble, because the user can re-import
immediately if they urgently need to add inodes. And if not, they'll
do it sometime, presumably, and the change will take effect then.
Sponsored-by: Erik Bjäreholt on Patreon
2022-09-16 18:11:25 +00:00
|
|
|
-- ignored.
|
change retrieveExportWithContentIdentifier to take a list of ContentIdentifier
This partly fixes an issue where there are duplicate files in the
special remote, and the first file gets swapped with another duplicate,
or deleted. The swap case is fixed by this, the deleted case will need
other changes.
This makes retrieveExportWithContentIdentifier take a list of allowed
ContentIdentifier, same as storeExportWithContentIdentifier,
removeExportWithContentIdentifier, and
checkPresentExportWithContentIdentifier.
Of the special remotes that support importtree, borg is a special case
and does not use content identifiers, S3 I assume can't get mixed up
like this, directory certainly has the problem, and adb also appears to
have had the problem.
Sponsored-by: Graham Spencer on Patreon
2022-09-20 17:15:31 +00:00
|
|
|
guardSameContentIdentifiers :: a -> [ContentIdentifier] -> Maybe ContentIdentifier -> a
|
deal with ignoreinode config setting
Improve handling of directory special remotes with importtree=yes whose
ignoreinode setting has been changed. (By either enableremote or by
upgrading to commit 3e2f1f73cbc5fc10475745b3c3133267bd1850a7.)
When getting a file from such a remote, accept the content that would have
been accepted with the previous ignoreinode setting.
After a change to ignoreinode, importing a tree from the remote will
re-import and generate new content identifiers using the new config. So
when ignoreinode has changed to no, the inodes will be learned, and after
that point, a change in an inode will be detected as a change. Before
re-importing, a change in an inode will be ignored, as it was before the
ignoreinode change. This seems acceptble, because the user can re-import
immediately if they urgently need to add inodes. And if not, they'll
do it sometime, presumably, and the change will take effect then.
Sponsored-by: Erik Bjäreholt on Patreon
2022-09-16 18:11:25 +00:00
|
|
|
guardSameContentIdentifiers _ _ Nothing = giveup "file not found"
|
change retrieveExportWithContentIdentifier to take a list of ContentIdentifier
This partly fixes an issue where there are duplicate files in the
special remote, and the first file gets swapped with another duplicate,
or deleted. The swap case is fixed by this, the deleted case will need
other changes.
This makes retrieveExportWithContentIdentifier take a list of allowed
ContentIdentifier, same as storeExportWithContentIdentifier,
removeExportWithContentIdentifier, and
checkPresentExportWithContentIdentifier.
Of the special remotes that support importtree, borg is a special case
and does not use content identifiers, S3 I assume can't get mixed up
like this, directory certainly has the problem, and adb also appears to
have had the problem.
Sponsored-by: Graham Spencer on Patreon
2022-09-20 17:15:31 +00:00
|
|
|
guardSameContentIdentifiers cont olds (Just new)
|
|
|
|
| any (new ==) olds = cont
|
|
|
|
| any (ignoreinode new ==) olds = cont
|
|
|
|
| any (\old -> new == ignoreinode old) olds = cont
|
2020-07-03 17:41:57 +00:00
|
|
|
| otherwise = giveup "file content has changed"
|
deal with ignoreinode config setting
Improve handling of directory special remotes with importtree=yes whose
ignoreinode setting has been changed. (By either enableremote or by
upgrading to commit 3e2f1f73cbc5fc10475745b3c3133267bd1850a7.)
When getting a file from such a remote, accept the content that would have
been accepted with the previous ignoreinode setting.
After a change to ignoreinode, importing a tree from the remote will
re-import and generate new content identifiers using the new config. So
when ignoreinode has changed to no, the inodes will be learned, and after
that point, a change in an inode will be detected as a change. Before
re-importing, a change in an inode will be ignored, as it was before the
ignoreinode change. This seems acceptble, because the user can re-import
immediately if they urgently need to add inodes. And if not, they'll
do it sometime, presumably, and the change will take effect then.
Sponsored-by: Erik Bjäreholt on Patreon
2022-09-16 18:11:25 +00:00
|
|
|
where
|
|
|
|
ignoreinode cid@(ContentIdentifier b) =
|
|
|
|
case readInodeCache (decodeBS b) of
|
|
|
|
Nothing -> cid
|
|
|
|
Just ic ->
|
|
|
|
let ic' = replaceInode 0 ic
|
|
|
|
in ContentIdentifier (encodeBS (showInodeCache ic'))
|
2020-07-03 17:41:57 +00:00
|
|
|
|
2022-03-21 17:12:02 +00:00
|
|
|
importKeyM :: IgnoreInodes -> RawFilePath -> ExportLocation -> ContentIdentifier -> ByteSize -> MeterUpdate -> Annex (Maybe Key)
|
|
|
|
importKeyM ii dir loc cid sz p = do
|
2020-10-30 14:29:42 +00:00
|
|
|
backend <- chooseBackend f
|
2020-12-21 20:03:27 +00:00
|
|
|
unsizedk <- fst <$> genKey ks p backend
|
|
|
|
let k = alterKey unsizedk $ \kd -> kd
|
|
|
|
{ keySize = keySize kd <|> Just sz }
|
2022-03-21 17:12:02 +00:00
|
|
|
currcid <- liftIO $ mkContentIdentifier ii absf
|
2022-09-05 17:44:03 +00:00
|
|
|
=<< R.getSymbolicLinkStatus absf
|
change retrieveExportWithContentIdentifier to take a list of ContentIdentifier
This partly fixes an issue where there are duplicate files in the
special remote, and the first file gets swapped with another duplicate,
or deleted. The swap case is fixed by this, the deleted case will need
other changes.
This makes retrieveExportWithContentIdentifier take a list of allowed
ContentIdentifier, same as storeExportWithContentIdentifier,
removeExportWithContentIdentifier, and
checkPresentExportWithContentIdentifier.
Of the special remotes that support importtree, borg is a special case
and does not use content identifiers, S3 I assume can't get mixed up
like this, directory certainly has the problem, and adb also appears to
have had the problem.
Sponsored-by: Graham Spencer on Patreon
2022-09-20 17:15:31 +00:00
|
|
|
guardSameContentIdentifiers (return (Just k)) [cid] currcid
|
2020-07-03 17:41:57 +00:00
|
|
|
where
|
|
|
|
f = fromExportLocation loc
|
2020-10-30 14:29:42 +00:00
|
|
|
absf = dir P.</> f
|
2020-07-03 17:41:57 +00:00
|
|
|
ks = KeySource
|
|
|
|
{ keyFilename = f
|
2020-10-30 14:29:42 +00:00
|
|
|
, contentLocation = absf
|
2020-07-03 17:41:57 +00:00
|
|
|
, inodeCache = Nothing
|
|
|
|
}
|
|
|
|
|
change retrieveExportWithContentIdentifier to take a list of ContentIdentifier
This partly fixes an issue where there are duplicate files in the
special remote, and the first file gets swapped with another duplicate,
or deleted. The swap case is fixed by this, the deleted case will need
other changes.
This makes retrieveExportWithContentIdentifier take a list of allowed
ContentIdentifier, same as storeExportWithContentIdentifier,
removeExportWithContentIdentifier, and
checkPresentExportWithContentIdentifier.
Of the special remotes that support importtree, borg is a special case
and does not use content identifiers, S3 I assume can't get mixed up
like this, directory certainly has the problem, and adb also appears to
have had the problem.
Sponsored-by: Graham Spencer on Patreon
2022-09-20 17:15:31 +00:00
|
|
|
retrieveExportWithContentIdentifierM :: IgnoreInodes -> RawFilePath -> CopyCoWTried -> ExportLocation -> [ContentIdentifier] -> FilePath -> Either Key (Annex Key) -> MeterUpdate -> Annex (Key, Verification)
|
|
|
|
retrieveExportWithContentIdentifierM ii dir cow loc cids dest gk p =
|
2022-05-09 19:38:21 +00:00
|
|
|
case gk of
|
|
|
|
Right mkkey -> do
|
|
|
|
go Nothing
|
|
|
|
k <- mkkey
|
|
|
|
return (k, UnVerified)
|
|
|
|
Left k -> do
|
|
|
|
v <- verifyKeyContentIncrementally DefaultVerify k go
|
|
|
|
return (k, v)
|
2019-03-04 17:20:58 +00:00
|
|
|
where
|
2019-03-05 18:20:14 +00:00
|
|
|
f = exportPath dir loc
|
2020-10-30 14:29:42 +00:00
|
|
|
f' = fromRawFilePath f
|
2022-05-09 19:38:21 +00:00
|
|
|
|
|
|
|
go iv = precheck (docopy iv)
|
2019-03-04 17:20:58 +00:00
|
|
|
|
2022-05-09 19:38:21 +00:00
|
|
|
docopy iv = ifM (liftIO $ tryCopyCoW cow f' dest p)
|
|
|
|
( postcheckcow (liftIO $ maybe noop unableIncrementalVerifier iv)
|
|
|
|
, docopynoncow iv
|
2021-04-14 20:10:09 +00:00
|
|
|
)
|
|
|
|
|
2022-05-09 19:38:21 +00:00
|
|
|
docopynoncow iv = do
|
2019-03-04 17:20:58 +00:00
|
|
|
#ifndef mingw32_HOST_OS
|
2020-06-05 19:34:43 +00:00
|
|
|
let open = do
|
2022-05-09 19:38:21 +00:00
|
|
|
-- Need a duplicate fd for the post check.
|
2023-08-01 22:41:27 +00:00
|
|
|
fd <- openFdWithMode f ReadOnly Nothing defaultFileFlags
|
2020-06-05 19:34:43 +00:00
|
|
|
dupfd <- dup fd
|
|
|
|
h <- fdToHandle fd
|
|
|
|
return (h, dupfd)
|
|
|
|
let close (h, dupfd) = do
|
|
|
|
hClose h
|
|
|
|
closeFd dupfd
|
|
|
|
bracketIO open close $ \(h, dupfd) -> do
|
2019-03-04 17:20:58 +00:00
|
|
|
#else
|
2020-10-30 14:29:42 +00:00
|
|
|
let open = openBinaryFile f' ReadMode
|
2020-06-05 19:34:43 +00:00
|
|
|
let close = hClose
|
2020-07-02 15:35:05 +00:00
|
|
|
bracketIO open close $ \h -> do
|
2019-03-04 17:20:58 +00:00
|
|
|
#endif
|
2022-05-09 19:38:21 +00:00
|
|
|
liftIO $ fileContentCopier h dest p iv
|
2019-03-04 17:20:58 +00:00
|
|
|
#ifndef mingw32_HOST_OS
|
2022-05-09 19:38:21 +00:00
|
|
|
postchecknoncow dupfd (return ())
|
2019-03-04 17:20:58 +00:00
|
|
|
#else
|
2022-05-09 19:38:21 +00:00
|
|
|
postchecknoncow (return ())
|
2019-03-04 17:20:58 +00:00
|
|
|
#endif
|
|
|
|
|
|
|
|
-- Check before copy, to avoid expensive copy of wrong file
|
|
|
|
-- content.
|
change retrieveExportWithContentIdentifier to take a list of ContentIdentifier
This partly fixes an issue where there are duplicate files in the
special remote, and the first file gets swapped with another duplicate,
or deleted. The swap case is fixed by this, the deleted case will need
other changes.
This makes retrieveExportWithContentIdentifier take a list of allowed
ContentIdentifier, same as storeExportWithContentIdentifier,
removeExportWithContentIdentifier, and
checkPresentExportWithContentIdentifier.
Of the special remotes that support importtree, borg is a special case
and does not use content identifiers, S3 I assume can't get mixed up
like this, directory certainly has the problem, and adb also appears to
have had the problem.
Sponsored-by: Graham Spencer on Patreon
2022-09-20 17:15:31 +00:00
|
|
|
precheck cont = guardSameContentIdentifiers cont cids
|
2022-03-21 17:12:02 +00:00
|
|
|
=<< liftIO . mkContentIdentifier ii f
|
2022-09-05 17:44:03 +00:00
|
|
|
=<< liftIO (R.getSymbolicLinkStatus f)
|
2019-03-04 17:20:58 +00:00
|
|
|
|
|
|
|
-- Check after copy, in case the file was changed while it was
|
|
|
|
-- being copied.
|
|
|
|
--
|
|
|
|
-- When possible (not on Windows), check the same handle
|
2019-04-09 21:52:41 +00:00
|
|
|
-- that the file was copied from. Avoids some race cases where
|
|
|
|
-- the file is modified while it's copied but then gets restored
|
|
|
|
-- to the original content afterwards.
|
2019-03-04 17:20:58 +00:00
|
|
|
--
|
|
|
|
-- This does not guard against every possible race, but neither
|
|
|
|
-- can InodeCaches detect every possible modification to a file.
|
|
|
|
-- It's probably as good or better than git's handling of similar
|
|
|
|
-- situations with files being modified while it's updating the
|
|
|
|
-- working tree for a merge.
|
|
|
|
#ifndef mingw32_HOST_OS
|
2021-04-14 20:10:09 +00:00
|
|
|
postchecknoncow fd cont = do
|
2019-03-04 17:20:58 +00:00
|
|
|
#else
|
2021-04-14 20:10:09 +00:00
|
|
|
postchecknoncow cont = do
|
2019-03-04 17:20:58 +00:00
|
|
|
#endif
|
2022-03-21 17:12:02 +00:00
|
|
|
currcid <- liftIO $ mkContentIdentifier ii f
|
2019-03-04 17:20:58 +00:00
|
|
|
#ifndef mingw32_HOST_OS
|
|
|
|
=<< getFdStatus fd
|
|
|
|
#else
|
2022-09-05 17:44:03 +00:00
|
|
|
=<< R.getSymbolicLinkStatus f
|
2019-03-04 17:20:58 +00:00
|
|
|
#endif
|
change retrieveExportWithContentIdentifier to take a list of ContentIdentifier
This partly fixes an issue where there are duplicate files in the
special remote, and the first file gets swapped with another duplicate,
or deleted. The swap case is fixed by this, the deleted case will need
other changes.
This makes retrieveExportWithContentIdentifier take a list of allowed
ContentIdentifier, same as storeExportWithContentIdentifier,
removeExportWithContentIdentifier, and
checkPresentExportWithContentIdentifier.
Of the special remotes that support importtree, borg is a special case
and does not use content identifiers, S3 I assume can't get mixed up
like this, directory certainly has the problem, and adb also appears to
have had the problem.
Sponsored-by: Graham Spencer on Patreon
2022-09-20 17:15:31 +00:00
|
|
|
guardSameContentIdentifiers cont cids currcid
|
2019-02-27 17:42:34 +00:00
|
|
|
|
2021-04-14 20:10:09 +00:00
|
|
|
-- When copy-on-write was done, cannot check the handle that was
|
|
|
|
-- copied from, but such a copy should run very fast, so
|
|
|
|
-- it's very unlikely that the file changed after precheck,
|
|
|
|
-- the modified version was copied CoW, and then the file was
|
|
|
|
-- restored to the original content before this check.
|
|
|
|
postcheckcow cont = do
|
2022-03-21 17:12:02 +00:00
|
|
|
currcid <- liftIO $ mkContentIdentifier ii f
|
2022-09-05 17:44:03 +00:00
|
|
|
=<< R.getSymbolicLinkStatus f
|
change retrieveExportWithContentIdentifier to take a list of ContentIdentifier
This partly fixes an issue where there are duplicate files in the
special remote, and the first file gets swapped with another duplicate,
or deleted. The swap case is fixed by this, the deleted case will need
other changes.
This makes retrieveExportWithContentIdentifier take a list of allowed
ContentIdentifier, same as storeExportWithContentIdentifier,
removeExportWithContentIdentifier, and
checkPresentExportWithContentIdentifier.
Of the special remotes that support importtree, borg is a special case
and does not use content identifiers, S3 I assume can't get mixed up
like this, directory certainly has the problem, and adb also appears to
have had the problem.
Sponsored-by: Graham Spencer on Patreon
2022-09-20 17:15:31 +00:00
|
|
|
guardSameContentIdentifiers cont cids currcid
|
2021-04-14 20:10:09 +00:00
|
|
|
|
2022-03-21 17:12:02 +00:00
|
|
|
storeExportWithContentIdentifierM :: IgnoreInodes -> RawFilePath -> CopyCoWTried -> FilePath -> Key -> ExportLocation -> [ContentIdentifier] -> MeterUpdate -> Annex ContentIdentifier
|
|
|
|
storeExportWithContentIdentifierM ii dir cow src _k loc overwritablecids p = do
|
2022-08-12 16:45:46 +00:00
|
|
|
liftIO $ createDirectoryUnder [dir] (toRawFilePath destdir)
|
2021-04-20 15:41:43 +00:00
|
|
|
withTmpFileIn destdir template $ \tmpf tmph -> do
|
|
|
|
liftIO $ hClose tmph
|
2022-05-09 19:38:21 +00:00
|
|
|
void $ liftIO $ fileCopier cow src tmpf p Nothing
|
2020-11-06 18:10:58 +00:00
|
|
|
let tmpf' = toRawFilePath tmpf
|
|
|
|
resetAnnexFilePerm tmpf'
|
2023-03-01 19:55:58 +00:00
|
|
|
liftIO (R.getSymbolicLinkStatus tmpf') >>= liftIO . mkContentIdentifier ii tmpf' >>= \case
|
2020-05-15 16:17:15 +00:00
|
|
|
Nothing -> giveup "unable to generate content identifier"
|
|
|
|
Just newcid -> do
|
2022-03-21 17:12:02 +00:00
|
|
|
checkExportContent ii dir loc
|
2021-01-25 17:31:17 +00:00
|
|
|
overwritablecids
|
2020-05-15 16:17:15 +00:00
|
|
|
(giveup "unsafe to overwrite file")
|
2022-07-12 18:53:32 +00:00
|
|
|
(const $ liftIO $ R.rename tmpf' dest)
|
2020-05-15 16:17:15 +00:00
|
|
|
return newcid
|
2019-08-13 16:05:00 +00:00
|
|
|
where
|
2022-07-12 18:53:32 +00:00
|
|
|
dest = exportPath dir loc
|
|
|
|
(destdir, base) = splitFileName (fromRawFilePath dest)
|
2019-03-04 18:46:25 +00:00
|
|
|
template = relatedTemplate (base ++ ".tmp")
|
|
|
|
|
2022-03-21 17:12:02 +00:00
|
|
|
removeExportWithContentIdentifierM :: IgnoreInodes -> RawFilePath -> Key -> ExportLocation -> [ContentIdentifier] -> Annex ()
|
|
|
|
removeExportWithContentIdentifierM ii dir k loc removeablecids =
|
|
|
|
checkExportContent ii dir loc removeablecids (giveup "unsafe to remove modified file") $ \case
|
2020-05-15 18:11:59 +00:00
|
|
|
DoesNotExist -> return ()
|
2019-03-05 21:04:00 +00:00
|
|
|
KnownContentIdentifier -> removeExportM dir k loc
|
2019-03-05 18:20:14 +00:00
|
|
|
|
2022-03-21 17:12:02 +00:00
|
|
|
checkPresentExportWithContentIdentifierM :: IgnoreInodes -> RawFilePath -> Key -> ExportLocation -> [ContentIdentifier] -> Annex Bool
|
|
|
|
checkPresentExportWithContentIdentifierM ii dir _k loc knowncids =
|
2019-03-05 20:02:33 +00:00
|
|
|
checkPresentGeneric' dir $
|
2022-03-21 17:12:02 +00:00
|
|
|
checkExportContent ii dir loc knowncids (return False) $ \case
|
2019-03-05 21:04:00 +00:00
|
|
|
DoesNotExist -> return False
|
|
|
|
KnownContentIdentifier -> return True
|
|
|
|
|
|
|
|
data CheckResult = DoesNotExist | KnownContentIdentifier
|
2019-03-05 20:02:33 +00:00
|
|
|
|
2019-03-05 18:20:14 +00:00
|
|
|
-- Checks if the content at an ExportLocation is in the knowncids,
|
|
|
|
-- and only runs the callback that modifies it if it's safe to do so.
|
|
|
|
--
|
|
|
|
-- This should avoid races to the extent possible. However,
|
|
|
|
-- if something has the file open for write, it could write to the handle
|
|
|
|
-- after the callback has overwritten or deleted it, and its write would
|
|
|
|
-- be lost, and we don't need to detect that.
|
|
|
|
-- (In similar situations, git doesn't either!)
|
|
|
|
--
|
|
|
|
-- It follows that if something is written to the destination file
|
|
|
|
-- shortly before, it's acceptable to run the callback anyway, as that's
|
|
|
|
-- nearly indistinguishable from the above case.
|
|
|
|
--
|
|
|
|
-- So, it suffices to check if the destination file's current
|
|
|
|
-- content is known, and immediately run the callback.
|
2022-03-21 17:12:02 +00:00
|
|
|
checkExportContent :: IgnoreInodes -> RawFilePath -> ExportLocation -> [ContentIdentifier] -> Annex a -> (CheckResult -> Annex a) -> Annex a
|
|
|
|
checkExportContent ii dir loc knowncids unsafe callback =
|
2022-09-05 17:44:03 +00:00
|
|
|
tryWhenExists (liftIO $ R.getSymbolicLinkStatus dest) >>= \case
|
2019-03-05 18:20:14 +00:00
|
|
|
Just destst
|
2020-05-15 16:17:15 +00:00
|
|
|
| not (isRegularFile destst) -> unsafe
|
2022-03-21 17:12:02 +00:00
|
|
|
| otherwise -> catchDefaultIO Nothing (liftIO $ mkContentIdentifier ii dest destst) >>= \case
|
2019-03-04 18:46:25 +00:00
|
|
|
Just destcid
|
2019-03-05 21:04:00 +00:00
|
|
|
| destcid `elem` knowncids -> callback KnownContentIdentifier
|
2019-03-04 18:46:25 +00:00
|
|
|
-- dest exists with other content
|
2020-05-15 16:17:15 +00:00
|
|
|
| otherwise -> unsafe
|
2019-03-05 18:20:14 +00:00
|
|
|
-- should never happen
|
2020-05-15 16:17:15 +00:00
|
|
|
Nothing -> unsafe
|
2019-03-05 18:20:14 +00:00
|
|
|
-- dest does not exist
|
2019-03-05 21:04:00 +00:00
|
|
|
Nothing -> callback DoesNotExist
|
2019-03-05 18:20:14 +00:00
|
|
|
where
|
|
|
|
dest = exportPath dir loc
|