make local gcrypt storeKey be atomic
Reuse Remote.Directory's code.
This commit is contained in:
parent
6cecffea89
commit
22c7a7a41a
2 changed files with 28 additions and 20 deletions
|
@ -7,7 +7,11 @@
|
||||||
|
|
||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
|
|
||||||
module Remote.Directory (remote, removeDirGeneric) where
|
module Remote.Directory (
|
||||||
|
remote,
|
||||||
|
finalizeStoreGeneric,
|
||||||
|
removeDirGeneric,
|
||||||
|
) where
|
||||||
|
|
||||||
import qualified Data.ByteString.Lazy as L
|
import qualified Data.ByteString.Lazy as L
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
|
@ -114,24 +118,30 @@ store :: FilePath -> ChunkConfig -> Key -> L.ByteString -> MeterUpdate -> Annex
|
||||||
store d chunkconfig k b p = liftIO $ do
|
store d chunkconfig k b p = liftIO $ do
|
||||||
void $ tryIO $ createDirectoryIfMissing True tmpdir
|
void $ tryIO $ createDirectoryIfMissing True tmpdir
|
||||||
case chunkconfig of
|
case chunkconfig of
|
||||||
LegacyChunks chunksize -> Legacy.store chunksize finalizer k b p tmpdir destdir
|
LegacyChunks chunksize -> Legacy.store chunksize finalizeStoreGeneric k b p tmpdir destdir
|
||||||
_ -> do
|
_ -> do
|
||||||
let tmpf = tmpdir </> keyFile k
|
let tmpf = tmpdir </> keyFile k
|
||||||
meteredWriteFile p tmpf b
|
meteredWriteFile p tmpf b
|
||||||
finalizer tmpdir destdir
|
finalizeStoreGeneric tmpdir destdir
|
||||||
return True
|
return True
|
||||||
where
|
where
|
||||||
tmpdir = tmpDir d k
|
tmpdir = tmpDir d k
|
||||||
destdir = storeDir d k
|
destdir = storeDir d k
|
||||||
finalizer tmp dest = do
|
|
||||||
void $ tryIO $ allowWrite dest -- may already exist
|
{- Passed a temp directory that contains the files that should be placed
|
||||||
void $ tryIO $ removeDirectoryRecursive dest -- or not exist
|
- in the dest directory, moves it into place. Anything already existing
|
||||||
createDirectoryIfMissing True (parentDir dest)
|
- in the dest directory will be deleted. File permissions will be locked
|
||||||
renameDirectory tmp dest
|
- down. -}
|
||||||
-- may fail on some filesystems
|
finalizeStoreGeneric :: FilePath -> FilePath -> IO ()
|
||||||
void $ tryIO $ do
|
finalizeStoreGeneric tmp dest = do
|
||||||
mapM_ preventWrite =<< dirContents dest
|
void $ tryIO $ allowWrite dest -- may already exist
|
||||||
preventWrite dest
|
void $ tryIO $ removeDirectoryRecursive dest -- or not exist
|
||||||
|
createDirectoryIfMissing True (parentDir dest)
|
||||||
|
renameDirectory tmp dest
|
||||||
|
-- may fail on some filesystems
|
||||||
|
void $ tryIO $ do
|
||||||
|
mapM_ preventWrite =<< dirContents dest
|
||||||
|
preventWrite dest
|
||||||
|
|
||||||
retrieve :: FilePath -> ChunkConfig -> Preparer Retriever
|
retrieve :: FilePath -> ChunkConfig -> Preparer Retriever
|
||||||
retrieve d (LegacyChunks _) = Legacy.retrieve locations d
|
retrieve d (LegacyChunks _) = Legacy.retrieve locations d
|
||||||
|
|
|
@ -306,14 +306,12 @@ store :: Remote -> Remote.Rsync.RsyncOpts -> Storer
|
||||||
store r rsyncopts
|
store r rsyncopts
|
||||||
| not $ Git.repoIsUrl (repo r) =
|
| not $ Git.repoIsUrl (repo r) =
|
||||||
byteStorer $ \k b p -> guardUsable (repo r) False $ liftIO $ do
|
byteStorer $ \k b p -> guardUsable (repo r) False $ liftIO $ do
|
||||||
let f = gCryptLocation r k
|
let tmpdir = Git.repoLocation (repo r) </> "tmp" </> keyFile k
|
||||||
let d = parentDir f
|
void $ tryIO $ createDirectoryIfMissing True tmpdir
|
||||||
createDirectoryIfMissing True d
|
let tmpf = tmpdir </> keyFile k
|
||||||
allowWrite d
|
meteredWriteFile p tmpf b
|
||||||
void $ liftIO $ tryIO $ allowWrite f
|
let destdir = parentDir $ gCryptLocation r k
|
||||||
meteredWriteFile p f b
|
Remote.Directory.finalizeStoreGeneric tmpdir destdir
|
||||||
preventWrite f
|
|
||||||
preventWrite d
|
|
||||||
return True
|
return True
|
||||||
| Git.repoIsSsh (repo r) = if isShell r
|
| Git.repoIsSsh (repo r) = if isShell r
|
||||||
then fileStorer $ \k f p -> Ssh.rsyncHelper (Just p)
|
then fileStorer $ \k f p -> Ssh.rsyncHelper (Just p)
|
||||||
|
|
Loading…
Reference in a new issue