import Utility.FileMode
import Utility.Touch
import Utility.Hash (IncrementalVerifier(..))
+import qualified Utility.FileIO as F
import qualified Utility.RawFilePath as R
import Control.Concurrent
- The destination file must not exist yet (or may exist but be empty),
- or it will fail to make a CoW copy, and will return false.
-}
-tryCopyCoW :: CopyCoWTried -> FilePath -> FilePath -> MeterUpdate -> IO Bool
+tryCopyCoW :: CopyCoWTried -> OsPath -> OsPath -> MeterUpdate -> IO Bool
tryCopyCoW (CopyCoWTried copycowtried) src dest meterupdate =
-- If multiple threads reach this at the same time, they
-- will both try CoW, which is acceptable.
-- CoW is known to work, so delete
-- dest if it exists in order to do a fast
-- CoW copy.
- void $ tryIO $ removeFile dest'
+ void $ tryIO $ removeFile dest
docopycow
, return False
)
)
where
- docopycow = watchFileSize dest' meterupdate $ const $
+ docopycow = watchFileSize dest meterupdate $ const $
copyCoW CopyTimeStamps src dest
-
- dest' = toOsPath dest
-- Check if the dest file already exists, which would prevent
-- probing CoW. If the file exists but is empty, there's no benefit
-- to resuming from it when CoW does not work, so remove it.
destfilealreadypopulated =
- tryIO (R.getFileStatus (toRawFilePath dest)) >>= \case
+ tryIO (R.getFileStatus (fromOsPath dest)) >>= \case
Left _ -> return False
Right st -> do
- sz <- getFileSize' dest' st
+ sz <- getFileSize' dest st
if sz == 0
- then tryIO (removeFile dest') >>= \case
+ then tryIO (removeFile dest) >>= \case
Right () -> return False
Left _ -> return True
else return True
- (eg when isStableKey is false), and doing this avoids getting a
- corrupted file in such cases.
-}
-fileCopier :: CopyCoWTried -> FilePath -> FilePath -> MeterUpdate -> Maybe IncrementalVerifier -> IO CopyMethod
+fileCopier :: CopyCoWTried -> OsPath -> OsPath -> MeterUpdate -> Maybe IncrementalVerifier -> IO CopyMethod
#ifdef mingw32_HOST_OS
fileCopier _ src dest meterupdate iv = docopy
#else
docopy = do
-- The file might have had the write bit removed,
-- so make sure we can write to it.
- void $ tryIO $ allowWrite (toOsPath dest)
+ void $ tryIO $ allowWrite dest
- withBinaryFile src ReadMode $ \hsrc ->
+ F.withBinaryFile src ReadMode $ \hsrc ->
fileContentCopier hsrc dest meterupdate iv
-- Copy src mode and mtime.
- mode <- fileMode <$> R.getFileStatus (toRawFilePath src)
- mtime <- utcTimeToPOSIXSeconds
- <$> getModificationTime (toOsPath src)
+ mode <- fileMode <$> R.getFileStatus (fromOsPath src)
+ mtime <- utcTimeToPOSIXSeconds <$> getModificationTime src
+ let dest' = fromOsPath dest
R.setFileMode dest' mode
touch dest' mtime False
return Copied
-
- dest' = toRawFilePath dest
{- Copies content from a handle to a destination file. Does not
- use copy-on-write, and does not copy file mode and mtime.
-}
-fileContentCopier :: Handle -> FilePath -> MeterUpdate -> Maybe IncrementalVerifier -> IO ()
+fileContentCopier :: Handle -> OsPath -> MeterUpdate -> Maybe IncrementalVerifier -> IO ()
fileContentCopier hsrc dest meterupdate iv =
- withBinaryFile dest ReadWriteMode $ \hdest -> do
+ F.withBinaryFile dest ReadWriteMode $ \hdest -> do
sofar <- compareexisting hdest zeroBytesProcessed
docopy hdest sofar
where
in byteStorer go k c m
NoChunks ->
let go _k src p = liftIO $ do
- void $ fileCopier cow (fromOsPath src) (fromOsPath tmpf) p Nothing
+ void $ fileCopier cow src tmpf p Nothing
finalizeStoreGeneric d tmpdir destdir
in fileStorer go k c m
_ ->
retrieveKeyFileM d (LegacyChunks _) _ = Legacy.retrieve locations' d
retrieveKeyFileM d NoChunks cow = fileRetriever' $ \dest k p iv -> do
src <- liftIO $ getLocation d k
- void $ liftIO $ fileCopier cow (fromOsPath src) (fromOsPath dest) p iv
+ void $ liftIO $ fileCopier cow src dest p iv
retrieveKeyFileM d _ _ = byteRetriever $ \k sink ->
sink =<< liftIO (F.readFile =<< getLocation d k)
where
dest = exportPath d loc
go tmp () = void $ liftIO $
- fileCopier cow (fromOsPath src) (fromOsPath tmp) p Nothing
+ fileCopier cow src tmp p Nothing
retrieveExportM :: OsPath -> CopyCoWTried -> Key -> ExportLocation -> OsPath -> MeterUpdate -> Annex Verification
retrieveExportM d cow k loc dest p =
verifyKeyContentIncrementally AlwaysVerify k $ \iv ->
- void $ liftIO $ fileCopier cow src (fromOsPath dest) p iv
+ void $ liftIO $ fileCopier cow src dest p iv
where
- src = fromOsPath $ exportPath d loc
+ src = exportPath d loc
removeExportM :: OsPath -> Key -> ExportLocation -> Annex ()
removeExportM d _k loc = liftIO $ do
go iv = precheck (docopy iv)
- docopy iv = ifM (liftIO $ tryCopyCoW cow (fromOsPath f) (fromOsPath dest) p)
+ docopy iv = ifM (liftIO $ tryCopyCoW cow f dest p)
( postcheckcow (liftIO $ maybe noop unableIncrementalVerifier iv)
, docopynoncow iv
)
let close = hClose
bracketIO open close $ \h -> do
#endif
- liftIO $ fileContentCopier h (fromOsPath dest) p iv
+ liftIO $ fileContentCopier h dest p iv
#ifndef mingw32_HOST_OS
postchecknoncow dupfd (return ())
#else
withTmpFileIn destdir template $ \tmpf tmph -> do
let tmpf' = fromOsPath tmpf
liftIO $ hClose tmph
- void $ liftIO $ fileCopier cow (fromOsPath src) (fromOsPath tmpf) p Nothing
+ void $ liftIO $ fileCopier cow src tmpf p Nothing
resetAnnexFilePerm tmpf
liftIO (R.getSymbolicLinkStatus tmpf') >>= liftIO . mkContentIdentifier ii tmpf >>= \case
Nothing -> giveup "unable to generate content identifier"
- The dest file must not exist yet, or it will fail to make a CoW copy,
- and will return False.
-}
-copyCoW :: CopyMetaData -> FilePath -> FilePath -> IO Bool
+copyCoW :: CopyMetaData -> OsPath -> OsPath -> IO Bool
copyCoW meta src dest
| BuildInfo.cp_reflink_supported = do
-- When CoW is not supported, cp will complain to stderr,
-- so have to discard its stderr.
ok <- catchBoolIO $ withNullHandle $ \nullh ->
- let p = (proc "cp" $ toCommand $ params ++ [File src, File dest])
+ let p = (proc "cp" $ toCommand $ params ++ [File (fromOsPath src), File (fromOsPath dest)])
{ std_out = UseHandle nullh
, std_err = UseHandle nullh
}
-- When CoW is not supported, cp creates the destination
-- file but leaves it empty.
unless ok $
- void $ tryIO $ removeFile $ toOsPath dest
+ void $ tryIO $ removeFile dest
return ok
| otherwise = return False
where