replace removeLink with removeFile
same reasoning as in commit 5cc8d9d03b
This commit is contained in:
parent
90eb1e2da6
commit
f8bb9a8734
9 changed files with 16 additions and 21 deletions
|
@ -34,10 +34,9 @@ populatePointerFile :: Restage -> Key -> OsPath -> OsPath -> Annex (Maybe InodeC
|
||||||
populatePointerFile restage k obj f = go =<< liftIO (isPointerFile f)
|
populatePointerFile restage k obj f = go =<< liftIO (isPointerFile f)
|
||||||
where
|
where
|
||||||
go (Just k') | k == k' = do
|
go (Just k') | k == k' = do
|
||||||
let f' = fromOsPath f
|
|
||||||
destmode <- liftIO $ catchMaybeIO $
|
destmode <- liftIO $ catchMaybeIO $
|
||||||
fileMode <$> R.getFileStatus f'
|
fileMode <$> R.getFileStatus (fromOsPath f)
|
||||||
liftIO $ removeWhenExistsWith R.removeLink f'
|
liftIO $ removeWhenExistsWith removeFile f
|
||||||
(ic, populated) <- replaceWorkTreeFile f $ \tmp -> do
|
(ic, populated) <- replaceWorkTreeFile f $ \tmp -> do
|
||||||
ok <- linkOrCopy k obj tmp destmode >>= \case
|
ok <- linkOrCopy k obj tmp destmode >>= \case
|
||||||
Just _ -> thawContent tmp >> return True
|
Just _ -> thawContent tmp >> return True
|
||||||
|
@ -55,11 +54,10 @@ populatePointerFile restage k obj f = go =<< liftIO (isPointerFile f)
|
||||||
- Does not check if the pointer file is modified. -}
|
- Does not check if the pointer file is modified. -}
|
||||||
depopulatePointerFile :: Key -> OsPath -> Annex ()
|
depopulatePointerFile :: Key -> OsPath -> Annex ()
|
||||||
depopulatePointerFile key file = do
|
depopulatePointerFile key file = do
|
||||||
let file' = fromOsPath file
|
st <- liftIO $ catchMaybeIO $ R.getFileStatus (fromOsPath file)
|
||||||
st <- liftIO $ catchMaybeIO $ R.getFileStatus file'
|
|
||||||
let mode = fmap fileMode st
|
let mode = fmap fileMode st
|
||||||
secureErase file
|
secureErase file
|
||||||
liftIO $ removeWhenExistsWith R.removeLink file'
|
liftIO $ removeWhenExistsWith removeFile file
|
||||||
ic <- replaceWorkTreeFile file $ \tmp -> do
|
ic <- replaceWorkTreeFile file $ \tmp -> do
|
||||||
liftIO $ writePointerFile tmp key mode
|
liftIO $ writePointerFile tmp key mode
|
||||||
#if ! defined(mingw32_HOST_OS)
|
#if ! defined(mingw32_HOST_OS)
|
||||||
|
|
|
@ -116,7 +116,7 @@ inAnnexSafe key = inAnnex' (fromMaybe True) (Just False) go key
|
||||||
Nothing -> return is_locked
|
Nothing -> return is_locked
|
||||||
Just lockhandle -> do
|
Just lockhandle -> do
|
||||||
dropLock lockhandle
|
dropLock lockhandle
|
||||||
void $ tryIO $ removeWhenExistsWith R.removeLink lockfile
|
void $ tryIO $ removeWhenExistsWith removeFile lockfile
|
||||||
return is_unlocked
|
return is_unlocked
|
||||||
, return is_missing
|
, return is_missing
|
||||||
)
|
)
|
||||||
|
|
|
@ -112,9 +112,8 @@ fixupUnusualRepos r@(Repo { location = l@(Local { worktree = Just w, gitdir = d
|
||||||
|
|
||||||
replacedotgit = whenM (doesFileExist dotgit) $ do
|
replacedotgit = whenM (doesFileExist dotgit) $ do
|
||||||
linktarget <- relPathDirToFile w d
|
linktarget <- relPathDirToFile w d
|
||||||
let dotgit' = fromOsPath dotgit
|
removeWhenExistsWith removeFile dotgit
|
||||||
removeWhenExistsWith R.removeLink dotgit'
|
R.createSymbolicLink (fromOsPath linktarget) (fromOsPath dotgit)
|
||||||
R.createSymbolicLink (fromOsPath linktarget) dotgit'
|
|
||||||
|
|
||||||
-- Unsetting a config fails if it's not set, so ignore failure.
|
-- Unsetting a config fails if it's not set, so ignore failure.
|
||||||
unsetcoreworktree = void $ Git.Config.unset "core.worktree" r
|
unsetcoreworktree = void $ Git.Config.unset "core.worktree" r
|
||||||
|
|
|
@ -120,7 +120,7 @@ lockDown' cfg file = tryNonAsync $ ifM crippledFileSystem
|
||||||
relatedTemplate $ fromOsPath $
|
relatedTemplate $ fromOsPath $
|
||||||
literalOsPath "ingest-" <> takeFileName file
|
literalOsPath "ingest-" <> takeFileName file
|
||||||
hClose h
|
hClose h
|
||||||
removeWhenExistsWith R.removeLink (fromOsPath tmpfile)
|
removeWhenExistsWith removeFile tmpfile
|
||||||
withhardlink' delta tmpfile
|
withhardlink' delta tmpfile
|
||||||
`catchIO` const (nohardlink' delta)
|
`catchIO` const (nohardlink' delta)
|
||||||
|
|
||||||
|
|
|
@ -116,12 +116,10 @@ makeAnnexLink = makeGitLink
|
||||||
makeGitLink :: LinkTarget -> OsPath -> Annex ()
|
makeGitLink :: LinkTarget -> OsPath -> Annex ()
|
||||||
makeGitLink linktarget file = ifM (coreSymlinks <$> Annex.getGitConfig)
|
makeGitLink linktarget file = ifM (coreSymlinks <$> Annex.getGitConfig)
|
||||||
( liftIO $ do
|
( liftIO $ do
|
||||||
void $ tryIO $ R.removeLink file'
|
void $ tryIO $ removeFile file
|
||||||
R.createSymbolicLink linktarget file'
|
R.createSymbolicLink linktarget (fromOsPath file)
|
||||||
, liftIO $ F.writeFile' file linktarget
|
, liftIO $ F.writeFile' file linktarget
|
||||||
)
|
)
|
||||||
where
|
|
||||||
file' = fromOsPath file
|
|
||||||
|
|
||||||
{- Creates a link on disk, and additionally stages it in git. -}
|
{- Creates a link on disk, and additionally stages it in git. -}
|
||||||
addAnnexLink :: LinkTarget -> OsPath -> Annex ()
|
addAnnexLink :: LinkTarget -> OsPath -> Annex ()
|
||||||
|
|
|
@ -61,7 +61,7 @@ cleanupOtherTmp = do
|
||||||
tmpdir <- fromRepo gitAnnexTmpOtherDir
|
tmpdir <- fromRepo gitAnnexTmpOtherDir
|
||||||
void $ liftIO $ tryIO $ removeDirectoryRecursive tmpdir
|
void $ liftIO $ tryIO $ removeDirectoryRecursive tmpdir
|
||||||
oldtmp <- fromRepo gitAnnexTmpOtherDirOld
|
oldtmp <- fromRepo gitAnnexTmpOtherDirOld
|
||||||
liftIO $ mapM_ (cleanold . fromOsPath)
|
liftIO $ mapM_ cleanold
|
||||||
=<< emptyWhenDoesNotExist (dirContentsRecursive oldtmp)
|
=<< emptyWhenDoesNotExist (dirContentsRecursive oldtmp)
|
||||||
-- remove when empty
|
-- remove when empty
|
||||||
liftIO $ void $ tryIO $ removeDirectory oldtmp
|
liftIO $ void $ tryIO $ removeDirectory oldtmp
|
||||||
|
@ -69,7 +69,7 @@ cleanupOtherTmp = do
|
||||||
cleanold f = do
|
cleanold f = do
|
||||||
now <- liftIO getPOSIXTime
|
now <- liftIO getPOSIXTime
|
||||||
let oldenough = now - (60 * 60 * 24 * 7)
|
let oldenough = now - (60 * 60 * 24 * 7)
|
||||||
catchMaybeIO (modificationTime <$> R.getSymbolicLinkStatus f) >>= \case
|
catchMaybeIO (modificationTime <$> R.getSymbolicLinkStatus (fromOsPath f)) >>= \case
|
||||||
Just mtime | realToFrac mtime <= oldenough ->
|
Just mtime | realToFrac mtime <= oldenough ->
|
||||||
void $ tryIO $ removeWhenExistsWith R.removeLink f
|
void $ tryIO $ removeWhenExistsWith removeFile f
|
||||||
_ -> return ()
|
_ -> return ()
|
||||||
|
|
|
@ -216,7 +216,7 @@ runTransfer' ignorelock t eventualbackend afile stalldetection retrydecider tran
|
||||||
-}
|
-}
|
||||||
maybe noop dropLock moldlockhandle
|
maybe noop dropLock moldlockhandle
|
||||||
dropLock lockhandle
|
dropLock lockhandle
|
||||||
void $ tryIO $ R.removeLink lckfile
|
void $ tryIO $ removeFile lckfile
|
||||||
maybe noop (void . tryIO . removeFile) moldlckfile
|
maybe noop (void . tryIO . removeFile) moldlckfile
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
|
|
|
@ -233,7 +233,7 @@ buildrpms topdir l = do
|
||||||
<$> liftIO (getDirectoryContents rpmrepo)
|
<$> liftIO (getDirectoryContents rpmrepo)
|
||||||
forM_ tarrpmarches $ \(tararch, rpmarch) ->
|
forM_ tarrpmarches $ \(tararch, rpmarch) ->
|
||||||
forM_ (filter (isstandalonetarball tararch . fst) l) $ \(tarball, v) -> do
|
forM_ (filter (isstandalonetarball tararch . fst) l) $ \(tarball, v) -> do
|
||||||
liftIO $ mapM_ (removeWhenExistsWith (R.removeLink . toRawFilePath))
|
liftIO $ mapM_ (removeWhenExistsWith removeFile)
|
||||||
(filter ((rpmarch ++ ".rpm") `isSuffixOf`) oldrpms)
|
(filter ((rpmarch ++ ".rpm") `isSuffixOf`) oldrpms)
|
||||||
void $ liftIO $ boolSystem script
|
void $ liftIO $ boolSystem script
|
||||||
[ Param rpmarch
|
[ Param rpmarch
|
||||||
|
|
|
@ -246,7 +246,7 @@ fixLink key file = do
|
||||||
| want /= fromInternalGitPath have = do
|
| want /= fromInternalGitPath have = do
|
||||||
showNote "fixing link"
|
showNote "fixing link"
|
||||||
createWorkTreeDirectory (parentDir file)
|
createWorkTreeDirectory (parentDir file)
|
||||||
liftIO $ R.removeLink (fromOsPath file)
|
liftIO $ removeFile file
|
||||||
addAnnexLink (fromOsPath want) file
|
addAnnexLink (fromOsPath want) file
|
||||||
| otherwise = noop
|
| otherwise = noop
|
||||||
|
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue