finished this stage of the RawFilePath conversion

This commit was sponsored by Denis Dzyubenko on Patreon.
This commit is contained in:
Joey Hess 2020-11-06 14:10:58 -04:00
parent 2c8cf06e75
commit 1db49497e0
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
27 changed files with 100 additions and 93 deletions

View file

@ -208,7 +208,7 @@ downloadTorrentFile u = do
else withOtherTmp $ \othertmp -> do
withTmpFileIn (fromRawFilePath othertmp) "torrent" $ \f h -> do
liftIO $ hClose h
resetAnnexFilePerm f
resetAnnexFilePerm (toRawFilePath f)
ok <- Url.withUrlOptions $
Url.download nullMeterUpdate u f
when ok $

View file

@ -166,18 +166,18 @@ storeDir d k = P.addTrailingPathSeparator $
- store the key. Note that the unencrypted key size is checked. -}
storeKeyM :: RawFilePath -> ChunkConfig -> Storer
storeKeyM d chunkconfig k c m =
ifM (checkDiskSpaceDirectory (fromRawFilePath d) k)
ifM (checkDiskSpaceDirectory d k)
( byteStorer (store d chunkconfig) k c m
, giveup "Not enough free disk space."
)
checkDiskSpaceDirectory :: FilePath -> Key -> Annex Bool
checkDiskSpaceDirectory :: RawFilePath -> Key -> Annex Bool
checkDiskSpaceDirectory d k = do
annexdir <- fromRepo gitAnnexObjectDir
samefilesystem <- liftIO $ catchDefaultIO False $
(\a b -> deviceID a == deviceID b)
<$> getFileStatus d
<*> getFileStatus annexdir
<$> R.getFileStatus d
<*> R.getFileStatus annexdir
checkDiskSpace (Just d) k 0 samefilesystem
store :: RawFilePath -> ChunkConfig -> Key -> L.ByteString -> MeterUpdate -> Annex ()
@ -212,8 +212,8 @@ finalizeStoreGeneric d tmp dest = do
renameDirectory (fromRawFilePath tmp) dest'
-- may fail on some filesystems
void $ tryIO $ do
mapM_ preventWrite =<< dirContents dest'
preventWrite dest'
mapM_ (preventWrite . toRawFilePath) =<< dirContents dest'
preventWrite dest
where
dest' = fromRawFilePath dest
@ -254,7 +254,7 @@ removeKeyM d k = liftIO $ removeDirGeneric
-}
removeDirGeneric :: FilePath -> FilePath -> IO ()
removeDirGeneric topdir dir = do
void $ tryIO $ allowWrite dir
void $ tryIO $ allowWrite (toRawFilePath dir)
#ifdef mingw32_HOST_OS
{- Windows needs the files inside the directory to be writable
- before it can delete them. -}
@ -454,11 +454,12 @@ storeExportWithContentIdentifierM :: RawFilePath -> FilePath -> Key -> ExportLoc
storeExportWithContentIdentifierM dir src _k loc overwritablecids p = do
liftIO $ createDirectoryUnder dir (toRawFilePath destdir)
withTmpFileIn destdir template $ \tmpf tmph -> do
let tmpf' = toRawFilePath tmpf
liftIO $ withMeteredFile src p (L.hPut tmph)
liftIO $ hFlush tmph
liftIO $ hClose tmph
resetAnnexFilePerm tmpf
liftIO (getFileStatus tmpf) >>= liftIO . mkContentIdentifier (toRawFilePath tmpf) >>= \case
resetAnnexFilePerm tmpf'
liftIO (getFileStatus tmpf) >>= liftIO . mkContentIdentifier tmpf' >>= \case
Nothing -> giveup "unable to generate content identifier"
Just newcid -> do
checkExportContent dir loc

View file

@ -82,9 +82,10 @@ storeHelper repotop finalizer key storer tmpdir destdir = do
Legacy.storeChunks key tmpdir destdir storer recorder (legacyFinalizer finalizer)
where
recorder f s = do
void $ tryIO $ allowWrite f
let f' = toRawFilePath f
void $ tryIO $ allowWrite f'
writeFile f s
void $ tryIO $ preventWrite f
void $ tryIO $ preventWrite f'
store :: FilePath -> ChunkSize -> (RawFilePath -> RawFilePath -> IO ()) -> Key -> L.ByteString -> MeterUpdate -> FilePath -> FilePath -> IO ()
store repotop chunksize finalizer k b p = storeHelper repotop finalizer k $ \dests ->

View file

@ -820,7 +820,7 @@ rsyncOrCopyFile st rsyncparams src dest p =
State _ _ (CopyCoWTried v) _ _ -> v
dorsync = do
-- dest may already exist, so make sure rsync can write to it
void $ liftIO $ tryIO $ allowWrite dest
void $ liftIO $ tryIO $ allowWrite (toRawFilePath dest)
oh <- mkOutputHandlerQuiet
Ssh.rsyncHelper oh (Just p) $
rsyncparams ++ [File src, File dest]