simplify replaceFile using relatedTemplate

Now that truncateFilePath and relatedTemplate have both been optimised,
may as well use them in replaceFile, rather than the custom hack it
used.

Removed the windows-specific ifdef as well, because on Windows long
filepaths no longer really a problem, since ghc and git-annex use UNC
converted paths.

replaceFile no longer checks fileNameLengthLimit. That took a syscall,
and since we have an existing file, we know filenames of its length are
supported by the filesystem. Assuming that the withOtherTmp directory is
on the same filesystem as the file replaceFile is being called on, which
I believe it is.

Sponsored-by: Leon Schuermann
This commit is contained in:
Joey Hess 2025-01-22 13:22:51 -04:00
parent f17ec601c4
commit af3b9cbd36
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
2 changed files with 15 additions and 24 deletions

View file

@ -1,12 +1,10 @@
{- git-annex file replacing {- git-annex file replacing
- -
- Copyright 2013-2021 Joey Hess <id@joeyh.name> - Copyright 2013-2025 Joey Hess <id@joeyh.name>
- -
- Licensed under the GNU AGPL version 3 or higher. - Licensed under the GNU AGPL version 3 or higher.
-} -}
{-# LANGUAGE CPP #-}
module Annex.ReplaceFile ( module Annex.ReplaceFile (
replaceGitAnnexDirFile, replaceGitAnnexDirFile,
replaceGitDirFile, replaceGitDirFile,
@ -19,11 +17,11 @@ import Annex.Common
import Annex.Tmp import Annex.Tmp
import Annex.Perms import Annex.Perms
import Git import Git
import Utility.Tmp
import Utility.Tmp.Dir import Utility.Tmp.Dir
import Utility.Directory.Create import Utility.Directory.Create
#ifndef mingw32_HOST_OS
import Utility.Path.Max import qualified System.FilePath.ByteString as P
#endif
{- replaceFile on a file located inside the gitAnnexDir. -} {- replaceFile on a file located inside the gitAnnexDir. -}
replaceGitAnnexDirFile :: FilePath -> (RawFilePath -> Annex a) -> Annex a replaceGitAnnexDirFile :: FilePath -> (RawFilePath -> Annex a) -> Annex a
@ -59,20 +57,9 @@ replaceFile createdirectory file action = replaceFile' createdirectory file (con
replaceFile' :: (RawFilePath -> Annex ()) -> FilePath -> (a -> Bool) -> (RawFilePath -> Annex a) -> Annex a replaceFile' :: (RawFilePath -> Annex ()) -> FilePath -> (a -> Bool) -> (RawFilePath -> Annex a) -> Annex a
replaceFile' createdirectory file checkres action = withOtherTmp $ \othertmpdir -> do replaceFile' createdirectory file checkres action = withOtherTmp $ \othertmpdir -> do
let othertmpdir' = fromRawFilePath othertmpdir let basetmp = relatedTemplate' (toRawFilePath file)
#ifndef mingw32_HOST_OS withTmpDirIn (fromRawFilePath othertmpdir) (toOsPath basetmp) $ \tmpdir -> do
-- Use part of the filename as the template for the temp let tmpfile = toRawFilePath tmpdir P.</> basetmp
-- directory. This does not need to be unique, but it
-- makes it more clear what this temp directory is for.
filemax <- liftIO $ fileNameLengthLimit othertmpdir'
let basetmp = take (filemax `div` 2) (takeFileName file)
#else
-- Windows has limits on the whole path length, so keep
-- it short.
let basetmp = "t"
#endif
withTmpDirIn othertmpdir' (toOsPath (toRawFilePath basetmp)) $ \tmpdir -> do
let tmpfile = toRawFilePath (tmpdir </> basetmp)
r <- action tmpfile r <- action tmpfile
when (checkres r) $ when (checkres r) $
replaceFileFrom tmpfile (toRawFilePath file) createdirectory replaceFileFrom tmpfile (toRawFilePath file) createdirectory

View file

@ -13,8 +13,9 @@ module Utility.Tmp (
viaTmp, viaTmp,
withTmpFile, withTmpFile,
withTmpFileIn, withTmpFileIn,
relatedTemplate,
openTmpFileIn, openTmpFileIn,
relatedTemplate,
relatedTemplate',
) where ) where
import System.IO import System.IO
@ -107,14 +108,17 @@ withTmpFileIn tmpdir template a = bracket create remove use
- This generates a template that is never too long. - This generates a template that is never too long.
-} -}
relatedTemplate :: RawFilePath -> Template relatedTemplate :: RawFilePath -> Template
relatedTemplate f relatedTemplate = toOsPath . relatedTemplate'
relatedTemplate' :: RawFilePath -> RawFilePath
relatedTemplate' f
| len > templateAddedLength = | len > templateAddedLength =
{- Some filesystems like FAT have issues with filenames {- Some filesystems like FAT have issues with filenames
- ending in ".", so avoid truncating a filename to end - ending in ".", so avoid truncating a filename to end
- that way. -} - that way. -}
toOsPath $ B.dropWhileEnd (== dot) $ B.dropWhileEnd (== dot) $
truncateFilePath (len - templateAddedLength) f truncateFilePath (len - templateAddedLength) f
| otherwise = toOsPath f | otherwise = f
where where
len = B.length f len = B.length f
dot = fromIntegral (ord '.') dot = fromIntegral (ord '.')